# 18 "parsing/lexer.mll" open Lexing open Misc open Parser type error = | Illegal_character of char | Illegal_escape of string * string option | Reserved_sequence of string * string option | Unterminated_comment of Location.t | Unterminated_string | Unterminated_string_in_comment of Location.t * Location.t | Empty_character_literal | Keyword_as_label of string | Capitalized_label of string | Invalid_literal of string | Invalid_directive of string * string option | Invalid_encoding of string | Invalid_char_in_ident of Uchar.t | Non_lowercase_delimiter of string | Capitalized_raw_identifier of string | Unknown_keyword of string exception Error of error * Location.t (* The table of keywords *) let all_keywords = let v5_3 = Some (5,3) in let v1_0 = Some (1,0) in let v1_6 = Some (1,6) in let v4_2 = Some (4,2) in let always = None in [ "and", AND, always; "as", AS, always; "assert", ASSERT, v1_6; "begin", BEGIN, always; "class", CLASS, v1_0; "constraint", CONSTRAINT, v1_0; "do", DO, always; "done", DONE, always; "downto", DOWNTO, always; "effect", EFFECT, v5_3; "else", ELSE, always; "end", END, always; "exception", EXCEPTION, always; "external", EXTERNAL, always; "false", FALSE, always; "for", FOR, always; "fun", FUN, always; "function", FUNCTION, always; "functor", FUNCTOR, always; "if", IF, always; "in", IN, always; "include", INCLUDE, always; "inherit", INHERIT, v1_0; "initializer", INITIALIZER, v1_0; "lazy", LAZY, v1_6; "let", LET, always; "match", MATCH, always; "method", METHOD, v1_0; "module", MODULE, always; "mutable", MUTABLE, always; "new", NEW, v1_0; "nonrec", NONREC, v4_2; "object", OBJECT, v1_0; "of", OF, always; "open", OPEN, always; "or", OR, always; (* "parser", PARSER; *) "private", PRIVATE, v1_0; "rec", REC, always; "sig", SIG, always; "struct", STRUCT, always; "then", THEN, always; "to", TO, always; "true", TRUE, always; "try", TRY, always; "type", TYPE, always; "val", VAL, always; "virtual", VIRTUAL, v1_0; "when", WHEN, always; "while", WHILE, always; "with", WITH, always; "lor", INFIXOP3("lor"), always; (* Should be INFIXOP2 *) "lxor", INFIXOP3("lxor"), always; (* Should be INFIXOP2 *) "mod", INFIXOP3("mod"), always; "land", INFIXOP3("land"), always; "lsl", INFIXOP4("lsl"), always; "lsr", INFIXOP4("lsr"), always; "asr", INFIXOP4("asr"), always ] let keyword_table = Hashtbl.create 149 let populate_keywords (version,keywords) = let greater (x:(int*int) option) (y:(int*int) option) = match x, y with | None, _ | _, None -> true | Some x, Some y -> x >= y in let tbl = keyword_table in Hashtbl.clear tbl; let add_keyword (name, token, since) = if greater version since then Hashtbl.replace tbl name (Some token) in List.iter add_keyword all_keywords; List.iter (fun name -> match List.find (fun (n,_,_) -> n = name) all_keywords with | (_,tok,_) -> Hashtbl.replace tbl name (Some tok) | exception Not_found -> Hashtbl.replace tbl name None ) keywords (* To buffer string literals *) let string_buffer = Buffer.create 256 let reset_string_buffer () = Buffer.reset string_buffer let get_stored_string () = Buffer.contents string_buffer let store_string_char c = Buffer.add_char string_buffer c let store_string_utf_8_uchar u = Buffer.add_utf_8_uchar string_buffer u let store_string s = Buffer.add_string string_buffer s let store_substring s ~pos ~len = Buffer.add_substring string_buffer s pos len let store_lexeme lexbuf = store_string (Lexing.lexeme lexbuf) let store_normalized_newline newline = (* #12502: we normalize "\r\n" to "\n" at lexing time, to avoid behavior difference due to OS-specific newline characters in string literals. (For example, Git for Windows will translate \n in versioned files into \r\n sequences when checking out files on Windows. If your code contains multiline quoted string literals, the raw content of the string literal would be different between Git for Windows users and all other users. Thanks to newline normalization, the value of the literal as a string constant will be the same no matter which programming tools are used.) Many programming languages use the same approach, for example Java, Javascript, Kotlin, Python, Swift and C++. *) (* Our 'newline' regexp accepts \r*\n, but we only wish to normalize \r?\n into \n -- see the discussion in #12502. All carriage returns except for the (optional) last one are reproduced in the output. We implement this by skipping the first carriage return, if any. *) let len = String.length newline in if len = 1 then store_string_char '\n' else store_substring newline ~pos:1 ~len:(len - 1) (* To store the position of the beginning of a string and comment *) let string_start_loc = ref Location.none let comment_start_loc = ref [] let in_comment () = !comment_start_loc <> [] let is_in_string = ref false let in_string () = !is_in_string let print_warnings = ref true (* Escaped chars are interpreted in strings unless they are in comments. *) let store_escaped_char lexbuf c = if in_comment () then store_lexeme lexbuf else store_string_char c let store_escaped_uchar lexbuf u = if in_comment () then store_lexeme lexbuf else store_string_utf_8_uchar u let compute_quoted_string_idloc {Location.loc_start = orig_loc } shift id = let id_start_pos = orig_loc.Lexing.pos_cnum + shift in let loc_start = Lexing.{orig_loc with pos_cnum = id_start_pos } in let loc_end = Lexing.{orig_loc with pos_cnum = id_start_pos + String.length id} in {Location. loc_start ; loc_end ; loc_ghost = false } let wrap_string_lexer f lexbuf = let loc_start = lexbuf.lex_curr_p in reset_string_buffer(); is_in_string := true; let string_start = lexbuf.lex_start_p in string_start_loc := Location.curr lexbuf; let loc_end = f lexbuf in is_in_string := false; lexbuf.lex_start_p <- string_start; let loc = Location.{loc_ghost= false; loc_start; loc_end} in get_stored_string (), loc let wrap_comment_lexer comment lexbuf = let start_loc = Location.curr lexbuf in comment_start_loc := [start_loc]; reset_string_buffer (); let end_loc = comment lexbuf in let s = get_stored_string () in reset_string_buffer (); s, { start_loc with Location.loc_end = end_loc.Location.loc_end } let error lexbuf e = raise (Error(e, Location.curr lexbuf)) let error_loc loc e = raise (Error(e, loc)) (* to translate escape sequences *) let digit_value c = match c with | 'a' .. 'f' -> 10 + Char.code c - Char.code 'a' | 'A' .. 'F' -> 10 + Char.code c - Char.code 'A' | '0' .. '9' -> Char.code c - Char.code '0' | _ -> assert false let num_value lexbuf ~base ~first ~last = let c = ref 0 in for i = first to last do let v = digit_value (Lexing.lexeme_char lexbuf i) in assert(v < base); c := (base * !c) + v done; !c let char_for_backslash = function | 'n' -> '\010' | 'r' -> '\013' | 'b' -> '\008' | 't' -> '\009' | c -> c let illegal_escape lexbuf reason = let error = Illegal_escape (Lexing.lexeme lexbuf, Some reason) in raise (Error (error, Location.curr lexbuf)) let char_for_decimal_code lexbuf i = let c = num_value lexbuf ~base:10 ~first:i ~last:(i+2) in if (c < 0 || c > 255) then if in_comment () then 'x' else illegal_escape lexbuf (Printf.sprintf "%d is outside the range of legal characters (0-255)." c) else Char.chr c let char_for_octal_code lexbuf i = let c = num_value lexbuf ~base:8 ~first:i ~last:(i+2) in if (c < 0 || c > 255) then if in_comment () then 'x' else illegal_escape lexbuf (Printf.sprintf "o%o (=%d) is outside the range of legal characters (0-255)." c c) else Char.chr c let char_for_hexadecimal_code lexbuf i = Char.chr (num_value lexbuf ~base:16 ~first:i ~last:(i+1)) let uchar_for_uchar_escape lexbuf = let len = Lexing.lexeme_end lexbuf - Lexing.lexeme_start lexbuf in let first = 3 (* skip opening \u{ *) in let last = len - 2 (* skip closing } *) in let digit_count = last - first + 1 in match digit_count > 6 with | true -> illegal_escape lexbuf "too many digits, expected 1 to 6 hexadecimal digits" | false -> let cp = num_value lexbuf ~base:16 ~first ~last in if Uchar.is_valid cp then Uchar.unsafe_of_int cp else illegal_escape lexbuf (Printf.sprintf "%X is not a Unicode scalar value" cp) let validate_encoding lexbuf raw_name = match Utf8_lexeme.normalize raw_name with | Error _ -> error lexbuf (Invalid_encoding raw_name) | Ok name -> name let ident_for_extended lexbuf raw_name = let name = validate_encoding lexbuf raw_name in match Utf8_lexeme.validate_identifier name with | Utf8_lexeme.Valid -> name | Utf8_lexeme.Invalid_character u -> error lexbuf (Invalid_char_in_ident u) | Utf8_lexeme.Invalid_beginning _ -> assert false (* excluded by the regexps *) let validate_delim lexbuf raw_name = let name = validate_encoding lexbuf raw_name in if Utf8_lexeme.is_lowercase name then name else error lexbuf (Non_lowercase_delimiter name) let validate_ext lexbuf name = let name = validate_encoding lexbuf name in match Utf8_lexeme.validate_identifier ~with_dot:true name with | Utf8_lexeme.Valid -> name | Utf8_lexeme.Invalid_character u -> error lexbuf (Invalid_char_in_ident u) | Utf8_lexeme.Invalid_beginning _ -> assert false (* excluded by the regexps *) let lax_delim raw_name = match Utf8_lexeme.normalize raw_name with | Error _ -> None | Ok name -> if Utf8_lexeme.is_lowercase name then Some name else None let is_keyword name = Hashtbl.mem keyword_table name let find_keyword lexbuf name = match Hashtbl.find keyword_table name with | Some x -> x | None -> error lexbuf (Unknown_keyword name) | exception Not_found -> LIDENT name let check_label_name ?(raw_escape=false) lexbuf name = if Utf8_lexeme.is_capitalized name then error lexbuf (Capitalized_label name); if not raw_escape && is_keyword name then error lexbuf (Keyword_as_label name) (* Update the current location with file name and line number. *) let update_loc lexbuf file line absolute chars = let pos = lexbuf.lex_curr_p in let new_file = match file with | None -> pos.pos_fname | Some s -> s in lexbuf.lex_curr_p <- { pos with pos_fname = new_file; pos_lnum = if absolute then line else pos.pos_lnum + line; pos_bol = pos.pos_cnum - chars; } let preprocessor = ref None let escaped_newlines = ref false let handle_docstrings = ref true let comment_list = ref [] let add_comment com = comment_list := com :: !comment_list let add_docstring_comment ds = let com = ("*" ^ Docstrings.docstring_body ds, Docstrings.docstring_loc ds) in add_comment com let comments () = List.rev !comment_list (* Error report *) open Format_doc let prepare_error loc = function | Illegal_character c -> Location.errorf ~loc "Illegal character (%s)" (Char.escaped c) | Illegal_escape (s, explanation) -> Location.errorf ~loc "Illegal backslash escape in string or character (%s)%t" s (fun ppf -> match explanation with | None -> () | Some expl -> fprintf ppf ": %s" expl) | Reserved_sequence (s, explanation) -> Location.errorf ~loc "Reserved character sequence: %s%t" s (fun ppf -> match explanation with | None -> () | Some expl -> fprintf ppf " %s" expl) | Unterminated_comment _ -> Location.errorf ~loc "Comment not terminated" | Unterminated_string -> Location.errorf ~loc "String literal not terminated" | Unterminated_string_in_comment (_, literal_loc) -> Location.errorf ~loc "This comment contains an unterminated string literal" ~sub:[Location.msg ~loc:literal_loc "String literal begins here"] | Empty_character_literal -> let msg = "Illegal empty character literal ''" in let sub = [Location.msg "@{Hint@}: Did you mean %a or a type variable %a?" Style.inline_code "' '" Style.inline_code "'a" ] in Location.error ~loc ~sub msg | Keyword_as_label kwd -> Location.errorf ~loc "%a is a keyword, it cannot be used as label name" Style.inline_code kwd | Capitalized_label lbl -> Location.errorf ~loc "%a cannot be used as label name, \ it must start with a lowercase letter" Style.inline_code lbl | Invalid_literal s -> Location.errorf ~loc "Invalid literal %s" s | Invalid_directive (dir, explanation) -> Location.errorf ~loc "Invalid lexer directive %S%t" dir (fun ppf -> match explanation with | None -> () | Some expl -> fprintf ppf ": %s" expl) | Invalid_encoding s -> Location.errorf ~loc "Invalid encoding of identifier %s." s | Invalid_char_in_ident u -> Location.errorf ~loc "Invalid character U+%04X in identifier" (Uchar.to_int u) | Capitalized_raw_identifier lbl -> Location.errorf ~loc "%a cannot be used as a raw identifier, \ it must start with a lowercase letter" Style.inline_code lbl | Non_lowercase_delimiter name -> Location.errorf ~loc "%a cannot be used as a quoted string delimiter,@ \ it must contain only lowercase letters." Style.inline_code name | Unknown_keyword name -> Location.errorf ~loc "%a has been defined as an additional keyword.@ \ This version of OCaml does not support this keyword." Style.inline_code name let () = Location.register_error_of_exn (function | Error (err, loc) -> Some (prepare_error loc err) | _ -> None ) # 437 "parsing/lexer.ml" let __ocaml_lex_tables = { Lexing.lex_base = "\000\000\156\255\157\255\224\000\003\001\038\001\073\001\108\001\ \143\001\182\255\178\001\215\001\190\255\171\001\254\001\033\002\ \068\000\070\000\068\002\208\255\210\255\213\255\103\002\138\002\ \173\002\087\000\255\000\203\002\236\255\164\003\248\003\076\004\ \037\005\254\005\215\006\176\007\143\008\110\009\177\009\138\010\ \121\000\254\255\001\000\124\000\202\010\255\255\005\000\163\011\ \163\012\006\000\002\013\164\013\100\000\126\014\126\015\249\255\ \248\255\215\015\150\016\117\017\205\255\250\255\244\017\206\018\ \101\000\167\019\167\020\246\255\245\255\232\020\193\021\157\022\ \036\013\118\023\082\024\049\025\164\013\079\025\117\017\244\017\ \163\025\247\025\075\026\159\026\243\026\071\027\155\027\090\000\ \239\027\067\028\151\028\235\028\063\029\112\000\188\255\122\029\ \235\255\122\030\187\030\251\030\251\031\243\032\234\033\234\255\ \042\034\042\035\176\035\168\036\168\037\233\255\040\038\105\038\ \105\039\097\040\088\041\232\255\152\041\152\042\030\043\022\044\ \022\045\231\255\150\045\215\045\223\255\183\046\109\000\110\000\ \007\000\230\255\229\255\224\255\024\003\122\000\130\000\111\000\ \228\255\224\000\112\000\227\255\003\001\193\002\113\000\226\255\ \112\005\115\000\225\255\114\000\219\255\116\000\218\255\147\000\ \183\046\217\255\222\046\012\047\051\047\086\047\124\047\200\255\ \201\255\202\255\198\255\159\047\153\000\127\000\191\255\192\255\ \193\255\194\000\178\255\176\255\185\255\194\047\181\255\183\255\ \229\047\008\048\043\048\078\048\079\003\167\005\255\001\038\001\ \024\001\140\048\241\255\102\049\063\050\243\255\011\000\244\255\ \099\002\026\051\253\255\218\000\221\000\255\255\254\255\252\255\ \026\052\091\052\054\053\054\054\046\055\110\055\101\056\165\056\ \165\057\043\058\035\059\035\060\131\060\225\000\244\000\012\000\ \251\255\250\255\249\255\073\006\038\001\052\003\250\000\248\255\ \135\005\252\000\247\255\064\003\068\004\003\001\246\255\034\007\ \004\001\245\255\013\000\036\061\244\032\245\255\246\255\247\255\ \017\000\164\060\255\255\248\255\177\000\251\007\029\005\096\006\ \253\255\050\001\018\000\080\001\106\006\252\255\246\005\128\006\ \251\255\222\008\250\255\128\009\036\013\249\255\094\001\182\001\ \252\255\101\061\254\255\255\255\095\001\104\001\253\255\101\062\ \063\063\063\064\025\001\035\001\063\001\067\001\036\001\068\001\ \044\001\019\000\255\255"; Lexing.lex_backtrk = "\255\255\255\255\255\255\094\000\093\000\090\000\089\000\082\000\ \080\000\255\255\071\000\068\000\255\255\061\000\060\000\058\000\ \056\000\052\000\085\000\255\255\255\255\255\255\040\000\039\000\ \046\000\044\000\043\000\066\000\255\255\014\000\014\000\013\000\ \012\000\011\000\011\000\011\000\008\000\049\000\004\000\003\000\ \002\000\255\255\099\000\099\000\255\255\255\255\255\255\013\000\ \013\000\255\255\088\000\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\051\000\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\011\000\011\000\ \096\000\011\000\011\000\097\000\018\000\018\000\016\000\015\000\ \018\000\015\000\015\000\014\000\016\000\015\000\016\000\255\255\ \017\000\017\000\014\000\014\000\016\000\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\031\000\031\000\031\000\031\000\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\033\000\255\255\034\000\255\255\035\000\ \092\000\255\255\095\000\041\000\091\000\086\000\048\000\255\255\ \255\255\255\255\255\255\059\000\078\000\075\000\255\255\255\255\ \255\255\076\000\255\255\255\255\255\255\069\000\255\255\255\255\ \087\000\081\000\084\000\083\000\255\255\255\255\255\255\255\255\ \000\000\255\255\255\255\013\000\013\000\255\255\014\000\255\255\ \014\000\014\000\255\255\014\000\014\000\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\013\000\255\255\255\255\255\255\255\255\ \010\000\010\000\255\255\255\255\007\000\007\000\007\000\007\000\ \255\255\001\000\007\000\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\003\000\255\255\255\255\003\000\255\255\255\255\255\255\ \255\255\255\255\002\000\255\255\255\255\001\000\255\255\255\255\ \255\255\255\255\255\255"; Lexing.lex_default = "\001\000\000\000\000\000\255\255\255\255\255\255\255\255\255\255\ \255\255\000\000\255\255\255\255\000\000\255\255\255\255\255\255\ \255\255\255\255\255\255\000\000\000\000\000\000\255\255\255\255\ \255\255\255\255\126\000\255\255\000\000\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\000\000\255\255\255\255\255\255\000\000\255\255\255\255\ \048\000\255\255\255\255\057\000\255\255\255\255\054\000\000\000\ \000\000\255\255\255\255\255\255\000\000\000\000\063\000\255\255\ \255\255\255\255\066\000\000\000\000\000\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\000\000\255\255\ \000\000\097\000\255\255\255\255\101\000\255\255\255\255\000\000\ \255\255\105\000\107\000\255\255\108\000\000\000\110\000\255\255\ \113\000\255\255\255\255\000\000\255\255\117\000\119\000\255\255\ \120\000\000\000\122\000\255\255\000\000\131\000\255\255\255\255\ \255\255\000\000\000\000\000\000\255\255\255\255\255\255\255\255\ \000\000\255\255\255\255\000\000\255\255\255\255\255\255\000\000\ \255\255\255\255\000\000\255\255\000\000\255\255\000\000\255\255\ \255\255\000\000\255\255\255\255\255\255\255\255\255\255\000\000\ \000\000\000\000\000\000\255\255\255\255\255\255\000\000\000\000\ \000\000\255\255\000\000\000\000\000\000\255\255\000\000\000\000\ \255\255\255\255\255\255\255\255\255\255\255\255\182\000\255\255\ \184\000\186\000\000\000\255\255\255\255\000\000\255\255\000\000\ \213\000\255\255\000\000\255\255\255\255\000\000\000\000\000\000\ \200\000\255\255\255\255\204\000\255\255\255\255\255\255\255\255\ \208\000\210\000\255\255\211\000\255\255\255\255\255\255\255\255\ \000\000\000\000\000\000\255\255\255\255\255\255\255\255\000\000\ \255\255\255\255\000\000\255\255\255\255\255\255\000\000\255\255\ \255\255\000\000\255\255\235\000\237\000\000\000\000\000\000\000\ \255\255\243\000\000\000\000\000\255\255\255\255\255\255\255\255\ \000\000\255\255\255\255\255\255\255\255\000\000\255\255\255\255\ \000\000\255\255\000\000\255\255\255\255\000\000\255\255\008\001\ \000\000\255\255\000\000\000\000\255\255\255\255\000\000\016\001\ \255\255\017\001\255\255\255\255\020\001\023\001\255\255\023\001\ \255\255\255\255\000\000"; Lexing.lex_trans = "\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\040\000\041\000\041\000\040\000\042\000\049\000\045\000\ \041\000\127\000\046\000\049\000\128\000\189\000\214\000\189\000\ \234\000\215\000\234\000\239\000\249\000\026\001\006\001\251\000\ \040\000\008\000\028\000\023\000\006\000\004\000\022\000\026\000\ \025\000\020\000\024\000\007\000\019\000\018\000\037\000\003\000\ \030\000\029\000\029\000\029\000\029\000\029\000\029\000\029\000\ \029\000\029\000\017\000\016\000\015\000\014\000\010\000\036\000\ \005\000\032\000\032\000\032\000\032\000\032\000\032\000\032\000\ \032\000\032\000\032\000\032\000\032\000\032\000\032\000\032\000\ \032\000\032\000\032\000\032\000\032\000\032\000\032\000\032\000\ \032\000\032\000\032\000\013\000\043\000\012\000\005\000\039\000\ \021\000\034\000\033\000\033\000\033\000\033\000\033\000\033\000\ \033\000\033\000\033\000\033\000\035\000\033\000\033\000\033\000\ \033\000\033\000\033\000\033\000\033\000\033\000\033\000\033\000\ \033\000\033\000\033\000\027\000\011\000\009\000\038\000\162\000\ \161\000\147\000\040\000\160\000\159\000\040\000\045\000\058\000\ \069\000\046\000\086\000\086\000\086\000\086\000\086\000\086\000\ \086\000\086\000\086\000\086\000\130\000\129\000\136\000\139\000\ \143\000\040\000\146\000\148\000\149\000\150\000\151\000\044\000\ \092\000\092\000\092\000\092\000\092\000\092\000\092\000\092\000\ \092\000\092\000\140\000\140\000\140\000\140\000\140\000\140\000\ \140\000\140\000\137\000\137\000\137\000\137\000\137\000\137\000\ \137\000\137\000\137\000\137\000\150\000\151\000\171\000\169\000\ \031\000\031\000\031\000\031\000\031\000\031\000\031\000\031\000\ \031\000\031\000\031\000\031\000\031\000\031\000\031\000\031\000\ \031\000\031\000\031\000\031\000\031\000\031\000\031\000\031\000\ \031\000\031\000\031\000\031\000\031\000\031\000\031\000\031\000\ \031\000\031\000\031\000\031\000\031\000\031\000\031\000\031\000\ \031\000\031\000\031\000\031\000\031\000\031\000\031\000\031\000\ \031\000\031\000\031\000\031\000\031\000\031\000\031\000\031\000\ \031\000\031\000\031\000\031\000\031\000\031\000\031\000\031\000\ \002\000\003\000\170\000\198\000\003\000\003\000\003\000\197\000\ \218\000\127\000\003\000\003\000\128\000\003\000\003\000\003\000\ \138\000\138\000\138\000\138\000\138\000\138\000\138\000\138\000\ \138\000\138\000\003\000\217\000\003\000\003\000\003\000\003\000\ \003\000\223\000\255\255\226\000\003\000\255\255\124\000\003\000\ \003\000\003\000\230\000\233\000\003\001\003\000\003\000\183\000\ \003\000\003\000\003\000\141\000\141\000\141\000\141\000\141\000\ \141\000\141\000\141\000\249\000\019\001\003\000\003\000\003\000\ \003\000\003\000\003\000\003\000\020\001\024\001\183\000\005\000\ \182\000\021\001\005\000\005\000\005\000\022\001\022\001\025\001\ \005\000\005\000\249\000\005\000\005\000\005\000\227\000\227\000\ \227\000\227\000\249\000\125\000\003\000\251\000\003\000\000\000\ \005\000\003\000\005\000\005\000\005\000\005\000\005\000\000\000\ \239\000\011\001\006\000\006\001\013\001\006\000\006\000\006\000\ \000\000\000\000\011\001\006\000\006\000\013\001\006\000\006\000\ \006\000\000\000\000\000\000\000\000\000\000\000\000\000\003\000\ \000\000\003\000\000\000\006\000\005\000\006\000\006\000\006\000\ \006\000\006\000\000\000\000\000\000\000\156\000\000\000\000\000\ \156\000\156\000\156\000\000\000\000\000\000\000\156\000\156\000\ \000\000\156\000\179\000\156\000\000\000\000\000\000\000\000\000\ \000\000\000\000\005\000\000\000\005\000\000\000\156\000\006\000\ \156\000\178\000\156\000\156\000\156\000\000\000\000\000\000\000\ \176\000\000\000\176\000\176\000\176\000\176\000\000\000\000\000\ \000\000\176\000\176\000\000\000\176\000\176\000\176\000\000\000\ \011\001\000\000\000\000\012\001\000\000\006\000\000\000\006\000\ \000\000\176\000\156\000\176\000\177\000\176\000\176\000\176\000\ \164\000\000\000\000\000\006\000\000\000\000\000\006\000\006\000\ \006\000\000\000\000\000\000\000\006\000\006\000\000\000\006\000\ \006\000\006\000\000\000\000\000\000\000\000\000\000\000\167\000\ \156\000\166\000\156\000\165\000\006\000\176\000\006\000\006\000\ \006\000\006\000\006\000\000\000\000\000\000\000\000\000\000\000\ \006\000\000\000\000\000\006\000\006\000\006\000\000\000\255\255\ \000\000\006\000\006\000\000\000\006\000\006\000\006\000\000\000\ \000\000\255\255\000\000\176\000\255\255\176\000\000\000\175\000\ \006\000\006\000\000\000\006\000\006\000\006\000\006\000\006\000\ \255\255\000\000\000\000\000\000\000\000\000\000\000\000\006\000\ \000\000\184\000\006\000\006\000\006\000\000\000\000\000\168\000\ \006\000\006\000\000\000\006\000\006\000\006\000\006\000\174\000\ \006\000\000\000\009\001\000\000\172\000\006\000\000\000\000\000\ \006\000\000\000\006\000\006\000\006\000\006\000\006\000\255\255\ \000\000\000\000\006\000\255\255\255\255\006\000\006\000\006\000\ \000\000\000\000\000\000\006\000\006\000\000\000\163\000\006\000\ \006\000\000\000\000\000\173\000\000\000\006\000\000\000\000\000\ \000\000\000\000\000\000\006\000\006\000\006\000\006\000\006\000\ \006\000\006\000\000\000\000\000\000\000\156\000\000\000\000\000\ \156\000\156\000\156\000\000\000\000\000\214\000\156\000\156\000\ \215\000\156\000\157\000\156\000\000\000\000\000\000\000\000\000\ \000\000\000\000\006\000\000\000\006\000\000\000\156\000\006\000\ \156\000\156\000\158\000\156\000\156\000\000\000\000\000\000\000\ \006\000\000\000\216\000\006\000\006\000\155\000\000\000\000\000\ \000\000\006\000\006\000\000\000\006\000\006\000\006\000\000\000\ \000\000\000\000\000\000\000\000\000\000\006\000\000\000\006\000\ \000\000\006\000\156\000\006\000\006\000\006\000\006\000\006\000\ \000\000\000\000\000\000\154\000\000\000\154\000\154\000\154\000\ \154\000\000\000\000\000\000\000\154\000\154\000\010\001\154\000\ \154\000\154\000\000\000\000\000\000\000\000\000\000\000\212\000\ \156\000\000\000\156\000\000\000\154\000\006\000\154\000\154\000\ \154\000\154\000\154\000\000\000\000\000\000\000\003\000\000\000\ \000\000\003\000\003\000\003\000\000\000\000\000\153\000\152\000\ \003\000\000\000\003\000\003\000\003\000\000\000\000\000\000\000\ \000\000\000\000\000\000\006\000\000\000\006\000\000\000\003\000\ \154\000\003\000\003\000\003\000\003\000\003\000\000\000\000\000\ \095\000\142\000\142\000\142\000\142\000\142\000\142\000\142\000\ \142\000\000\000\000\000\000\000\000\000\000\000\000\000\255\255\ \000\000\000\000\000\000\000\000\000\000\000\000\154\000\094\000\ \154\000\000\000\000\000\003\000\098\000\098\000\098\000\098\000\ \098\000\098\000\098\000\098\000\098\000\098\000\098\000\098\000\ \098\000\098\000\098\000\098\000\098\000\098\000\098\000\098\000\ \098\000\098\000\098\000\098\000\098\000\098\000\000\000\000\000\ \000\000\003\000\098\000\003\000\098\000\098\000\098\000\098\000\ \098\000\098\000\098\000\098\000\098\000\098\000\098\000\098\000\ \098\000\098\000\098\000\098\000\098\000\098\000\098\000\098\000\ \098\000\098\000\098\000\098\000\098\000\098\000\000\000\096\000\ \144\000\144\000\144\000\144\000\144\000\144\000\144\000\144\000\ \144\000\144\000\000\000\000\000\000\000\000\000\000\000\000\000\ \180\000\144\000\144\000\144\000\144\000\144\000\144\000\000\000\ \000\000\000\000\000\000\255\255\224\000\224\000\224\000\224\000\ \224\000\224\000\224\000\224\000\224\000\224\000\000\000\180\000\ \228\000\228\000\228\000\228\000\228\000\228\000\228\000\228\000\ \000\000\144\000\144\000\144\000\144\000\144\000\144\000\181\000\ \181\000\181\000\181\000\181\000\181\000\181\000\181\000\181\000\ \181\000\000\000\000\000\097\000\097\000\097\000\097\000\097\000\ \097\000\097\000\097\000\097\000\097\000\097\000\097\000\097\000\ \097\000\097\000\097\000\097\000\097\000\097\000\097\000\097\000\ \097\000\097\000\097\000\097\000\097\000\097\000\097\000\097\000\ \097\000\097\000\097\000\097\000\097\000\097\000\097\000\097\000\ \097\000\097\000\097\000\097\000\097\000\097\000\097\000\097\000\ \097\000\097\000\097\000\097\000\097\000\097\000\097\000\097\000\ \097\000\097\000\097\000\097\000\097\000\097\000\097\000\097\000\ \097\000\097\000\097\000\076\000\000\000\000\000\000\000\000\000\ \000\000\000\000\078\000\000\000\029\000\029\000\029\000\029\000\ \029\000\029\000\029\000\029\000\029\000\029\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\076\000\076\000\076\000\ \076\000\077\000\076\000\079\000\079\000\079\000\079\000\079\000\ \079\000\079\000\079\000\079\000\079\000\079\000\079\000\079\000\ \079\000\079\000\079\000\079\000\079\000\079\000\079\000\000\000\ \000\000\000\000\000\000\029\000\000\000\076\000\076\000\076\000\ \076\000\077\000\076\000\079\000\079\000\079\000\079\000\079\000\ \079\000\079\000\079\000\079\000\079\000\079\000\079\000\079\000\ \079\000\079\000\079\000\079\000\079\000\079\000\079\000\076\000\ \000\000\000\000\000\000\000\000\000\000\000\000\078\000\000\000\ \029\000\029\000\029\000\029\000\029\000\029\000\029\000\029\000\ \029\000\029\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\076\000\080\000\076\000\076\000\077\000\076\000\079\000\ \079\000\079\000\079\000\079\000\079\000\079\000\079\000\081\000\ \079\000\079\000\079\000\079\000\079\000\079\000\079\000\079\000\ \082\000\079\000\079\000\000\000\000\000\000\000\000\000\029\000\ \000\000\076\000\080\000\076\000\076\000\077\000\076\000\079\000\ \079\000\079\000\079\000\079\000\079\000\079\000\079\000\081\000\ \079\000\079\000\079\000\079\000\079\000\079\000\079\000\079\000\ \082\000\079\000\079\000\047\000\229\000\229\000\229\000\229\000\ \229\000\229\000\229\000\229\000\047\000\047\000\047\000\047\000\ \047\000\047\000\047\000\047\000\047\000\047\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\047\000\047\000\047\000\ \047\000\047\000\047\000\047\000\047\000\047\000\047\000\047\000\ \047\000\047\000\047\000\047\000\047\000\047\000\047\000\047\000\ \047\000\047\000\047\000\047\000\047\000\047\000\047\000\000\000\ \000\000\000\000\000\000\047\000\000\000\047\000\047\000\047\000\ \047\000\047\000\047\000\047\000\047\000\047\000\047\000\047\000\ \047\000\047\000\047\000\047\000\047\000\047\000\047\000\047\000\ \047\000\047\000\047\000\047\000\047\000\047\000\047\000\000\000\ \000\000\000\000\000\000\000\000\031\000\031\000\031\000\031\000\ \031\000\031\000\031\000\031\000\031\000\031\000\031\000\031\000\ \031\000\031\000\031\000\031\000\031\000\031\000\031\000\031\000\ \031\000\031\000\031\000\031\000\031\000\031\000\031\000\031\000\ \031\000\031\000\031\000\031\000\031\000\031\000\031\000\031\000\ \031\000\031\000\031\000\031\000\031\000\031\000\031\000\031\000\ \031\000\031\000\031\000\031\000\031\000\031\000\031\000\031\000\ \031\000\031\000\031\000\031\000\031\000\031\000\031\000\031\000\ \031\000\031\000\031\000\031\000\048\000\048\000\048\000\048\000\ \048\000\048\000\048\000\048\000\048\000\048\000\048\000\048\000\ \048\000\048\000\048\000\048\000\048\000\048\000\048\000\048\000\ \048\000\048\000\048\000\048\000\048\000\048\000\048\000\048\000\ \048\000\048\000\048\000\048\000\048\000\048\000\048\000\048\000\ \048\000\048\000\048\000\048\000\048\000\048\000\048\000\048\000\ \048\000\048\000\048\000\048\000\048\000\048\000\048\000\048\000\ \048\000\048\000\048\000\048\000\048\000\048\000\048\000\048\000\ \048\000\048\000\048\000\048\000\032\000\254\000\254\000\254\000\ \254\000\254\000\254\000\254\000\254\000\032\000\032\000\032\000\ \032\000\032\000\032\000\032\000\032\000\032\000\032\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\032\000\032\000\ \032\000\032\000\032\000\032\000\032\000\032\000\032\000\032\000\ \032\000\032\000\032\000\032\000\032\000\032\000\032\000\032\000\ \032\000\032\000\032\000\032\000\032\000\032\000\032\000\032\000\ \000\000\000\000\000\000\000\000\032\000\000\000\032\000\032\000\ \032\000\032\000\032\000\032\000\032\000\032\000\032\000\032\000\ \032\000\032\000\032\000\032\000\032\000\032\000\032\000\032\000\ \032\000\032\000\032\000\032\000\032\000\032\000\032\000\032\000\ \145\000\145\000\145\000\145\000\145\000\145\000\145\000\145\000\ \145\000\145\000\000\000\000\000\000\000\000\000\000\000\000\000\ \183\000\145\000\145\000\145\000\145\000\145\000\145\000\225\000\ \225\000\225\000\225\000\225\000\225\000\225\000\225\000\225\000\ \225\000\000\000\000\000\000\000\000\000\000\000\000\000\183\000\ \000\000\182\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\145\000\145\000\145\000\145\000\145\000\145\000\181\000\ \181\000\181\000\181\000\181\000\181\000\181\000\181\000\181\000\ \181\000\000\000\000\000\000\000\000\000\048\000\048\000\048\000\ \048\000\048\000\048\000\048\000\048\000\048\000\048\000\048\000\ \048\000\048\000\048\000\048\000\048\000\048\000\048\000\048\000\ \048\000\048\000\048\000\048\000\048\000\048\000\048\000\048\000\ \048\000\048\000\048\000\048\000\048\000\048\000\048\000\048\000\ \048\000\048\000\048\000\048\000\048\000\048\000\048\000\048\000\ \048\000\048\000\048\000\048\000\048\000\048\000\048\000\048\000\ \048\000\048\000\048\000\048\000\048\000\048\000\048\000\048\000\ \048\000\048\000\048\000\048\000\048\000\033\000\255\000\255\000\ \255\000\255\000\255\000\255\000\255\000\255\000\033\000\033\000\ \033\000\033\000\033\000\033\000\033\000\033\000\033\000\033\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\033\000\ \033\000\033\000\033\000\033\000\033\000\033\000\033\000\033\000\ \033\000\033\000\033\000\033\000\033\000\033\000\033\000\033\000\ \033\000\033\000\033\000\033\000\033\000\033\000\033\000\033\000\ \033\000\000\000\000\000\000\000\000\000\033\000\000\000\033\000\ \033\000\033\000\033\000\033\000\033\000\033\000\033\000\033\000\ \033\000\033\000\033\000\033\000\033\000\033\000\033\000\033\000\ \033\000\033\000\033\000\033\000\033\000\033\000\033\000\033\000\ \033\000\231\000\231\000\231\000\231\000\231\000\231\000\231\000\ \231\000\231\000\231\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\231\000\231\000\231\000\231\000\231\000\231\000\ \252\000\252\000\252\000\252\000\252\000\252\000\252\000\252\000\ \252\000\252\000\253\000\253\000\253\000\253\000\253\000\253\000\ \253\000\253\000\253\000\253\000\000\000\000\000\000\000\000\000\ \000\000\000\000\231\000\231\000\231\000\231\000\231\000\231\000\ \000\001\000\001\000\001\000\001\000\001\000\001\000\001\000\001\ \000\000\000\000\000\000\000\000\000\000\000\000\048\000\048\000\ \048\000\048\000\048\000\048\000\048\000\048\000\048\000\048\000\ \048\000\048\000\048\000\048\000\048\000\048\000\048\000\048\000\ \048\000\048\000\048\000\048\000\048\000\048\000\048\000\048\000\ \048\000\048\000\048\000\048\000\048\000\048\000\048\000\048\000\ \048\000\048\000\048\000\048\000\048\000\048\000\048\000\048\000\ \048\000\048\000\048\000\048\000\048\000\048\000\048\000\048\000\ \048\000\048\000\048\000\048\000\048\000\048\000\048\000\048\000\ \048\000\048\000\048\000\048\000\048\000\048\000\033\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\033\000\ \033\000\033\000\033\000\033\000\033\000\033\000\033\000\033\000\ \033\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \033\000\033\000\033\000\033\000\033\000\033\000\033\000\033\000\ \033\000\033\000\033\000\033\000\033\000\033\000\033\000\033\000\ \033\000\033\000\033\000\033\000\033\000\033\000\033\000\033\000\ \033\000\033\000\000\000\000\000\000\000\000\000\033\000\000\000\ \033\000\033\000\033\000\033\000\033\000\033\000\033\000\033\000\ \033\000\033\000\033\000\033\000\033\000\073\000\033\000\033\000\ \033\000\033\000\033\000\033\000\033\000\033\000\033\000\033\000\ \033\000\033\000\232\000\232\000\232\000\232\000\232\000\232\000\ \232\000\232\000\232\000\232\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\232\000\232\000\232\000\232\000\232\000\ \232\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\232\000\232\000\232\000\232\000\232\000\ \232\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\048\000\ \048\000\048\000\048\000\048\000\048\000\048\000\048\000\048\000\ \048\000\048\000\048\000\048\000\048\000\048\000\048\000\048\000\ \048\000\048\000\048\000\048\000\048\000\048\000\048\000\048\000\ \048\000\048\000\048\000\048\000\048\000\048\000\048\000\048\000\ \048\000\048\000\048\000\048\000\048\000\048\000\048\000\048\000\ \048\000\048\000\048\000\048\000\048\000\048\000\048\000\048\000\ \048\000\048\000\048\000\048\000\048\000\048\000\048\000\048\000\ \048\000\048\000\048\000\048\000\048\000\048\000\048\000\033\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \033\000\033\000\033\000\033\000\033\000\033\000\033\000\033\000\ \033\000\033\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\033\000\033\000\033\000\033\000\033\000\033\000\033\000\ \033\000\033\000\033\000\033\000\033\000\033\000\033\000\033\000\ \033\000\033\000\033\000\033\000\033\000\033\000\033\000\033\000\ \033\000\033\000\033\000\000\000\000\000\000\000\000\000\033\000\ \000\000\033\000\033\000\033\000\033\000\070\000\033\000\033\000\ \033\000\033\000\033\000\033\000\033\000\033\000\033\000\033\000\ \033\000\033\000\033\000\033\000\033\000\033\000\033\000\033\000\ \033\000\033\000\033\000\001\001\001\001\001\001\001\001\001\001\ \001\001\001\001\001\001\001\001\001\001\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\001\001\001\001\001\001\001\001\ \001\001\001\001\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\001\001\001\001\001\001\001\001\ \001\001\001\001\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \048\000\048\000\048\000\048\000\048\000\048\000\048\000\048\000\ \048\000\048\000\048\000\048\000\048\000\048\000\048\000\048\000\ \048\000\048\000\048\000\048\000\048\000\048\000\048\000\048\000\ \048\000\048\000\048\000\048\000\048\000\048\000\048\000\048\000\ \048\000\048\000\048\000\048\000\048\000\048\000\048\000\048\000\ \048\000\048\000\048\000\048\000\048\000\048\000\048\000\048\000\ \048\000\048\000\048\000\048\000\048\000\048\000\048\000\048\000\ \048\000\048\000\048\000\048\000\048\000\048\000\048\000\048\000\ \050\000\000\000\050\000\050\000\050\000\050\000\000\000\000\000\ \000\000\050\000\050\000\000\000\050\000\050\000\050\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\050\000\000\000\050\000\050\000\050\000\050\000\050\000\ \063\000\063\000\063\000\063\000\063\000\063\000\063\000\063\000\ \063\000\063\000\063\000\063\000\063\000\063\000\063\000\063\000\ \063\000\063\000\063\000\063\000\063\000\063\000\063\000\063\000\ \063\000\063\000\000\000\064\000\000\000\050\000\065\000\000\000\ \065\000\065\000\065\000\065\000\065\000\065\000\065\000\065\000\ \065\000\065\000\065\000\065\000\065\000\065\000\065\000\065\000\ \065\000\065\000\065\000\065\000\065\000\065\000\065\000\065\000\ \065\000\065\000\000\000\050\000\000\000\050\000\002\001\002\001\ \002\001\002\001\002\001\002\001\002\001\002\001\002\001\002\001\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\002\001\ \002\001\002\001\002\001\002\001\002\001\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\002\001\ \002\001\002\001\002\001\002\001\002\001\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\062\000\ \062\000\062\000\062\000\062\000\062\000\062\000\062\000\062\000\ \062\000\062\000\062\000\062\000\062\000\062\000\062\000\062\000\ \062\000\062\000\062\000\062\000\062\000\062\000\062\000\062\000\ \062\000\062\000\062\000\062\000\062\000\062\000\062\000\062\000\ \062\000\062\000\062\000\062\000\062\000\062\000\062\000\062\000\ \062\000\062\000\062\000\062\000\062\000\062\000\062\000\062\000\ \062\000\062\000\062\000\062\000\062\000\062\000\062\000\062\000\ \062\000\062\000\062\000\062\000\062\000\062\000\062\000\059\000\ \000\000\000\000\059\000\059\000\059\000\000\000\000\000\000\000\ \059\000\059\000\000\000\059\000\060\000\059\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \059\000\000\000\000\000\059\000\059\000\059\000\059\000\000\000\ \004\001\004\001\004\001\004\001\004\001\004\001\004\001\004\001\ \004\001\004\001\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\004\001\004\001\004\001\004\001\004\001\004\001\000\000\ \000\000\000\000\000\000\000\000\059\000\000\000\000\000\000\000\ \000\000\000\000\050\000\000\000\050\000\050\000\050\000\050\000\ \000\000\000\000\000\000\050\000\050\000\000\000\050\000\050\000\ \050\000\004\001\004\001\004\001\004\001\004\001\004\001\000\000\ \000\000\000\000\059\000\050\000\061\000\050\000\050\000\050\000\ \050\000\050\000\053\000\053\000\053\000\053\000\053\000\053\000\ \053\000\053\000\053\000\053\000\053\000\053\000\053\000\053\000\ \053\000\053\000\053\000\053\000\053\000\053\000\053\000\053\000\ \053\000\053\000\053\000\053\000\000\000\052\000\000\000\050\000\ \053\000\000\000\053\000\053\000\053\000\053\000\053\000\053\000\ \053\000\053\000\053\000\053\000\053\000\053\000\053\000\053\000\ \053\000\053\000\053\000\053\000\053\000\053\000\053\000\053\000\ \053\000\053\000\053\000\053\000\000\000\050\000\000\000\050\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\051\000\051\000\051\000\051\000\051\000\051\000\051\000\ \051\000\051\000\051\000\051\000\051\000\051\000\051\000\051\000\ \051\000\051\000\051\000\051\000\051\000\051\000\051\000\051\000\ \051\000\051\000\051\000\051\000\051\000\051\000\051\000\051\000\ \051\000\051\000\051\000\051\000\051\000\051\000\051\000\051\000\ \051\000\051\000\051\000\051\000\051\000\051\000\051\000\051\000\ \051\000\051\000\051\000\051\000\051\000\051\000\051\000\051\000\ \051\000\051\000\051\000\051\000\051\000\051\000\051\000\051\000\ \051\000\033\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\033\000\033\000\033\000\033\000\033\000\033\000\ \033\000\033\000\033\000\033\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\033\000\033\000\033\000\033\000\033\000\ \033\000\033\000\033\000\033\000\033\000\033\000\033\000\033\000\ \033\000\033\000\033\000\033\000\033\000\033\000\033\000\033\000\ \033\000\033\000\033\000\033\000\033\000\000\000\000\000\000\000\ \000\000\033\000\000\000\033\000\033\000\033\000\033\000\033\000\ \033\000\033\000\033\000\033\000\033\000\033\000\033\000\033\000\ \033\000\033\000\033\000\033\000\033\000\033\000\033\000\033\000\ \033\000\033\000\033\000\033\000\033\000\000\000\000\000\000\000\ \000\000\000\000\000\000\047\000\047\000\047\000\047\000\047\000\ \047\000\047\000\047\000\047\000\047\000\047\000\047\000\047\000\ \047\000\047\000\047\000\047\000\047\000\047\000\047\000\047\000\ \047\000\047\000\047\000\047\000\047\000\000\000\000\000\000\000\ \000\000\047\000\000\000\047\000\047\000\047\000\047\000\047\000\ \047\000\047\000\047\000\047\000\047\000\047\000\047\000\047\000\ \047\000\047\000\047\000\047\000\047\000\047\000\047\000\047\000\ \047\000\047\000\047\000\047\000\047\000\000\000\000\000\000\000\ \000\000\000\000\048\000\048\000\048\000\048\000\048\000\048\000\ \048\000\048\000\048\000\048\000\048\000\048\000\048\000\048\000\ \048\000\048\000\048\000\048\000\048\000\048\000\048\000\048\000\ \048\000\048\000\048\000\048\000\048\000\048\000\048\000\048\000\ \048\000\048\000\048\000\048\000\048\000\048\000\048\000\048\000\ \048\000\048\000\048\000\048\000\048\000\048\000\048\000\048\000\ \048\000\048\000\048\000\048\000\048\000\048\000\048\000\048\000\ \048\000\048\000\048\000\048\000\048\000\048\000\048\000\048\000\ \048\000\048\000\031\000\031\000\031\000\031\000\031\000\031\000\ \031\000\031\000\031\000\031\000\031\000\031\000\031\000\031\000\ \031\000\031\000\031\000\031\000\031\000\031\000\031\000\031\000\ \031\000\031\000\031\000\031\000\031\000\031\000\031\000\031\000\ \031\000\031\000\031\000\031\000\031\000\031\000\031\000\031\000\ \031\000\031\000\031\000\031\000\031\000\031\000\031\000\031\000\ \031\000\031\000\031\000\031\000\031\000\031\000\031\000\031\000\ \031\000\031\000\031\000\031\000\031\000\031\000\031\000\031\000\ \031\000\031\000\047\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\047\000\047\000\047\000\047\000\047\000\ \047\000\047\000\047\000\047\000\047\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\047\000\047\000\047\000\047\000\ \047\000\047\000\047\000\047\000\047\000\047\000\047\000\047\000\ \047\000\047\000\047\000\047\000\047\000\047\000\047\000\047\000\ \047\000\047\000\047\000\047\000\047\000\047\000\000\000\000\000\ \000\000\000\000\047\000\000\000\047\000\047\000\047\000\047\000\ \047\000\047\000\047\000\047\000\047\000\047\000\047\000\047\000\ \047\000\047\000\047\000\047\000\047\000\047\000\047\000\047\000\ \047\000\047\000\047\000\047\000\047\000\047\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\048\000\048\000\048\000\048\000\048\000\ \048\000\048\000\048\000\048\000\048\000\048\000\048\000\048\000\ \048\000\048\000\048\000\048\000\048\000\048\000\048\000\048\000\ \048\000\048\000\048\000\048\000\048\000\048\000\048\000\048\000\ \048\000\048\000\048\000\048\000\048\000\048\000\048\000\048\000\ \048\000\048\000\048\000\048\000\048\000\048\000\048\000\048\000\ \048\000\048\000\048\000\048\000\048\000\048\000\048\000\048\000\ \048\000\048\000\048\000\048\000\048\000\048\000\048\000\048\000\ \048\000\048\000\048\000\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\047\000\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\047\000\047\000\047\000\047\000\047\000\ \047\000\047\000\047\000\047\000\047\000\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\047\000\047\000\047\000\047\000\ \047\000\047\000\047\000\047\000\047\000\047\000\047\000\047\000\ \047\000\047\000\047\000\047\000\047\000\047\000\047\000\047\000\ \047\000\047\000\047\000\047\000\047\000\047\000\255\255\255\255\ \255\255\255\255\047\000\255\255\047\000\047\000\047\000\047\000\ \047\000\047\000\047\000\047\000\047\000\047\000\047\000\047\000\ \047\000\047\000\047\000\047\000\047\000\047\000\047\000\047\000\ \047\000\047\000\047\000\047\000\047\000\047\000\255\255\255\255\ \255\255\255\255\255\255\050\000\000\000\050\000\050\000\050\000\ \050\000\000\000\000\000\000\000\050\000\050\000\000\000\050\000\ \050\000\050\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\050\000\000\000\050\000\050\000\ \050\000\050\000\050\000\000\000\000\000\072\000\000\000\000\000\ \072\000\072\000\072\000\000\000\000\000\000\000\072\000\072\000\ \000\000\072\000\000\000\072\000\004\001\004\001\004\001\004\001\ \004\001\004\001\004\001\004\001\004\001\004\001\072\000\000\000\ \050\000\072\000\072\000\072\000\072\000\004\001\004\001\004\001\ \004\001\004\001\004\001\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\050\000\000\000\ \050\000\000\000\072\000\000\000\000\000\004\001\004\001\004\001\ \004\001\004\001\004\001\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \072\000\005\001\000\000\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\076\000\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\076\000\076\000\076\000\076\000\ \076\000\076\000\076\000\076\000\076\000\076\000\056\000\255\255\ \255\255\255\255\255\255\255\255\255\255\076\000\076\000\076\000\ \076\000\076\000\076\000\076\000\076\000\076\000\076\000\076\000\ \076\000\076\000\076\000\076\000\076\000\076\000\076\000\076\000\ \076\000\076\000\076\000\076\000\076\000\076\000\076\000\255\255\ \255\255\255\255\255\255\076\000\255\255\076\000\076\000\076\000\ \076\000\076\000\076\000\076\000\076\000\076\000\076\000\076\000\ \076\000\076\000\076\000\076\000\076\000\076\000\076\000\076\000\ \076\000\076\000\076\000\076\000\076\000\076\000\076\000\255\255\ \255\255\255\255\255\255\255\255\051\000\051\000\051\000\051\000\ \051\000\051\000\051\000\051\000\051\000\051\000\051\000\051\000\ \051\000\051\000\051\000\051\000\051\000\051\000\051\000\051\000\ \051\000\051\000\051\000\051\000\051\000\051\000\051\000\051\000\ \051\000\051\000\051\000\051\000\051\000\051\000\051\000\051\000\ \051\000\051\000\051\000\051\000\051\000\051\000\051\000\051\000\ \051\000\051\000\051\000\051\000\051\000\051\000\051\000\051\000\ \051\000\051\000\051\000\051\000\051\000\051\000\051\000\051\000\ \051\000\051\000\051\000\051\000\054\000\054\000\054\000\054\000\ \054\000\054\000\054\000\054\000\054\000\054\000\054\000\054\000\ \054\000\054\000\054\000\054\000\054\000\054\000\054\000\054\000\ \054\000\054\000\054\000\054\000\054\000\054\000\054\000\054\000\ \054\000\054\000\054\000\054\000\054\000\054\000\054\000\054\000\ \054\000\054\000\054\000\054\000\054\000\054\000\054\000\054\000\ \054\000\054\000\054\000\054\000\054\000\054\000\054\000\054\000\ \054\000\054\000\054\000\054\000\054\000\054\000\054\000\054\000\ \054\000\054\000\054\000\054\000\255\255\053\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\053\000\053\000\ \053\000\053\000\053\000\053\000\053\000\053\000\053\000\053\000\ \055\000\000\000\000\000\000\000\000\000\000\000\000\000\053\000\ \053\000\053\000\053\000\053\000\053\000\053\000\053\000\053\000\ \053\000\053\000\053\000\053\000\053\000\053\000\053\000\053\000\ \053\000\053\000\053\000\053\000\053\000\053\000\053\000\053\000\ \053\000\000\000\000\000\000\000\000\000\053\000\000\000\053\000\ \053\000\053\000\053\000\053\000\053\000\053\000\053\000\053\000\ \053\000\053\000\053\000\053\000\053\000\053\000\053\000\053\000\ \053\000\053\000\053\000\053\000\053\000\053\000\053\000\053\000\ \053\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\054\000\054\000\ \054\000\054\000\054\000\054\000\054\000\054\000\054\000\054\000\ \054\000\054\000\054\000\054\000\054\000\054\000\054\000\054\000\ \054\000\054\000\054\000\054\000\054\000\054\000\054\000\054\000\ \054\000\054\000\054\000\054\000\054\000\054\000\054\000\054\000\ \054\000\054\000\054\000\054\000\054\000\054\000\054\000\054\000\ \054\000\054\000\054\000\054\000\054\000\054\000\054\000\054\000\ \054\000\054\000\054\000\054\000\054\000\054\000\054\000\054\000\ \054\000\054\000\054\000\054\000\054\000\054\000\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\057\000\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\057\000\057\000\ \057\000\057\000\057\000\057\000\057\000\057\000\057\000\057\000\ \056\000\255\255\255\255\255\255\255\255\255\255\255\255\057\000\ \057\000\057\000\057\000\057\000\057\000\057\000\057\000\057\000\ \057\000\057\000\057\000\057\000\057\000\057\000\057\000\057\000\ \057\000\057\000\057\000\057\000\057\000\057\000\057\000\057\000\ \057\000\255\255\255\255\255\255\255\255\057\000\255\255\057\000\ \057\000\057\000\057\000\057\000\057\000\057\000\057\000\057\000\ \057\000\057\000\057\000\057\000\057\000\057\000\057\000\057\000\ \057\000\057\000\057\000\057\000\057\000\057\000\057\000\057\000\ \057\000\255\255\255\255\255\255\255\255\255\255\057\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\057\000\ \057\000\057\000\057\000\057\000\057\000\057\000\057\000\057\000\ \057\000\056\000\000\000\000\000\000\000\000\000\000\000\000\000\ \057\000\057\000\057\000\057\000\057\000\057\000\057\000\057\000\ \057\000\057\000\057\000\057\000\057\000\057\000\057\000\057\000\ \057\000\057\000\057\000\057\000\057\000\057\000\057\000\057\000\ \057\000\057\000\000\000\000\000\000\000\000\000\057\000\000\000\ \057\000\057\000\057\000\057\000\057\000\057\000\057\000\057\000\ \057\000\057\000\057\000\057\000\057\000\057\000\057\000\057\000\ \057\000\057\000\057\000\057\000\057\000\057\000\057\000\057\000\ \057\000\057\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\255\255\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\054\000\ \054\000\054\000\054\000\054\000\054\000\054\000\054\000\054\000\ \054\000\054\000\054\000\054\000\054\000\054\000\054\000\054\000\ \054\000\054\000\054\000\054\000\054\000\054\000\054\000\054\000\ \054\000\054\000\054\000\054\000\054\000\054\000\054\000\054\000\ \054\000\054\000\054\000\054\000\054\000\054\000\054\000\054\000\ \054\000\054\000\054\000\054\000\054\000\054\000\054\000\054\000\ \054\000\054\000\054\000\054\000\054\000\054\000\054\000\054\000\ \054\000\054\000\054\000\054\000\054\000\054\000\054\000\057\000\ \057\000\057\000\057\000\057\000\057\000\057\000\057\000\057\000\ \057\000\057\000\057\000\057\000\057\000\057\000\057\000\057\000\ \057\000\057\000\057\000\057\000\057\000\057\000\057\000\057\000\ \057\000\000\000\000\000\000\000\000\000\057\000\000\000\057\000\ \057\000\057\000\057\000\057\000\057\000\057\000\057\000\057\000\ \057\000\057\000\057\000\057\000\057\000\057\000\057\000\057\000\ \057\000\057\000\057\000\057\000\057\000\057\000\057\000\057\000\ \057\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\051\000\051\000\ \051\000\051\000\051\000\051\000\051\000\051\000\051\000\051\000\ \051\000\051\000\051\000\051\000\051\000\051\000\051\000\051\000\ \051\000\051\000\051\000\051\000\051\000\051\000\051\000\051\000\ \051\000\051\000\051\000\051\000\051\000\051\000\051\000\051\000\ \051\000\051\000\051\000\051\000\051\000\051\000\051\000\051\000\ \051\000\051\000\051\000\051\000\051\000\051\000\051\000\051\000\ \051\000\051\000\051\000\051\000\051\000\051\000\051\000\051\000\ \051\000\051\000\051\000\051\000\051\000\051\000\059\000\000\000\ \000\000\059\000\059\000\059\000\076\000\000\000\000\000\059\000\ \059\000\000\000\059\000\059\000\059\000\078\000\078\000\078\000\ \078\000\078\000\078\000\078\000\078\000\078\000\078\000\059\000\ \000\000\059\000\059\000\059\000\059\000\059\000\076\000\076\000\ \076\000\076\000\077\000\076\000\088\000\088\000\088\000\088\000\ \088\000\088\000\088\000\088\000\088\000\088\000\088\000\088\000\ \088\000\088\000\088\000\088\000\088\000\088\000\088\000\088\000\ \000\000\000\000\000\000\059\000\078\000\000\000\076\000\076\000\ \076\000\076\000\077\000\076\000\088\000\088\000\088\000\088\000\ \088\000\088\000\088\000\088\000\088\000\088\000\088\000\088\000\ \088\000\088\000\088\000\088\000\088\000\088\000\088\000\088\000\ \000\000\059\000\000\000\059\000\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\076\000\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\076\000\076\000\076\000\076\000\ \076\000\076\000\076\000\076\000\076\000\076\000\068\000\255\255\ \255\255\255\255\255\255\255\255\255\255\076\000\076\000\076\000\ \076\000\076\000\076\000\076\000\076\000\076\000\076\000\076\000\ \076\000\076\000\076\000\076\000\076\000\076\000\076\000\076\000\ \076\000\076\000\076\000\076\000\076\000\076\000\076\000\255\255\ \255\255\255\255\255\255\076\000\255\255\076\000\076\000\076\000\ \076\000\076\000\076\000\076\000\076\000\076\000\076\000\076\000\ \076\000\076\000\076\000\076\000\076\000\076\000\076\000\076\000\ \076\000\076\000\076\000\076\000\076\000\076\000\076\000\255\255\ \255\255\255\255\255\255\255\255\062\000\062\000\062\000\062\000\ \062\000\062\000\062\000\062\000\062\000\062\000\062\000\062\000\ \062\000\062\000\062\000\062\000\062\000\062\000\062\000\062\000\ \062\000\062\000\062\000\062\000\062\000\062\000\062\000\062\000\ \062\000\062\000\062\000\062\000\062\000\062\000\062\000\062\000\ \062\000\062\000\062\000\062\000\062\000\062\000\062\000\062\000\ \062\000\062\000\062\000\062\000\062\000\062\000\062\000\062\000\ \062\000\062\000\062\000\062\000\062\000\062\000\062\000\062\000\ \062\000\062\000\062\000\062\000\066\000\066\000\066\000\066\000\ \066\000\066\000\066\000\066\000\066\000\066\000\066\000\066\000\ \066\000\066\000\066\000\066\000\066\000\066\000\066\000\066\000\ \066\000\066\000\066\000\066\000\066\000\066\000\066\000\066\000\ \066\000\066\000\066\000\066\000\066\000\066\000\066\000\066\000\ \066\000\066\000\066\000\066\000\066\000\066\000\066\000\066\000\ \066\000\066\000\066\000\066\000\066\000\066\000\066\000\066\000\ \066\000\066\000\066\000\066\000\066\000\066\000\066\000\066\000\ \066\000\066\000\066\000\066\000\255\255\063\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\063\000\063\000\ \063\000\063\000\063\000\063\000\063\000\063\000\063\000\063\000\ \068\000\000\000\000\000\000\000\000\000\000\000\000\000\063\000\ \063\000\063\000\063\000\063\000\063\000\063\000\063\000\063\000\ \063\000\063\000\063\000\063\000\063\000\063\000\063\000\063\000\ \063\000\063\000\063\000\063\000\063\000\063\000\063\000\063\000\ \063\000\000\000\000\000\000\000\000\000\063\000\000\000\063\000\ \063\000\063\000\063\000\063\000\063\000\063\000\063\000\063\000\ \063\000\063\000\063\000\063\000\063\000\063\000\063\000\063\000\ \063\000\063\000\063\000\063\000\063\000\063\000\063\000\063\000\ \063\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\066\000\066\000\ \066\000\066\000\066\000\066\000\066\000\066\000\066\000\066\000\ \066\000\066\000\066\000\066\000\066\000\066\000\066\000\066\000\ \066\000\066\000\066\000\066\000\066\000\066\000\066\000\066\000\ \066\000\066\000\066\000\066\000\066\000\066\000\066\000\066\000\ \066\000\066\000\066\000\066\000\066\000\066\000\066\000\066\000\ \066\000\066\000\066\000\066\000\066\000\066\000\066\000\066\000\ \066\000\066\000\066\000\066\000\066\000\066\000\066\000\066\000\ \066\000\066\000\066\000\066\000\066\000\066\000\065\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\065\000\ \065\000\065\000\065\000\065\000\065\000\065\000\065\000\065\000\ \065\000\067\000\000\000\000\000\000\000\000\000\000\000\000\000\ \065\000\065\000\065\000\065\000\065\000\065\000\065\000\065\000\ \065\000\065\000\065\000\065\000\065\000\065\000\065\000\065\000\ \065\000\065\000\065\000\065\000\065\000\065\000\065\000\065\000\ \065\000\065\000\000\000\000\000\000\000\000\000\065\000\000\000\ \065\000\065\000\065\000\065\000\065\000\065\000\065\000\065\000\ \065\000\065\000\065\000\065\000\065\000\065\000\065\000\065\000\ \065\000\065\000\065\000\065\000\065\000\065\000\065\000\065\000\ \065\000\065\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\066\000\ \066\000\066\000\066\000\066\000\066\000\066\000\066\000\066\000\ \066\000\066\000\066\000\066\000\066\000\066\000\066\000\066\000\ \066\000\066\000\066\000\066\000\066\000\066\000\066\000\066\000\ \066\000\066\000\066\000\066\000\066\000\066\000\066\000\066\000\ \066\000\066\000\066\000\066\000\066\000\066\000\066\000\066\000\ \066\000\066\000\066\000\066\000\066\000\066\000\066\000\066\000\ \066\000\066\000\066\000\066\000\066\000\066\000\066\000\066\000\ \066\000\066\000\066\000\066\000\066\000\066\000\066\000\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\063\000\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\063\000\ \063\000\063\000\063\000\063\000\063\000\063\000\063\000\063\000\ \063\000\068\000\255\255\255\255\255\255\255\255\255\255\255\255\ \063\000\063\000\063\000\063\000\063\000\063\000\063\000\063\000\ \063\000\063\000\063\000\063\000\063\000\063\000\063\000\063\000\ \063\000\063\000\063\000\063\000\063\000\063\000\063\000\063\000\ \063\000\063\000\255\255\255\255\255\255\255\255\063\000\255\255\ \063\000\063\000\063\000\063\000\063\000\063\000\063\000\063\000\ \063\000\063\000\063\000\063\000\063\000\063\000\063\000\063\000\ \063\000\063\000\063\000\063\000\063\000\063\000\063\000\063\000\ \063\000\063\000\255\255\255\255\255\255\255\255\255\255\000\000\ \000\000\063\000\063\000\063\000\063\000\063\000\063\000\063\000\ \063\000\063\000\063\000\063\000\063\000\063\000\063\000\063\000\ \063\000\063\000\063\000\063\000\063\000\063\000\063\000\063\000\ \063\000\063\000\063\000\000\000\000\000\000\000\000\000\063\000\ \000\000\063\000\063\000\063\000\063\000\063\000\063\000\063\000\ \063\000\063\000\063\000\063\000\063\000\063\000\063\000\063\000\ \063\000\063\000\063\000\063\000\063\000\063\000\063\000\063\000\ \063\000\063\000\063\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\255\255\ \062\000\062\000\062\000\062\000\062\000\062\000\062\000\062\000\ \062\000\062\000\062\000\062\000\062\000\062\000\062\000\062\000\ \062\000\062\000\062\000\062\000\062\000\062\000\062\000\062\000\ \062\000\062\000\062\000\062\000\062\000\062\000\062\000\062\000\ \062\000\062\000\062\000\062\000\062\000\062\000\062\000\062\000\ \062\000\062\000\062\000\062\000\062\000\062\000\062\000\062\000\ \062\000\062\000\062\000\062\000\062\000\062\000\062\000\062\000\ \062\000\062\000\062\000\062\000\062\000\062\000\062\000\062\000\ \033\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\033\000\033\000\033\000\033\000\033\000\033\000\033\000\ \033\000\033\000\033\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\033\000\033\000\033\000\033\000\033\000\033\000\ \033\000\033\000\033\000\033\000\033\000\033\000\033\000\033\000\ \033\000\033\000\033\000\033\000\033\000\033\000\033\000\033\000\ \033\000\033\000\033\000\033\000\000\000\000\000\000\000\000\000\ \033\000\000\000\033\000\033\000\033\000\033\000\033\000\033\000\ \033\000\033\000\033\000\033\000\033\000\033\000\033\000\033\000\ \033\000\033\000\033\000\033\000\033\000\071\000\033\000\033\000\ \033\000\033\000\033\000\033\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\048\000\048\000\048\000\048\000\048\000\048\000\048\000\ \048\000\048\000\048\000\048\000\048\000\048\000\048\000\048\000\ \048\000\048\000\048\000\048\000\048\000\048\000\048\000\048\000\ \048\000\048\000\048\000\048\000\048\000\048\000\048\000\048\000\ \048\000\048\000\048\000\048\000\048\000\048\000\048\000\048\000\ \048\000\048\000\048\000\048\000\048\000\048\000\048\000\048\000\ \048\000\048\000\048\000\048\000\048\000\048\000\048\000\048\000\ \048\000\048\000\048\000\048\000\048\000\048\000\048\000\048\000\ \048\000\072\000\000\000\072\000\033\000\000\000\000\000\072\000\ \072\000\000\000\072\000\000\000\072\000\033\000\033\000\033\000\ \033\000\033\000\033\000\033\000\033\000\033\000\033\000\000\000\ \000\000\072\000\072\000\072\000\000\000\072\000\033\000\033\000\ \033\000\033\000\033\000\033\000\033\000\033\000\033\000\033\000\ \033\000\033\000\033\000\033\000\033\000\033\000\033\000\033\000\ \033\000\033\000\033\000\033\000\033\000\033\000\033\000\033\000\ \000\000\000\000\000\000\072\000\033\000\000\000\033\000\033\000\ \033\000\033\000\033\000\033\000\033\000\033\000\033\000\033\000\ \033\000\033\000\033\000\033\000\033\000\033\000\033\000\033\000\ \033\000\033\000\033\000\033\000\033\000\033\000\033\000\033\000\ \000\000\072\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\048\000\048\000\048\000\ \048\000\048\000\048\000\048\000\048\000\048\000\048\000\048\000\ \048\000\048\000\048\000\048\000\048\000\048\000\048\000\048\000\ \048\000\048\000\048\000\048\000\048\000\048\000\048\000\048\000\ \048\000\048\000\048\000\048\000\048\000\048\000\048\000\048\000\ \048\000\048\000\048\000\048\000\048\000\048\000\048\000\048\000\ \048\000\048\000\048\000\048\000\048\000\048\000\048\000\048\000\ \048\000\048\000\048\000\048\000\048\000\048\000\048\000\048\000\ \048\000\048\000\048\000\048\000\048\000\033\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\033\000\033\000\ \033\000\033\000\033\000\033\000\033\000\033\000\033\000\033\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\033\000\ \033\000\033\000\033\000\033\000\033\000\033\000\033\000\033\000\ \033\000\033\000\033\000\033\000\033\000\033\000\033\000\033\000\ \033\000\033\000\033\000\033\000\033\000\033\000\033\000\033\000\ \033\000\000\000\000\000\000\000\000\000\033\000\000\000\033\000\ \033\000\033\000\074\000\033\000\033\000\033\000\033\000\033\000\ \033\000\033\000\033\000\033\000\033\000\033\000\033\000\033\000\ \033\000\033\000\033\000\033\000\033\000\033\000\033\000\033\000\ \033\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\048\000\048\000\ \048\000\048\000\048\000\048\000\048\000\048\000\048\000\048\000\ \048\000\048\000\048\000\048\000\048\000\048\000\048\000\048\000\ \048\000\048\000\048\000\048\000\048\000\048\000\048\000\048\000\ \048\000\048\000\048\000\048\000\048\000\048\000\048\000\048\000\ \048\000\048\000\048\000\048\000\048\000\048\000\048\000\048\000\ \048\000\048\000\048\000\048\000\048\000\048\000\048\000\048\000\ \048\000\048\000\048\000\048\000\048\000\048\000\048\000\048\000\ \048\000\048\000\048\000\048\000\048\000\048\000\075\000\000\000\ \075\000\033\000\000\000\000\000\075\000\075\000\000\000\075\000\ \000\000\075\000\033\000\033\000\033\000\033\000\033\000\033\000\ \033\000\033\000\033\000\033\000\000\000\000\000\075\000\075\000\ \075\000\000\000\075\000\033\000\033\000\033\000\033\000\033\000\ \033\000\033\000\033\000\033\000\033\000\033\000\033\000\033\000\ \033\000\033\000\033\000\033\000\033\000\033\000\033\000\033\000\ \033\000\033\000\033\000\033\000\033\000\000\000\000\000\000\000\ \075\000\033\000\000\000\033\000\033\000\033\000\033\000\033\000\ \033\000\033\000\033\000\033\000\033\000\033\000\033\000\033\000\ \033\000\033\000\033\000\033\000\033\000\033\000\033\000\033\000\ \033\000\033\000\033\000\033\000\033\000\000\000\075\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\048\000\048\000\048\000\048\000\048\000\048\000\ \048\000\048\000\048\000\048\000\048\000\048\000\048\000\048\000\ \048\000\048\000\048\000\048\000\048\000\048\000\048\000\048\000\ \048\000\048\000\048\000\048\000\048\000\048\000\048\000\048\000\ \048\000\048\000\048\000\048\000\048\000\048\000\048\000\048\000\ \048\000\048\000\048\000\048\000\048\000\048\000\048\000\048\000\ \048\000\048\000\048\000\048\000\048\000\048\000\048\000\048\000\ \048\000\048\000\048\000\048\000\048\000\048\000\048\000\048\000\ \048\000\048\000\075\000\000\000\000\000\075\000\075\000\075\000\ \000\000\000\000\000\000\075\000\075\000\000\000\075\000\000\000\ \075\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\075\000\000\000\000\000\075\000\075\000\ \075\000\075\000\000\000\000\000\000\000\000\000\076\000\000\000\ \000\000\000\000\093\000\000\000\093\000\000\000\000\000\092\000\ \092\000\092\000\092\000\092\000\092\000\092\000\092\000\092\000\ \092\000\000\000\000\000\000\000\000\000\000\000\000\000\075\000\ \076\000\076\000\076\000\076\000\076\000\076\000\076\000\076\000\ \076\000\076\000\076\000\076\000\076\000\076\000\076\000\076\000\ \076\000\076\000\076\000\076\000\076\000\076\000\076\000\076\000\ \076\000\076\000\000\000\000\000\000\000\075\000\076\000\000\000\ \076\000\076\000\076\000\076\000\076\000\076\000\076\000\076\000\ \076\000\076\000\076\000\076\000\076\000\076\000\076\000\076\000\ \076\000\076\000\076\000\076\000\076\000\076\000\076\000\076\000\ \076\000\076\000\076\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\091\000\091\000\076\000\076\000\076\000\ \076\000\076\000\076\000\076\000\076\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\076\000\076\000\076\000\076\000\ \076\000\076\000\076\000\076\000\076\000\076\000\076\000\076\000\ \076\000\076\000\076\000\076\000\076\000\076\000\076\000\076\000\ \076\000\076\000\076\000\076\000\076\000\076\000\000\000\000\000\ \000\000\000\000\076\000\000\000\076\000\076\000\076\000\076\000\ \076\000\076\000\076\000\076\000\076\000\076\000\076\000\076\000\ \076\000\076\000\076\000\076\000\076\000\076\000\076\000\076\000\ \076\000\076\000\076\000\076\000\076\000\076\000\076\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\090\000\ \090\000\090\000\090\000\090\000\090\000\090\000\090\000\076\000\ \076\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \076\000\076\000\076\000\076\000\076\000\076\000\076\000\076\000\ \076\000\076\000\076\000\076\000\076\000\076\000\076\000\076\000\ \076\000\076\000\076\000\076\000\076\000\076\000\076\000\076\000\ \076\000\076\000\000\000\000\000\000\000\000\000\076\000\000\000\ \076\000\076\000\076\000\076\000\076\000\076\000\076\000\076\000\ \076\000\076\000\076\000\076\000\076\000\076\000\076\000\076\000\ \076\000\076\000\076\000\076\000\076\000\076\000\076\000\076\000\ \076\000\076\000\076\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\083\000\083\000\083\000\083\000\083\000\ \083\000\083\000\083\000\083\000\083\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\083\000\083\000\083\000\083\000\ \083\000\083\000\076\000\076\000\076\000\076\000\076\000\076\000\ \076\000\076\000\076\000\076\000\076\000\076\000\076\000\076\000\ \076\000\076\000\076\000\076\000\076\000\076\000\000\000\000\000\ \000\000\000\000\076\000\000\000\083\000\083\000\083\000\083\000\ \083\000\083\000\076\000\076\000\076\000\076\000\076\000\076\000\ \076\000\076\000\076\000\076\000\076\000\076\000\076\000\076\000\ \076\000\076\000\076\000\076\000\076\000\076\000\076\000\000\000\ \000\000\000\000\000\000\000\000\000\000\084\000\000\000\083\000\ \083\000\083\000\083\000\083\000\083\000\083\000\083\000\083\000\ \083\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \083\000\083\000\083\000\083\000\083\000\083\000\079\000\079\000\ \079\000\079\000\079\000\079\000\079\000\079\000\079\000\085\000\ \079\000\079\000\079\000\079\000\079\000\079\000\079\000\079\000\ \079\000\079\000\000\000\000\000\000\000\000\000\083\000\000\000\ \083\000\083\000\083\000\083\000\083\000\083\000\079\000\079\000\ \079\000\079\000\079\000\079\000\079\000\079\000\079\000\085\000\ \079\000\079\000\079\000\079\000\079\000\079\000\079\000\079\000\ \079\000\079\000\076\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\084\000\084\000\084\000\084\000\084\000\ \084\000\084\000\084\000\084\000\084\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\084\000\084\000\084\000\084\000\ \084\000\084\000\088\000\088\000\088\000\088\000\088\000\088\000\ \088\000\088\000\088\000\089\000\088\000\088\000\088\000\088\000\ \088\000\088\000\088\000\088\000\088\000\088\000\000\000\000\000\ \000\000\000\000\084\000\000\000\084\000\084\000\084\000\084\000\ \084\000\084\000\088\000\088\000\088\000\088\000\088\000\088\000\ \088\000\088\000\088\000\089\000\088\000\088\000\088\000\088\000\ \088\000\088\000\088\000\088\000\088\000\088\000\076\000\000\000\ \000\000\000\000\087\000\000\000\087\000\000\000\000\000\086\000\ \086\000\086\000\086\000\086\000\086\000\086\000\086\000\086\000\ \086\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \076\000\076\000\076\000\076\000\076\000\076\000\076\000\076\000\ \076\000\076\000\076\000\076\000\076\000\076\000\076\000\076\000\ \076\000\076\000\076\000\076\000\076\000\076\000\076\000\076\000\ \076\000\076\000\000\000\000\000\000\000\000\000\076\000\000\000\ \076\000\076\000\076\000\076\000\076\000\076\000\076\000\076\000\ \076\000\076\000\076\000\076\000\076\000\076\000\076\000\076\000\ \076\000\076\000\076\000\076\000\076\000\076\000\076\000\076\000\ \076\000\076\000\076\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\086\000\086\000\086\000\086\000\086\000\ \086\000\086\000\086\000\086\000\086\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\076\000\076\000\076\000\076\000\ \076\000\076\000\088\000\088\000\088\000\088\000\088\000\088\000\ \088\000\088\000\088\000\088\000\088\000\088\000\088\000\088\000\ \088\000\088\000\088\000\088\000\088\000\088\000\000\000\000\000\ \000\000\000\000\086\000\000\000\076\000\076\000\076\000\076\000\ \076\000\076\000\088\000\088\000\088\000\088\000\088\000\088\000\ \088\000\088\000\088\000\088\000\088\000\088\000\088\000\088\000\ \088\000\088\000\088\000\088\000\088\000\088\000\076\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\076\000\ \076\000\076\000\076\000\076\000\076\000\076\000\076\000\076\000\ \076\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \076\000\076\000\076\000\076\000\076\000\076\000\076\000\076\000\ \076\000\076\000\076\000\076\000\076\000\076\000\076\000\076\000\ \076\000\076\000\076\000\076\000\076\000\076\000\076\000\076\000\ \076\000\076\000\000\000\000\000\000\000\000\000\076\000\000\000\ \076\000\076\000\076\000\076\000\076\000\076\000\076\000\076\000\ \076\000\076\000\076\000\076\000\076\000\076\000\076\000\076\000\ \076\000\076\000\076\000\076\000\076\000\076\000\076\000\076\000\ \076\000\076\000\076\000\000\000\000\000\000\000\087\000\000\000\ \087\000\000\000\000\000\086\000\086\000\086\000\086\000\086\000\ \086\000\086\000\086\000\086\000\086\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\076\000\076\000\076\000\076\000\ \076\000\076\000\076\000\076\000\076\000\076\000\076\000\076\000\ \076\000\076\000\076\000\076\000\076\000\076\000\076\000\076\000\ \076\000\076\000\076\000\076\000\076\000\076\000\000\000\000\000\ \000\000\000\000\076\000\000\000\076\000\076\000\076\000\076\000\ \076\000\076\000\076\000\076\000\076\000\076\000\076\000\076\000\ \076\000\076\000\076\000\076\000\076\000\076\000\076\000\076\000\ \076\000\076\000\076\000\076\000\076\000\076\000\076\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\090\000\ \090\000\090\000\090\000\090\000\090\000\090\000\090\000\076\000\ \076\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \076\000\076\000\076\000\076\000\076\000\076\000\079\000\079\000\ \079\000\079\000\079\000\079\000\079\000\079\000\079\000\079\000\ \079\000\079\000\079\000\079\000\079\000\079\000\079\000\079\000\ \079\000\079\000\000\000\000\000\000\000\000\000\090\000\000\000\ \076\000\076\000\076\000\076\000\076\000\076\000\079\000\079\000\ \079\000\079\000\079\000\079\000\079\000\079\000\079\000\079\000\ \079\000\079\000\079\000\079\000\079\000\079\000\079\000\079\000\ \079\000\079\000\076\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\091\000\091\000\076\000\076\000\076\000\ \076\000\076\000\076\000\076\000\076\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\076\000\076\000\076\000\076\000\ \076\000\076\000\079\000\079\000\079\000\079\000\079\000\079\000\ \079\000\079\000\079\000\079\000\079\000\079\000\079\000\079\000\ \079\000\079\000\079\000\079\000\079\000\079\000\000\000\000\000\ \000\000\000\000\091\000\000\000\076\000\076\000\076\000\076\000\ \076\000\076\000\079\000\079\000\079\000\079\000\079\000\079\000\ \079\000\079\000\079\000\079\000\079\000\079\000\079\000\079\000\ \079\000\079\000\079\000\079\000\079\000\079\000\076\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\092\000\ \092\000\092\000\092\000\092\000\092\000\092\000\092\000\092\000\ \092\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \076\000\076\000\076\000\076\000\076\000\076\000\088\000\088\000\ \088\000\088\000\088\000\088\000\088\000\088\000\088\000\088\000\ \088\000\088\000\088\000\088\000\088\000\088\000\088\000\088\000\ \088\000\088\000\000\000\000\000\000\000\000\000\092\000\099\000\ \076\000\076\000\076\000\076\000\076\000\076\000\088\000\088\000\ \088\000\088\000\088\000\088\000\088\000\088\000\088\000\088\000\ \088\000\088\000\088\000\088\000\088\000\088\000\088\000\088\000\ \088\000\088\000\000\000\101\000\101\000\101\000\101\000\101\000\ \101\000\101\000\101\000\101\000\101\000\101\000\101\000\101\000\ \101\000\101\000\101\000\101\000\101\000\101\000\101\000\101\000\ \101\000\101\000\101\000\101\000\101\000\000\000\000\000\000\000\ \000\000\101\000\000\000\101\000\101\000\101\000\101\000\101\000\ \101\000\101\000\101\000\101\000\101\000\101\000\101\000\101\000\ \101\000\101\000\101\000\101\000\101\000\101\000\101\000\101\000\ \101\000\101\000\101\000\101\000\101\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\100\000\100\000\100\000\100\000\100\000\100\000\ \100\000\100\000\100\000\100\000\100\000\100\000\100\000\100\000\ \100\000\100\000\100\000\100\000\100\000\100\000\100\000\100\000\ \100\000\100\000\100\000\100\000\100\000\100\000\100\000\100\000\ \100\000\100\000\100\000\100\000\100\000\100\000\100\000\100\000\ \100\000\100\000\100\000\100\000\100\000\100\000\100\000\100\000\ \100\000\100\000\100\000\100\000\100\000\100\000\100\000\100\000\ \100\000\100\000\100\000\100\000\100\000\100\000\100\000\100\000\ \100\000\100\000\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\098\000\098\000\098\000\098\000\098\000\ \098\000\098\000\098\000\098\000\098\000\098\000\098\000\098\000\ \098\000\098\000\098\000\098\000\098\000\098\000\098\000\098\000\ \098\000\098\000\098\000\098\000\098\000\255\255\255\255\255\255\ \255\255\098\000\255\255\098\000\098\000\098\000\098\000\098\000\ \098\000\098\000\098\000\098\000\098\000\098\000\098\000\098\000\ \098\000\098\000\098\000\098\000\098\000\098\000\098\000\098\000\ \098\000\098\000\098\000\098\000\098\000\255\255\096\000\255\255\ \255\255\255\255\000\000\000\000\098\000\098\000\098\000\098\000\ \098\000\098\000\098\000\098\000\098\000\098\000\098\000\098\000\ \098\000\098\000\098\000\098\000\098\000\098\000\098\000\098\000\ \098\000\098\000\098\000\098\000\098\000\098\000\000\000\000\000\ \000\000\000\000\098\000\000\000\098\000\098\000\098\000\098\000\ \098\000\098\000\098\000\098\000\098\000\098\000\098\000\098\000\ \098\000\098\000\098\000\098\000\098\000\098\000\098\000\098\000\ \098\000\098\000\098\000\098\000\098\000\098\000\000\000\096\000\ \000\000\000\000\000\000\000\000\113\000\113\000\113\000\113\000\ \113\000\113\000\113\000\113\000\113\000\113\000\113\000\113\000\ \113\000\113\000\113\000\113\000\113\000\113\000\113\000\113\000\ \113\000\113\000\113\000\113\000\113\000\113\000\000\000\000\000\ \000\000\000\000\113\000\000\000\113\000\113\000\113\000\113\000\ \113\000\113\000\113\000\113\000\113\000\113\000\113\000\113\000\ \113\000\113\000\113\000\113\000\113\000\113\000\113\000\113\000\ \113\000\113\000\113\000\113\000\113\000\113\000\000\000\000\000\ \000\000\000\000\255\255\097\000\097\000\097\000\097\000\097\000\ \097\000\097\000\097\000\097\000\097\000\097\000\097\000\097\000\ \097\000\097\000\097\000\097\000\097\000\097\000\097\000\097\000\ \097\000\097\000\097\000\097\000\097\000\097\000\097\000\097\000\ \097\000\097\000\097\000\097\000\097\000\097\000\097\000\097\000\ \097\000\097\000\097\000\097\000\097\000\097\000\097\000\097\000\ \097\000\097\000\097\000\097\000\097\000\097\000\097\000\097\000\ \097\000\097\000\097\000\097\000\097\000\097\000\097\000\097\000\ \097\000\097\000\097\000\112\000\112\000\112\000\112\000\112\000\ \112\000\112\000\112\000\112\000\112\000\112\000\112\000\112\000\ \112\000\112\000\112\000\112\000\112\000\112\000\112\000\112\000\ \112\000\112\000\112\000\112\000\112\000\112\000\112\000\112\000\ \112\000\112\000\112\000\112\000\112\000\112\000\112\000\112\000\ \112\000\112\000\112\000\112\000\112\000\112\000\112\000\112\000\ \112\000\112\000\112\000\112\000\112\000\112\000\112\000\112\000\ \112\000\112\000\112\000\112\000\112\000\112\000\112\000\112\000\ \112\000\112\000\112\000\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\102\000\255\255\255\255\102\000\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\102\000\255\255\255\255\255\255\255\255\ \255\255\255\255\000\000\255\255\255\255\255\255\255\255\255\255\ \255\255\104\000\255\255\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\255\255\255\255\ \255\255\255\255\000\000\255\255\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\255\255\103\000\ \255\255\255\255\255\255\100\000\100\000\100\000\100\000\100\000\ \100\000\100\000\100\000\100\000\100\000\100\000\100\000\100\000\ \100\000\100\000\100\000\100\000\100\000\100\000\100\000\100\000\ \100\000\100\000\100\000\100\000\100\000\100\000\100\000\100\000\ \100\000\100\000\100\000\100\000\100\000\100\000\100\000\100\000\ \100\000\100\000\100\000\100\000\100\000\100\000\100\000\100\000\ \100\000\100\000\100\000\100\000\100\000\100\000\100\000\100\000\ \100\000\100\000\100\000\100\000\100\000\100\000\100\000\100\000\ \100\000\100\000\100\000\105\000\105\000\105\000\105\000\105\000\ \105\000\105\000\105\000\105\000\105\000\105\000\105\000\105\000\ \105\000\105\000\105\000\105\000\105\000\105\000\105\000\105\000\ \105\000\105\000\105\000\105\000\105\000\105\000\105\000\105\000\ \105\000\105\000\105\000\105\000\105\000\105\000\105\000\105\000\ \105\000\105\000\105\000\105\000\105\000\105\000\105\000\105\000\ \105\000\105\000\105\000\105\000\105\000\105\000\105\000\105\000\ \105\000\105\000\105\000\105\000\105\000\105\000\105\000\105\000\ \105\000\105\000\105\000\255\255\102\000\000\000\239\000\102\000\ \000\000\240\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\102\000\000\000\000\000\242\000\000\000\ \000\000\000\000\101\000\000\000\000\000\000\000\000\000\000\000\ \000\000\104\000\000\000\101\000\101\000\101\000\101\000\101\000\ \101\000\101\000\101\000\101\000\101\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\101\000\101\000\101\000\101\000\ \101\000\101\000\101\000\101\000\101\000\101\000\101\000\101\000\ \101\000\101\000\101\000\101\000\101\000\101\000\101\000\101\000\ \101\000\101\000\101\000\101\000\101\000\101\000\000\000\000\000\ \241\000\000\000\101\000\000\000\101\000\101\000\101\000\101\000\ \101\000\101\000\101\000\101\000\101\000\101\000\101\000\101\000\ \101\000\101\000\101\000\101\000\101\000\101\000\101\000\101\000\ \101\000\101\000\101\000\101\000\101\000\101\000\000\000\103\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\105\000\105\000\105\000\105\000\105\000\ \105\000\105\000\105\000\105\000\105\000\105\000\105\000\105\000\ \105\000\105\000\105\000\105\000\105\000\105\000\105\000\105\000\ \105\000\105\000\105\000\105\000\105\000\105\000\105\000\105\000\ \105\000\105\000\105\000\105\000\105\000\105\000\105\000\105\000\ \105\000\105\000\105\000\105\000\105\000\105\000\105\000\105\000\ \105\000\105\000\105\000\105\000\105\000\105\000\105\000\105\000\ \105\000\105\000\105\000\105\000\105\000\105\000\105\000\105\000\ \105\000\105\000\105\000\102\000\238\000\000\000\102\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\102\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\111\000\111\000\111\000\111\000\111\000\ \111\000\111\000\111\000\111\000\111\000\111\000\111\000\111\000\ \111\000\111\000\111\000\111\000\111\000\111\000\111\000\111\000\ \111\000\111\000\111\000\111\000\111\000\000\000\000\000\000\000\ \000\000\111\000\000\000\111\000\111\000\111\000\111\000\111\000\ \111\000\111\000\111\000\111\000\111\000\111\000\111\000\111\000\ \111\000\111\000\111\000\111\000\111\000\111\000\111\000\111\000\ \111\000\111\000\111\000\111\000\111\000\000\000\109\000\000\000\ \000\000\000\000\000\000\107\000\107\000\107\000\107\000\107\000\ \107\000\107\000\107\000\107\000\107\000\107\000\107\000\107\000\ \107\000\107\000\107\000\107\000\107\000\107\000\107\000\107\000\ \107\000\107\000\107\000\107\000\107\000\000\000\000\000\000\000\ \000\000\107\000\000\000\107\000\107\000\107\000\107\000\107\000\ \107\000\107\000\107\000\107\000\107\000\107\000\107\000\107\000\ \107\000\107\000\107\000\107\000\107\000\107\000\107\000\107\000\ \107\000\107\000\107\000\107\000\107\000\000\000\000\000\000\000\ \000\000\000\000\110\000\110\000\110\000\110\000\110\000\110\000\ \110\000\110\000\110\000\110\000\110\000\110\000\110\000\110\000\ \110\000\110\000\110\000\110\000\110\000\110\000\110\000\110\000\ \110\000\110\000\110\000\110\000\110\000\110\000\110\000\110\000\ \110\000\110\000\110\000\110\000\110\000\110\000\110\000\110\000\ \110\000\110\000\110\000\110\000\110\000\110\000\110\000\110\000\ \110\000\110\000\110\000\110\000\110\000\110\000\110\000\110\000\ \110\000\110\000\110\000\110\000\110\000\110\000\110\000\110\000\ \110\000\110\000\106\000\106\000\106\000\106\000\106\000\106\000\ \106\000\106\000\106\000\106\000\106\000\106\000\106\000\106\000\ \106\000\106\000\106\000\106\000\106\000\106\000\106\000\106\000\ \106\000\106\000\106\000\106\000\106\000\106\000\106\000\106\000\ \106\000\106\000\106\000\106\000\106\000\106\000\106\000\106\000\ \106\000\106\000\106\000\106\000\106\000\106\000\106\000\106\000\ \106\000\106\000\106\000\106\000\106\000\106\000\106\000\106\000\ \106\000\106\000\106\000\106\000\106\000\106\000\106\000\106\000\ \106\000\106\000\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\102\000\255\255\255\255\102\000\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\102\000\255\255\255\255\255\255\255\255\255\255\ \255\255\101\000\255\255\255\255\255\255\255\255\255\255\255\255\ \104\000\255\255\101\000\101\000\101\000\101\000\101\000\101\000\ \101\000\101\000\101\000\101\000\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\101\000\101\000\101\000\101\000\101\000\ \101\000\101\000\101\000\101\000\101\000\101\000\101\000\101\000\ \101\000\101\000\101\000\101\000\101\000\101\000\101\000\101\000\ \101\000\101\000\101\000\101\000\101\000\255\255\255\255\255\255\ \255\255\101\000\255\255\101\000\101\000\101\000\101\000\101\000\ \101\000\101\000\101\000\101\000\101\000\101\000\101\000\101\000\ \101\000\101\000\101\000\101\000\101\000\101\000\101\000\101\000\ \101\000\101\000\101\000\101\000\101\000\255\255\103\000\255\255\ \255\255\255\255\000\000\000\000\000\000\000\000\000\000\000\000\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\102\000\255\255\255\255\102\000\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \102\000\255\255\255\255\255\255\255\255\255\255\255\255\000\000\ \255\255\255\255\255\255\255\255\255\255\255\255\104\000\255\255\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\255\255\255\255\255\255\255\255\000\000\ \255\255\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\255\255\255\255\103\000\255\255\255\255\255\255\ \106\000\106\000\106\000\106\000\106\000\106\000\106\000\106\000\ \106\000\106\000\106\000\106\000\106\000\106\000\106\000\106\000\ \106\000\106\000\106\000\106\000\106\000\106\000\106\000\106\000\ \106\000\106\000\106\000\106\000\106\000\106\000\106\000\106\000\ \106\000\106\000\106\000\106\000\106\000\106\000\106\000\106\000\ \106\000\106\000\106\000\106\000\106\000\106\000\106\000\106\000\ \106\000\106\000\106\000\106\000\106\000\106\000\106\000\106\000\ \106\000\106\000\106\000\106\000\106\000\106\000\106\000\106\000\ \108\000\108\000\108\000\108\000\108\000\108\000\108\000\108\000\ \108\000\108\000\108\000\108\000\108\000\108\000\108\000\108\000\ \108\000\108\000\108\000\108\000\108\000\108\000\108\000\108\000\ \108\000\108\000\108\000\108\000\108\000\108\000\108\000\108\000\ \108\000\108\000\108\000\108\000\108\000\108\000\108\000\108\000\ \108\000\108\000\108\000\108\000\108\000\108\000\108\000\108\000\ \108\000\108\000\108\000\108\000\108\000\108\000\108\000\108\000\ \108\000\108\000\108\000\108\000\108\000\108\000\108\000\108\000\ \255\255\102\000\000\000\000\000\102\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \102\000\000\000\000\000\000\000\000\000\000\000\000\000\107\000\ \000\000\000\000\000\000\000\000\000\000\000\000\104\000\000\000\ \107\000\107\000\107\000\107\000\107\000\107\000\107\000\107\000\ \107\000\107\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\107\000\107\000\107\000\107\000\107\000\107\000\107\000\ \107\000\107\000\107\000\107\000\107\000\107\000\107\000\107\000\ \107\000\107\000\107\000\107\000\107\000\107\000\107\000\107\000\ \107\000\107\000\107\000\000\000\000\000\000\000\000\000\107\000\ \000\000\107\000\107\000\107\000\107\000\107\000\107\000\107\000\ \107\000\107\000\107\000\107\000\107\000\107\000\107\000\107\000\ \107\000\107\000\107\000\107\000\107\000\107\000\107\000\107\000\ \107\000\107\000\107\000\000\000\103\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \108\000\108\000\108\000\108\000\108\000\108\000\108\000\108\000\ \108\000\108\000\108\000\108\000\108\000\108\000\108\000\108\000\ \108\000\108\000\108\000\108\000\108\000\108\000\108\000\108\000\ \108\000\108\000\108\000\108\000\108\000\108\000\108\000\108\000\ \108\000\108\000\108\000\108\000\108\000\108\000\108\000\108\000\ \108\000\108\000\108\000\108\000\108\000\108\000\108\000\108\000\ \108\000\108\000\108\000\108\000\108\000\108\000\108\000\108\000\ \108\000\108\000\108\000\108\000\108\000\108\000\108\000\108\000\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\102\000\255\255\255\255\102\000\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \102\000\255\255\255\255\255\255\255\255\255\255\255\255\107\000\ \255\255\255\255\255\255\255\255\255\255\255\255\104\000\255\255\ \107\000\107\000\107\000\107\000\107\000\107\000\107\000\107\000\ \107\000\107\000\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\107\000\107\000\107\000\107\000\107\000\107\000\107\000\ \107\000\107\000\107\000\107\000\107\000\107\000\107\000\107\000\ \107\000\107\000\107\000\107\000\107\000\107\000\107\000\107\000\ \107\000\107\000\107\000\255\255\255\255\255\255\255\255\107\000\ \255\255\107\000\107\000\107\000\107\000\107\000\107\000\107\000\ \107\000\107\000\107\000\107\000\107\000\107\000\107\000\107\000\ \107\000\107\000\107\000\107\000\107\000\107\000\107\000\107\000\ \107\000\107\000\107\000\255\255\103\000\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\111\000\111\000\111\000\111\000\111\000\111\000\111\000\ \111\000\111\000\111\000\111\000\111\000\111\000\111\000\111\000\ \111\000\111\000\111\000\111\000\111\000\111\000\111\000\111\000\ \111\000\111\000\111\000\255\255\255\255\255\255\255\255\111\000\ \255\255\111\000\111\000\111\000\111\000\111\000\111\000\111\000\ \111\000\111\000\111\000\111\000\111\000\111\000\111\000\111\000\ \111\000\111\000\111\000\111\000\111\000\111\000\111\000\111\000\ \111\000\111\000\111\000\255\255\109\000\255\255\255\255\255\255\ \255\255\000\000\111\000\111\000\111\000\111\000\111\000\111\000\ \111\000\111\000\111\000\111\000\111\000\111\000\111\000\111\000\ \111\000\111\000\111\000\111\000\111\000\111\000\111\000\111\000\ \111\000\111\000\111\000\111\000\000\000\000\000\000\000\000\000\ \111\000\000\000\111\000\111\000\111\000\111\000\111\000\111\000\ \111\000\111\000\111\000\111\000\111\000\111\000\111\000\111\000\ \111\000\111\000\111\000\111\000\111\000\111\000\111\000\111\000\ \111\000\111\000\111\000\111\000\000\000\109\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \255\255\110\000\110\000\110\000\110\000\110\000\110\000\110\000\ \110\000\110\000\110\000\110\000\110\000\110\000\110\000\110\000\ \110\000\110\000\110\000\110\000\110\000\110\000\110\000\110\000\ \110\000\110\000\110\000\110\000\110\000\110\000\110\000\110\000\ \110\000\110\000\110\000\110\000\110\000\110\000\110\000\110\000\ \110\000\110\000\110\000\110\000\110\000\110\000\110\000\110\000\ \110\000\110\000\110\000\110\000\110\000\110\000\110\000\110\000\ \110\000\110\000\110\000\110\000\110\000\110\000\110\000\110\000\ \110\000\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\114\000\255\255\255\255\114\000\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\114\000\255\255\255\255\255\255\255\255\255\255\255\255\ \000\000\255\255\255\255\255\255\255\255\255\255\255\255\116\000\ \255\255\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\255\255\255\255\255\255\255\255\ \000\000\255\255\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\255\255\115\000\255\255\255\255\ \255\255\112\000\112\000\112\000\112\000\112\000\112\000\112\000\ \112\000\112\000\112\000\112\000\112\000\112\000\112\000\112\000\ \112\000\112\000\112\000\112\000\112\000\112\000\112\000\112\000\ \112\000\112\000\112\000\112\000\112\000\112\000\112\000\112\000\ \112\000\112\000\112\000\112\000\112\000\112\000\112\000\112\000\ \112\000\112\000\112\000\112\000\112\000\112\000\112\000\112\000\ \112\000\112\000\112\000\112\000\112\000\112\000\112\000\112\000\ \112\000\112\000\112\000\112\000\112\000\112\000\112\000\112\000\ \112\000\117\000\117\000\117\000\117\000\117\000\117\000\117\000\ \117\000\117\000\117\000\117\000\117\000\117\000\117\000\117\000\ \117\000\117\000\117\000\117\000\117\000\117\000\117\000\117\000\ \117\000\117\000\117\000\117\000\117\000\117\000\117\000\117\000\ \117\000\117\000\117\000\117\000\117\000\117\000\117\000\117\000\ \117\000\117\000\117\000\117\000\117\000\117\000\117\000\117\000\ \117\000\117\000\117\000\117\000\117\000\117\000\117\000\117\000\ \117\000\117\000\117\000\117\000\117\000\117\000\117\000\117\000\ \117\000\255\255\114\000\000\000\000\000\114\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\114\000\000\000\000\000\000\000\000\000\000\000\000\000\ \113\000\000\000\000\000\000\000\000\000\000\000\000\000\116\000\ \000\000\113\000\113\000\113\000\113\000\113\000\113\000\113\000\ \113\000\113\000\113\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\113\000\113\000\113\000\113\000\113\000\113\000\ \113\000\113\000\113\000\113\000\113\000\113\000\113\000\113\000\ \113\000\113\000\113\000\113\000\113\000\113\000\113\000\113\000\ \113\000\113\000\113\000\113\000\000\000\000\000\000\000\000\000\ \113\000\000\000\113\000\113\000\113\000\113\000\113\000\113\000\ \113\000\113\000\113\000\113\000\113\000\113\000\113\000\113\000\ \113\000\113\000\113\000\113\000\113\000\113\000\113\000\113\000\ \113\000\113\000\113\000\113\000\000\000\115\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\117\000\117\000\117\000\117\000\117\000\117\000\117\000\ \117\000\117\000\117\000\117\000\117\000\117\000\117\000\117\000\ \117\000\117\000\117\000\117\000\117\000\117\000\117\000\117\000\ \117\000\117\000\117\000\117\000\117\000\117\000\117\000\117\000\ \117\000\117\000\117\000\117\000\117\000\117\000\117\000\117\000\ \117\000\117\000\117\000\117\000\117\000\117\000\117\000\117\000\ \117\000\117\000\117\000\117\000\117\000\117\000\117\000\117\000\ \117\000\117\000\117\000\117\000\117\000\117\000\117\000\117\000\ \117\000\114\000\000\000\000\000\114\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \114\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\123\000\123\000\123\000\123\000\123\000\123\000\123\000\ \123\000\123\000\123\000\123\000\123\000\123\000\123\000\123\000\ \123\000\123\000\123\000\123\000\123\000\123\000\123\000\123\000\ \123\000\123\000\123\000\000\000\000\000\000\000\000\000\123\000\ \000\000\123\000\123\000\123\000\123\000\123\000\123\000\123\000\ \123\000\123\000\123\000\123\000\123\000\123\000\123\000\123\000\ \123\000\123\000\123\000\123\000\123\000\123\000\123\000\123\000\ \123\000\123\000\123\000\000\000\121\000\000\000\000\000\000\000\ \000\000\119\000\119\000\119\000\119\000\119\000\119\000\119\000\ \119\000\119\000\119\000\119\000\119\000\119\000\119\000\119\000\ \119\000\119\000\119\000\119\000\119\000\119\000\119\000\119\000\ \119\000\119\000\119\000\000\000\000\000\000\000\000\000\119\000\ \000\000\119\000\119\000\119\000\119\000\119\000\119\000\119\000\ \119\000\119\000\119\000\119\000\119\000\119\000\119\000\119\000\ \119\000\119\000\119\000\119\000\119\000\119\000\119\000\119\000\ \119\000\119\000\119\000\000\000\000\000\000\000\000\000\000\000\ \122\000\122\000\122\000\122\000\122\000\122\000\122\000\122\000\ \122\000\122\000\122\000\122\000\122\000\122\000\122\000\122\000\ \122\000\122\000\122\000\122\000\122\000\122\000\122\000\122\000\ \122\000\122\000\122\000\122\000\122\000\122\000\122\000\122\000\ \122\000\122\000\122\000\122\000\122\000\122\000\122\000\122\000\ \122\000\122\000\122\000\122\000\122\000\122\000\122\000\122\000\ \122\000\122\000\122\000\122\000\122\000\122\000\122\000\122\000\ \122\000\122\000\122\000\122\000\122\000\122\000\122\000\122\000\ \118\000\118\000\118\000\118\000\118\000\118\000\118\000\118\000\ \118\000\118\000\118\000\118\000\118\000\118\000\118\000\118\000\ \118\000\118\000\118\000\118\000\118\000\118\000\118\000\118\000\ \118\000\118\000\118\000\118\000\118\000\118\000\118\000\118\000\ \118\000\118\000\118\000\118\000\118\000\118\000\118\000\118\000\ \118\000\118\000\118\000\118\000\118\000\118\000\118\000\118\000\ \118\000\118\000\118\000\118\000\118\000\118\000\118\000\118\000\ \118\000\118\000\118\000\118\000\118\000\118\000\118\000\118\000\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\114\000\255\255\255\255\114\000\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \114\000\255\255\255\255\255\255\255\255\255\255\255\255\113\000\ \255\255\255\255\255\255\255\255\255\255\255\255\116\000\255\255\ \113\000\113\000\113\000\113\000\113\000\113\000\113\000\113\000\ \113\000\113\000\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\113\000\113\000\113\000\113\000\113\000\113\000\113\000\ \113\000\113\000\113\000\113\000\113\000\113\000\113\000\113\000\ \113\000\113\000\113\000\113\000\113\000\113\000\113\000\113\000\ \113\000\113\000\113\000\255\255\255\255\255\255\255\255\113\000\ \255\255\113\000\113\000\113\000\113\000\113\000\113\000\113\000\ \113\000\113\000\113\000\113\000\113\000\113\000\113\000\113\000\ \113\000\113\000\113\000\113\000\113\000\113\000\113\000\113\000\ \113\000\113\000\113\000\255\255\115\000\255\255\255\255\255\255\ \000\000\000\000\000\000\000\000\000\000\000\000\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\114\000\ \255\255\255\255\114\000\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\114\000\255\255\ \255\255\255\255\255\255\255\255\255\255\000\000\255\255\255\255\ \255\255\255\255\255\255\255\255\116\000\255\255\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\255\255\255\255\255\255\255\255\000\000\255\255\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \255\255\255\255\115\000\255\255\255\255\255\255\118\000\118\000\ \118\000\118\000\118\000\118\000\118\000\118\000\118\000\118\000\ \118\000\118\000\118\000\118\000\118\000\118\000\118\000\118\000\ \118\000\118\000\118\000\118\000\118\000\118\000\118\000\118\000\ \118\000\118\000\118\000\118\000\118\000\118\000\118\000\118\000\ \118\000\118\000\118\000\118\000\118\000\118\000\118\000\118\000\ \118\000\118\000\118\000\118\000\118\000\118\000\118\000\118\000\ \118\000\118\000\118\000\118\000\118\000\118\000\118\000\118\000\ \118\000\118\000\118\000\118\000\118\000\118\000\120\000\120\000\ \120\000\120\000\120\000\120\000\120\000\120\000\120\000\120\000\ \120\000\120\000\120\000\120\000\120\000\120\000\120\000\120\000\ \120\000\120\000\120\000\120\000\120\000\120\000\120\000\120\000\ \120\000\120\000\120\000\120\000\120\000\120\000\120\000\120\000\ \120\000\120\000\120\000\120\000\120\000\120\000\120\000\120\000\ \120\000\120\000\120\000\120\000\120\000\120\000\120\000\120\000\ \120\000\120\000\120\000\120\000\120\000\120\000\120\000\120\000\ \120\000\120\000\120\000\120\000\120\000\120\000\255\255\114\000\ \000\000\000\000\114\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\114\000\000\000\ \000\000\000\000\000\000\000\000\000\000\119\000\000\000\000\000\ \000\000\000\000\000\000\000\000\116\000\000\000\119\000\119\000\ \119\000\119\000\119\000\119\000\119\000\119\000\119\000\119\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\119\000\ \119\000\119\000\119\000\119\000\119\000\119\000\119\000\119\000\ \119\000\119\000\119\000\119\000\119\000\119\000\119\000\119\000\ \119\000\119\000\119\000\119\000\119\000\119\000\119\000\119\000\ \119\000\000\000\000\000\000\000\000\000\119\000\000\000\119\000\ \119\000\119\000\119\000\119\000\119\000\119\000\119\000\119\000\ \119\000\119\000\119\000\119\000\119\000\119\000\119\000\119\000\ \119\000\119\000\119\000\119\000\119\000\119\000\119\000\119\000\ \119\000\000\000\115\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\120\000\120\000\ \120\000\120\000\120\000\120\000\120\000\120\000\120\000\120\000\ \120\000\120\000\120\000\120\000\120\000\120\000\120\000\120\000\ \120\000\120\000\120\000\120\000\120\000\120\000\120\000\120\000\ \120\000\120\000\120\000\120\000\120\000\120\000\120\000\120\000\ \120\000\120\000\120\000\120\000\120\000\120\000\120\000\120\000\ \120\000\120\000\120\000\120\000\120\000\120\000\120\000\120\000\ \120\000\120\000\120\000\120\000\120\000\120\000\120\000\120\000\ \120\000\120\000\120\000\120\000\120\000\120\000\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\114\000\ \255\255\255\255\114\000\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\114\000\255\255\ \255\255\255\255\255\255\255\255\255\255\119\000\255\255\255\255\ \255\255\255\255\255\255\255\255\116\000\255\255\119\000\119\000\ \119\000\119\000\119\000\119\000\119\000\119\000\119\000\119\000\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\119\000\ \119\000\119\000\119\000\119\000\119\000\119\000\119\000\119\000\ \119\000\119\000\119\000\119\000\119\000\119\000\119\000\119\000\ \119\000\119\000\119\000\119\000\119\000\119\000\119\000\119\000\ \119\000\255\255\255\255\255\255\255\255\119\000\255\255\119\000\ \119\000\119\000\119\000\119\000\119\000\119\000\119\000\119\000\ \119\000\119\000\119\000\119\000\119\000\119\000\119\000\119\000\ \119\000\119\000\119\000\119\000\119\000\119\000\119\000\119\000\ \119\000\255\255\115\000\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\123\000\ \123\000\123\000\123\000\123\000\123\000\123\000\123\000\123\000\ \123\000\123\000\123\000\123\000\123\000\123\000\123\000\123\000\ \123\000\123\000\123\000\123\000\123\000\123\000\123\000\123\000\ \123\000\255\255\255\255\255\255\255\255\123\000\255\255\123\000\ \123\000\123\000\123\000\123\000\123\000\123\000\123\000\123\000\ \123\000\123\000\123\000\123\000\123\000\123\000\123\000\123\000\ \123\000\123\000\123\000\123\000\123\000\123\000\123\000\123\000\ \123\000\255\255\121\000\255\255\255\255\255\255\255\255\000\000\ \123\000\123\000\123\000\123\000\123\000\123\000\123\000\123\000\ \123\000\123\000\123\000\123\000\123\000\123\000\123\000\123\000\ \123\000\123\000\123\000\123\000\123\000\123\000\123\000\123\000\ \123\000\123\000\000\000\000\000\000\000\000\000\123\000\000\000\ \123\000\123\000\123\000\123\000\123\000\123\000\123\000\123\000\ \123\000\123\000\123\000\123\000\123\000\123\000\123\000\123\000\ \123\000\123\000\123\000\123\000\123\000\123\000\123\000\123\000\ \123\000\123\000\000\000\121\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\255\255\122\000\ \122\000\122\000\122\000\122\000\122\000\122\000\122\000\122\000\ \122\000\122\000\122\000\122\000\122\000\122\000\122\000\122\000\ \122\000\122\000\122\000\122\000\122\000\122\000\122\000\122\000\ \122\000\122\000\122\000\122\000\122\000\122\000\122\000\122\000\ \122\000\122\000\122\000\122\000\122\000\122\000\122\000\122\000\ \122\000\122\000\122\000\122\000\122\000\122\000\122\000\122\000\ \122\000\122\000\122\000\122\000\122\000\122\000\122\000\122\000\ \122\000\122\000\122\000\122\000\122\000\122\000\122\000\135\000\ \152\000\135\000\255\255\152\000\152\000\152\000\135\000\000\000\ \000\000\152\000\152\000\000\000\152\000\152\000\152\000\134\000\ \134\000\134\000\134\000\134\000\134\000\134\000\134\000\134\000\ \134\000\152\000\000\000\152\000\152\000\152\000\152\000\152\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\154\000\ \000\000\154\000\154\000\154\000\154\000\000\000\000\000\000\000\ \154\000\154\000\000\000\154\000\154\000\154\000\000\000\000\000\ \000\000\000\000\000\000\135\000\000\000\152\000\000\000\000\000\ \154\000\135\000\154\000\154\000\154\000\154\000\154\000\000\000\ \000\000\000\000\000\000\000\000\000\000\135\000\133\000\000\000\ \000\000\135\000\000\000\135\000\000\000\006\000\000\000\132\000\ \006\000\006\000\006\000\152\000\000\000\152\000\006\000\006\000\ \000\000\006\000\006\000\006\000\154\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\006\000\000\000\ \006\000\006\000\006\000\006\000\006\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\156\000\000\000\000\000\156\000\ \156\000\156\000\154\000\000\000\154\000\156\000\156\000\000\000\ \156\000\156\000\156\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\006\000\000\000\000\000\156\000\000\000\156\000\ \156\000\156\000\156\000\156\000\000\000\000\000\000\000\156\000\ \000\000\000\000\156\000\156\000\156\000\000\000\000\000\000\000\ \156\000\156\000\000\000\156\000\156\000\156\000\000\000\000\000\ \006\000\000\000\006\000\000\000\000\000\000\000\000\000\000\000\ \156\000\156\000\156\000\156\000\156\000\156\000\156\000\000\000\ \000\000\000\000\000\000\000\000\000\000\156\000\000\000\000\000\ \156\000\156\000\156\000\000\000\000\000\000\000\156\000\156\000\ \000\000\156\000\156\000\156\000\000\000\000\000\000\000\156\000\ \000\000\156\000\000\000\000\000\156\000\000\000\156\000\255\255\ \156\000\156\000\156\000\156\000\156\000\000\000\000\000\000\000\ \006\000\000\000\000\000\006\000\006\000\006\000\000\000\000\000\ \000\000\006\000\006\000\000\000\006\000\006\000\006\000\000\000\ \000\000\000\000\156\000\000\000\156\000\000\000\000\000\000\000\ \000\000\006\000\156\000\006\000\006\000\006\000\006\000\006\000\ \000\000\000\000\000\000\006\000\000\000\000\000\006\000\006\000\ \006\000\000\000\000\000\000\000\006\000\006\000\000\000\006\000\ \006\000\006\000\000\000\000\000\000\000\000\000\000\000\000\000\ \156\000\000\000\156\000\000\000\006\000\006\000\006\000\006\000\ \006\000\006\000\006\000\000\000\000\000\000\000\176\000\000\000\ \176\000\176\000\176\000\176\000\000\000\000\000\000\000\176\000\ \176\000\000\000\176\000\176\000\176\000\000\000\000\000\000\000\ \000\000\000\000\000\000\006\000\000\000\006\000\000\000\176\000\ \006\000\176\000\176\000\176\000\176\000\176\000\000\000\000\000\ \000\000\176\000\000\000\176\000\176\000\176\000\176\000\000\000\ \000\000\000\000\176\000\176\000\000\000\176\000\176\000\176\000\ \000\000\000\000\000\000\000\000\000\000\000\000\006\000\000\000\ \006\000\000\000\176\000\176\000\176\000\176\000\176\000\176\000\ \176\000\000\000\000\000\000\000\156\000\000\000\000\000\156\000\ \156\000\156\000\000\000\000\000\000\000\156\000\156\000\000\000\ \156\000\156\000\156\000\000\000\000\000\000\000\000\000\000\000\ \000\000\176\000\000\000\176\000\000\000\156\000\176\000\156\000\ \156\000\156\000\156\000\156\000\000\000\000\000\000\000\156\000\ \000\000\000\000\156\000\156\000\156\000\000\000\000\000\000\000\ \156\000\156\000\000\000\156\000\156\000\156\000\000\000\000\000\ \000\000\000\000\000\000\000\000\176\000\000\000\176\000\000\000\ \156\000\156\000\156\000\156\000\156\000\156\000\156\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\189\000\000\000\ \000\000\190\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\156\000\ \000\000\156\000\000\000\000\000\156\000\000\000\194\000\000\000\ \000\000\000\000\000\000\192\000\196\000\000\000\195\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\156\000\000\000\156\000\188\000\188\000\188\000\ \188\000\188\000\188\000\188\000\188\000\188\000\188\000\188\000\ \188\000\188\000\188\000\188\000\188\000\188\000\188\000\188\000\ \188\000\188\000\188\000\188\000\188\000\188\000\188\000\000\000\ \000\000\000\000\000\000\188\000\000\000\188\000\188\000\188\000\ \188\000\188\000\188\000\188\000\188\000\188\000\188\000\188\000\ \188\000\188\000\188\000\188\000\188\000\188\000\188\000\188\000\ \188\000\188\000\188\000\188\000\188\000\188\000\188\000\193\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\187\000\187\000\187\000\187\000\ \187\000\187\000\187\000\187\000\187\000\187\000\187\000\187\000\ \187\000\187\000\187\000\187\000\187\000\187\000\187\000\187\000\ \187\000\187\000\187\000\187\000\187\000\187\000\187\000\187\000\ \187\000\187\000\187\000\187\000\187\000\187\000\187\000\187\000\ \187\000\187\000\187\000\187\000\187\000\187\000\187\000\187\000\ \187\000\187\000\187\000\187\000\187\000\187\000\187\000\187\000\ \187\000\187\000\187\000\187\000\187\000\187\000\187\000\187\000\ \187\000\187\000\187\000\187\000\191\000\188\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\188\000\188\000\ \188\000\188\000\188\000\188\000\188\000\188\000\188\000\188\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\188\000\ \188\000\188\000\188\000\188\000\188\000\188\000\188\000\188\000\ \188\000\188\000\188\000\188\000\188\000\188\000\188\000\188\000\ \188\000\188\000\188\000\188\000\188\000\188\000\188\000\188\000\ \188\000\000\000\000\000\000\000\000\000\188\000\000\000\188\000\ \188\000\188\000\188\000\188\000\188\000\188\000\188\000\188\000\ \188\000\188\000\188\000\188\000\188\000\188\000\188\000\188\000\ \188\000\188\000\188\000\188\000\188\000\188\000\188\000\188\000\ \188\000\000\000\000\000\000\000\000\000\000\000\187\000\187\000\ \187\000\187\000\187\000\187\000\187\000\187\000\187\000\187\000\ \187\000\187\000\187\000\187\000\187\000\187\000\187\000\187\000\ \187\000\187\000\187\000\187\000\187\000\187\000\187\000\187\000\ \187\000\187\000\187\000\187\000\187\000\187\000\187\000\187\000\ \187\000\187\000\187\000\187\000\187\000\187\000\187\000\187\000\ \187\000\187\000\187\000\187\000\187\000\187\000\187\000\187\000\ \187\000\187\000\187\000\187\000\187\000\187\000\187\000\187\000\ \187\000\187\000\187\000\187\000\187\000\187\000\235\000\235\000\ \235\000\235\000\235\000\235\000\235\000\235\000\235\000\235\000\ \235\000\235\000\235\000\235\000\235\000\235\000\235\000\235\000\ \235\000\235\000\235\000\235\000\235\000\235\000\235\000\235\000\ \235\000\235\000\235\000\235\000\235\000\235\000\235\000\235\000\ \235\000\235\000\235\000\235\000\235\000\235\000\235\000\235\000\ \235\000\235\000\235\000\235\000\235\000\235\000\235\000\235\000\ \235\000\235\000\235\000\235\000\235\000\235\000\235\000\235\000\ \235\000\235\000\235\000\235\000\235\000\235\000\188\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\188\000\ \188\000\188\000\188\000\188\000\188\000\188\000\188\000\188\000\ \188\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \188\000\188\000\188\000\188\000\188\000\188\000\188\000\188\000\ \188\000\188\000\188\000\188\000\188\000\188\000\188\000\188\000\ \188\000\188\000\188\000\188\000\188\000\188\000\188\000\188\000\ \188\000\188\000\000\000\000\000\000\000\000\000\188\000\000\000\ \188\000\188\000\188\000\188\000\188\000\188\000\188\000\188\000\ \188\000\188\000\188\000\188\000\188\000\188\000\188\000\188\000\ \188\000\188\000\188\000\188\000\188\000\188\000\188\000\188\000\ \188\000\188\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\235\000\ \235\000\235\000\235\000\235\000\235\000\235\000\235\000\235\000\ \235\000\235\000\235\000\235\000\235\000\235\000\235\000\235\000\ \235\000\235\000\235\000\235\000\235\000\235\000\235\000\235\000\ \235\000\235\000\235\000\235\000\235\000\235\000\235\000\235\000\ \235\000\235\000\235\000\235\000\235\000\235\000\235\000\235\000\ \235\000\235\000\235\000\235\000\235\000\235\000\235\000\235\000\ \235\000\235\000\235\000\235\000\235\000\235\000\235\000\235\000\ \235\000\235\000\235\000\235\000\235\000\235\000\235\000\202\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\201\000\201\000\201\000\201\000\201\000\ \201\000\201\000\201\000\201\000\201\000\201\000\201\000\201\000\ \201\000\201\000\201\000\201\000\201\000\201\000\201\000\201\000\ \201\000\201\000\201\000\201\000\201\000\000\000\000\000\000\000\ \000\000\201\000\000\000\201\000\201\000\201\000\201\000\201\000\ \201\000\201\000\201\000\201\000\201\000\201\000\201\000\201\000\ \201\000\201\000\201\000\201\000\201\000\201\000\201\000\201\000\ \201\000\201\000\201\000\201\000\201\000\000\000\199\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\200\000\200\000\200\000\200\000\200\000\200\000\ \200\000\200\000\200\000\200\000\200\000\200\000\200\000\200\000\ \200\000\200\000\200\000\200\000\200\000\200\000\200\000\200\000\ \200\000\200\000\200\000\200\000\200\000\200\000\200\000\200\000\ \200\000\200\000\200\000\200\000\200\000\200\000\200\000\200\000\ \200\000\200\000\200\000\200\000\200\000\200\000\200\000\200\000\ \200\000\200\000\200\000\200\000\200\000\200\000\200\000\200\000\ \200\000\200\000\200\000\200\000\200\000\200\000\200\000\200\000\ \200\000\200\000\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\201\000\201\000\201\000\201\000\201\000\ \201\000\201\000\201\000\201\000\201\000\201\000\201\000\201\000\ \201\000\201\000\201\000\201\000\201\000\201\000\201\000\201\000\ \201\000\201\000\201\000\201\000\201\000\255\255\255\255\255\255\ \255\255\201\000\255\255\201\000\201\000\201\000\201\000\201\000\ \201\000\201\000\201\000\201\000\201\000\201\000\201\000\201\000\ \201\000\201\000\201\000\201\000\201\000\201\000\201\000\201\000\ \201\000\201\000\201\000\201\000\201\000\255\255\199\000\255\255\ \255\255\255\255\000\000\000\000\201\000\201\000\201\000\201\000\ \201\000\201\000\201\000\201\000\201\000\201\000\201\000\201\000\ \201\000\201\000\201\000\201\000\201\000\201\000\201\000\201\000\ \201\000\201\000\201\000\201\000\201\000\201\000\000\000\000\000\ \000\000\000\000\201\000\000\000\201\000\201\000\201\000\201\000\ \201\000\201\000\201\000\201\000\201\000\201\000\201\000\201\000\ \201\000\201\000\201\000\201\000\201\000\201\000\201\000\201\000\ \201\000\201\000\201\000\201\000\201\000\201\000\000\000\199\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\255\255\200\000\200\000\200\000\200\000\200\000\ \200\000\200\000\200\000\200\000\200\000\200\000\200\000\200\000\ \200\000\200\000\200\000\200\000\200\000\200\000\200\000\200\000\ \200\000\200\000\200\000\200\000\200\000\200\000\200\000\200\000\ \200\000\200\000\200\000\200\000\200\000\200\000\200\000\200\000\ \200\000\200\000\200\000\200\000\200\000\200\000\200\000\200\000\ \200\000\200\000\200\000\200\000\200\000\200\000\200\000\200\000\ \200\000\200\000\200\000\200\000\200\000\200\000\200\000\200\000\ \200\000\200\000\200\000\205\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\204\000\ \204\000\204\000\204\000\204\000\204\000\204\000\204\000\204\000\ \204\000\204\000\204\000\204\000\204\000\204\000\204\000\204\000\ \204\000\204\000\204\000\204\000\204\000\204\000\204\000\204\000\ \204\000\000\000\000\000\000\000\000\000\204\000\000\000\204\000\ \204\000\204\000\204\000\204\000\204\000\204\000\204\000\204\000\ \204\000\204\000\204\000\204\000\204\000\204\000\204\000\204\000\ \204\000\204\000\204\000\204\000\204\000\204\000\204\000\204\000\ \204\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\203\000\203\000\ \203\000\203\000\203\000\203\000\203\000\203\000\203\000\203\000\ \203\000\203\000\203\000\203\000\203\000\203\000\203\000\203\000\ \203\000\203\000\203\000\203\000\203\000\203\000\203\000\203\000\ \203\000\203\000\203\000\203\000\203\000\203\000\203\000\203\000\ \203\000\203\000\203\000\203\000\203\000\203\000\203\000\203\000\ \203\000\203\000\203\000\203\000\203\000\203\000\203\000\203\000\ \203\000\203\000\203\000\203\000\203\000\203\000\203\000\203\000\ \203\000\203\000\203\000\203\000\203\000\203\000\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\206\000\ \255\255\255\255\206\000\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\206\000\255\255\ \255\255\255\255\255\255\255\255\255\255\000\000\255\255\255\255\ \255\255\255\255\255\255\255\255\207\000\255\255\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\255\255\255\255\255\255\255\255\000\000\255\255\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\255\255\199\000\255\255\255\255\255\255\203\000\203\000\ \203\000\203\000\203\000\203\000\203\000\203\000\203\000\203\000\ \203\000\203\000\203\000\203\000\203\000\203\000\203\000\203\000\ \203\000\203\000\203\000\203\000\203\000\203\000\203\000\203\000\ \203\000\203\000\203\000\203\000\203\000\203\000\203\000\203\000\ \203\000\203\000\203\000\203\000\203\000\203\000\203\000\203\000\ \203\000\203\000\203\000\203\000\203\000\203\000\203\000\203\000\ \203\000\203\000\203\000\203\000\203\000\203\000\203\000\203\000\ \203\000\203\000\203\000\203\000\203\000\203\000\208\000\208\000\ \208\000\208\000\208\000\208\000\208\000\208\000\208\000\208\000\ \208\000\208\000\208\000\208\000\208\000\208\000\208\000\208\000\ \208\000\208\000\208\000\208\000\208\000\208\000\208\000\208\000\ \208\000\208\000\208\000\208\000\208\000\208\000\208\000\208\000\ \208\000\208\000\208\000\208\000\208\000\208\000\208\000\208\000\ \208\000\208\000\208\000\208\000\208\000\208\000\208\000\208\000\ \208\000\208\000\208\000\208\000\208\000\208\000\208\000\208\000\ \208\000\208\000\208\000\208\000\208\000\208\000\255\255\206\000\ \000\000\000\000\206\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\206\000\000\000\ \000\000\000\000\000\000\000\000\000\000\204\000\000\000\000\000\ \000\000\000\000\000\000\000\000\207\000\000\000\204\000\204\000\ \204\000\204\000\204\000\204\000\204\000\204\000\204\000\204\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\204\000\ \204\000\204\000\204\000\204\000\204\000\204\000\204\000\204\000\ \204\000\204\000\204\000\204\000\204\000\204\000\204\000\204\000\ \204\000\204\000\204\000\204\000\204\000\204\000\204\000\204\000\ \204\000\000\000\000\000\000\000\000\000\204\000\000\000\204\000\ \204\000\204\000\204\000\204\000\204\000\204\000\204\000\204\000\ \204\000\204\000\204\000\204\000\204\000\204\000\204\000\204\000\ \204\000\204\000\204\000\204\000\204\000\204\000\204\000\204\000\ \204\000\000\000\199\000\000\000\000\000\000\000\000\000\204\000\ \204\000\204\000\204\000\204\000\204\000\204\000\204\000\204\000\ \204\000\204\000\204\000\204\000\204\000\204\000\204\000\204\000\ \204\000\204\000\204\000\204\000\204\000\204\000\204\000\204\000\ \204\000\000\000\000\000\000\000\000\000\204\000\000\000\204\000\ \204\000\204\000\204\000\204\000\204\000\204\000\204\000\204\000\ \204\000\204\000\204\000\204\000\204\000\204\000\204\000\204\000\ \204\000\204\000\204\000\204\000\204\000\204\000\204\000\204\000\ \204\000\000\000\000\000\000\000\000\000\000\000\208\000\208\000\ \208\000\208\000\208\000\208\000\208\000\208\000\208\000\208\000\ \208\000\208\000\208\000\208\000\208\000\208\000\208\000\208\000\ \208\000\208\000\208\000\208\000\208\000\208\000\208\000\208\000\ \208\000\208\000\208\000\208\000\208\000\208\000\208\000\208\000\ \208\000\208\000\208\000\208\000\208\000\208\000\208\000\208\000\ \208\000\208\000\208\000\208\000\208\000\208\000\208\000\208\000\ \208\000\208\000\208\000\208\000\208\000\208\000\208\000\208\000\ \208\000\208\000\208\000\208\000\208\000\208\000\203\000\203\000\ \203\000\203\000\203\000\203\000\203\000\203\000\203\000\203\000\ \203\000\203\000\203\000\203\000\203\000\203\000\203\000\203\000\ \203\000\203\000\203\000\203\000\203\000\203\000\203\000\203\000\ \203\000\203\000\203\000\203\000\203\000\203\000\203\000\203\000\ \203\000\203\000\203\000\203\000\203\000\203\000\203\000\203\000\ \203\000\203\000\203\000\203\000\203\000\203\000\203\000\203\000\ \203\000\203\000\203\000\203\000\203\000\203\000\203\000\203\000\ \203\000\203\000\203\000\203\000\203\000\203\000\206\000\000\000\ \000\000\206\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\206\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\201\000\201\000\ \201\000\201\000\201\000\201\000\201\000\201\000\201\000\201\000\ \201\000\201\000\201\000\201\000\201\000\201\000\201\000\201\000\ \201\000\201\000\201\000\201\000\201\000\201\000\201\000\201\000\ \000\000\000\000\000\000\000\000\201\000\000\000\201\000\201\000\ \201\000\201\000\201\000\201\000\201\000\201\000\201\000\201\000\ \201\000\201\000\201\000\201\000\201\000\201\000\201\000\201\000\ \201\000\201\000\201\000\201\000\201\000\201\000\201\000\201\000\ \000\000\199\000\000\000\000\000\000\000\000\000\210\000\210\000\ \210\000\210\000\210\000\210\000\210\000\210\000\210\000\210\000\ \210\000\210\000\210\000\210\000\210\000\210\000\210\000\210\000\ \210\000\210\000\210\000\210\000\210\000\210\000\210\000\210\000\ \000\000\000\000\000\000\000\000\210\000\000\000\210\000\210\000\ \210\000\210\000\210\000\210\000\210\000\210\000\210\000\210\000\ \210\000\210\000\210\000\210\000\210\000\210\000\210\000\210\000\ \210\000\210\000\210\000\210\000\210\000\210\000\210\000\210\000\ \000\000\000\000\000\000\000\000\000\000\200\000\200\000\200\000\ \200\000\200\000\200\000\200\000\200\000\200\000\200\000\200\000\ \200\000\200\000\200\000\200\000\200\000\200\000\200\000\200\000\ \200\000\200\000\200\000\200\000\200\000\200\000\200\000\200\000\ \200\000\200\000\200\000\200\000\200\000\200\000\200\000\200\000\ \200\000\200\000\200\000\200\000\200\000\200\000\200\000\200\000\ \200\000\200\000\200\000\200\000\200\000\200\000\200\000\200\000\ \200\000\200\000\200\000\200\000\200\000\200\000\200\000\200\000\ \200\000\200\000\200\000\200\000\200\000\209\000\209\000\209\000\ \209\000\209\000\209\000\209\000\209\000\209\000\209\000\209\000\ \209\000\209\000\209\000\209\000\209\000\209\000\209\000\209\000\ \209\000\209\000\209\000\209\000\209\000\209\000\209\000\209\000\ \209\000\209\000\209\000\209\000\209\000\209\000\209\000\209\000\ \209\000\209\000\209\000\209\000\209\000\209\000\209\000\209\000\ \209\000\209\000\209\000\209\000\209\000\209\000\209\000\209\000\ \209\000\209\000\209\000\209\000\209\000\209\000\209\000\209\000\ \209\000\209\000\209\000\209\000\209\000\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\206\000\255\255\ \255\255\206\000\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\206\000\255\255\255\255\ \255\255\255\255\255\255\255\255\204\000\255\255\255\255\255\255\ \255\255\255\255\255\255\207\000\255\255\204\000\204\000\204\000\ \204\000\204\000\204\000\204\000\204\000\204\000\204\000\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\204\000\204\000\ \204\000\204\000\204\000\204\000\204\000\204\000\204\000\204\000\ \204\000\204\000\204\000\204\000\204\000\204\000\204\000\204\000\ \204\000\204\000\204\000\204\000\204\000\204\000\204\000\204\000\ \255\255\255\255\255\255\255\255\204\000\255\255\204\000\204\000\ \204\000\204\000\204\000\204\000\204\000\204\000\204\000\204\000\ \204\000\204\000\204\000\204\000\204\000\204\000\204\000\204\000\ \204\000\204\000\204\000\204\000\204\000\204\000\204\000\204\000\ \255\255\199\000\255\255\255\255\255\255\000\000\000\000\000\000\ \000\000\000\000\000\000\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\206\000\255\255\255\255\206\000\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\206\000\255\255\255\255\255\255\255\255\ \255\255\255\255\000\000\255\255\255\255\255\255\255\255\255\255\ \255\255\207\000\255\255\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\255\255\255\255\ \255\255\255\255\000\000\255\255\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\255\255\255\255\199\000\ \255\255\255\255\255\255\209\000\209\000\209\000\209\000\209\000\ \209\000\209\000\209\000\209\000\209\000\209\000\209\000\209\000\ \209\000\209\000\209\000\209\000\209\000\209\000\209\000\209\000\ \209\000\209\000\209\000\209\000\209\000\209\000\209\000\209\000\ \209\000\209\000\209\000\209\000\209\000\209\000\209\000\209\000\ \209\000\209\000\209\000\209\000\209\000\209\000\209\000\209\000\ \209\000\209\000\209\000\209\000\209\000\209\000\209\000\209\000\ \209\000\209\000\209\000\209\000\209\000\209\000\209\000\209\000\ \209\000\209\000\209\000\211\000\211\000\211\000\211\000\211\000\ \211\000\211\000\211\000\211\000\211\000\211\000\211\000\211\000\ \211\000\211\000\211\000\211\000\211\000\211\000\211\000\211\000\ \211\000\211\000\211\000\211\000\211\000\211\000\211\000\211\000\ \211\000\211\000\211\000\211\000\211\000\211\000\211\000\211\000\ \211\000\211\000\211\000\211\000\211\000\211\000\211\000\211\000\ \211\000\211\000\211\000\211\000\211\000\211\000\211\000\211\000\ \211\000\211\000\211\000\211\000\211\000\211\000\211\000\211\000\ \211\000\211\000\211\000\255\255\206\000\000\000\000\000\206\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\206\000\000\000\000\000\000\000\000\000\ \000\000\000\000\210\000\000\000\000\000\000\000\000\000\000\000\ \000\000\207\000\000\000\210\000\210\000\210\000\210\000\210\000\ \210\000\210\000\210\000\210\000\210\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\210\000\210\000\210\000\210\000\ \210\000\210\000\210\000\210\000\210\000\210\000\210\000\210\000\ \210\000\210\000\210\000\210\000\210\000\210\000\210\000\210\000\ \210\000\210\000\210\000\210\000\210\000\210\000\000\000\000\000\ \000\000\000\000\210\000\000\000\210\000\210\000\210\000\210\000\ \210\000\210\000\210\000\210\000\210\000\210\000\210\000\210\000\ \210\000\210\000\210\000\210\000\210\000\210\000\210\000\210\000\ \210\000\210\000\210\000\210\000\210\000\210\000\000\000\199\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\211\000\211\000\211\000\211\000\211\000\ \211\000\211\000\211\000\211\000\211\000\211\000\211\000\211\000\ \211\000\211\000\211\000\211\000\211\000\211\000\211\000\211\000\ \211\000\211\000\211\000\211\000\211\000\211\000\211\000\211\000\ \211\000\211\000\211\000\211\000\211\000\211\000\211\000\211\000\ \211\000\211\000\211\000\211\000\211\000\211\000\211\000\211\000\ \211\000\211\000\211\000\211\000\211\000\211\000\211\000\211\000\ \211\000\211\000\211\000\211\000\211\000\211\000\211\000\211\000\ \211\000\211\000\211\000\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\206\000\255\255\255\255\206\000\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\206\000\255\255\255\255\255\255\255\255\ \255\255\255\255\210\000\255\255\255\255\255\255\255\255\255\255\ \255\255\207\000\255\255\210\000\210\000\210\000\210\000\210\000\ \210\000\210\000\210\000\210\000\210\000\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\210\000\210\000\210\000\210\000\ \210\000\210\000\210\000\210\000\210\000\210\000\210\000\210\000\ \210\000\210\000\210\000\210\000\210\000\210\000\210\000\210\000\ \210\000\210\000\210\000\210\000\210\000\210\000\255\255\255\255\ \255\255\255\255\210\000\255\255\210\000\210\000\210\000\210\000\ \210\000\210\000\210\000\210\000\210\000\210\000\210\000\210\000\ \210\000\210\000\210\000\210\000\210\000\210\000\210\000\210\000\ \210\000\210\000\210\000\210\000\210\000\210\000\255\255\199\000\ \255\255\255\255\255\255\222\000\000\000\222\000\000\000\000\000\ \000\000\000\000\222\000\000\000\000\000\000\000\249\000\000\000\ \000\000\250\000\000\000\221\000\221\000\221\000\221\000\221\000\ \221\000\221\000\221\000\221\000\221\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\248\000\000\000\248\000\000\000\ \000\000\000\000\000\000\248\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\247\000\247\000\247\000\247\000\ \247\000\247\000\247\000\247\000\247\000\247\000\000\000\222\000\ \000\000\000\000\000\000\000\000\000\000\222\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\222\000\220\000\000\000\000\000\222\000\000\000\222\000\ \000\000\000\000\000\000\219\000\000\000\000\000\000\000\000\000\ \248\000\000\000\000\000\000\000\000\000\000\000\248\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\248\000\246\000\000\000\000\000\248\000\000\000\ \248\000\244\000\000\000\000\000\245\000\000\000\000\000\000\000\ \000\000\000\000\000\000\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\188\000\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\188\000\188\000\188\000\188\000\ \188\000\188\000\188\000\188\000\188\000\188\000\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\188\000\188\000\188\000\ \188\000\188\000\188\000\188\000\188\000\188\000\188\000\188\000\ \188\000\188\000\188\000\188\000\188\000\188\000\188\000\188\000\ \188\000\188\000\188\000\188\000\188\000\188\000\188\000\255\255\ \255\255\255\255\255\255\188\000\255\255\188\000\188\000\188\000\ \188\000\188\000\188\000\188\000\188\000\188\000\188\000\188\000\ \188\000\188\000\188\000\188\000\188\000\188\000\188\000\188\000\ \188\000\188\000\188\000\188\000\188\000\188\000\188\000\255\255\ \255\255\255\255\255\255\255\255\255\255\000\000\016\001\016\001\ \016\001\016\001\016\001\016\001\016\001\016\001\016\001\016\001\ \016\001\016\001\016\001\016\001\016\001\016\001\016\001\016\001\ \016\001\016\001\016\001\016\001\016\001\016\001\016\001\016\001\ \000\000\000\000\000\000\000\000\016\001\000\000\016\001\016\001\ \016\001\016\001\016\001\016\001\016\001\016\001\016\001\016\001\ \016\001\016\001\016\001\016\001\016\001\016\001\016\001\016\001\ \016\001\016\001\016\001\016\001\016\001\016\001\016\001\016\001\ \000\000\000\000\014\001\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\255\255\015\001\015\001\015\001\ \015\001\015\001\015\001\015\001\015\001\015\001\015\001\015\001\ \015\001\015\001\015\001\015\001\015\001\015\001\015\001\015\001\ \015\001\015\001\015\001\015\001\015\001\015\001\015\001\015\001\ \015\001\015\001\015\001\015\001\015\001\015\001\015\001\015\001\ \015\001\015\001\015\001\015\001\015\001\015\001\015\001\015\001\ \015\001\015\001\015\001\015\001\015\001\015\001\015\001\015\001\ \015\001\015\001\015\001\015\001\015\001\015\001\015\001\015\001\ \015\001\015\001\015\001\015\001\015\001\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\000\000\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \255\255\255\255\255\255\255\255\000\000\255\255\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \255\255\255\255\014\001\255\255\255\255\015\001\015\001\015\001\ \015\001\015\001\015\001\015\001\015\001\015\001\015\001\015\001\ \015\001\015\001\015\001\015\001\015\001\015\001\015\001\015\001\ \015\001\015\001\015\001\015\001\015\001\015\001\015\001\015\001\ \015\001\015\001\015\001\015\001\015\001\015\001\015\001\015\001\ \015\001\015\001\015\001\015\001\015\001\015\001\015\001\015\001\ \015\001\015\001\015\001\015\001\015\001\015\001\015\001\015\001\ \015\001\015\001\015\001\015\001\015\001\015\001\015\001\015\001\ \015\001\015\001\015\001\015\001\015\001\017\001\017\001\017\001\ \017\001\017\001\017\001\017\001\017\001\017\001\017\001\017\001\ \017\001\017\001\017\001\017\001\017\001\017\001\017\001\017\001\ \017\001\017\001\017\001\017\001\017\001\017\001\017\001\017\001\ \017\001\017\001\017\001\017\001\017\001\017\001\017\001\017\001\ \017\001\017\001\017\001\017\001\017\001\017\001\017\001\017\001\ \017\001\017\001\017\001\017\001\017\001\017\001\017\001\017\001\ \017\001\017\001\017\001\017\001\017\001\017\001\017\001\017\001\ \017\001\017\001\017\001\017\001\017\001\255\255\016\001\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\016\001\ \016\001\016\001\016\001\016\001\016\001\016\001\016\001\016\001\ \016\001\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \016\001\016\001\016\001\016\001\016\001\016\001\016\001\016\001\ \016\001\016\001\016\001\016\001\016\001\016\001\016\001\016\001\ \016\001\016\001\016\001\016\001\016\001\016\001\016\001\016\001\ \016\001\016\001\000\000\000\000\000\000\000\000\016\001\000\000\ \016\001\016\001\016\001\016\001\016\001\016\001\016\001\016\001\ \016\001\016\001\016\001\016\001\016\001\016\001\016\001\016\001\ \016\001\016\001\016\001\016\001\016\001\016\001\016\001\016\001\ \016\001\016\001\000\000\000\000\014\001\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\017\001\ \017\001\017\001\017\001\017\001\017\001\017\001\017\001\017\001\ \017\001\017\001\017\001\017\001\017\001\017\001\017\001\017\001\ \017\001\017\001\017\001\017\001\017\001\017\001\017\001\017\001\ \017\001\017\001\017\001\017\001\017\001\017\001\017\001\017\001\ \017\001\017\001\017\001\017\001\017\001\017\001\017\001\017\001\ \017\001\017\001\017\001\017\001\017\001\017\001\017\001\017\001\ \017\001\017\001\017\001\017\001\017\001\017\001\017\001\017\001\ \017\001\017\001\017\001\017\001\017\001\017\001\017\001\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\016\001\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\016\001\ \016\001\016\001\016\001\016\001\016\001\016\001\016\001\016\001\ \016\001\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \016\001\016\001\016\001\016\001\016\001\016\001\016\001\016\001\ \016\001\016\001\016\001\016\001\016\001\016\001\016\001\016\001\ \016\001\016\001\016\001\016\001\016\001\016\001\016\001\016\001\ \016\001\016\001\255\255\255\255\255\255\255\255\016\001\255\255\ \016\001\016\001\016\001\016\001\016\001\016\001\016\001\016\001\ \016\001\016\001\016\001\016\001\016\001\016\001\016\001\016\001\ \016\001\016\001\016\001\016\001\016\001\016\001\016\001\016\001\ \016\001\016\001\255\255\255\255\014\001\255\255\255\255\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\255\255\ "; Lexing.lex_check = "\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\000\000\000\000\042\000\000\000\000\000\042\000\046\000\ \049\000\128\000\046\000\049\000\128\000\190\000\215\000\234\000\ \190\000\215\000\234\000\240\000\250\000\025\001\240\000\250\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\016\000\ \017\000\025\000\040\000\017\000\017\000\040\000\043\000\052\000\ \064\000\043\000\087\000\087\000\087\000\087\000\087\000\087\000\ \087\000\087\000\087\000\087\000\126\000\127\000\135\000\138\000\ \142\000\040\000\145\000\147\000\147\000\149\000\149\000\043\000\ \093\000\093\000\093\000\093\000\093\000\093\000\093\000\093\000\ \093\000\093\000\133\000\133\000\133\000\133\000\133\000\133\000\ \133\000\133\000\134\000\134\000\134\000\134\000\134\000\134\000\ \134\000\134\000\134\000\134\000\151\000\151\000\164\000\165\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\003\000\169\000\195\000\003\000\003\000\003\000\196\000\ \213\000\026\000\003\000\003\000\026\000\003\000\003\000\003\000\ \137\000\137\000\137\000\137\000\137\000\137\000\137\000\137\000\ \137\000\137\000\003\000\214\000\003\000\003\000\003\000\003\000\ \003\000\222\000\184\000\225\000\004\000\184\000\026\000\004\000\ \004\000\004\000\229\000\232\000\244\000\004\000\004\000\183\000\ \004\000\004\000\004\000\140\000\140\000\140\000\140\000\140\000\ \140\000\140\000\140\000\249\000\018\001\004\000\003\000\004\000\ \004\000\004\000\004\000\004\000\019\001\022\001\183\000\005\000\ \183\000\020\001\005\000\005\000\005\000\021\001\023\001\024\001\ \005\000\005\000\249\000\005\000\005\000\005\000\220\000\220\000\ \220\000\220\000\251\000\026\000\003\000\251\000\003\000\255\255\ \005\000\004\000\005\000\005\000\005\000\005\000\005\000\255\255\ \006\001\012\001\006\000\006\001\012\001\006\000\006\000\006\000\ \255\255\255\255\013\001\006\000\006\000\013\001\006\000\006\000\ \006\000\255\255\255\255\255\255\255\255\255\255\255\255\004\000\ \255\255\004\000\255\255\006\000\005\000\006\000\006\000\006\000\ \006\000\006\000\255\255\255\255\255\255\007\000\255\255\255\255\ \007\000\007\000\007\000\255\255\255\255\255\255\007\000\007\000\ \255\255\007\000\007\000\007\000\255\255\255\255\255\255\255\255\ \255\255\255\255\005\000\255\255\005\000\255\255\007\000\006\000\ \007\000\007\000\007\000\007\000\007\000\255\255\255\255\255\255\ \008\000\255\255\008\000\008\000\008\000\008\000\255\255\255\255\ \255\255\008\000\008\000\255\255\008\000\008\000\008\000\255\255\ \007\001\255\255\255\255\007\001\255\255\006\000\255\255\006\000\ \255\255\008\000\007\000\008\000\008\000\008\000\008\000\008\000\ \013\000\255\255\255\255\010\000\255\255\255\255\010\000\010\000\ \010\000\255\255\255\255\255\255\010\000\010\000\255\255\010\000\ \010\000\010\000\255\255\255\255\255\255\255\255\255\255\013\000\ \007\000\013\000\007\000\013\000\010\000\008\000\010\000\010\000\ \010\000\010\000\010\000\255\255\255\255\255\255\255\255\255\255\ \011\000\255\255\255\255\011\000\011\000\011\000\255\255\026\000\ \255\255\011\000\011\000\255\255\011\000\011\000\011\000\255\255\ \255\255\182\000\255\255\008\000\182\000\008\000\255\255\010\000\ \010\000\011\000\255\255\011\000\011\000\011\000\011\000\011\000\ \184\000\255\255\255\255\255\255\255\255\255\255\255\255\014\000\ \255\255\182\000\014\000\014\000\014\000\255\255\255\255\013\000\ \014\000\014\000\255\255\014\000\014\000\014\000\010\000\010\000\ \010\000\255\255\007\001\255\255\011\000\011\000\255\255\255\255\ \014\000\255\255\014\000\014\000\014\000\014\000\014\000\020\001\ \255\255\255\255\015\000\021\001\023\001\015\000\015\000\015\000\ \255\255\255\255\255\255\015\000\015\000\255\255\015\000\015\000\ \015\000\255\255\255\255\011\000\255\255\011\000\255\255\255\255\ \255\255\255\255\255\255\015\000\014\000\015\000\015\000\015\000\ \015\000\015\000\255\255\255\255\255\255\018\000\255\255\255\255\ \018\000\018\000\018\000\255\255\255\255\192\000\018\000\018\000\ \192\000\018\000\018\000\018\000\255\255\255\255\255\255\255\255\ \255\255\255\255\014\000\255\255\014\000\255\255\018\000\015\000\ \018\000\018\000\018\000\018\000\018\000\255\255\255\255\255\255\ \022\000\255\255\192\000\022\000\022\000\022\000\255\255\255\255\ \255\255\022\000\022\000\255\255\022\000\022\000\022\000\255\255\ \255\255\255\255\255\255\255\255\255\255\015\000\255\255\015\000\ \255\255\022\000\018\000\022\000\022\000\022\000\022\000\022\000\ \255\255\255\255\255\255\023\000\255\255\023\000\023\000\023\000\ \023\000\255\255\255\255\255\255\023\000\023\000\007\001\023\000\ \023\000\023\000\255\255\255\255\255\255\255\255\255\255\192\000\ \018\000\255\255\018\000\255\255\023\000\022\000\023\000\023\000\ \023\000\023\000\023\000\255\255\255\255\255\255\024\000\255\255\ \255\255\024\000\024\000\024\000\255\255\255\255\024\000\024\000\ \024\000\255\255\024\000\024\000\024\000\255\255\255\255\255\255\ \255\255\255\255\255\255\022\000\255\255\022\000\255\255\024\000\ \023\000\024\000\024\000\024\000\024\000\024\000\255\255\255\255\ \027\000\141\000\141\000\141\000\141\000\141\000\141\000\141\000\ \141\000\255\255\255\255\255\255\255\255\255\255\255\255\182\000\ \255\255\255\255\255\255\255\255\255\255\255\255\023\000\027\000\ \023\000\255\255\255\255\024\000\027\000\027\000\027\000\027\000\ \027\000\027\000\027\000\027\000\027\000\027\000\027\000\027\000\ \027\000\027\000\027\000\027\000\027\000\027\000\027\000\027\000\ \027\000\027\000\027\000\027\000\027\000\027\000\255\255\255\255\ \255\255\024\000\027\000\024\000\027\000\027\000\027\000\027\000\ \027\000\027\000\027\000\027\000\027\000\027\000\027\000\027\000\ \027\000\027\000\027\000\027\000\027\000\027\000\027\000\027\000\ \027\000\027\000\027\000\027\000\027\000\027\000\255\255\027\000\ \132\000\132\000\132\000\132\000\132\000\132\000\132\000\132\000\ \132\000\132\000\255\255\255\255\255\255\255\255\255\255\255\255\ \180\000\132\000\132\000\132\000\132\000\132\000\132\000\255\255\ \255\255\255\255\255\255\192\000\221\000\221\000\221\000\221\000\ \221\000\221\000\221\000\221\000\221\000\221\000\255\255\180\000\ \227\000\227\000\227\000\227\000\227\000\227\000\227\000\227\000\ \255\255\132\000\132\000\132\000\132\000\132\000\132\000\180\000\ \180\000\180\000\180\000\180\000\180\000\180\000\180\000\180\000\ \180\000\255\255\255\255\027\000\027\000\027\000\027\000\027\000\ \027\000\027\000\027\000\027\000\027\000\027\000\027\000\027\000\ \027\000\027\000\027\000\027\000\027\000\027\000\027\000\027\000\ \027\000\027\000\027\000\027\000\027\000\027\000\027\000\027\000\ \027\000\027\000\027\000\027\000\027\000\027\000\027\000\027\000\ \027\000\027\000\027\000\027\000\027\000\027\000\027\000\027\000\ \027\000\027\000\027\000\027\000\027\000\027\000\027\000\027\000\ \027\000\027\000\027\000\027\000\027\000\027\000\027\000\027\000\ \027\000\027\000\027\000\029\000\255\255\255\255\255\255\255\255\ \255\255\255\255\029\000\255\255\029\000\029\000\029\000\029\000\ \029\000\029\000\029\000\029\000\029\000\029\000\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\029\000\029\000\029\000\ \029\000\029\000\029\000\029\000\029\000\029\000\029\000\029\000\ \029\000\029\000\029\000\029\000\029\000\029\000\029\000\029\000\ \029\000\029\000\029\000\029\000\029\000\029\000\029\000\255\255\ \255\255\255\255\255\255\029\000\255\255\029\000\029\000\029\000\ \029\000\029\000\029\000\029\000\029\000\029\000\029\000\029\000\ \029\000\029\000\029\000\029\000\029\000\029\000\029\000\029\000\ \029\000\029\000\029\000\029\000\029\000\029\000\029\000\030\000\ \255\255\255\255\255\255\255\255\255\255\255\255\030\000\255\255\ \030\000\030\000\030\000\030\000\030\000\030\000\030\000\030\000\ \030\000\030\000\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\030\000\030\000\030\000\030\000\030\000\030\000\030\000\ \030\000\030\000\030\000\030\000\030\000\030\000\030\000\030\000\ \030\000\030\000\030\000\030\000\030\000\030\000\030\000\030\000\ \030\000\030\000\030\000\255\255\255\255\255\255\255\255\030\000\ \255\255\030\000\030\000\030\000\030\000\030\000\030\000\030\000\ \030\000\030\000\030\000\030\000\030\000\030\000\030\000\030\000\ \030\000\030\000\030\000\030\000\030\000\030\000\030\000\030\000\ \030\000\030\000\030\000\031\000\228\000\228\000\228\000\228\000\ \228\000\228\000\228\000\228\000\031\000\031\000\031\000\031\000\ \031\000\031\000\031\000\031\000\031\000\031\000\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\031\000\031\000\031\000\ \031\000\031\000\031\000\031\000\031\000\031\000\031\000\031\000\ \031\000\031\000\031\000\031\000\031\000\031\000\031\000\031\000\ \031\000\031\000\031\000\031\000\031\000\031\000\031\000\255\255\ \255\255\255\255\255\255\031\000\255\255\031\000\031\000\031\000\ \031\000\031\000\031\000\031\000\031\000\031\000\031\000\031\000\ \031\000\031\000\031\000\031\000\031\000\031\000\031\000\031\000\ \031\000\031\000\031\000\031\000\031\000\031\000\031\000\255\255\ \255\255\255\255\255\255\255\255\031\000\031\000\031\000\031\000\ \031\000\031\000\031\000\031\000\031\000\031\000\031\000\031\000\ \031\000\031\000\031\000\031\000\031\000\031\000\031\000\031\000\ \031\000\031\000\031\000\031\000\031\000\031\000\031\000\031\000\ \031\000\031\000\031\000\031\000\031\000\031\000\031\000\031\000\ \031\000\031\000\031\000\031\000\031\000\031\000\031\000\031\000\ \031\000\031\000\031\000\031\000\031\000\031\000\031\000\031\000\ \031\000\031\000\031\000\031\000\031\000\031\000\031\000\031\000\ \031\000\031\000\031\000\031\000\031\000\031\000\031\000\031\000\ \031\000\031\000\031\000\031\000\031\000\031\000\031\000\031\000\ \031\000\031\000\031\000\031\000\031\000\031\000\031\000\031\000\ \031\000\031\000\031\000\031\000\031\000\031\000\031\000\031\000\ \031\000\031\000\031\000\031\000\031\000\031\000\031\000\031\000\ \031\000\031\000\031\000\031\000\031\000\031\000\031\000\031\000\ \031\000\031\000\031\000\031\000\031\000\031\000\031\000\031\000\ \031\000\031\000\031\000\031\000\031\000\031\000\031\000\031\000\ \031\000\031\000\031\000\031\000\032\000\246\000\246\000\246\000\ \246\000\246\000\246\000\246\000\246\000\032\000\032\000\032\000\ \032\000\032\000\032\000\032\000\032\000\032\000\032\000\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\032\000\032\000\ \032\000\032\000\032\000\032\000\032\000\032\000\032\000\032\000\ \032\000\032\000\032\000\032\000\032\000\032\000\032\000\032\000\ \032\000\032\000\032\000\032\000\032\000\032\000\032\000\032\000\ \255\255\255\255\255\255\255\255\032\000\255\255\032\000\032\000\ \032\000\032\000\032\000\032\000\032\000\032\000\032\000\032\000\ \032\000\032\000\032\000\032\000\032\000\032\000\032\000\032\000\ \032\000\032\000\032\000\032\000\032\000\032\000\032\000\032\000\ \144\000\144\000\144\000\144\000\144\000\144\000\144\000\144\000\ \144\000\144\000\255\255\255\255\255\255\255\255\255\255\255\255\ \181\000\144\000\144\000\144\000\144\000\144\000\144\000\224\000\ \224\000\224\000\224\000\224\000\224\000\224\000\224\000\224\000\ \224\000\255\255\255\255\255\255\255\255\255\255\255\255\181\000\ \255\255\181\000\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\144\000\144\000\144\000\144\000\144\000\144\000\181\000\ \181\000\181\000\181\000\181\000\181\000\181\000\181\000\181\000\ \181\000\255\255\255\255\255\255\255\255\032\000\032\000\032\000\ \032\000\032\000\032\000\032\000\032\000\032\000\032\000\032\000\ \032\000\032\000\032\000\032\000\032\000\032\000\032\000\032\000\ \032\000\032\000\032\000\032\000\032\000\032\000\032\000\032\000\ \032\000\032\000\032\000\032\000\032\000\032\000\032\000\032\000\ \032\000\032\000\032\000\032\000\032\000\032\000\032\000\032\000\ \032\000\032\000\032\000\032\000\032\000\032\000\032\000\032\000\ \032\000\032\000\032\000\032\000\032\000\032\000\032\000\032\000\ \032\000\032\000\032\000\032\000\032\000\033\000\254\000\254\000\ \254\000\254\000\254\000\254\000\254\000\254\000\033\000\033\000\ \033\000\033\000\033\000\033\000\033\000\033\000\033\000\033\000\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\033\000\ \033\000\033\000\033\000\033\000\033\000\033\000\033\000\033\000\ \033\000\033\000\033\000\033\000\033\000\033\000\033\000\033\000\ \033\000\033\000\033\000\033\000\033\000\033\000\033\000\033\000\ \033\000\255\255\255\255\255\255\255\255\033\000\255\255\033\000\ \033\000\033\000\033\000\033\000\033\000\033\000\033\000\033\000\ \033\000\033\000\033\000\033\000\033\000\033\000\033\000\033\000\ \033\000\033\000\033\000\033\000\033\000\033\000\033\000\033\000\ \033\000\219\000\219\000\219\000\219\000\219\000\219\000\219\000\ \219\000\219\000\219\000\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\219\000\219\000\219\000\219\000\219\000\219\000\ \247\000\247\000\247\000\247\000\247\000\247\000\247\000\247\000\ \247\000\247\000\252\000\252\000\252\000\252\000\252\000\252\000\ \252\000\252\000\252\000\252\000\255\255\255\255\255\255\255\255\ \255\255\255\255\219\000\219\000\219\000\219\000\219\000\219\000\ \255\000\255\000\255\000\255\000\255\000\255\000\255\000\255\000\ \255\255\255\255\255\255\255\255\255\255\255\255\033\000\033\000\ \033\000\033\000\033\000\033\000\033\000\033\000\033\000\033\000\ \033\000\033\000\033\000\033\000\033\000\033\000\033\000\033\000\ \033\000\033\000\033\000\033\000\033\000\033\000\033\000\033\000\ \033\000\033\000\033\000\033\000\033\000\033\000\033\000\033\000\ \033\000\033\000\033\000\033\000\033\000\033\000\033\000\033\000\ \033\000\033\000\033\000\033\000\033\000\033\000\033\000\033\000\ \033\000\033\000\033\000\033\000\033\000\033\000\033\000\033\000\ \033\000\033\000\033\000\033\000\033\000\033\000\034\000\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\034\000\ \034\000\034\000\034\000\034\000\034\000\034\000\034\000\034\000\ \034\000\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \034\000\034\000\034\000\034\000\034\000\034\000\034\000\034\000\ \034\000\034\000\034\000\034\000\034\000\034\000\034\000\034\000\ \034\000\034\000\034\000\034\000\034\000\034\000\034\000\034\000\ \034\000\034\000\255\255\255\255\255\255\255\255\034\000\255\255\ \034\000\034\000\034\000\034\000\034\000\034\000\034\000\034\000\ \034\000\034\000\034\000\034\000\034\000\034\000\034\000\034\000\ \034\000\034\000\034\000\034\000\034\000\034\000\034\000\034\000\ \034\000\034\000\231\000\231\000\231\000\231\000\231\000\231\000\ \231\000\231\000\231\000\231\000\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\231\000\231\000\231\000\231\000\231\000\ \231\000\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\231\000\231\000\231\000\231\000\231\000\ \231\000\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\034\000\ \034\000\034\000\034\000\034\000\034\000\034\000\034\000\034\000\ \034\000\034\000\034\000\034\000\034\000\034\000\034\000\034\000\ \034\000\034\000\034\000\034\000\034\000\034\000\034\000\034\000\ \034\000\034\000\034\000\034\000\034\000\034\000\034\000\034\000\ \034\000\034\000\034\000\034\000\034\000\034\000\034\000\034\000\ \034\000\034\000\034\000\034\000\034\000\034\000\034\000\034\000\ \034\000\034\000\034\000\034\000\034\000\034\000\034\000\034\000\ \034\000\034\000\034\000\034\000\034\000\034\000\034\000\035\000\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \035\000\035\000\035\000\035\000\035\000\035\000\035\000\035\000\ \035\000\035\000\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\035\000\035\000\035\000\035\000\035\000\035\000\035\000\ \035\000\035\000\035\000\035\000\035\000\035\000\035\000\035\000\ \035\000\035\000\035\000\035\000\035\000\035\000\035\000\035\000\ \035\000\035\000\035\000\255\255\255\255\255\255\255\255\035\000\ \255\255\035\000\035\000\035\000\035\000\035\000\035\000\035\000\ \035\000\035\000\035\000\035\000\035\000\035\000\035\000\035\000\ \035\000\035\000\035\000\035\000\035\000\035\000\035\000\035\000\ \035\000\035\000\035\000\245\000\245\000\245\000\245\000\245\000\ \245\000\245\000\245\000\245\000\245\000\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\245\000\245\000\245\000\245\000\ \245\000\245\000\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\245\000\245\000\245\000\245\000\ \245\000\245\000\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \035\000\035\000\035\000\035\000\035\000\035\000\035\000\035\000\ \035\000\035\000\035\000\035\000\035\000\035\000\035\000\035\000\ \035\000\035\000\035\000\035\000\035\000\035\000\035\000\035\000\ \035\000\035\000\035\000\035\000\035\000\035\000\035\000\035\000\ \035\000\035\000\035\000\035\000\035\000\035\000\035\000\035\000\ \035\000\035\000\035\000\035\000\035\000\035\000\035\000\035\000\ \035\000\035\000\035\000\035\000\035\000\035\000\035\000\035\000\ \035\000\035\000\035\000\035\000\035\000\035\000\035\000\035\000\ \036\000\255\255\036\000\036\000\036\000\036\000\255\255\255\255\ \255\255\036\000\036\000\255\255\036\000\036\000\036\000\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\036\000\255\255\036\000\036\000\036\000\036\000\036\000\ \036\000\036\000\036\000\036\000\036\000\036\000\036\000\036\000\ \036\000\036\000\036\000\036\000\036\000\036\000\036\000\036\000\ \036\000\036\000\036\000\036\000\036\000\036\000\036\000\036\000\ \036\000\036\000\255\255\036\000\255\255\036\000\036\000\255\255\ \036\000\036\000\036\000\036\000\036\000\036\000\036\000\036\000\ \036\000\036\000\036\000\036\000\036\000\036\000\036\000\036\000\ \036\000\036\000\036\000\036\000\036\000\036\000\036\000\036\000\ \036\000\036\000\255\255\036\000\255\255\036\000\001\001\001\001\ \001\001\001\001\001\001\001\001\001\001\001\001\001\001\001\001\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\001\001\ \001\001\001\001\001\001\001\001\001\001\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\001\001\ \001\001\001\001\001\001\001\001\001\001\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\036\000\ \036\000\036\000\036\000\036\000\036\000\036\000\036\000\036\000\ \036\000\036\000\036\000\036\000\036\000\036\000\036\000\036\000\ \036\000\036\000\036\000\036\000\036\000\036\000\036\000\036\000\ \036\000\036\000\036\000\036\000\036\000\036\000\036\000\036\000\ \036\000\036\000\036\000\036\000\036\000\036\000\036\000\036\000\ \036\000\036\000\036\000\036\000\036\000\036\000\036\000\036\000\ \036\000\036\000\036\000\036\000\036\000\036\000\036\000\036\000\ \036\000\036\000\036\000\036\000\036\000\036\000\036\000\037\000\ \255\255\255\255\037\000\037\000\037\000\255\255\255\255\255\255\ \037\000\037\000\255\255\037\000\037\000\037\000\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \037\000\255\255\255\255\037\000\037\000\037\000\037\000\255\255\ \003\001\003\001\003\001\003\001\003\001\003\001\003\001\003\001\ \003\001\003\001\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\003\001\003\001\003\001\003\001\003\001\003\001\255\255\ \255\255\255\255\255\255\255\255\037\000\255\255\255\255\255\255\ \255\255\255\255\038\000\255\255\038\000\038\000\038\000\038\000\ \255\255\255\255\255\255\038\000\038\000\255\255\038\000\038\000\ \038\000\003\001\003\001\003\001\003\001\003\001\003\001\255\255\ \255\255\255\255\037\000\038\000\037\000\038\000\038\000\038\000\ \038\000\038\000\038\000\038\000\038\000\038\000\038\000\038\000\ \038\000\038\000\038\000\038\000\038\000\038\000\038\000\038\000\ \038\000\038\000\038\000\038\000\038\000\038\000\038\000\038\000\ \038\000\038\000\038\000\038\000\255\255\038\000\255\255\038\000\ \038\000\255\255\038\000\038\000\038\000\038\000\038\000\038\000\ \038\000\038\000\038\000\038\000\038\000\038\000\038\000\038\000\ \038\000\038\000\038\000\038\000\038\000\038\000\038\000\038\000\ \038\000\038\000\038\000\038\000\255\255\038\000\255\255\038\000\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\038\000\038\000\038\000\038\000\038\000\038\000\038\000\ \038\000\038\000\038\000\038\000\038\000\038\000\038\000\038\000\ \038\000\038\000\038\000\038\000\038\000\038\000\038\000\038\000\ \038\000\038\000\038\000\038\000\038\000\038\000\038\000\038\000\ \038\000\038\000\038\000\038\000\038\000\038\000\038\000\038\000\ \038\000\038\000\038\000\038\000\038\000\038\000\038\000\038\000\ \038\000\038\000\038\000\038\000\038\000\038\000\038\000\038\000\ \038\000\038\000\038\000\038\000\038\000\038\000\038\000\038\000\ \038\000\039\000\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\039\000\039\000\039\000\039\000\039\000\039\000\ \039\000\039\000\039\000\039\000\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\039\000\039\000\039\000\039\000\039\000\ \039\000\039\000\039\000\039\000\039\000\039\000\039\000\039\000\ \039\000\039\000\039\000\039\000\039\000\039\000\039\000\039\000\ \039\000\039\000\039\000\039\000\039\000\255\255\255\255\255\255\ \255\255\039\000\255\255\039\000\039\000\039\000\039\000\039\000\ \039\000\039\000\039\000\039\000\039\000\039\000\039\000\039\000\ \039\000\039\000\039\000\039\000\039\000\039\000\039\000\039\000\ \039\000\039\000\039\000\039\000\039\000\255\255\255\255\255\255\ \255\255\255\255\255\255\044\000\044\000\044\000\044\000\044\000\ \044\000\044\000\044\000\044\000\044\000\044\000\044\000\044\000\ \044\000\044\000\044\000\044\000\044\000\044\000\044\000\044\000\ \044\000\044\000\044\000\044\000\044\000\255\255\255\255\255\255\ \255\255\044\000\255\255\044\000\044\000\044\000\044\000\044\000\ \044\000\044\000\044\000\044\000\044\000\044\000\044\000\044\000\ \044\000\044\000\044\000\044\000\044\000\044\000\044\000\044\000\ \044\000\044\000\044\000\044\000\044\000\255\255\255\255\255\255\ \255\255\255\255\039\000\039\000\039\000\039\000\039\000\039\000\ \039\000\039\000\039\000\039\000\039\000\039\000\039\000\039\000\ \039\000\039\000\039\000\039\000\039\000\039\000\039\000\039\000\ \039\000\039\000\039\000\039\000\039\000\039\000\039\000\039\000\ \039\000\039\000\039\000\039\000\039\000\039\000\039\000\039\000\ \039\000\039\000\039\000\039\000\039\000\039\000\039\000\039\000\ \039\000\039\000\039\000\039\000\039\000\039\000\039\000\039\000\ \039\000\039\000\039\000\039\000\039\000\039\000\039\000\039\000\ \039\000\039\000\044\000\044\000\044\000\044\000\044\000\044\000\ \044\000\044\000\044\000\044\000\044\000\044\000\044\000\044\000\ \044\000\044\000\044\000\044\000\044\000\044\000\044\000\044\000\ \044\000\044\000\044\000\044\000\044\000\044\000\044\000\044\000\ \044\000\044\000\044\000\044\000\044\000\044\000\044\000\044\000\ \044\000\044\000\044\000\044\000\044\000\044\000\044\000\044\000\ \044\000\044\000\044\000\044\000\044\000\044\000\044\000\044\000\ \044\000\044\000\044\000\044\000\044\000\044\000\044\000\044\000\ \044\000\044\000\047\000\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\047\000\047\000\047\000\047\000\047\000\ \047\000\047\000\047\000\047\000\047\000\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\047\000\047\000\047\000\047\000\ \047\000\047\000\047\000\047\000\047\000\047\000\047\000\047\000\ \047\000\047\000\047\000\047\000\047\000\047\000\047\000\047\000\ \047\000\047\000\047\000\047\000\047\000\047\000\255\255\255\255\ \255\255\255\255\047\000\255\255\047\000\047\000\047\000\047\000\ \047\000\047\000\047\000\047\000\047\000\047\000\047\000\047\000\ \047\000\047\000\047\000\047\000\047\000\047\000\047\000\047\000\ \047\000\047\000\047\000\047\000\047\000\047\000\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\047\000\047\000\047\000\047\000\047\000\ \047\000\047\000\047\000\047\000\047\000\047\000\047\000\047\000\ \047\000\047\000\047\000\047\000\047\000\047\000\047\000\047\000\ \047\000\047\000\047\000\047\000\047\000\047\000\047\000\047\000\ \047\000\047\000\047\000\047\000\047\000\047\000\047\000\047\000\ \047\000\047\000\047\000\047\000\047\000\047\000\047\000\047\000\ \047\000\047\000\047\000\047\000\047\000\047\000\047\000\047\000\ \047\000\047\000\047\000\047\000\047\000\047\000\047\000\047\000\ \047\000\047\000\047\000\048\000\048\000\048\000\048\000\048\000\ \048\000\048\000\048\000\048\000\048\000\048\000\048\000\048\000\ \048\000\048\000\048\000\048\000\048\000\048\000\048\000\048\000\ \048\000\048\000\048\000\048\000\048\000\048\000\048\000\048\000\ \048\000\048\000\048\000\048\000\048\000\048\000\048\000\048\000\ \048\000\048\000\048\000\048\000\048\000\048\000\048\000\048\000\ \048\000\048\000\048\000\048\000\048\000\048\000\048\000\048\000\ \048\000\048\000\048\000\048\000\048\000\048\000\048\000\048\000\ \048\000\048\000\048\000\048\000\048\000\048\000\048\000\048\000\ \048\000\048\000\048\000\048\000\048\000\048\000\048\000\048\000\ \048\000\048\000\048\000\048\000\048\000\048\000\048\000\048\000\ \048\000\048\000\048\000\048\000\048\000\048\000\048\000\048\000\ \048\000\048\000\048\000\048\000\048\000\048\000\048\000\048\000\ \048\000\048\000\048\000\048\000\048\000\048\000\048\000\048\000\ \048\000\048\000\048\000\048\000\048\000\048\000\048\000\048\000\ \048\000\048\000\048\000\048\000\048\000\048\000\048\000\048\000\ \048\000\048\000\048\000\050\000\255\255\050\000\050\000\050\000\ \050\000\255\255\255\255\255\255\050\000\050\000\255\255\050\000\ \050\000\050\000\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\050\000\255\255\050\000\050\000\ \050\000\050\000\050\000\255\255\255\255\072\000\255\255\255\255\ \072\000\072\000\072\000\255\255\255\255\255\255\072\000\072\000\ \255\255\072\000\255\255\072\000\004\001\004\001\004\001\004\001\ \004\001\004\001\004\001\004\001\004\001\004\001\072\000\255\255\ \050\000\072\000\072\000\072\000\072\000\004\001\004\001\004\001\ \004\001\004\001\004\001\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\050\000\255\255\ \050\000\255\255\072\000\255\255\255\255\004\001\004\001\004\001\ \004\001\004\001\004\001\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \072\000\004\001\255\255\048\000\051\000\051\000\051\000\051\000\ \051\000\051\000\051\000\051\000\051\000\051\000\051\000\051\000\ \051\000\051\000\051\000\051\000\051\000\051\000\051\000\051\000\ \051\000\051\000\051\000\051\000\051\000\051\000\051\000\051\000\ \051\000\051\000\051\000\051\000\051\000\051\000\051\000\051\000\ \051\000\051\000\051\000\076\000\051\000\051\000\051\000\051\000\ \051\000\051\000\051\000\051\000\076\000\076\000\076\000\076\000\ \076\000\076\000\076\000\076\000\076\000\076\000\051\000\051\000\ \051\000\051\000\051\000\051\000\051\000\076\000\076\000\076\000\ \076\000\076\000\076\000\076\000\076\000\076\000\076\000\076\000\ \076\000\076\000\076\000\076\000\076\000\076\000\076\000\076\000\ \076\000\076\000\076\000\076\000\076\000\076\000\076\000\051\000\ \051\000\051\000\051\000\076\000\051\000\076\000\076\000\076\000\ \076\000\076\000\076\000\076\000\076\000\076\000\076\000\076\000\ \076\000\076\000\076\000\076\000\076\000\076\000\076\000\076\000\ \076\000\076\000\076\000\076\000\076\000\076\000\076\000\051\000\ \051\000\051\000\051\000\051\000\051\000\051\000\051\000\051\000\ \051\000\051\000\051\000\051\000\051\000\051\000\051\000\051\000\ \051\000\051\000\051\000\051\000\051\000\051\000\051\000\051\000\ \051\000\051\000\051\000\051\000\051\000\051\000\051\000\051\000\ \051\000\051\000\051\000\051\000\051\000\051\000\051\000\051\000\ \051\000\051\000\051\000\051\000\051\000\051\000\051\000\051\000\ \051\000\051\000\051\000\051\000\051\000\051\000\051\000\051\000\ \051\000\051\000\051\000\051\000\051\000\051\000\051\000\051\000\ \051\000\051\000\051\000\051\000\051\000\051\000\051\000\051\000\ \051\000\051\000\051\000\051\000\051\000\051\000\051\000\051\000\ \051\000\051\000\051\000\051\000\051\000\051\000\051\000\051\000\ \051\000\051\000\051\000\051\000\051\000\051\000\051\000\051\000\ \051\000\051\000\051\000\051\000\051\000\051\000\051\000\051\000\ \051\000\051\000\051\000\051\000\051\000\051\000\051\000\051\000\ \051\000\051\000\051\000\051\000\051\000\051\000\051\000\051\000\ \051\000\051\000\051\000\051\000\051\000\051\000\051\000\051\000\ \051\000\051\000\051\000\051\000\051\000\053\000\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\053\000\053\000\ \053\000\053\000\053\000\053\000\053\000\053\000\053\000\053\000\ \053\000\255\255\255\255\255\255\255\255\255\255\255\255\053\000\ \053\000\053\000\053\000\053\000\053\000\053\000\053\000\053\000\ \053\000\053\000\053\000\053\000\053\000\053\000\053\000\053\000\ \053\000\053\000\053\000\053\000\053\000\053\000\053\000\053\000\ \053\000\255\255\255\255\255\255\255\255\053\000\255\255\053\000\ \053\000\053\000\053\000\053\000\053\000\053\000\053\000\053\000\ \053\000\053\000\053\000\053\000\053\000\053\000\053\000\053\000\ \053\000\053\000\053\000\053\000\053\000\053\000\053\000\053\000\ \053\000\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\053\000\053\000\ \053\000\053\000\053\000\053\000\053\000\053\000\053\000\053\000\ \053\000\053\000\053\000\053\000\053\000\053\000\053\000\053\000\ \053\000\053\000\053\000\053\000\053\000\053\000\053\000\053\000\ \053\000\053\000\053\000\053\000\053\000\053\000\053\000\053\000\ \053\000\053\000\053\000\053\000\053\000\053\000\053\000\053\000\ \053\000\053\000\053\000\053\000\053\000\053\000\053\000\053\000\ \053\000\053\000\053\000\053\000\053\000\053\000\053\000\053\000\ \053\000\053\000\053\000\053\000\053\000\053\000\054\000\054\000\ \054\000\054\000\054\000\054\000\054\000\054\000\054\000\054\000\ \054\000\054\000\054\000\054\000\054\000\054\000\054\000\054\000\ \054\000\054\000\054\000\054\000\054\000\054\000\054\000\054\000\ \054\000\054\000\054\000\054\000\054\000\054\000\054\000\054\000\ \054\000\054\000\054\000\054\000\054\000\054\000\054\000\054\000\ \054\000\054\000\054\000\054\000\054\000\054\000\054\000\054\000\ \054\000\054\000\054\000\054\000\054\000\054\000\054\000\054\000\ \054\000\054\000\054\000\054\000\054\000\054\000\054\000\054\000\ \054\000\054\000\054\000\054\000\054\000\054\000\054\000\054\000\ \054\000\054\000\054\000\054\000\054\000\054\000\054\000\054\000\ \054\000\054\000\054\000\054\000\054\000\054\000\054\000\054\000\ \054\000\054\000\054\000\054\000\054\000\054\000\054\000\054\000\ \054\000\054\000\054\000\054\000\054\000\054\000\054\000\054\000\ \054\000\054\000\054\000\054\000\054\000\054\000\054\000\054\000\ \054\000\054\000\054\000\054\000\054\000\054\000\054\000\054\000\ \054\000\054\000\054\000\054\000\054\000\054\000\057\000\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\057\000\ \057\000\057\000\057\000\057\000\057\000\057\000\057\000\057\000\ \057\000\057\000\255\255\255\255\255\255\255\255\255\255\255\255\ \057\000\057\000\057\000\057\000\057\000\057\000\057\000\057\000\ \057\000\057\000\057\000\057\000\057\000\057\000\057\000\057\000\ \057\000\057\000\057\000\057\000\057\000\057\000\057\000\057\000\ \057\000\057\000\255\255\255\255\255\255\255\255\057\000\255\255\ \057\000\057\000\057\000\057\000\057\000\057\000\057\000\057\000\ \057\000\057\000\057\000\057\000\057\000\057\000\057\000\057\000\ \057\000\057\000\057\000\057\000\057\000\057\000\057\000\057\000\ \057\000\057\000\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\054\000\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\057\000\ \057\000\057\000\057\000\057\000\057\000\057\000\057\000\057\000\ \057\000\057\000\057\000\057\000\057\000\057\000\057\000\057\000\ \057\000\057\000\057\000\057\000\057\000\057\000\057\000\057\000\ \057\000\057\000\057\000\057\000\057\000\057\000\057\000\057\000\ \057\000\057\000\057\000\057\000\057\000\057\000\057\000\057\000\ \057\000\057\000\057\000\057\000\057\000\057\000\057\000\057\000\ \057\000\057\000\057\000\057\000\057\000\057\000\057\000\057\000\ \057\000\057\000\057\000\057\000\057\000\057\000\057\000\058\000\ \058\000\058\000\058\000\058\000\058\000\058\000\058\000\058\000\ \058\000\058\000\058\000\058\000\058\000\058\000\058\000\058\000\ \058\000\058\000\058\000\058\000\058\000\058\000\058\000\058\000\ \058\000\255\255\255\255\255\255\255\255\058\000\255\255\058\000\ \058\000\058\000\058\000\058\000\058\000\058\000\058\000\058\000\ \058\000\058\000\058\000\058\000\058\000\058\000\058\000\058\000\ \058\000\058\000\058\000\058\000\058\000\058\000\058\000\058\000\ \058\000\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\058\000\058\000\ \058\000\058\000\058\000\058\000\058\000\058\000\058\000\058\000\ \058\000\058\000\058\000\058\000\058\000\058\000\058\000\058\000\ \058\000\058\000\058\000\058\000\058\000\058\000\058\000\058\000\ \058\000\058\000\058\000\058\000\058\000\058\000\058\000\058\000\ \058\000\058\000\058\000\058\000\058\000\058\000\058\000\058\000\ \058\000\058\000\058\000\058\000\058\000\058\000\058\000\058\000\ \058\000\058\000\058\000\058\000\058\000\058\000\058\000\058\000\ \058\000\058\000\058\000\058\000\058\000\058\000\059\000\255\255\ \255\255\059\000\059\000\059\000\078\000\255\255\255\255\059\000\ \059\000\255\255\059\000\059\000\059\000\078\000\078\000\078\000\ \078\000\078\000\078\000\078\000\078\000\078\000\078\000\059\000\ \255\255\059\000\059\000\059\000\059\000\059\000\078\000\078\000\ \078\000\078\000\078\000\078\000\078\000\078\000\078\000\078\000\ \078\000\078\000\078\000\078\000\078\000\078\000\078\000\078\000\ \078\000\078\000\078\000\078\000\078\000\078\000\078\000\078\000\ \255\255\255\255\255\255\059\000\078\000\255\255\078\000\078\000\ \078\000\078\000\078\000\078\000\078\000\078\000\078\000\078\000\ \078\000\078\000\078\000\078\000\078\000\078\000\078\000\078\000\ \078\000\078\000\078\000\078\000\078\000\078\000\078\000\078\000\ \255\255\059\000\255\255\059\000\062\000\062\000\062\000\062\000\ \062\000\062\000\062\000\062\000\062\000\062\000\062\000\062\000\ \062\000\062\000\062\000\062\000\062\000\062\000\062\000\062\000\ \062\000\062\000\062\000\062\000\062\000\062\000\062\000\062\000\ \062\000\062\000\062\000\062\000\062\000\062\000\062\000\062\000\ \062\000\062\000\062\000\079\000\062\000\062\000\062\000\062\000\ \062\000\062\000\062\000\062\000\079\000\079\000\079\000\079\000\ \079\000\079\000\079\000\079\000\079\000\079\000\062\000\062\000\ \062\000\062\000\062\000\062\000\062\000\079\000\079\000\079\000\ \079\000\079\000\079\000\079\000\079\000\079\000\079\000\079\000\ \079\000\079\000\079\000\079\000\079\000\079\000\079\000\079\000\ \079\000\079\000\079\000\079\000\079\000\079\000\079\000\062\000\ \062\000\062\000\062\000\079\000\062\000\079\000\079\000\079\000\ \079\000\079\000\079\000\079\000\079\000\079\000\079\000\079\000\ \079\000\079\000\079\000\079\000\079\000\079\000\079\000\079\000\ \079\000\079\000\079\000\079\000\079\000\079\000\079\000\062\000\ \062\000\062\000\062\000\062\000\062\000\062\000\062\000\062\000\ \062\000\062\000\062\000\062\000\062\000\062\000\062\000\062\000\ \062\000\062\000\062\000\062\000\062\000\062\000\062\000\062\000\ \062\000\062\000\062\000\062\000\062\000\062\000\062\000\062\000\ \062\000\062\000\062\000\062\000\062\000\062\000\062\000\062\000\ \062\000\062\000\062\000\062\000\062\000\062\000\062\000\062\000\ \062\000\062\000\062\000\062\000\062\000\062\000\062\000\062\000\ \062\000\062\000\062\000\062\000\062\000\062\000\062\000\062\000\ \062\000\062\000\062\000\062\000\062\000\062\000\062\000\062\000\ \062\000\062\000\062\000\062\000\062\000\062\000\062\000\062\000\ \062\000\062\000\062\000\062\000\062\000\062\000\062\000\062\000\ \062\000\062\000\062\000\062\000\062\000\062\000\062\000\062\000\ \062\000\062\000\062\000\062\000\062\000\062\000\062\000\062\000\ \062\000\062\000\062\000\062\000\062\000\062\000\062\000\062\000\ \062\000\062\000\062\000\062\000\062\000\062\000\062\000\062\000\ \062\000\062\000\062\000\062\000\062\000\062\000\062\000\062\000\ \062\000\062\000\062\000\062\000\062\000\063\000\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\063\000\063\000\ \063\000\063\000\063\000\063\000\063\000\063\000\063\000\063\000\ \063\000\255\255\255\255\255\255\255\255\255\255\255\255\063\000\ \063\000\063\000\063\000\063\000\063\000\063\000\063\000\063\000\ \063\000\063\000\063\000\063\000\063\000\063\000\063\000\063\000\ \063\000\063\000\063\000\063\000\063\000\063\000\063\000\063\000\ \063\000\255\255\255\255\255\255\255\255\063\000\255\255\063\000\ \063\000\063\000\063\000\063\000\063\000\063\000\063\000\063\000\ \063\000\063\000\063\000\063\000\063\000\063\000\063\000\063\000\ \063\000\063\000\063\000\063\000\063\000\063\000\063\000\063\000\ \063\000\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\063\000\063\000\ \063\000\063\000\063\000\063\000\063\000\063\000\063\000\063\000\ \063\000\063\000\063\000\063\000\063\000\063\000\063\000\063\000\ \063\000\063\000\063\000\063\000\063\000\063\000\063\000\063\000\ \063\000\063\000\063\000\063\000\063\000\063\000\063\000\063\000\ \063\000\063\000\063\000\063\000\063\000\063\000\063\000\063\000\ \063\000\063\000\063\000\063\000\063\000\063\000\063\000\063\000\ \063\000\063\000\063\000\063\000\063\000\063\000\063\000\063\000\ \063\000\063\000\063\000\063\000\063\000\063\000\065\000\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\065\000\ \065\000\065\000\065\000\065\000\065\000\065\000\065\000\065\000\ \065\000\065\000\255\255\255\255\255\255\255\255\255\255\255\255\ \065\000\065\000\065\000\065\000\065\000\065\000\065\000\065\000\ \065\000\065\000\065\000\065\000\065\000\065\000\065\000\065\000\ \065\000\065\000\065\000\065\000\065\000\065\000\065\000\065\000\ \065\000\065\000\255\255\255\255\255\255\255\255\065\000\255\255\ \065\000\065\000\065\000\065\000\065\000\065\000\065\000\065\000\ \065\000\065\000\065\000\065\000\065\000\065\000\065\000\065\000\ \065\000\065\000\065\000\065\000\065\000\065\000\065\000\065\000\ \065\000\065\000\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\065\000\ \065\000\065\000\065\000\065\000\065\000\065\000\065\000\065\000\ \065\000\065\000\065\000\065\000\065\000\065\000\065\000\065\000\ \065\000\065\000\065\000\065\000\065\000\065\000\065\000\065\000\ \065\000\065\000\065\000\065\000\065\000\065\000\065\000\065\000\ \065\000\065\000\065\000\065\000\065\000\065\000\065\000\065\000\ \065\000\065\000\065\000\065\000\065\000\065\000\065\000\065\000\ \065\000\065\000\065\000\065\000\065\000\065\000\065\000\065\000\ \065\000\065\000\065\000\065\000\065\000\065\000\065\000\066\000\ \066\000\066\000\066\000\066\000\066\000\066\000\066\000\066\000\ \066\000\066\000\066\000\066\000\066\000\066\000\066\000\066\000\ \066\000\066\000\066\000\066\000\066\000\066\000\066\000\066\000\ \066\000\066\000\066\000\066\000\066\000\066\000\066\000\066\000\ \066\000\066\000\066\000\066\000\066\000\066\000\066\000\066\000\ \066\000\066\000\066\000\066\000\066\000\066\000\066\000\066\000\ \066\000\066\000\066\000\066\000\066\000\066\000\066\000\066\000\ \066\000\066\000\066\000\066\000\066\000\066\000\066\000\066\000\ \066\000\066\000\066\000\066\000\066\000\066\000\066\000\066\000\ \066\000\066\000\066\000\066\000\066\000\066\000\066\000\066\000\ \066\000\066\000\066\000\066\000\066\000\066\000\066\000\066\000\ \066\000\066\000\066\000\066\000\066\000\066\000\066\000\066\000\ \066\000\066\000\066\000\066\000\066\000\066\000\066\000\066\000\ \066\000\066\000\066\000\066\000\066\000\066\000\066\000\066\000\ \066\000\066\000\066\000\066\000\066\000\066\000\066\000\066\000\ \066\000\066\000\066\000\066\000\066\000\066\000\066\000\255\255\ \255\255\069\000\069\000\069\000\069\000\069\000\069\000\069\000\ \069\000\069\000\069\000\069\000\069\000\069\000\069\000\069\000\ \069\000\069\000\069\000\069\000\069\000\069\000\069\000\069\000\ \069\000\069\000\069\000\255\255\255\255\255\255\255\255\069\000\ \255\255\069\000\069\000\069\000\069\000\069\000\069\000\069\000\ \069\000\069\000\069\000\069\000\069\000\069\000\069\000\069\000\ \069\000\069\000\069\000\069\000\069\000\069\000\069\000\069\000\ \069\000\069\000\069\000\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\066\000\ \069\000\069\000\069\000\069\000\069\000\069\000\069\000\069\000\ \069\000\069\000\069\000\069\000\069\000\069\000\069\000\069\000\ \069\000\069\000\069\000\069\000\069\000\069\000\069\000\069\000\ \069\000\069\000\069\000\069\000\069\000\069\000\069\000\069\000\ \069\000\069\000\069\000\069\000\069\000\069\000\069\000\069\000\ \069\000\069\000\069\000\069\000\069\000\069\000\069\000\069\000\ \069\000\069\000\069\000\069\000\069\000\069\000\069\000\069\000\ \069\000\069\000\069\000\069\000\069\000\069\000\069\000\069\000\ \070\000\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\070\000\070\000\070\000\070\000\070\000\070\000\070\000\ \070\000\070\000\070\000\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\070\000\070\000\070\000\070\000\070\000\070\000\ \070\000\070\000\070\000\070\000\070\000\070\000\070\000\070\000\ \070\000\070\000\070\000\070\000\070\000\070\000\070\000\070\000\ \070\000\070\000\070\000\070\000\255\255\255\255\255\255\255\255\ \070\000\255\255\070\000\070\000\070\000\070\000\070\000\070\000\ \070\000\070\000\070\000\070\000\070\000\070\000\070\000\070\000\ \070\000\070\000\070\000\070\000\070\000\070\000\070\000\070\000\ \070\000\070\000\070\000\070\000\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\070\000\070\000\070\000\070\000\070\000\070\000\070\000\ \070\000\070\000\070\000\070\000\070\000\070\000\070\000\070\000\ \070\000\070\000\070\000\070\000\070\000\070\000\070\000\070\000\ \070\000\070\000\070\000\070\000\070\000\070\000\070\000\070\000\ \070\000\070\000\070\000\070\000\070\000\070\000\070\000\070\000\ \070\000\070\000\070\000\070\000\070\000\070\000\070\000\070\000\ \070\000\070\000\070\000\070\000\070\000\070\000\070\000\070\000\ \070\000\070\000\070\000\070\000\070\000\070\000\070\000\070\000\ \070\000\071\000\255\255\071\000\071\000\255\255\255\255\071\000\ \071\000\255\255\071\000\255\255\071\000\071\000\071\000\071\000\ \071\000\071\000\071\000\071\000\071\000\071\000\071\000\255\255\ \255\255\071\000\071\000\071\000\255\255\071\000\071\000\071\000\ \071\000\071\000\071\000\071\000\071\000\071\000\071\000\071\000\ \071\000\071\000\071\000\071\000\071\000\071\000\071\000\071\000\ \071\000\071\000\071\000\071\000\071\000\071\000\071\000\071\000\ \255\255\255\255\255\255\071\000\071\000\255\255\071\000\071\000\ \071\000\071\000\071\000\071\000\071\000\071\000\071\000\071\000\ \071\000\071\000\071\000\071\000\071\000\071\000\071\000\071\000\ \071\000\071\000\071\000\071\000\071\000\071\000\071\000\071\000\ \255\255\071\000\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\071\000\071\000\071\000\ \071\000\071\000\071\000\071\000\071\000\071\000\071\000\071\000\ \071\000\071\000\071\000\071\000\071\000\071\000\071\000\071\000\ \071\000\071\000\071\000\071\000\071\000\071\000\071\000\071\000\ \071\000\071\000\071\000\071\000\071\000\071\000\071\000\071\000\ \071\000\071\000\071\000\071\000\071\000\071\000\071\000\071\000\ \071\000\071\000\071\000\071\000\071\000\071\000\071\000\071\000\ \071\000\071\000\071\000\071\000\071\000\071\000\071\000\071\000\ \071\000\071\000\071\000\071\000\071\000\073\000\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\073\000\073\000\ \073\000\073\000\073\000\073\000\073\000\073\000\073\000\073\000\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\073\000\ \073\000\073\000\073\000\073\000\073\000\073\000\073\000\073\000\ \073\000\073\000\073\000\073\000\073\000\073\000\073\000\073\000\ \073\000\073\000\073\000\073\000\073\000\073\000\073\000\073\000\ \073\000\255\255\255\255\255\255\255\255\073\000\255\255\073\000\ \073\000\073\000\073\000\073\000\073\000\073\000\073\000\073\000\ \073\000\073\000\073\000\073\000\073\000\073\000\073\000\073\000\ \073\000\073\000\073\000\073\000\073\000\073\000\073\000\073\000\ \073\000\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\073\000\073\000\ \073\000\073\000\073\000\073\000\073\000\073\000\073\000\073\000\ \073\000\073\000\073\000\073\000\073\000\073\000\073\000\073\000\ \073\000\073\000\073\000\073\000\073\000\073\000\073\000\073\000\ \073\000\073\000\073\000\073\000\073\000\073\000\073\000\073\000\ \073\000\073\000\073\000\073\000\073\000\073\000\073\000\073\000\ \073\000\073\000\073\000\073\000\073\000\073\000\073\000\073\000\ \073\000\073\000\073\000\073\000\073\000\073\000\073\000\073\000\ \073\000\073\000\073\000\073\000\073\000\073\000\074\000\255\255\ \074\000\074\000\255\255\255\255\074\000\074\000\255\255\074\000\ \255\255\074\000\074\000\074\000\074\000\074\000\074\000\074\000\ \074\000\074\000\074\000\074\000\255\255\255\255\074\000\074\000\ \074\000\255\255\074\000\074\000\074\000\074\000\074\000\074\000\ \074\000\074\000\074\000\074\000\074\000\074\000\074\000\074\000\ \074\000\074\000\074\000\074\000\074\000\074\000\074\000\074\000\ \074\000\074\000\074\000\074\000\074\000\255\255\255\255\255\255\ \074\000\074\000\255\255\074\000\074\000\074\000\074\000\074\000\ \074\000\074\000\074\000\074\000\074\000\074\000\074\000\074\000\ \074\000\074\000\074\000\074\000\074\000\074\000\074\000\074\000\ \074\000\074\000\074\000\074\000\074\000\255\255\074\000\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\074\000\074\000\074\000\074\000\074\000\074\000\ \074\000\074\000\074\000\074\000\074\000\074\000\074\000\074\000\ \074\000\074\000\074\000\074\000\074\000\074\000\074\000\074\000\ \074\000\074\000\074\000\074\000\074\000\074\000\074\000\074\000\ \074\000\074\000\074\000\074\000\074\000\074\000\074\000\074\000\ \074\000\074\000\074\000\074\000\074\000\074\000\074\000\074\000\ \074\000\074\000\074\000\074\000\074\000\074\000\074\000\074\000\ \074\000\074\000\074\000\074\000\074\000\074\000\074\000\074\000\ \074\000\074\000\075\000\255\255\255\255\075\000\075\000\075\000\ \255\255\255\255\255\255\075\000\075\000\255\255\075\000\255\255\ \075\000\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\075\000\255\255\255\255\075\000\075\000\ \075\000\075\000\255\255\255\255\255\255\255\255\077\000\255\255\ \255\255\255\255\077\000\255\255\077\000\255\255\255\255\077\000\ \077\000\077\000\077\000\077\000\077\000\077\000\077\000\077\000\ \077\000\255\255\255\255\255\255\255\255\255\255\255\255\075\000\ \077\000\077\000\077\000\077\000\077\000\077\000\077\000\077\000\ \077\000\077\000\077\000\077\000\077\000\077\000\077\000\077\000\ \077\000\077\000\077\000\077\000\077\000\077\000\077\000\077\000\ \077\000\077\000\255\255\255\255\255\255\075\000\077\000\255\255\ \077\000\077\000\077\000\077\000\077\000\077\000\077\000\077\000\ \077\000\077\000\077\000\077\000\077\000\077\000\077\000\077\000\ \077\000\077\000\077\000\077\000\077\000\077\000\077\000\077\000\ \077\000\077\000\080\000\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\080\000\080\000\080\000\080\000\080\000\ \080\000\080\000\080\000\080\000\080\000\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\080\000\080\000\080\000\080\000\ \080\000\080\000\080\000\080\000\080\000\080\000\080\000\080\000\ \080\000\080\000\080\000\080\000\080\000\080\000\080\000\080\000\ \080\000\080\000\080\000\080\000\080\000\080\000\255\255\255\255\ \255\255\255\255\080\000\255\255\080\000\080\000\080\000\080\000\ \080\000\080\000\080\000\080\000\080\000\080\000\080\000\080\000\ \080\000\080\000\080\000\080\000\080\000\080\000\080\000\080\000\ \080\000\080\000\080\000\080\000\080\000\080\000\081\000\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\081\000\ \081\000\081\000\081\000\081\000\081\000\081\000\081\000\081\000\ \081\000\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \081\000\081\000\081\000\081\000\081\000\081\000\081\000\081\000\ \081\000\081\000\081\000\081\000\081\000\081\000\081\000\081\000\ \081\000\081\000\081\000\081\000\081\000\081\000\081\000\081\000\ \081\000\081\000\255\255\255\255\255\255\255\255\081\000\255\255\ \081\000\081\000\081\000\081\000\081\000\081\000\081\000\081\000\ \081\000\081\000\081\000\081\000\081\000\081\000\081\000\081\000\ \081\000\081\000\081\000\081\000\081\000\081\000\081\000\081\000\ \081\000\081\000\082\000\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\082\000\082\000\082\000\082\000\082\000\ \082\000\082\000\082\000\082\000\082\000\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\082\000\082\000\082\000\082\000\ \082\000\082\000\082\000\082\000\082\000\082\000\082\000\082\000\ \082\000\082\000\082\000\082\000\082\000\082\000\082\000\082\000\ \082\000\082\000\082\000\082\000\082\000\082\000\255\255\255\255\ \255\255\255\255\082\000\255\255\082\000\082\000\082\000\082\000\ \082\000\082\000\082\000\082\000\082\000\082\000\082\000\082\000\ \082\000\082\000\082\000\082\000\082\000\082\000\082\000\082\000\ \082\000\082\000\082\000\082\000\082\000\082\000\083\000\255\255\ \255\255\255\255\255\255\255\255\255\255\083\000\255\255\083\000\ \083\000\083\000\083\000\083\000\083\000\083\000\083\000\083\000\ \083\000\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \083\000\083\000\083\000\083\000\083\000\083\000\083\000\083\000\ \083\000\083\000\083\000\083\000\083\000\083\000\083\000\083\000\ \083\000\083\000\083\000\083\000\083\000\083\000\083\000\083\000\ \083\000\083\000\255\255\255\255\255\255\255\255\083\000\255\255\ \083\000\083\000\083\000\083\000\083\000\083\000\083\000\083\000\ \083\000\083\000\083\000\083\000\083\000\083\000\083\000\083\000\ \083\000\083\000\083\000\083\000\083\000\083\000\083\000\083\000\ \083\000\083\000\084\000\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\084\000\084\000\084\000\084\000\084\000\ \084\000\084\000\084\000\084\000\084\000\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\084\000\084\000\084\000\084\000\ \084\000\084\000\084\000\084\000\084\000\084\000\084\000\084\000\ \084\000\084\000\084\000\084\000\084\000\084\000\084\000\084\000\ \084\000\084\000\084\000\084\000\084\000\084\000\255\255\255\255\ \255\255\255\255\084\000\255\255\084\000\084\000\084\000\084\000\ \084\000\084\000\084\000\084\000\084\000\084\000\084\000\084\000\ \084\000\084\000\084\000\084\000\084\000\084\000\084\000\084\000\ \084\000\084\000\084\000\084\000\084\000\084\000\085\000\255\255\ \255\255\255\255\085\000\255\255\085\000\255\255\255\255\085\000\ \085\000\085\000\085\000\085\000\085\000\085\000\085\000\085\000\ \085\000\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \085\000\085\000\085\000\085\000\085\000\085\000\085\000\085\000\ \085\000\085\000\085\000\085\000\085\000\085\000\085\000\085\000\ \085\000\085\000\085\000\085\000\085\000\085\000\085\000\085\000\ \085\000\085\000\255\255\255\255\255\255\255\255\085\000\255\255\ \085\000\085\000\085\000\085\000\085\000\085\000\085\000\085\000\ \085\000\085\000\085\000\085\000\085\000\085\000\085\000\085\000\ \085\000\085\000\085\000\085\000\085\000\085\000\085\000\085\000\ \085\000\085\000\086\000\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\086\000\086\000\086\000\086\000\086\000\ \086\000\086\000\086\000\086\000\086\000\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\086\000\086\000\086\000\086\000\ \086\000\086\000\086\000\086\000\086\000\086\000\086\000\086\000\ \086\000\086\000\086\000\086\000\086\000\086\000\086\000\086\000\ \086\000\086\000\086\000\086\000\086\000\086\000\255\255\255\255\ \255\255\255\255\086\000\255\255\086\000\086\000\086\000\086\000\ \086\000\086\000\086\000\086\000\086\000\086\000\086\000\086\000\ \086\000\086\000\086\000\086\000\086\000\086\000\086\000\086\000\ \086\000\086\000\086\000\086\000\086\000\086\000\088\000\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\088\000\ \088\000\088\000\088\000\088\000\088\000\088\000\088\000\088\000\ \088\000\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \088\000\088\000\088\000\088\000\088\000\088\000\088\000\088\000\ \088\000\088\000\088\000\088\000\088\000\088\000\088\000\088\000\ \088\000\088\000\088\000\088\000\088\000\088\000\088\000\088\000\ \088\000\088\000\255\255\255\255\255\255\255\255\088\000\255\255\ \088\000\088\000\088\000\088\000\088\000\088\000\088\000\088\000\ \088\000\088\000\088\000\088\000\088\000\088\000\088\000\088\000\ \088\000\088\000\088\000\088\000\088\000\088\000\088\000\088\000\ \088\000\088\000\089\000\255\255\255\255\255\255\089\000\255\255\ \089\000\255\255\255\255\089\000\089\000\089\000\089\000\089\000\ \089\000\089\000\089\000\089\000\089\000\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\089\000\089\000\089\000\089\000\ \089\000\089\000\089\000\089\000\089\000\089\000\089\000\089\000\ \089\000\089\000\089\000\089\000\089\000\089\000\089\000\089\000\ \089\000\089\000\089\000\089\000\089\000\089\000\255\255\255\255\ \255\255\255\255\089\000\255\255\089\000\089\000\089\000\089\000\ \089\000\089\000\089\000\089\000\089\000\089\000\089\000\089\000\ \089\000\089\000\089\000\089\000\089\000\089\000\089\000\089\000\ \089\000\089\000\089\000\089\000\089\000\089\000\090\000\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\090\000\ \090\000\090\000\090\000\090\000\090\000\090\000\090\000\090\000\ \090\000\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \090\000\090\000\090\000\090\000\090\000\090\000\090\000\090\000\ \090\000\090\000\090\000\090\000\090\000\090\000\090\000\090\000\ \090\000\090\000\090\000\090\000\090\000\090\000\090\000\090\000\ \090\000\090\000\255\255\255\255\255\255\255\255\090\000\255\255\ \090\000\090\000\090\000\090\000\090\000\090\000\090\000\090\000\ \090\000\090\000\090\000\090\000\090\000\090\000\090\000\090\000\ \090\000\090\000\090\000\090\000\090\000\090\000\090\000\090\000\ \090\000\090\000\091\000\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\091\000\091\000\091\000\091\000\091\000\ \091\000\091\000\091\000\091\000\091\000\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\091\000\091\000\091\000\091\000\ \091\000\091\000\091\000\091\000\091\000\091\000\091\000\091\000\ \091\000\091\000\091\000\091\000\091\000\091\000\091\000\091\000\ \091\000\091\000\091\000\091\000\091\000\091\000\255\255\255\255\ \255\255\255\255\091\000\255\255\091\000\091\000\091\000\091\000\ \091\000\091\000\091\000\091\000\091\000\091\000\091\000\091\000\ \091\000\091\000\091\000\091\000\091\000\091\000\091\000\091\000\ \091\000\091\000\091\000\091\000\091\000\091\000\092\000\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\092\000\ \092\000\092\000\092\000\092\000\092\000\092\000\092\000\092\000\ \092\000\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \092\000\092\000\092\000\092\000\092\000\092\000\092\000\092\000\ \092\000\092\000\092\000\092\000\092\000\092\000\092\000\092\000\ \092\000\092\000\092\000\092\000\092\000\092\000\092\000\092\000\ \092\000\092\000\255\255\255\255\255\255\255\255\092\000\095\000\ \092\000\092\000\092\000\092\000\092\000\092\000\092\000\092\000\ \092\000\092\000\092\000\092\000\092\000\092\000\092\000\092\000\ \092\000\092\000\092\000\092\000\092\000\092\000\092\000\092\000\ \092\000\092\000\255\255\095\000\095\000\095\000\095\000\095\000\ \095\000\095\000\095\000\095\000\095\000\095\000\095\000\095\000\ \095\000\095\000\095\000\095\000\095\000\095\000\095\000\095\000\ \095\000\095\000\095\000\095\000\095\000\255\255\255\255\255\255\ \255\255\095\000\255\255\095\000\095\000\095\000\095\000\095\000\ \095\000\095\000\095\000\095\000\095\000\095\000\095\000\095\000\ \095\000\095\000\095\000\095\000\095\000\095\000\095\000\095\000\ \095\000\095\000\095\000\095\000\095\000\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\095\000\095\000\095\000\095\000\095\000\095\000\ \095\000\095\000\095\000\095\000\095\000\095\000\095\000\095\000\ \095\000\095\000\095\000\095\000\095\000\095\000\095\000\095\000\ \095\000\095\000\095\000\095\000\095\000\095\000\095\000\095\000\ \095\000\095\000\095\000\095\000\095\000\095\000\095\000\095\000\ \095\000\095\000\095\000\095\000\095\000\095\000\095\000\095\000\ \095\000\095\000\095\000\095\000\095\000\095\000\095\000\095\000\ \095\000\095\000\095\000\095\000\095\000\095\000\095\000\095\000\ \095\000\095\000\097\000\097\000\097\000\097\000\097\000\097\000\ \097\000\097\000\097\000\097\000\097\000\097\000\097\000\097\000\ \097\000\097\000\097\000\097\000\097\000\097\000\097\000\097\000\ \097\000\097\000\097\000\097\000\097\000\097\000\097\000\097\000\ \097\000\097\000\097\000\097\000\097\000\097\000\097\000\097\000\ \097\000\097\000\097\000\097\000\097\000\097\000\097\000\097\000\ \097\000\097\000\097\000\097\000\097\000\097\000\097\000\097\000\ \097\000\097\000\097\000\097\000\097\000\097\000\097\000\097\000\ \097\000\097\000\097\000\097\000\097\000\097\000\097\000\097\000\ \097\000\097\000\097\000\097\000\097\000\097\000\097\000\097\000\ \097\000\097\000\097\000\097\000\097\000\097\000\097\000\097\000\ \097\000\097\000\097\000\097\000\097\000\097\000\097\000\097\000\ \097\000\097\000\097\000\097\000\097\000\097\000\097\000\097\000\ \097\000\097\000\097\000\097\000\097\000\097\000\097\000\097\000\ \097\000\097\000\097\000\097\000\097\000\097\000\097\000\097\000\ \097\000\097\000\097\000\097\000\097\000\097\000\097\000\097\000\ \097\000\097\000\255\255\255\255\098\000\098\000\098\000\098\000\ \098\000\098\000\098\000\098\000\098\000\098\000\098\000\098\000\ \098\000\098\000\098\000\098\000\098\000\098\000\098\000\098\000\ \098\000\098\000\098\000\098\000\098\000\098\000\255\255\255\255\ \255\255\255\255\098\000\255\255\098\000\098\000\098\000\098\000\ \098\000\098\000\098\000\098\000\098\000\098\000\098\000\098\000\ \098\000\098\000\098\000\098\000\098\000\098\000\098\000\098\000\ \098\000\098\000\098\000\098\000\098\000\098\000\255\255\098\000\ \255\255\255\255\255\255\255\255\099\000\099\000\099\000\099\000\ \099\000\099\000\099\000\099\000\099\000\099\000\099\000\099\000\ \099\000\099\000\099\000\099\000\099\000\099\000\099\000\099\000\ \099\000\099\000\099\000\099\000\099\000\099\000\255\255\255\255\ \255\255\255\255\099\000\255\255\099\000\099\000\099\000\099\000\ \099\000\099\000\099\000\099\000\099\000\099\000\099\000\099\000\ \099\000\099\000\099\000\099\000\099\000\099\000\099\000\099\000\ \099\000\099\000\099\000\099\000\099\000\099\000\255\255\255\255\ \255\255\255\255\097\000\098\000\098\000\098\000\098\000\098\000\ \098\000\098\000\098\000\098\000\098\000\098\000\098\000\098\000\ \098\000\098\000\098\000\098\000\098\000\098\000\098\000\098\000\ \098\000\098\000\098\000\098\000\098\000\098\000\098\000\098\000\ \098\000\098\000\098\000\098\000\098\000\098\000\098\000\098\000\ \098\000\098\000\098\000\098\000\098\000\098\000\098\000\098\000\ \098\000\098\000\098\000\098\000\098\000\098\000\098\000\098\000\ \098\000\098\000\098\000\098\000\098\000\098\000\098\000\098\000\ \098\000\098\000\098\000\099\000\099\000\099\000\099\000\099\000\ \099\000\099\000\099\000\099\000\099\000\099\000\099\000\099\000\ \099\000\099\000\099\000\099\000\099\000\099\000\099\000\099\000\ \099\000\099\000\099\000\099\000\099\000\099\000\099\000\099\000\ \099\000\099\000\099\000\099\000\099\000\099\000\099\000\099\000\ \099\000\099\000\099\000\099\000\099\000\099\000\099\000\099\000\ \099\000\099\000\099\000\099\000\099\000\099\000\099\000\099\000\ \099\000\099\000\099\000\099\000\099\000\099\000\099\000\099\000\ \099\000\099\000\099\000\100\000\100\000\100\000\100\000\100\000\ \100\000\100\000\100\000\100\000\100\000\100\000\100\000\100\000\ \100\000\100\000\100\000\100\000\100\000\100\000\100\000\100\000\ \100\000\100\000\100\000\100\000\100\000\100\000\100\000\100\000\ \100\000\100\000\100\000\100\000\100\000\100\000\100\000\100\000\ \100\000\100\000\255\255\100\000\100\000\100\000\100\000\100\000\ \100\000\100\000\100\000\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\100\000\100\000\100\000\ \100\000\100\000\100\000\100\000\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\100\000\100\000\ \100\000\100\000\255\255\100\000\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\100\000\100\000\ \100\000\100\000\100\000\100\000\100\000\100\000\100\000\100\000\ \100\000\100\000\100\000\100\000\100\000\100\000\100\000\100\000\ \100\000\100\000\100\000\100\000\100\000\100\000\100\000\100\000\ \100\000\100\000\100\000\100\000\100\000\100\000\100\000\100\000\ \100\000\100\000\100\000\100\000\100\000\100\000\100\000\100\000\ \100\000\100\000\100\000\100\000\100\000\100\000\100\000\100\000\ \100\000\100\000\100\000\100\000\100\000\100\000\100\000\100\000\ \100\000\100\000\100\000\100\000\100\000\100\000\100\000\100\000\ \100\000\100\000\100\000\100\000\100\000\100\000\100\000\100\000\ \100\000\100\000\100\000\100\000\100\000\100\000\100\000\100\000\ \100\000\100\000\100\000\100\000\100\000\100\000\100\000\100\000\ \100\000\100\000\100\000\100\000\100\000\100\000\100\000\100\000\ \100\000\100\000\100\000\100\000\100\000\100\000\100\000\100\000\ \100\000\100\000\100\000\100\000\100\000\100\000\100\000\100\000\ \100\000\100\000\100\000\100\000\100\000\100\000\100\000\100\000\ \100\000\100\000\100\000\100\000\100\000\100\000\100\000\100\000\ \100\000\100\000\100\000\100\000\101\000\255\255\236\000\101\000\ \255\255\236\000\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\101\000\255\255\255\255\236\000\255\255\ \255\255\255\255\101\000\255\255\255\255\255\255\255\255\255\255\ \255\255\101\000\255\255\101\000\101\000\101\000\101\000\101\000\ \101\000\101\000\101\000\101\000\101\000\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\101\000\101\000\101\000\101\000\ \101\000\101\000\101\000\101\000\101\000\101\000\101\000\101\000\ \101\000\101\000\101\000\101\000\101\000\101\000\101\000\101\000\ \101\000\101\000\101\000\101\000\101\000\101\000\255\255\255\255\ \236\000\255\255\101\000\255\255\101\000\101\000\101\000\101\000\ \101\000\101\000\101\000\101\000\101\000\101\000\101\000\101\000\ \101\000\101\000\101\000\101\000\101\000\101\000\101\000\101\000\ \101\000\101\000\101\000\101\000\101\000\101\000\255\255\101\000\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\101\000\101\000\101\000\101\000\101\000\ \101\000\101\000\101\000\101\000\101\000\101\000\101\000\101\000\ \101\000\101\000\101\000\101\000\101\000\101\000\101\000\101\000\ \101\000\101\000\101\000\101\000\101\000\101\000\101\000\101\000\ \101\000\101\000\101\000\101\000\101\000\101\000\101\000\101\000\ \101\000\101\000\101\000\101\000\101\000\101\000\101\000\101\000\ \101\000\101\000\101\000\101\000\101\000\101\000\101\000\101\000\ \101\000\101\000\101\000\101\000\101\000\101\000\101\000\101\000\ \101\000\101\000\101\000\102\000\236\000\255\255\102\000\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\102\000\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\102\000\102\000\102\000\102\000\102\000\ \102\000\102\000\102\000\102\000\102\000\102\000\102\000\102\000\ \102\000\102\000\102\000\102\000\102\000\102\000\102\000\102\000\ \102\000\102\000\102\000\102\000\102\000\255\255\255\255\255\255\ \255\255\102\000\255\255\102\000\102\000\102\000\102\000\102\000\ \102\000\102\000\102\000\102\000\102\000\102\000\102\000\102\000\ \102\000\102\000\102\000\102\000\102\000\102\000\102\000\102\000\ \102\000\102\000\102\000\102\000\102\000\255\255\102\000\255\255\ \255\255\255\255\255\255\104\000\104\000\104\000\104\000\104\000\ \104\000\104\000\104\000\104\000\104\000\104\000\104\000\104\000\ \104\000\104\000\104\000\104\000\104\000\104\000\104\000\104\000\ \104\000\104\000\104\000\104\000\104\000\255\255\255\255\255\255\ \255\255\104\000\255\255\104\000\104\000\104\000\104\000\104\000\ \104\000\104\000\104\000\104\000\104\000\104\000\104\000\104\000\ \104\000\104\000\104\000\104\000\104\000\104\000\104\000\104\000\ \104\000\104\000\104\000\104\000\104\000\255\255\255\255\255\255\ \255\255\255\255\102\000\102\000\102\000\102\000\102\000\102\000\ \102\000\102\000\102\000\102\000\102\000\102\000\102\000\102\000\ \102\000\102\000\102\000\102\000\102\000\102\000\102\000\102\000\ \102\000\102\000\102\000\102\000\102\000\102\000\102\000\102\000\ \102\000\102\000\102\000\102\000\102\000\102\000\102\000\102\000\ \102\000\102\000\102\000\102\000\102\000\102\000\102\000\102\000\ \102\000\102\000\102\000\102\000\102\000\102\000\102\000\102\000\ \102\000\102\000\102\000\102\000\102\000\102\000\102\000\102\000\ \102\000\102\000\104\000\104\000\104\000\104\000\104\000\104\000\ \104\000\104\000\104\000\104\000\104\000\104\000\104\000\104\000\ \104\000\104\000\104\000\104\000\104\000\104\000\104\000\104\000\ \104\000\104\000\104\000\104\000\104\000\104\000\104\000\104\000\ \104\000\104\000\104\000\104\000\104\000\104\000\104\000\104\000\ \104\000\104\000\104\000\104\000\104\000\104\000\104\000\104\000\ \104\000\104\000\104\000\104\000\104\000\104\000\104\000\104\000\ \104\000\104\000\104\000\104\000\104\000\104\000\104\000\104\000\ \104\000\104\000\105\000\105\000\105\000\105\000\105\000\105\000\ \105\000\105\000\105\000\105\000\105\000\105\000\105\000\105\000\ \105\000\105\000\105\000\105\000\105\000\105\000\105\000\105\000\ \105\000\105\000\105\000\105\000\105\000\105\000\105\000\105\000\ \105\000\105\000\105\000\105\000\105\000\105\000\105\000\105\000\ \105\000\105\000\105\000\105\000\105\000\105\000\105\000\105\000\ \105\000\105\000\105\000\105\000\105\000\105\000\105\000\105\000\ \105\000\105\000\105\000\105\000\105\000\105\000\105\000\105\000\ \105\000\105\000\105\000\105\000\105\000\105\000\105\000\105\000\ \105\000\105\000\105\000\105\000\105\000\105\000\105\000\105\000\ \105\000\105\000\105\000\105\000\105\000\105\000\105\000\105\000\ \105\000\105\000\105\000\105\000\105\000\105\000\105\000\105\000\ \105\000\105\000\105\000\105\000\105\000\105\000\105\000\105\000\ \105\000\105\000\105\000\105\000\105\000\105\000\105\000\105\000\ \105\000\105\000\105\000\105\000\105\000\105\000\105\000\105\000\ \105\000\105\000\105\000\105\000\105\000\105\000\105\000\105\000\ \105\000\105\000\255\255\255\255\255\255\255\255\255\255\255\255\ \106\000\106\000\106\000\106\000\106\000\106\000\106\000\106\000\ \106\000\106\000\106\000\106\000\106\000\106\000\106\000\106\000\ \106\000\106\000\106\000\106\000\106\000\106\000\106\000\106\000\ \106\000\106\000\106\000\106\000\106\000\106\000\106\000\106\000\ \106\000\106\000\106\000\106\000\106\000\106\000\106\000\255\255\ \106\000\106\000\106\000\106\000\106\000\106\000\106\000\106\000\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\106\000\106\000\106\000\106\000\106\000\106\000\ \106\000\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\106\000\106\000\106\000\106\000\255\255\ \106\000\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\105\000\106\000\106\000\106\000\106\000\106\000\ \106\000\106\000\106\000\106\000\106\000\106\000\106\000\106\000\ \106\000\106\000\106\000\106\000\106\000\106\000\106\000\106\000\ \106\000\106\000\106\000\106\000\106\000\106\000\106\000\106\000\ \106\000\106\000\106\000\106\000\106\000\106\000\106\000\106\000\ \106\000\106\000\106\000\106\000\106\000\106\000\106\000\106\000\ \106\000\106\000\106\000\106\000\106\000\106\000\106\000\106\000\ \106\000\106\000\106\000\106\000\106\000\106\000\106\000\106\000\ \106\000\106\000\106\000\106\000\106\000\106\000\106\000\106\000\ \106\000\106\000\106\000\106\000\106\000\106\000\106\000\106\000\ \106\000\106\000\106\000\106\000\106\000\106\000\106\000\106\000\ \106\000\106\000\106\000\106\000\106\000\106\000\106\000\106\000\ \106\000\106\000\106\000\106\000\106\000\106\000\106\000\106\000\ \106\000\106\000\106\000\106\000\106\000\106\000\106\000\106\000\ \106\000\106\000\106\000\106\000\106\000\106\000\106\000\106\000\ \106\000\106\000\106\000\106\000\106\000\106\000\106\000\106\000\ \106\000\106\000\106\000\106\000\106\000\106\000\106\000\106\000\ \106\000\107\000\255\255\255\255\107\000\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \107\000\255\255\255\255\255\255\255\255\255\255\255\255\107\000\ \255\255\255\255\255\255\255\255\255\255\255\255\107\000\255\255\ \107\000\107\000\107\000\107\000\107\000\107\000\107\000\107\000\ \107\000\107\000\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\107\000\107\000\107\000\107\000\107\000\107\000\107\000\ \107\000\107\000\107\000\107\000\107\000\107\000\107\000\107\000\ \107\000\107\000\107\000\107\000\107\000\107\000\107\000\107\000\ \107\000\107\000\107\000\255\255\255\255\255\255\255\255\107\000\ \255\255\107\000\107\000\107\000\107\000\107\000\107\000\107\000\ \107\000\107\000\107\000\107\000\107\000\107\000\107\000\107\000\ \107\000\107\000\107\000\107\000\107\000\107\000\107\000\107\000\ \107\000\107\000\107\000\255\255\107\000\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \107\000\107\000\107\000\107\000\107\000\107\000\107\000\107\000\ \107\000\107\000\107\000\107\000\107\000\107\000\107\000\107\000\ \107\000\107\000\107\000\107\000\107\000\107\000\107\000\107\000\ \107\000\107\000\107\000\107\000\107\000\107\000\107\000\107\000\ \107\000\107\000\107\000\107\000\107\000\107\000\107\000\107\000\ \107\000\107\000\107\000\107\000\107\000\107\000\107\000\107\000\ \107\000\107\000\107\000\107\000\107\000\107\000\107\000\107\000\ \107\000\107\000\107\000\107\000\107\000\107\000\107\000\107\000\ \108\000\108\000\108\000\108\000\108\000\108\000\108\000\108\000\ \108\000\108\000\108\000\108\000\108\000\108\000\108\000\108\000\ \108\000\108\000\108\000\108\000\108\000\108\000\108\000\108\000\ \108\000\108\000\108\000\108\000\108\000\108\000\108\000\108\000\ \108\000\108\000\108\000\108\000\108\000\108\000\108\000\108\000\ \108\000\108\000\108\000\108\000\108\000\108\000\108\000\108\000\ \108\000\108\000\108\000\108\000\108\000\108\000\108\000\108\000\ \108\000\108\000\108\000\108\000\108\000\108\000\108\000\108\000\ \108\000\108\000\108\000\108\000\108\000\108\000\108\000\108\000\ \108\000\108\000\108\000\108\000\108\000\108\000\108\000\108\000\ \108\000\108\000\108\000\108\000\108\000\108\000\108\000\108\000\ \108\000\108\000\108\000\108\000\108\000\108\000\108\000\108\000\ \108\000\108\000\108\000\108\000\108\000\108\000\108\000\108\000\ \108\000\108\000\108\000\108\000\108\000\108\000\108\000\108\000\ \108\000\108\000\108\000\108\000\108\000\108\000\108\000\108\000\ \108\000\108\000\108\000\108\000\108\000\108\000\108\000\108\000\ \110\000\110\000\110\000\110\000\110\000\110\000\110\000\110\000\ \110\000\110\000\110\000\110\000\110\000\110\000\110\000\110\000\ \110\000\110\000\110\000\110\000\110\000\110\000\110\000\110\000\ \110\000\110\000\110\000\110\000\110\000\110\000\110\000\110\000\ \110\000\110\000\110\000\110\000\110\000\110\000\110\000\110\000\ \110\000\110\000\110\000\110\000\110\000\110\000\110\000\110\000\ \110\000\110\000\110\000\110\000\110\000\110\000\110\000\110\000\ \110\000\110\000\110\000\110\000\110\000\110\000\110\000\110\000\ \110\000\110\000\110\000\110\000\110\000\110\000\110\000\110\000\ \110\000\110\000\110\000\110\000\110\000\110\000\110\000\110\000\ \110\000\110\000\110\000\110\000\110\000\110\000\110\000\110\000\ \110\000\110\000\110\000\110\000\110\000\110\000\110\000\110\000\ \110\000\110\000\110\000\110\000\110\000\110\000\110\000\110\000\ \110\000\110\000\110\000\110\000\110\000\110\000\110\000\110\000\ \110\000\110\000\110\000\110\000\110\000\110\000\110\000\110\000\ \110\000\110\000\110\000\110\000\110\000\110\000\110\000\110\000\ \108\000\255\255\111\000\111\000\111\000\111\000\111\000\111\000\ \111\000\111\000\111\000\111\000\111\000\111\000\111\000\111\000\ \111\000\111\000\111\000\111\000\111\000\111\000\111\000\111\000\ \111\000\111\000\111\000\111\000\255\255\255\255\255\255\255\255\ \111\000\255\255\111\000\111\000\111\000\111\000\111\000\111\000\ \111\000\111\000\111\000\111\000\111\000\111\000\111\000\111\000\ \111\000\111\000\111\000\111\000\111\000\111\000\111\000\111\000\ \111\000\111\000\111\000\111\000\255\255\111\000\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \110\000\111\000\111\000\111\000\111\000\111\000\111\000\111\000\ \111\000\111\000\111\000\111\000\111\000\111\000\111\000\111\000\ \111\000\111\000\111\000\111\000\111\000\111\000\111\000\111\000\ \111\000\111\000\111\000\111\000\111\000\111\000\111\000\111\000\ \111\000\111\000\111\000\111\000\111\000\111\000\111\000\111\000\ \111\000\111\000\111\000\111\000\111\000\111\000\111\000\111\000\ \111\000\111\000\111\000\111\000\111\000\111\000\111\000\111\000\ \111\000\111\000\111\000\111\000\111\000\111\000\111\000\111\000\ \111\000\112\000\112\000\112\000\112\000\112\000\112\000\112\000\ \112\000\112\000\112\000\112\000\112\000\112\000\112\000\112\000\ \112\000\112\000\112\000\112\000\112\000\112\000\112\000\112\000\ \112\000\112\000\112\000\112\000\112\000\112\000\112\000\112\000\ \112\000\112\000\112\000\112\000\112\000\112\000\112\000\112\000\ \255\255\112\000\112\000\112\000\112\000\112\000\112\000\112\000\ \112\000\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\112\000\112\000\112\000\112\000\112\000\ \112\000\112\000\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\112\000\112\000\112\000\112\000\ \255\255\112\000\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\112\000\112\000\112\000\112\000\ \112\000\112\000\112\000\112\000\112\000\112\000\112\000\112\000\ \112\000\112\000\112\000\112\000\112\000\112\000\112\000\112\000\ \112\000\112\000\112\000\112\000\112\000\112\000\112\000\112\000\ \112\000\112\000\112\000\112\000\112\000\112\000\112\000\112\000\ \112\000\112\000\112\000\112\000\112\000\112\000\112\000\112\000\ \112\000\112\000\112\000\112\000\112\000\112\000\112\000\112\000\ \112\000\112\000\112\000\112\000\112\000\112\000\112\000\112\000\ \112\000\112\000\112\000\112\000\112\000\112\000\112\000\112\000\ \112\000\112\000\112\000\112\000\112\000\112\000\112\000\112\000\ \112\000\112\000\112\000\112\000\112\000\112\000\112\000\112\000\ \112\000\112\000\112\000\112\000\112\000\112\000\112\000\112\000\ \112\000\112\000\112\000\112\000\112\000\112\000\112\000\112\000\ \112\000\112\000\112\000\112\000\112\000\112\000\112\000\112\000\ \112\000\112\000\112\000\112\000\112\000\112\000\112\000\112\000\ \112\000\112\000\112\000\112\000\112\000\112\000\112\000\112\000\ \112\000\112\000\112\000\112\000\112\000\112\000\112\000\112\000\ \112\000\112\000\113\000\255\255\255\255\113\000\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\113\000\255\255\255\255\255\255\255\255\255\255\255\255\ \113\000\255\255\255\255\255\255\255\255\255\255\255\255\113\000\ \255\255\113\000\113\000\113\000\113\000\113\000\113\000\113\000\ \113\000\113\000\113\000\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\113\000\113\000\113\000\113\000\113\000\113\000\ \113\000\113\000\113\000\113\000\113\000\113\000\113\000\113\000\ \113\000\113\000\113\000\113\000\113\000\113\000\113\000\113\000\ \113\000\113\000\113\000\113\000\255\255\255\255\255\255\255\255\ \113\000\255\255\113\000\113\000\113\000\113\000\113\000\113\000\ \113\000\113\000\113\000\113\000\113\000\113\000\113\000\113\000\ \113\000\113\000\113\000\113\000\113\000\113\000\113\000\113\000\ \113\000\113\000\113\000\113\000\255\255\113\000\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\113\000\113\000\113\000\113\000\113\000\113\000\113\000\ \113\000\113\000\113\000\113\000\113\000\113\000\113\000\113\000\ \113\000\113\000\113\000\113\000\113\000\113\000\113\000\113\000\ \113\000\113\000\113\000\113\000\113\000\113\000\113\000\113\000\ \113\000\113\000\113\000\113\000\113\000\113\000\113\000\113\000\ \113\000\113\000\113\000\113\000\113\000\113\000\113\000\113\000\ \113\000\113\000\113\000\113\000\113\000\113\000\113\000\113\000\ \113\000\113\000\113\000\113\000\113\000\113\000\113\000\113\000\ \113\000\114\000\255\255\255\255\114\000\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \114\000\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\114\000\114\000\114\000\114\000\114\000\114\000\114\000\ \114\000\114\000\114\000\114\000\114\000\114\000\114\000\114\000\ \114\000\114\000\114\000\114\000\114\000\114\000\114\000\114\000\ \114\000\114\000\114\000\255\255\255\255\255\255\255\255\114\000\ \255\255\114\000\114\000\114\000\114\000\114\000\114\000\114\000\ \114\000\114\000\114\000\114\000\114\000\114\000\114\000\114\000\ \114\000\114\000\114\000\114\000\114\000\114\000\114\000\114\000\ \114\000\114\000\114\000\255\255\114\000\255\255\255\255\255\255\ \255\255\116\000\116\000\116\000\116\000\116\000\116\000\116\000\ \116\000\116\000\116\000\116\000\116\000\116\000\116\000\116\000\ \116\000\116\000\116\000\116\000\116\000\116\000\116\000\116\000\ \116\000\116\000\116\000\255\255\255\255\255\255\255\255\116\000\ \255\255\116\000\116\000\116\000\116\000\116\000\116\000\116\000\ \116\000\116\000\116\000\116\000\116\000\116\000\116\000\116\000\ \116\000\116\000\116\000\116\000\116\000\116\000\116\000\116\000\ \116\000\116\000\116\000\255\255\255\255\255\255\255\255\255\255\ \114\000\114\000\114\000\114\000\114\000\114\000\114\000\114\000\ \114\000\114\000\114\000\114\000\114\000\114\000\114\000\114\000\ \114\000\114\000\114\000\114\000\114\000\114\000\114\000\114\000\ \114\000\114\000\114\000\114\000\114\000\114\000\114\000\114\000\ \114\000\114\000\114\000\114\000\114\000\114\000\114\000\114\000\ \114\000\114\000\114\000\114\000\114\000\114\000\114\000\114\000\ \114\000\114\000\114\000\114\000\114\000\114\000\114\000\114\000\ \114\000\114\000\114\000\114\000\114\000\114\000\114\000\114\000\ \116\000\116\000\116\000\116\000\116\000\116\000\116\000\116\000\ \116\000\116\000\116\000\116\000\116\000\116\000\116\000\116\000\ \116\000\116\000\116\000\116\000\116\000\116\000\116\000\116\000\ \116\000\116\000\116\000\116\000\116\000\116\000\116\000\116\000\ \116\000\116\000\116\000\116\000\116\000\116\000\116\000\116\000\ \116\000\116\000\116\000\116\000\116\000\116\000\116\000\116\000\ \116\000\116\000\116\000\116\000\116\000\116\000\116\000\116\000\ \116\000\116\000\116\000\116\000\116\000\116\000\116\000\116\000\ \117\000\117\000\117\000\117\000\117\000\117\000\117\000\117\000\ \117\000\117\000\117\000\117\000\117\000\117\000\117\000\117\000\ \117\000\117\000\117\000\117\000\117\000\117\000\117\000\117\000\ \117\000\117\000\117\000\117\000\117\000\117\000\117\000\117\000\ \117\000\117\000\117\000\117\000\117\000\117\000\117\000\117\000\ \117\000\117\000\117\000\117\000\117\000\117\000\117\000\117\000\ \117\000\117\000\117\000\117\000\117\000\117\000\117\000\117\000\ \117\000\117\000\117\000\117\000\117\000\117\000\117\000\117\000\ \117\000\117\000\117\000\117\000\117\000\117\000\117\000\117\000\ \117\000\117\000\117\000\117\000\117\000\117\000\117\000\117\000\ \117\000\117\000\117\000\117\000\117\000\117\000\117\000\117\000\ \117\000\117\000\117\000\117\000\117\000\117\000\117\000\117\000\ \117\000\117\000\117\000\117\000\117\000\117\000\117\000\117\000\ \117\000\117\000\117\000\117\000\117\000\117\000\117\000\117\000\ \117\000\117\000\117\000\117\000\117\000\117\000\117\000\117\000\ \117\000\117\000\117\000\117\000\117\000\117\000\117\000\117\000\ \255\255\255\255\255\255\255\255\255\255\255\255\118\000\118\000\ \118\000\118\000\118\000\118\000\118\000\118\000\118\000\118\000\ \118\000\118\000\118\000\118\000\118\000\118\000\118\000\118\000\ \118\000\118\000\118\000\118\000\118\000\118\000\118\000\118\000\ \118\000\118\000\118\000\118\000\118\000\118\000\118\000\118\000\ \118\000\118\000\118\000\118\000\118\000\255\255\118\000\118\000\ \118\000\118\000\118\000\118\000\118\000\118\000\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \118\000\118\000\118\000\118\000\118\000\118\000\118\000\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\118\000\118\000\118\000\118\000\255\255\118\000\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \117\000\118\000\118\000\118\000\118\000\118\000\118\000\118\000\ \118\000\118\000\118\000\118\000\118\000\118\000\118\000\118\000\ \118\000\118\000\118\000\118\000\118\000\118\000\118\000\118\000\ \118\000\118\000\118\000\118\000\118\000\118\000\118\000\118\000\ \118\000\118\000\118\000\118\000\118\000\118\000\118\000\118\000\ \118\000\118\000\118\000\118\000\118\000\118\000\118\000\118\000\ \118\000\118\000\118\000\118\000\118\000\118\000\118\000\118\000\ \118\000\118\000\118\000\118\000\118\000\118\000\118\000\118\000\ \118\000\118\000\118\000\118\000\118\000\118\000\118\000\118\000\ \118\000\118\000\118\000\118\000\118\000\118\000\118\000\118\000\ \118\000\118\000\118\000\118\000\118\000\118\000\118\000\118\000\ \118\000\118\000\118\000\118\000\118\000\118\000\118\000\118\000\ \118\000\118\000\118\000\118\000\118\000\118\000\118\000\118\000\ \118\000\118\000\118\000\118\000\118\000\118\000\118\000\118\000\ \118\000\118\000\118\000\118\000\118\000\118\000\118\000\118\000\ \118\000\118\000\118\000\118\000\118\000\118\000\118\000\118\000\ \118\000\118\000\118\000\118\000\118\000\118\000\118\000\119\000\ \255\255\255\255\119\000\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\119\000\255\255\ \255\255\255\255\255\255\255\255\255\255\119\000\255\255\255\255\ \255\255\255\255\255\255\255\255\119\000\255\255\119\000\119\000\ \119\000\119\000\119\000\119\000\119\000\119\000\119\000\119\000\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\119\000\ \119\000\119\000\119\000\119\000\119\000\119\000\119\000\119\000\ \119\000\119\000\119\000\119\000\119\000\119\000\119\000\119\000\ \119\000\119\000\119\000\119\000\119\000\119\000\119\000\119\000\ \119\000\255\255\255\255\255\255\255\255\119\000\255\255\119\000\ \119\000\119\000\119\000\119\000\119\000\119\000\119\000\119\000\ \119\000\119\000\119\000\119\000\119\000\119\000\119\000\119\000\ \119\000\119\000\119\000\119\000\119\000\119\000\119\000\119\000\ \119\000\255\255\119\000\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\119\000\119\000\ \119\000\119\000\119\000\119\000\119\000\119\000\119\000\119\000\ \119\000\119\000\119\000\119\000\119\000\119\000\119\000\119\000\ \119\000\119\000\119\000\119\000\119\000\119\000\119\000\119\000\ \119\000\119\000\119\000\119\000\119\000\119\000\119\000\119\000\ \119\000\119\000\119\000\119\000\119\000\119\000\119\000\119\000\ \119\000\119\000\119\000\119\000\119\000\119\000\119\000\119\000\ \119\000\119\000\119\000\119\000\119\000\119\000\119\000\119\000\ \119\000\119\000\119\000\119\000\119\000\119\000\120\000\120\000\ \120\000\120\000\120\000\120\000\120\000\120\000\120\000\120\000\ \120\000\120\000\120\000\120\000\120\000\120\000\120\000\120\000\ \120\000\120\000\120\000\120\000\120\000\120\000\120\000\120\000\ \120\000\120\000\120\000\120\000\120\000\120\000\120\000\120\000\ \120\000\120\000\120\000\120\000\120\000\120\000\120\000\120\000\ \120\000\120\000\120\000\120\000\120\000\120\000\120\000\120\000\ \120\000\120\000\120\000\120\000\120\000\120\000\120\000\120\000\ \120\000\120\000\120\000\120\000\120\000\120\000\120\000\120\000\ \120\000\120\000\120\000\120\000\120\000\120\000\120\000\120\000\ \120\000\120\000\120\000\120\000\120\000\120\000\120\000\120\000\ \120\000\120\000\120\000\120\000\120\000\120\000\120\000\120\000\ \120\000\120\000\120\000\120\000\120\000\120\000\120\000\120\000\ \120\000\120\000\120\000\120\000\120\000\120\000\120\000\120\000\ \120\000\120\000\120\000\120\000\120\000\120\000\120\000\120\000\ \120\000\120\000\120\000\120\000\120\000\120\000\120\000\120\000\ \120\000\120\000\120\000\120\000\120\000\120\000\122\000\122\000\ \122\000\122\000\122\000\122\000\122\000\122\000\122\000\122\000\ \122\000\122\000\122\000\122\000\122\000\122\000\122\000\122\000\ \122\000\122\000\122\000\122\000\122\000\122\000\122\000\122\000\ \122\000\122\000\122\000\122\000\122\000\122\000\122\000\122\000\ \122\000\122\000\122\000\122\000\122\000\122\000\122\000\122\000\ \122\000\122\000\122\000\122\000\122\000\122\000\122\000\122\000\ \122\000\122\000\122\000\122\000\122\000\122\000\122\000\122\000\ \122\000\122\000\122\000\122\000\122\000\122\000\122\000\122\000\ \122\000\122\000\122\000\122\000\122\000\122\000\122\000\122\000\ \122\000\122\000\122\000\122\000\122\000\122\000\122\000\122\000\ \122\000\122\000\122\000\122\000\122\000\122\000\122\000\122\000\ \122\000\122\000\122\000\122\000\122\000\122\000\122\000\122\000\ \122\000\122\000\122\000\122\000\122\000\122\000\122\000\122\000\ \122\000\122\000\122\000\122\000\122\000\122\000\122\000\122\000\ \122\000\122\000\122\000\122\000\122\000\122\000\122\000\122\000\ \122\000\122\000\122\000\122\000\122\000\122\000\120\000\255\255\ \123\000\123\000\123\000\123\000\123\000\123\000\123\000\123\000\ \123\000\123\000\123\000\123\000\123\000\123\000\123\000\123\000\ \123\000\123\000\123\000\123\000\123\000\123\000\123\000\123\000\ \123\000\123\000\255\255\255\255\255\255\255\255\123\000\255\255\ \123\000\123\000\123\000\123\000\123\000\123\000\123\000\123\000\ \123\000\123\000\123\000\123\000\123\000\123\000\123\000\123\000\ \123\000\123\000\123\000\123\000\123\000\123\000\123\000\123\000\ \123\000\123\000\255\255\123\000\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\122\000\123\000\ \123\000\123\000\123\000\123\000\123\000\123\000\123\000\123\000\ \123\000\123\000\123\000\123\000\123\000\123\000\123\000\123\000\ \123\000\123\000\123\000\123\000\123\000\123\000\123\000\123\000\ \123\000\123\000\123\000\123\000\123\000\123\000\123\000\123\000\ \123\000\123\000\123\000\123\000\123\000\123\000\123\000\123\000\ \123\000\123\000\123\000\123\000\123\000\123\000\123\000\123\000\ \123\000\123\000\123\000\123\000\123\000\123\000\123\000\123\000\ \123\000\123\000\123\000\123\000\123\000\123\000\123\000\125\000\ \152\000\125\000\125\000\152\000\152\000\152\000\125\000\255\255\ \255\255\152\000\152\000\255\255\152\000\152\000\152\000\125\000\ \125\000\125\000\125\000\125\000\125\000\125\000\125\000\125\000\ \125\000\152\000\255\255\152\000\152\000\152\000\152\000\152\000\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\154\000\ \255\255\154\000\154\000\154\000\154\000\255\255\255\255\255\255\ \154\000\154\000\255\255\154\000\154\000\154\000\255\255\255\255\ \255\255\255\255\255\255\125\000\255\255\152\000\255\255\255\255\ \154\000\125\000\154\000\154\000\154\000\154\000\154\000\255\255\ \255\255\255\255\255\255\255\255\255\255\125\000\125\000\255\255\ \255\255\125\000\255\255\125\000\255\255\155\000\255\255\125\000\ \155\000\155\000\155\000\152\000\255\255\152\000\155\000\155\000\ \255\255\155\000\155\000\155\000\154\000\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\155\000\255\255\ \155\000\155\000\155\000\155\000\155\000\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\156\000\255\255\255\255\156\000\ \156\000\156\000\154\000\255\255\154\000\156\000\156\000\255\255\ \156\000\156\000\156\000\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\155\000\255\255\255\255\156\000\255\255\156\000\ \156\000\156\000\156\000\156\000\255\255\255\255\255\255\157\000\ \255\255\255\255\157\000\157\000\157\000\255\255\255\255\255\255\ \157\000\157\000\255\255\157\000\157\000\157\000\255\255\255\255\ \155\000\255\255\155\000\255\255\255\255\255\255\255\255\255\255\ \157\000\156\000\157\000\157\000\157\000\157\000\157\000\255\255\ \255\255\255\255\255\255\255\255\255\255\158\000\255\255\255\255\ \158\000\158\000\158\000\255\255\255\255\255\255\158\000\158\000\ \255\255\158\000\158\000\158\000\255\255\255\255\255\255\156\000\ \255\255\156\000\255\255\255\255\157\000\255\255\158\000\125\000\ \158\000\158\000\158\000\158\000\158\000\255\255\255\255\255\255\ \163\000\255\255\255\255\163\000\163\000\163\000\255\255\255\255\ \255\255\163\000\163\000\255\255\163\000\163\000\163\000\255\255\ \255\255\255\255\157\000\255\255\157\000\255\255\255\255\255\255\ \255\255\163\000\158\000\163\000\163\000\163\000\163\000\163\000\ \255\255\255\255\255\255\173\000\255\255\255\255\173\000\173\000\ \173\000\255\255\255\255\255\255\173\000\173\000\255\255\173\000\ \173\000\173\000\255\255\255\255\255\255\255\255\255\255\255\255\ \158\000\255\255\158\000\255\255\173\000\163\000\173\000\173\000\ \173\000\173\000\173\000\255\255\255\255\255\255\176\000\255\255\ \176\000\176\000\176\000\176\000\255\255\255\255\255\255\176\000\ \176\000\255\255\176\000\176\000\176\000\255\255\255\255\255\255\ \255\255\255\255\255\255\163\000\255\255\163\000\255\255\176\000\ \173\000\176\000\176\000\176\000\176\000\176\000\255\255\255\255\ \255\255\177\000\255\255\177\000\177\000\177\000\177\000\255\255\ \255\255\255\255\177\000\177\000\255\255\177\000\177\000\177\000\ \255\255\255\255\255\255\255\255\255\255\255\255\173\000\255\255\ \173\000\255\255\177\000\176\000\177\000\177\000\177\000\177\000\ \177\000\255\255\255\255\255\255\178\000\255\255\255\255\178\000\ \178\000\178\000\255\255\255\255\255\255\178\000\178\000\255\255\ \178\000\178\000\178\000\255\255\255\255\255\255\255\255\255\255\ \255\255\176\000\255\255\176\000\255\255\178\000\177\000\178\000\ \178\000\178\000\178\000\178\000\255\255\255\255\255\255\179\000\ \255\255\255\255\179\000\179\000\179\000\255\255\255\255\255\255\ \179\000\179\000\255\255\179\000\179\000\179\000\255\255\255\255\ \255\255\255\255\255\255\255\255\177\000\255\255\177\000\255\255\ \179\000\178\000\179\000\179\000\179\000\179\000\179\000\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\185\000\255\255\ \255\255\185\000\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\178\000\ \255\255\178\000\255\255\255\255\179\000\255\255\185\000\255\255\ \255\255\255\255\255\255\185\000\185\000\255\255\185\000\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\179\000\255\255\179\000\185\000\185\000\185\000\ \185\000\185\000\185\000\185\000\185\000\185\000\185\000\185\000\ \185\000\185\000\185\000\185\000\185\000\185\000\185\000\185\000\ \185\000\185\000\185\000\185\000\185\000\185\000\185\000\255\255\ \255\255\255\255\255\255\185\000\255\255\185\000\185\000\185\000\ \185\000\185\000\185\000\185\000\185\000\185\000\185\000\185\000\ \185\000\185\000\185\000\185\000\185\000\185\000\185\000\185\000\ \185\000\185\000\185\000\185\000\185\000\185\000\185\000\185\000\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\185\000\185\000\185\000\185\000\ \185\000\185\000\185\000\185\000\185\000\185\000\185\000\185\000\ \185\000\185\000\185\000\185\000\185\000\185\000\185\000\185\000\ \185\000\185\000\185\000\185\000\185\000\185\000\185\000\185\000\ \185\000\185\000\185\000\185\000\185\000\185\000\185\000\185\000\ \185\000\185\000\185\000\185\000\185\000\185\000\185\000\185\000\ \185\000\185\000\185\000\185\000\185\000\185\000\185\000\185\000\ \185\000\185\000\185\000\185\000\185\000\185\000\185\000\185\000\ \185\000\185\000\185\000\185\000\185\000\187\000\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\187\000\187\000\ \187\000\187\000\187\000\187\000\187\000\187\000\187\000\187\000\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\187\000\ \187\000\187\000\187\000\187\000\187\000\187\000\187\000\187\000\ \187\000\187\000\187\000\187\000\187\000\187\000\187\000\187\000\ \187\000\187\000\187\000\187\000\187\000\187\000\187\000\187\000\ \187\000\255\255\255\255\255\255\255\255\187\000\255\255\187\000\ \187\000\187\000\187\000\187\000\187\000\187\000\187\000\187\000\ \187\000\187\000\187\000\187\000\187\000\187\000\187\000\187\000\ \187\000\187\000\187\000\187\000\187\000\187\000\187\000\187\000\ \187\000\255\255\255\255\255\255\255\255\255\255\187\000\187\000\ \187\000\187\000\187\000\187\000\187\000\187\000\187\000\187\000\ \187\000\187\000\187\000\187\000\187\000\187\000\187\000\187\000\ \187\000\187\000\187\000\187\000\187\000\187\000\187\000\187\000\ \187\000\187\000\187\000\187\000\187\000\187\000\187\000\187\000\ \187\000\187\000\187\000\187\000\187\000\187\000\187\000\187\000\ \187\000\187\000\187\000\187\000\187\000\187\000\187\000\187\000\ \187\000\187\000\187\000\187\000\187\000\187\000\187\000\187\000\ \187\000\187\000\187\000\187\000\187\000\187\000\187\000\187\000\ \187\000\187\000\187\000\187\000\187\000\187\000\187\000\187\000\ \187\000\187\000\187\000\187\000\187\000\187\000\187\000\187\000\ \187\000\187\000\187\000\187\000\187\000\187\000\187\000\187\000\ \187\000\187\000\187\000\187\000\187\000\187\000\187\000\187\000\ \187\000\187\000\187\000\187\000\187\000\187\000\187\000\187\000\ \187\000\187\000\187\000\187\000\187\000\187\000\187\000\187\000\ \187\000\187\000\187\000\187\000\187\000\187\000\187\000\187\000\ \187\000\187\000\187\000\187\000\187\000\187\000\188\000\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\188\000\ \188\000\188\000\188\000\188\000\188\000\188\000\188\000\188\000\ \188\000\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \188\000\188\000\188\000\188\000\188\000\188\000\188\000\188\000\ \188\000\188\000\188\000\188\000\188\000\188\000\188\000\188\000\ \188\000\188\000\188\000\188\000\188\000\188\000\188\000\188\000\ \188\000\188\000\255\255\255\255\255\255\255\255\188\000\255\255\ \188\000\188\000\188\000\188\000\188\000\188\000\188\000\188\000\ \188\000\188\000\188\000\188\000\188\000\188\000\188\000\188\000\ \188\000\188\000\188\000\188\000\188\000\188\000\188\000\188\000\ \188\000\188\000\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\188\000\ \188\000\188\000\188\000\188\000\188\000\188\000\188\000\188\000\ \188\000\188\000\188\000\188\000\188\000\188\000\188\000\188\000\ \188\000\188\000\188\000\188\000\188\000\188\000\188\000\188\000\ \188\000\188\000\188\000\188\000\188\000\188\000\188\000\188\000\ \188\000\188\000\188\000\188\000\188\000\188\000\188\000\188\000\ \188\000\188\000\188\000\188\000\188\000\188\000\188\000\188\000\ \188\000\188\000\188\000\188\000\188\000\188\000\188\000\188\000\ \188\000\188\000\188\000\188\000\188\000\188\000\188\000\193\000\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\193\000\193\000\193\000\193\000\193\000\ \193\000\193\000\193\000\193\000\193\000\193\000\193\000\193\000\ \193\000\193\000\193\000\193\000\193\000\193\000\193\000\193\000\ \193\000\193\000\193\000\193\000\193\000\255\255\255\255\255\255\ \255\255\193\000\255\255\193\000\193\000\193\000\193\000\193\000\ \193\000\193\000\193\000\193\000\193\000\193\000\193\000\193\000\ \193\000\193\000\193\000\193\000\193\000\193\000\193\000\193\000\ \193\000\193\000\193\000\193\000\193\000\255\255\193\000\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\193\000\193\000\193\000\193\000\193\000\193\000\ \193\000\193\000\193\000\193\000\193\000\193\000\193\000\193\000\ \193\000\193\000\193\000\193\000\193\000\193\000\193\000\193\000\ \193\000\193\000\193\000\193\000\193\000\193\000\193\000\193\000\ \193\000\193\000\193\000\193\000\193\000\193\000\193\000\193\000\ \193\000\193\000\193\000\193\000\193\000\193\000\193\000\193\000\ \193\000\193\000\193\000\193\000\193\000\193\000\193\000\193\000\ \193\000\193\000\193\000\193\000\193\000\193\000\193\000\193\000\ \193\000\193\000\200\000\200\000\200\000\200\000\200\000\200\000\ \200\000\200\000\200\000\200\000\200\000\200\000\200\000\200\000\ \200\000\200\000\200\000\200\000\200\000\200\000\200\000\200\000\ \200\000\200\000\200\000\200\000\200\000\200\000\200\000\200\000\ \200\000\200\000\200\000\200\000\200\000\200\000\200\000\200\000\ \200\000\200\000\200\000\200\000\200\000\200\000\200\000\200\000\ \200\000\200\000\200\000\200\000\200\000\200\000\200\000\200\000\ \200\000\200\000\200\000\200\000\200\000\200\000\200\000\200\000\ \200\000\200\000\200\000\200\000\200\000\200\000\200\000\200\000\ \200\000\200\000\200\000\200\000\200\000\200\000\200\000\200\000\ \200\000\200\000\200\000\200\000\200\000\200\000\200\000\200\000\ \200\000\200\000\200\000\200\000\200\000\200\000\200\000\200\000\ \200\000\200\000\200\000\200\000\200\000\200\000\200\000\200\000\ \200\000\200\000\200\000\200\000\200\000\200\000\200\000\200\000\ \200\000\200\000\200\000\200\000\200\000\200\000\200\000\200\000\ \200\000\200\000\200\000\200\000\200\000\200\000\200\000\200\000\ \200\000\200\000\255\255\255\255\201\000\201\000\201\000\201\000\ \201\000\201\000\201\000\201\000\201\000\201\000\201\000\201\000\ \201\000\201\000\201\000\201\000\201\000\201\000\201\000\201\000\ \201\000\201\000\201\000\201\000\201\000\201\000\255\255\255\255\ \255\255\255\255\201\000\255\255\201\000\201\000\201\000\201\000\ \201\000\201\000\201\000\201\000\201\000\201\000\201\000\201\000\ \201\000\201\000\201\000\201\000\201\000\201\000\201\000\201\000\ \201\000\201\000\201\000\201\000\201\000\201\000\255\255\201\000\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\200\000\201\000\201\000\201\000\201\000\201\000\ \201\000\201\000\201\000\201\000\201\000\201\000\201\000\201\000\ \201\000\201\000\201\000\201\000\201\000\201\000\201\000\201\000\ \201\000\201\000\201\000\201\000\201\000\201\000\201\000\201\000\ \201\000\201\000\201\000\201\000\201\000\201\000\201\000\201\000\ \201\000\201\000\201\000\201\000\201\000\201\000\201\000\201\000\ \201\000\201\000\201\000\201\000\201\000\201\000\201\000\201\000\ \201\000\201\000\201\000\201\000\201\000\201\000\201\000\201\000\ \201\000\201\000\201\000\202\000\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\202\000\ \202\000\202\000\202\000\202\000\202\000\202\000\202\000\202\000\ \202\000\202\000\202\000\202\000\202\000\202\000\202\000\202\000\ \202\000\202\000\202\000\202\000\202\000\202\000\202\000\202\000\ \202\000\255\255\255\255\255\255\255\255\202\000\255\255\202\000\ \202\000\202\000\202\000\202\000\202\000\202\000\202\000\202\000\ \202\000\202\000\202\000\202\000\202\000\202\000\202\000\202\000\ \202\000\202\000\202\000\202\000\202\000\202\000\202\000\202\000\ \202\000\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\202\000\202\000\ \202\000\202\000\202\000\202\000\202\000\202\000\202\000\202\000\ \202\000\202\000\202\000\202\000\202\000\202\000\202\000\202\000\ \202\000\202\000\202\000\202\000\202\000\202\000\202\000\202\000\ \202\000\202\000\202\000\202\000\202\000\202\000\202\000\202\000\ \202\000\202\000\202\000\202\000\202\000\202\000\202\000\202\000\ \202\000\202\000\202\000\202\000\202\000\202\000\202\000\202\000\ \202\000\202\000\202\000\202\000\202\000\202\000\202\000\202\000\ \202\000\202\000\202\000\202\000\202\000\202\000\203\000\203\000\ \203\000\203\000\203\000\203\000\203\000\203\000\203\000\203\000\ \203\000\203\000\203\000\203\000\203\000\203\000\203\000\203\000\ \203\000\203\000\203\000\203\000\203\000\203\000\203\000\203\000\ \203\000\203\000\203\000\203\000\203\000\203\000\203\000\203\000\ \203\000\203\000\203\000\203\000\203\000\255\255\203\000\203\000\ \203\000\203\000\203\000\203\000\203\000\203\000\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \203\000\203\000\203\000\203\000\203\000\203\000\203\000\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\203\000\203\000\203\000\203\000\255\255\203\000\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\203\000\203\000\203\000\203\000\203\000\203\000\203\000\ \203\000\203\000\203\000\203\000\203\000\203\000\203\000\203\000\ \203\000\203\000\203\000\203\000\203\000\203\000\203\000\203\000\ \203\000\203\000\203\000\203\000\203\000\203\000\203\000\203\000\ \203\000\203\000\203\000\203\000\203\000\203\000\203\000\203\000\ \203\000\203\000\203\000\203\000\203\000\203\000\203\000\203\000\ \203\000\203\000\203\000\203\000\203\000\203\000\203\000\203\000\ \203\000\203\000\203\000\203\000\203\000\203\000\203\000\203\000\ \203\000\203\000\203\000\203\000\203\000\203\000\203\000\203\000\ \203\000\203\000\203\000\203\000\203\000\203\000\203\000\203\000\ \203\000\203\000\203\000\203\000\203\000\203\000\203\000\203\000\ \203\000\203\000\203\000\203\000\203\000\203\000\203\000\203\000\ \203\000\203\000\203\000\203\000\203\000\203\000\203\000\203\000\ \203\000\203\000\203\000\203\000\203\000\203\000\203\000\203\000\ \203\000\203\000\203\000\203\000\203\000\203\000\203\000\203\000\ \203\000\203\000\203\000\203\000\203\000\203\000\203\000\203\000\ \203\000\203\000\203\000\203\000\203\000\203\000\203\000\204\000\ \255\255\255\255\204\000\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\204\000\255\255\ \255\255\255\255\255\255\255\255\255\255\204\000\255\255\255\255\ \255\255\255\255\255\255\255\255\204\000\255\255\204\000\204\000\ \204\000\204\000\204\000\204\000\204\000\204\000\204\000\204\000\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\204\000\ \204\000\204\000\204\000\204\000\204\000\204\000\204\000\204\000\ \204\000\204\000\204\000\204\000\204\000\204\000\204\000\204\000\ \204\000\204\000\204\000\204\000\204\000\204\000\204\000\204\000\ \204\000\255\255\255\255\255\255\255\255\204\000\255\255\204\000\ \204\000\204\000\204\000\204\000\204\000\204\000\204\000\204\000\ \204\000\204\000\204\000\204\000\204\000\204\000\204\000\204\000\ \204\000\204\000\204\000\204\000\204\000\204\000\204\000\204\000\ \204\000\255\255\204\000\255\255\255\255\255\255\255\255\205\000\ \205\000\205\000\205\000\205\000\205\000\205\000\205\000\205\000\ \205\000\205\000\205\000\205\000\205\000\205\000\205\000\205\000\ \205\000\205\000\205\000\205\000\205\000\205\000\205\000\205\000\ \205\000\255\255\255\255\255\255\255\255\205\000\255\255\205\000\ \205\000\205\000\205\000\205\000\205\000\205\000\205\000\205\000\ \205\000\205\000\205\000\205\000\205\000\205\000\205\000\205\000\ \205\000\205\000\205\000\205\000\205\000\205\000\205\000\205\000\ \205\000\255\255\255\255\255\255\255\255\255\255\204\000\204\000\ \204\000\204\000\204\000\204\000\204\000\204\000\204\000\204\000\ \204\000\204\000\204\000\204\000\204\000\204\000\204\000\204\000\ \204\000\204\000\204\000\204\000\204\000\204\000\204\000\204\000\ \204\000\204\000\204\000\204\000\204\000\204\000\204\000\204\000\ \204\000\204\000\204\000\204\000\204\000\204\000\204\000\204\000\ \204\000\204\000\204\000\204\000\204\000\204\000\204\000\204\000\ \204\000\204\000\204\000\204\000\204\000\204\000\204\000\204\000\ \204\000\204\000\204\000\204\000\204\000\204\000\205\000\205\000\ \205\000\205\000\205\000\205\000\205\000\205\000\205\000\205\000\ \205\000\205\000\205\000\205\000\205\000\205\000\205\000\205\000\ \205\000\205\000\205\000\205\000\205\000\205\000\205\000\205\000\ \205\000\205\000\205\000\205\000\205\000\205\000\205\000\205\000\ \205\000\205\000\205\000\205\000\205\000\205\000\205\000\205\000\ \205\000\205\000\205\000\205\000\205\000\205\000\205\000\205\000\ \205\000\205\000\205\000\205\000\205\000\205\000\205\000\205\000\ \205\000\205\000\205\000\205\000\205\000\205\000\206\000\255\255\ \255\255\206\000\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\206\000\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\206\000\206\000\ \206\000\206\000\206\000\206\000\206\000\206\000\206\000\206\000\ \206\000\206\000\206\000\206\000\206\000\206\000\206\000\206\000\ \206\000\206\000\206\000\206\000\206\000\206\000\206\000\206\000\ \255\255\255\255\255\255\255\255\206\000\255\255\206\000\206\000\ \206\000\206\000\206\000\206\000\206\000\206\000\206\000\206\000\ \206\000\206\000\206\000\206\000\206\000\206\000\206\000\206\000\ \206\000\206\000\206\000\206\000\206\000\206\000\206\000\206\000\ \255\255\206\000\255\255\255\255\255\255\255\255\207\000\207\000\ \207\000\207\000\207\000\207\000\207\000\207\000\207\000\207\000\ \207\000\207\000\207\000\207\000\207\000\207\000\207\000\207\000\ \207\000\207\000\207\000\207\000\207\000\207\000\207\000\207\000\ \255\255\255\255\255\255\255\255\207\000\255\255\207\000\207\000\ \207\000\207\000\207\000\207\000\207\000\207\000\207\000\207\000\ \207\000\207\000\207\000\207\000\207\000\207\000\207\000\207\000\ \207\000\207\000\207\000\207\000\207\000\207\000\207\000\207\000\ \255\255\255\255\255\255\255\255\255\255\206\000\206\000\206\000\ \206\000\206\000\206\000\206\000\206\000\206\000\206\000\206\000\ \206\000\206\000\206\000\206\000\206\000\206\000\206\000\206\000\ \206\000\206\000\206\000\206\000\206\000\206\000\206\000\206\000\ \206\000\206\000\206\000\206\000\206\000\206\000\206\000\206\000\ \206\000\206\000\206\000\206\000\206\000\206\000\206\000\206\000\ \206\000\206\000\206\000\206\000\206\000\206\000\206\000\206\000\ \206\000\206\000\206\000\206\000\206\000\206\000\206\000\206\000\ \206\000\206\000\206\000\206\000\206\000\207\000\207\000\207\000\ \207\000\207\000\207\000\207\000\207\000\207\000\207\000\207\000\ \207\000\207\000\207\000\207\000\207\000\207\000\207\000\207\000\ \207\000\207\000\207\000\207\000\207\000\207\000\207\000\207\000\ \207\000\207\000\207\000\207\000\207\000\207\000\207\000\207\000\ \207\000\207\000\207\000\207\000\207\000\207\000\207\000\207\000\ \207\000\207\000\207\000\207\000\207\000\207\000\207\000\207\000\ \207\000\207\000\207\000\207\000\207\000\207\000\207\000\207\000\ \207\000\207\000\207\000\207\000\207\000\208\000\208\000\208\000\ \208\000\208\000\208\000\208\000\208\000\208\000\208\000\208\000\ \208\000\208\000\208\000\208\000\208\000\208\000\208\000\208\000\ \208\000\208\000\208\000\208\000\208\000\208\000\208\000\208\000\ \208\000\208\000\208\000\208\000\208\000\208\000\208\000\208\000\ \208\000\208\000\208\000\208\000\208\000\208\000\208\000\208\000\ \208\000\208\000\208\000\208\000\208\000\208\000\208\000\208\000\ \208\000\208\000\208\000\208\000\208\000\208\000\208\000\208\000\ \208\000\208\000\208\000\208\000\208\000\208\000\208\000\208\000\ \208\000\208\000\208\000\208\000\208\000\208\000\208\000\208\000\ \208\000\208\000\208\000\208\000\208\000\208\000\208\000\208\000\ \208\000\208\000\208\000\208\000\208\000\208\000\208\000\208\000\ \208\000\208\000\208\000\208\000\208\000\208\000\208\000\208\000\ \208\000\208\000\208\000\208\000\208\000\208\000\208\000\208\000\ \208\000\208\000\208\000\208\000\208\000\208\000\208\000\208\000\ \208\000\208\000\208\000\208\000\208\000\208\000\208\000\208\000\ \208\000\208\000\208\000\208\000\208\000\255\255\255\255\255\255\ \255\255\255\255\255\255\209\000\209\000\209\000\209\000\209\000\ \209\000\209\000\209\000\209\000\209\000\209\000\209\000\209\000\ \209\000\209\000\209\000\209\000\209\000\209\000\209\000\209\000\ \209\000\209\000\209\000\209\000\209\000\209\000\209\000\209\000\ \209\000\209\000\209\000\209\000\209\000\209\000\209\000\209\000\ \209\000\209\000\255\255\209\000\209\000\209\000\209\000\209\000\ \209\000\209\000\209\000\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\209\000\209\000\209\000\ \209\000\209\000\209\000\209\000\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\209\000\209\000\ \209\000\209\000\255\255\209\000\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\208\000\209\000\209\000\ \209\000\209\000\209\000\209\000\209\000\209\000\209\000\209\000\ \209\000\209\000\209\000\209\000\209\000\209\000\209\000\209\000\ \209\000\209\000\209\000\209\000\209\000\209\000\209\000\209\000\ \209\000\209\000\209\000\209\000\209\000\209\000\209\000\209\000\ \209\000\209\000\209\000\209\000\209\000\209\000\209\000\209\000\ \209\000\209\000\209\000\209\000\209\000\209\000\209\000\209\000\ \209\000\209\000\209\000\209\000\209\000\209\000\209\000\209\000\ \209\000\209\000\209\000\209\000\209\000\209\000\209\000\209\000\ \209\000\209\000\209\000\209\000\209\000\209\000\209\000\209\000\ \209\000\209\000\209\000\209\000\209\000\209\000\209\000\209\000\ \209\000\209\000\209\000\209\000\209\000\209\000\209\000\209\000\ \209\000\209\000\209\000\209\000\209\000\209\000\209\000\209\000\ \209\000\209\000\209\000\209\000\209\000\209\000\209\000\209\000\ \209\000\209\000\209\000\209\000\209\000\209\000\209\000\209\000\ \209\000\209\000\209\000\209\000\209\000\209\000\209\000\209\000\ \209\000\209\000\209\000\209\000\209\000\209\000\209\000\209\000\ \209\000\209\000\209\000\209\000\210\000\255\255\255\255\210\000\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\210\000\255\255\255\255\255\255\255\255\ \255\255\255\255\210\000\255\255\255\255\255\255\255\255\255\255\ \255\255\210\000\255\255\210\000\210\000\210\000\210\000\210\000\ \210\000\210\000\210\000\210\000\210\000\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\210\000\210\000\210\000\210\000\ \210\000\210\000\210\000\210\000\210\000\210\000\210\000\210\000\ \210\000\210\000\210\000\210\000\210\000\210\000\210\000\210\000\ \210\000\210\000\210\000\210\000\210\000\210\000\255\255\255\255\ \255\255\255\255\210\000\255\255\210\000\210\000\210\000\210\000\ \210\000\210\000\210\000\210\000\210\000\210\000\210\000\210\000\ \210\000\210\000\210\000\210\000\210\000\210\000\210\000\210\000\ \210\000\210\000\210\000\210\000\210\000\210\000\255\255\210\000\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\210\000\210\000\210\000\210\000\210\000\ \210\000\210\000\210\000\210\000\210\000\210\000\210\000\210\000\ \210\000\210\000\210\000\210\000\210\000\210\000\210\000\210\000\ \210\000\210\000\210\000\210\000\210\000\210\000\210\000\210\000\ \210\000\210\000\210\000\210\000\210\000\210\000\210\000\210\000\ \210\000\210\000\210\000\210\000\210\000\210\000\210\000\210\000\ \210\000\210\000\210\000\210\000\210\000\210\000\210\000\210\000\ \210\000\210\000\210\000\210\000\210\000\210\000\210\000\210\000\ \210\000\210\000\210\000\211\000\211\000\211\000\211\000\211\000\ \211\000\211\000\211\000\211\000\211\000\211\000\211\000\211\000\ \211\000\211\000\211\000\211\000\211\000\211\000\211\000\211\000\ \211\000\211\000\211\000\211\000\211\000\211\000\211\000\211\000\ \211\000\211\000\211\000\211\000\211\000\211\000\211\000\211\000\ \211\000\211\000\211\000\211\000\211\000\211\000\211\000\211\000\ \211\000\211\000\211\000\211\000\211\000\211\000\211\000\211\000\ \211\000\211\000\211\000\211\000\211\000\211\000\211\000\211\000\ \211\000\211\000\211\000\211\000\211\000\211\000\211\000\211\000\ \211\000\211\000\211\000\211\000\211\000\211\000\211\000\211\000\ \211\000\211\000\211\000\211\000\211\000\211\000\211\000\211\000\ \211\000\211\000\211\000\211\000\211\000\211\000\211\000\211\000\ \211\000\211\000\211\000\211\000\211\000\211\000\211\000\211\000\ \211\000\211\000\211\000\211\000\211\000\211\000\211\000\211\000\ \211\000\211\000\211\000\211\000\211\000\211\000\211\000\211\000\ \211\000\211\000\211\000\211\000\211\000\211\000\211\000\211\000\ \211\000\211\000\211\000\212\000\255\255\212\000\255\255\255\255\ \255\255\255\255\212\000\255\255\255\255\255\255\241\000\255\255\ \255\255\241\000\255\255\212\000\212\000\212\000\212\000\212\000\ \212\000\212\000\212\000\212\000\212\000\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\241\000\255\255\241\000\255\255\ \255\255\255\255\255\255\241\000\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\241\000\241\000\241\000\241\000\ \241\000\241\000\241\000\241\000\241\000\241\000\255\255\212\000\ \255\255\255\255\255\255\255\255\255\255\212\000\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\212\000\212\000\255\255\255\255\212\000\255\255\212\000\ \255\255\255\255\255\255\212\000\255\255\255\255\255\255\255\255\ \241\000\255\255\255\255\255\255\255\255\255\255\241\000\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\241\000\241\000\255\255\255\255\241\000\255\255\ \241\000\241\000\255\255\255\255\241\000\255\255\255\255\255\255\ \255\255\255\255\255\255\211\000\235\000\235\000\235\000\235\000\ \235\000\235\000\235\000\235\000\235\000\235\000\235\000\235\000\ \235\000\235\000\235\000\235\000\235\000\235\000\235\000\235\000\ \235\000\235\000\235\000\235\000\235\000\235\000\235\000\235\000\ \235\000\235\000\235\000\235\000\235\000\235\000\235\000\235\000\ \235\000\235\000\235\000\235\000\235\000\235\000\235\000\235\000\ \235\000\235\000\235\000\235\000\235\000\235\000\235\000\235\000\ \235\000\235\000\235\000\235\000\235\000\235\000\235\000\235\000\ \235\000\235\000\235\000\235\000\235\000\235\000\235\000\235\000\ \235\000\235\000\235\000\235\000\235\000\235\000\235\000\235\000\ \235\000\235\000\235\000\235\000\235\000\235\000\235\000\235\000\ \235\000\235\000\235\000\235\000\235\000\235\000\235\000\235\000\ \235\000\235\000\235\000\235\000\235\000\235\000\235\000\235\000\ \235\000\235\000\235\000\235\000\235\000\235\000\235\000\235\000\ \235\000\235\000\235\000\235\000\235\000\235\000\235\000\235\000\ \235\000\235\000\235\000\235\000\235\000\235\000\235\000\235\000\ \235\000\235\000\235\000\235\000\241\000\255\255\009\001\009\001\ \009\001\009\001\009\001\009\001\009\001\009\001\009\001\009\001\ \009\001\009\001\009\001\009\001\009\001\009\001\009\001\009\001\ \009\001\009\001\009\001\009\001\009\001\009\001\009\001\009\001\ \255\255\255\255\255\255\255\255\009\001\255\255\009\001\009\001\ \009\001\009\001\009\001\009\001\009\001\009\001\009\001\009\001\ \009\001\009\001\009\001\009\001\009\001\009\001\009\001\009\001\ \009\001\009\001\009\001\009\001\009\001\009\001\009\001\009\001\ \255\255\255\255\009\001\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\235\000\009\001\009\001\009\001\ \009\001\009\001\009\001\009\001\009\001\009\001\009\001\009\001\ \009\001\009\001\009\001\009\001\009\001\009\001\009\001\009\001\ \009\001\009\001\009\001\009\001\009\001\009\001\009\001\009\001\ \009\001\009\001\009\001\009\001\009\001\009\001\009\001\009\001\ \009\001\009\001\009\001\009\001\009\001\009\001\009\001\009\001\ \009\001\009\001\009\001\009\001\009\001\009\001\009\001\009\001\ \009\001\009\001\009\001\009\001\009\001\009\001\009\001\009\001\ \009\001\009\001\009\001\009\001\009\001\015\001\015\001\015\001\ \015\001\015\001\015\001\015\001\015\001\015\001\015\001\015\001\ \015\001\015\001\015\001\015\001\015\001\015\001\015\001\015\001\ \015\001\015\001\015\001\015\001\015\001\015\001\015\001\015\001\ \015\001\015\001\015\001\015\001\015\001\015\001\015\001\015\001\ \015\001\015\001\015\001\015\001\255\255\015\001\015\001\015\001\ \015\001\015\001\015\001\015\001\015\001\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\015\001\ \015\001\015\001\015\001\015\001\015\001\015\001\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \015\001\015\001\015\001\015\001\255\255\015\001\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \015\001\015\001\015\001\015\001\015\001\015\001\015\001\015\001\ \015\001\015\001\015\001\015\001\015\001\015\001\015\001\015\001\ \015\001\015\001\015\001\015\001\015\001\015\001\015\001\015\001\ \015\001\015\001\015\001\015\001\015\001\015\001\015\001\015\001\ \015\001\015\001\015\001\015\001\015\001\015\001\015\001\015\001\ \015\001\015\001\015\001\015\001\015\001\015\001\015\001\015\001\ \015\001\015\001\015\001\015\001\015\001\015\001\015\001\015\001\ \015\001\015\001\015\001\015\001\015\001\015\001\015\001\015\001\ \015\001\015\001\015\001\015\001\015\001\015\001\015\001\015\001\ \015\001\015\001\015\001\015\001\015\001\015\001\015\001\015\001\ \015\001\015\001\015\001\015\001\015\001\015\001\015\001\015\001\ \015\001\015\001\015\001\015\001\015\001\015\001\015\001\015\001\ \015\001\015\001\015\001\015\001\015\001\015\001\015\001\015\001\ \015\001\015\001\015\001\015\001\015\001\015\001\015\001\015\001\ \015\001\015\001\015\001\015\001\015\001\015\001\015\001\015\001\ \015\001\015\001\015\001\015\001\015\001\015\001\015\001\015\001\ \015\001\015\001\015\001\015\001\015\001\015\001\016\001\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\016\001\ \016\001\016\001\016\001\016\001\016\001\016\001\016\001\016\001\ \016\001\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \016\001\016\001\016\001\016\001\016\001\016\001\016\001\016\001\ \016\001\016\001\016\001\016\001\016\001\016\001\016\001\016\001\ \016\001\016\001\016\001\016\001\016\001\016\001\016\001\016\001\ \016\001\016\001\255\255\255\255\255\255\255\255\016\001\255\255\ \016\001\016\001\016\001\016\001\016\001\016\001\016\001\016\001\ \016\001\016\001\016\001\016\001\016\001\016\001\016\001\016\001\ \016\001\016\001\016\001\016\001\016\001\016\001\016\001\016\001\ \016\001\016\001\255\255\255\255\016\001\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\016\001\ \016\001\016\001\016\001\016\001\016\001\016\001\016\001\016\001\ \016\001\016\001\016\001\016\001\016\001\016\001\016\001\016\001\ \016\001\016\001\016\001\016\001\016\001\016\001\016\001\016\001\ \016\001\016\001\016\001\016\001\016\001\016\001\016\001\016\001\ \016\001\016\001\016\001\016\001\016\001\016\001\016\001\016\001\ \016\001\016\001\016\001\016\001\016\001\016\001\016\001\016\001\ \016\001\016\001\016\001\016\001\016\001\016\001\016\001\016\001\ \016\001\016\001\016\001\016\001\016\001\016\001\016\001\017\001\ \017\001\017\001\017\001\017\001\017\001\017\001\017\001\017\001\ \017\001\017\001\017\001\017\001\017\001\017\001\017\001\017\001\ \017\001\017\001\017\001\017\001\017\001\017\001\017\001\017\001\ \017\001\017\001\017\001\017\001\017\001\017\001\017\001\017\001\ \017\001\017\001\017\001\017\001\017\001\017\001\017\001\017\001\ \017\001\017\001\017\001\017\001\017\001\017\001\017\001\017\001\ \017\001\017\001\017\001\017\001\017\001\017\001\017\001\017\001\ \017\001\017\001\017\001\017\001\017\001\017\001\017\001\017\001\ \017\001\017\001\017\001\017\001\017\001\017\001\017\001\017\001\ \017\001\017\001\017\001\017\001\017\001\017\001\017\001\017\001\ \017\001\017\001\017\001\017\001\017\001\017\001\017\001\017\001\ \017\001\017\001\017\001\017\001\017\001\017\001\017\001\017\001\ \017\001\017\001\017\001\017\001\017\001\017\001\017\001\017\001\ \017\001\017\001\017\001\017\001\017\001\017\001\017\001\017\001\ \017\001\017\001\017\001\017\001\017\001\017\001\017\001\017\001\ \017\001\017\001\017\001\017\001\017\001\017\001\017\001\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\017\001\ "; Lexing.lex_base_code = "\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\001\000\000\000\000\000\000\000\ \013\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \002\000\000\000\000\000\000\000\016\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\064\000\064\001\198\001\000\000\000\000\ \069\002\069\003\197\003\075\004\018\005\028\000\000\000\000\000\ \146\005\024\006\001\000\000\000\151\006\151\007\023\008\157\008\ \100\009\036\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\002\000\081\001\160\001\004\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\063\000\ \000\000\000\000\100\009\101\010\166\010\101\011\007\000\165\011\ \165\012\166\013\231\013\231\014\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\004\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\005\000\007\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000"; Lexing.lex_backtrk_code = "\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\007\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\007\000\ \007\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \051\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\063\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000"; Lexing.lex_default_code = "\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\019\000\019\000\000\000\000\000\ \000\000\019\000\019\000\019\000\019\000\000\000\000\000\000\000\ \022\000\022\000\000\000\000\000\000\000\022\000\022\000\022\000\ \022\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\022\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\060\000\000\000\000\000\000\000\000\000\ \060\000\060\000\000\000\060\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000"; Lexing.lex_trans_code = "\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\025\000\033\000\004\000\025\000\033\000\060\000\060\000\ \060\000\060\000\000\000\060\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \025\000\033\000\004\000\010\000\004\000\001\000\046\000\060\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\019\000\019\000\019\000\019\000\019\000\019\000\ \019\000\019\000\019\000\019\000\000\000\000\000\000\000\001\000\ \000\000\019\000\019\000\019\000\019\000\019\000\019\000\019\000\ \019\000\019\000\019\000\019\000\019\000\019\000\019\000\019\000\ \019\000\019\000\019\000\019\000\019\000\019\000\019\000\019\000\ \019\000\019\000\019\000\000\000\000\000\000\000\000\000\019\000\ \000\000\019\000\019\000\019\000\019\000\019\000\019\000\019\000\ \019\000\019\000\019\000\019\000\019\000\019\000\019\000\019\000\ \019\000\019\000\019\000\019\000\019\000\019\000\019\000\019\000\ \019\000\019\000\019\000\060\000\000\000\000\000\004\000\000\000\ \000\000\022\000\022\000\022\000\022\000\022\000\022\000\022\000\ \022\000\022\000\022\000\022\000\022\000\022\000\022\000\022\000\ \022\000\022\000\022\000\022\000\022\000\022\000\022\000\022\000\ \022\000\022\000\022\000\000\000\000\000\000\000\000\000\022\000\ \000\000\022\000\022\000\022\000\022\000\022\000\022\000\022\000\ \022\000\022\000\022\000\022\000\022\000\022\000\022\000\022\000\ \022\000\022\000\022\000\022\000\022\000\022\000\022\000\022\000\ \022\000\022\000\022\000\000\000\000\000\000\000\000\000\000\000\ \019\000\019\000\019\000\019\000\019\000\019\000\019\000\019\000\ \019\000\019\000\019\000\019\000\019\000\019\000\019\000\019\000\ \019\000\019\000\019\000\019\000\019\000\019\000\019\000\019\000\ \019\000\019\000\019\000\019\000\019\000\019\000\019\000\019\000\ \019\000\019\000\019\000\019\000\019\000\019\000\019\000\019\000\ \019\000\019\000\019\000\019\000\019\000\019\000\019\000\019\000\ \019\000\019\000\019\000\019\000\019\000\019\000\019\000\019\000\ \019\000\019\000\019\000\019\000\019\000\019\000\019\000\019\000\ \022\000\022\000\022\000\022\000\022\000\022\000\022\000\022\000\ \022\000\022\000\022\000\022\000\022\000\022\000\022\000\022\000\ \022\000\022\000\022\000\022\000\022\000\022\000\022\000\022\000\ \022\000\022\000\022\000\022\000\022\000\022\000\022\000\022\000\ \022\000\022\000\022\000\022\000\022\000\022\000\022\000\022\000\ \022\000\022\000\022\000\022\000\022\000\022\000\022\000\022\000\ \022\000\022\000\022\000\022\000\022\000\022\000\022\000\022\000\ \022\000\022\000\022\000\022\000\022\000\022\000\022\000\022\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\025\000\000\000\000\000\025\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \025\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\041\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\019\000\019\000\019\000\019\000\019\000\019\000\019\000\ \019\000\019\000\019\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\025\000\ \000\000\000\000\025\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\025\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\019\000\019\000\ \019\000\019\000\019\000\019\000\019\000\019\000\019\000\019\000\ \019\000\019\000\019\000\019\000\019\000\019\000\019\000\019\000\ \019\000\019\000\019\000\019\000\019\000\019\000\019\000\019\000\ \000\000\000\000\000\000\000\000\019\000\000\000\019\000\019\000\ \019\000\019\000\019\000\019\000\019\000\019\000\019\000\019\000\ \019\000\019\000\019\000\019\000\019\000\019\000\019\000\019\000\ \019\000\019\000\019\000\019\000\019\000\019\000\019\000\019\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\019\000\019\000\019\000\ \019\000\019\000\019\000\019\000\019\000\019\000\019\000\019\000\ \019\000\019\000\019\000\019\000\019\000\019\000\019\000\019\000\ \019\000\019\000\019\000\019\000\019\000\019\000\019\000\019\000\ \019\000\019\000\019\000\019\000\019\000\019\000\019\000\019\000\ \019\000\019\000\019\000\019\000\019\000\019\000\019\000\019\000\ \019\000\019\000\019\000\019\000\019\000\019\000\019\000\019\000\ \019\000\019\000\019\000\019\000\019\000\019\000\019\000\019\000\ \019\000\019\000\019\000\019\000\019\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\025\000\000\000\ \000\000\025\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\025\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\025\000\000\000\ \000\000\025\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\025\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\025\000\000\000\000\000\025\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\025\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\025\000\000\000\000\000\025\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\025\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\033\000\000\000\000\000\033\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\033\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\033\000\000\000\000\000\033\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \033\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \022\000\022\000\022\000\022\000\022\000\022\000\022\000\022\000\ \022\000\022\000\022\000\022\000\022\000\022\000\022\000\022\000\ \022\000\022\000\022\000\022\000\022\000\022\000\022\000\022\000\ \022\000\022\000\000\000\000\000\000\000\000\000\022\000\000\000\ \022\000\022\000\022\000\022\000\022\000\022\000\022\000\022\000\ \022\000\022\000\022\000\022\000\022\000\022\000\022\000\022\000\ \022\000\022\000\022\000\022\000\022\000\022\000\022\000\022\000\ \022\000\022\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\022\000\ \022\000\022\000\022\000\022\000\022\000\022\000\022\000\022\000\ \022\000\022\000\022\000\022\000\022\000\022\000\022\000\022\000\ \022\000\022\000\022\000\022\000\022\000\022\000\022\000\022\000\ \022\000\022\000\022\000\022\000\022\000\022\000\022\000\022\000\ \022\000\022\000\022\000\022\000\022\000\022\000\022\000\022\000\ \022\000\022\000\022\000\022\000\022\000\022\000\022\000\022\000\ \022\000\022\000\022\000\022\000\022\000\022\000\022\000\022\000\ \022\000\022\000\022\000\022\000\022\000\022\000\022\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \033\000\000\000\000\000\033\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\033\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \033\000\000\000\000\000\033\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\033\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\033\000\000\000\ \000\000\033\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\033\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\033\000\000\000\000\000\ \033\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\033\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\060\000\060\000\060\000\ \060\000\060\000\060\000\060\000\060\000\060\000\060\000\060\000\ \060\000\060\000\060\000\060\000\060\000\060\000\060\000\060\000\ \060\000\060\000\060\000\060\000\060\000\060\000\060\000\000\000\ \000\000\000\000\000\000\060\000\000\000\060\000\060\000\060\000\ \060\000\060\000\060\000\060\000\060\000\060\000\060\000\060\000\ \060\000\060\000\060\000\060\000\060\000\060\000\060\000\060\000\ \060\000\060\000\060\000\060\000\060\000\060\000\060\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\060\000\060\000\060\000\060\000\ \060\000\060\000\060\000\060\000\060\000\060\000\060\000\060\000\ \060\000\060\000\060\000\060\000\060\000\060\000\060\000\060\000\ \060\000\060\000\060\000\060\000\060\000\060\000\060\000\060\000\ \060\000\060\000\060\000\060\000\060\000\060\000\060\000\060\000\ \060\000\060\000\060\000\060\000\060\000\060\000\060\000\060\000\ \060\000\060\000\060\000\060\000\060\000\060\000\060\000\060\000\ \060\000\060\000\060\000\060\000\060\000\060\000\060\000\060\000\ \060\000\060\000\060\000\060\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\060\000\ \000\000\000\000\060\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\060\000\000\000\ \000\000\000\000\000\000\000\000\000\000\060\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\060\000\060\000\ \060\000\060\000\060\000\060\000\060\000\060\000\060\000\060\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\060\000\ \060\000\060\000\060\000\060\000\060\000\060\000\060\000\060\000\ \060\000\060\000\060\000\060\000\060\000\060\000\060\000\060\000\ \060\000\060\000\060\000\060\000\060\000\060\000\060\000\060\000\ \060\000\000\000\000\000\000\000\000\000\060\000\000\000\060\000\ \060\000\060\000\060\000\060\000\060\000\060\000\060\000\060\000\ \060\000\060\000\060\000\060\000\060\000\060\000\060\000\060\000\ \060\000\060\000\060\000\060\000\060\000\060\000\060\000\060\000\ \060\000\000\000\000\000\000\000\000\000\010\000\010\000\010\000\ \010\000\010\000\010\000\010\000\010\000\010\000\010\000\010\000\ \010\000\010\000\010\000\010\000\010\000\010\000\010\000\010\000\ \010\000\010\000\010\000\010\000\010\000\010\000\010\000\010\000\ \010\000\010\000\010\000\010\000\010\000\010\000\010\000\010\000\ \010\000\010\000\010\000\010\000\010\000\010\000\010\000\010\000\ \010\000\010\000\010\000\010\000\010\000\010\000\010\000\010\000\ \010\000\010\000\010\000\010\000\010\000\010\000\010\000\010\000\ \010\000\010\000\010\000\010\000\010\000\000\000\010\000\010\000\ \010\000\010\000\010\000\010\000\010\000\010\000\010\000\010\000\ \010\000\010\000\010\000\010\000\010\000\010\000\010\000\010\000\ \010\000\010\000\010\000\010\000\010\000\010\000\010\000\010\000\ \010\000\010\000\010\000\010\000\010\000\010\000\010\000\010\000\ \010\000\010\000\010\000\010\000\010\000\010\000\010\000\010\000\ \010\000\010\000\010\000\010\000\010\000\010\000\010\000\010\000\ \010\000\010\000\010\000\010\000\010\000\010\000\010\000\010\000\ \010\000\010\000\010\000\010\000\010\000\010\000\060\000\060\000\ \060\000\060\000\060\000\060\000\060\000\060\000\060\000\060\000\ \060\000\060\000\060\000\060\000\060\000\060\000\060\000\060\000\ \060\000\060\000\060\000\060\000\060\000\060\000\060\000\060\000\ \000\000\000\000\000\000\000\000\060\000\000\000\060\000\060\000\ \060\000\060\000\060\000\060\000\060\000\060\000\060\000\060\000\ \060\000\060\000\060\000\060\000\060\000\060\000\060\000\060\000\ \060\000\060\000\060\000\060\000\060\000\060\000\060\000\060\000\ \000\000\000\000\000\000\000\000\000\000\000\000\060\000\060\000\ \060\000\060\000\060\000\060\000\060\000\060\000\060\000\060\000\ \060\000\060\000\060\000\060\000\060\000\060\000\060\000\060\000\ \060\000\060\000\060\000\060\000\060\000\060\000\060\000\060\000\ \000\000\000\000\000\000\000\000\060\000\000\000\060\000\060\000\ \060\000\060\000\060\000\060\000\060\000\060\000\060\000\060\000\ \060\000\060\000\060\000\060\000\060\000\060\000\060\000\060\000\ \060\000\060\000\060\000\060\000\060\000\060\000\060\000\060\000\ \000\000\000\000\000\000\000\000\000\000\060\000\060\000\060\000\ \060\000\060\000\060\000\060\000\060\000\060\000\060\000\060\000\ \060\000\060\000\060\000\060\000\060\000\060\000\060\000\060\000\ \060\000\060\000\060\000\060\000\060\000\060\000\060\000\060\000\ \060\000\060\000\060\000\060\000\060\000\060\000\060\000\060\000\ \060\000\060\000\060\000\060\000\060\000\060\000\060\000\060\000\ \060\000\060\000\060\000\060\000\060\000\060\000\060\000\060\000\ \060\000\060\000\060\000\060\000\060\000\060\000\060\000\060\000\ \060\000\060\000\060\000\060\000\060\000\060\000\060\000\060\000\ \060\000\060\000\060\000\060\000\060\000\060\000\060\000\060\000\ \060\000\060\000\060\000\060\000\060\000\060\000\060\000\060\000\ \060\000\060\000\060\000\060\000\060\000\060\000\060\000\060\000\ \060\000\060\000\060\000\060\000\060\000\060\000\060\000\060\000\ \060\000\060\000\060\000\060\000\060\000\060\000\060\000\060\000\ \060\000\060\000\060\000\060\000\060\000\060\000\060\000\060\000\ \060\000\060\000\060\000\060\000\060\000\060\000\060\000\060\000\ \060\000\060\000\060\000\060\000\060\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\066\000\000\000\000\000\000\000\010\000\010\000\010\000\ \010\000\010\000\010\000\010\000\010\000\010\000\010\000\010\000\ \010\000\010\000\010\000\010\000\010\000\010\000\010\000\010\000\ \010\000\010\000\010\000\010\000\010\000\010\000\010\000\010\000\ \010\000\010\000\010\000\010\000\010\000\010\000\010\000\010\000\ \010\000\010\000\010\000\010\000\010\000\010\000\010\000\010\000\ \010\000\010\000\010\000\010\000\010\000\010\000\010\000\010\000\ \010\000\010\000\010\000\010\000\010\000\010\000\010\000\010\000\ \010\000\010\000\010\000\010\000\010\000\069\000\069\000\069\000\ \069\000\069\000\069\000\069\000\069\000\069\000\069\000\069\000\ \069\000\069\000\069\000\069\000\069\000\069\000\069\000\069\000\ \069\000\069\000\069\000\069\000\069\000\069\000\069\000\069\000\ \069\000\069\000\069\000\069\000\069\000\069\000\069\000\069\000\ \069\000\069\000\069\000\069\000\069\000\069\000\069\000\069\000\ \069\000\069\000\069\000\069\000\069\000\069\000\069\000\069\000\ \069\000\069\000\069\000\069\000\069\000\069\000\069\000\069\000\ \069\000\069\000\069\000\069\000\069\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \060\000\000\000\000\000\060\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\060\000\ \000\000\000\000\000\000\000\000\000\000\000\000\060\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\060\000\ \060\000\060\000\060\000\060\000\060\000\060\000\060\000\060\000\ \060\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \060\000\060\000\060\000\060\000\060\000\060\000\060\000\060\000\ \060\000\060\000\060\000\060\000\060\000\060\000\060\000\060\000\ \060\000\060\000\060\000\060\000\060\000\060\000\060\000\060\000\ \060\000\060\000\000\000\000\000\000\000\000\000\060\000\000\000\ \060\000\060\000\060\000\060\000\060\000\060\000\060\000\060\000\ \060\000\060\000\060\000\060\000\060\000\060\000\060\000\060\000\ \060\000\060\000\060\000\060\000\060\000\060\000\060\000\060\000\ \060\000\060\000\000\000\000\000\000\000\000\000\010\000\010\000\ \010\000\010\000\010\000\010\000\010\000\010\000\010\000\010\000\ \010\000\010\000\010\000\010\000\010\000\010\000\010\000\010\000\ \010\000\010\000\010\000\010\000\010\000\010\000\010\000\010\000\ \010\000\010\000\010\000\010\000\010\000\010\000\010\000\010\000\ \010\000\010\000\010\000\010\000\010\000\010\000\010\000\010\000\ \010\000\010\000\010\000\010\000\010\000\010\000\010\000\010\000\ \010\000\010\000\010\000\010\000\010\000\010\000\010\000\010\000\ \010\000\010\000\010\000\010\000\010\000\010\000\000\000\010\000\ \010\000\010\000\010\000\010\000\010\000\010\000\010\000\010\000\ \010\000\010\000\010\000\010\000\010\000\010\000\010\000\010\000\ \010\000\010\000\010\000\010\000\010\000\010\000\010\000\010\000\ \010\000\010\000\010\000\010\000\010\000\010\000\010\000\010\000\ \010\000\010\000\010\000\010\000\010\000\010\000\010\000\010\000\ \010\000\010\000\010\000\010\000\010\000\010\000\010\000\010\000\ \010\000\010\000\010\000\010\000\010\000\010\000\010\000\010\000\ \010\000\010\000\010\000\010\000\010\000\010\000\010\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\066\000\000\000\000\000\000\000\010\000\ \010\000\010\000\010\000\010\000\010\000\010\000\010\000\010\000\ \010\000\010\000\010\000\010\000\010\000\010\000\010\000\010\000\ \010\000\010\000\010\000\010\000\010\000\010\000\010\000\010\000\ \010\000\010\000\010\000\010\000\010\000\010\000\010\000\010\000\ \010\000\010\000\010\000\010\000\010\000\010\000\010\000\010\000\ \010\000\010\000\010\000\010\000\010\000\010\000\010\000\010\000\ \010\000\010\000\010\000\010\000\010\000\010\000\010\000\010\000\ \010\000\010\000\010\000\010\000\010\000\010\000\010\000\069\000\ \069\000\069\000\069\000\069\000\069\000\069\000\069\000\069\000\ \069\000\069\000\069\000\069\000\069\000\069\000\069\000\069\000\ \069\000\069\000\069\000\069\000\069\000\069\000\069\000\069\000\ \069\000\069\000\069\000\069\000\069\000\069\000\069\000\069\000\ \069\000\069\000\069\000\069\000\069\000\069\000\069\000\069\000\ \069\000\069\000\069\000\069\000\069\000\069\000\069\000\069\000\ \069\000\069\000\069\000\069\000\069\000\069\000\069\000\069\000\ \069\000\069\000\069\000\069\000\069\000\069\000\069\000\000\000\ "; Lexing.lex_check_code = "\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\102\000\114\000\180\000\102\000\114\000\241\000\250\000\ \206\000\251\000\255\255\206\000\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \102\000\114\000\180\000\043\000\052\000\064\000\183\000\206\000\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\180\000\180\000\180\000\180\000\180\000\180\000\ \180\000\180\000\180\000\180\000\255\255\255\255\255\255\000\000\ \255\255\095\000\095\000\095\000\095\000\095\000\095\000\095\000\ \095\000\095\000\095\000\095\000\095\000\095\000\095\000\095\000\ \095\000\095\000\095\000\095\000\095\000\095\000\095\000\095\000\ \095\000\095\000\095\000\255\255\255\255\255\255\255\255\095\000\ \255\255\095\000\095\000\095\000\095\000\095\000\095\000\095\000\ \095\000\095\000\095\000\095\000\095\000\095\000\095\000\095\000\ \095\000\095\000\095\000\095\000\095\000\095\000\095\000\095\000\ \095\000\095\000\095\000\185\000\255\255\255\255\000\000\255\255\ \255\255\099\000\099\000\099\000\099\000\099\000\099\000\099\000\ \099\000\099\000\099\000\099\000\099\000\099\000\099\000\099\000\ \099\000\099\000\099\000\099\000\099\000\099\000\099\000\099\000\ \099\000\099\000\099\000\255\255\255\255\255\255\255\255\099\000\ \255\255\099\000\099\000\099\000\099\000\099\000\099\000\099\000\ \099\000\099\000\099\000\099\000\099\000\099\000\099\000\099\000\ \099\000\099\000\099\000\099\000\099\000\099\000\099\000\099\000\ \099\000\099\000\099\000\255\255\255\255\255\255\255\255\255\255\ \095\000\095\000\095\000\095\000\095\000\095\000\095\000\095\000\ \095\000\095\000\095\000\095\000\095\000\095\000\095\000\095\000\ \095\000\095\000\095\000\095\000\095\000\095\000\095\000\095\000\ \095\000\095\000\095\000\095\000\095\000\095\000\095\000\095\000\ \095\000\095\000\095\000\095\000\095\000\095\000\095\000\095\000\ \095\000\095\000\095\000\095\000\095\000\095\000\095\000\095\000\ \095\000\095\000\095\000\095\000\095\000\095\000\095\000\095\000\ \095\000\095\000\095\000\095\000\095\000\095\000\095\000\095\000\ \099\000\099\000\099\000\099\000\099\000\099\000\099\000\099\000\ \099\000\099\000\099\000\099\000\099\000\099\000\099\000\099\000\ \099\000\099\000\099\000\099\000\099\000\099\000\099\000\099\000\ \099\000\099\000\099\000\099\000\099\000\099\000\099\000\099\000\ \099\000\099\000\099\000\099\000\099\000\099\000\099\000\099\000\ \099\000\099\000\099\000\099\000\099\000\099\000\099\000\099\000\ \099\000\099\000\099\000\099\000\099\000\099\000\099\000\099\000\ \099\000\099\000\099\000\099\000\099\000\099\000\099\000\099\000\ \100\000\100\000\100\000\100\000\100\000\100\000\100\000\100\000\ \100\000\100\000\100\000\100\000\100\000\100\000\100\000\100\000\ \100\000\100\000\100\000\100\000\100\000\100\000\100\000\100\000\ \100\000\100\000\100\000\100\000\100\000\100\000\100\000\100\000\ \100\000\100\000\100\000\100\000\100\000\100\000\100\000\255\255\ \100\000\100\000\100\000\100\000\100\000\100\000\100\000\100\000\ \255\255\255\255\255\255\181\000\255\255\255\255\255\255\255\255\ \255\255\255\255\100\000\100\000\100\000\100\000\100\000\100\000\ \100\000\181\000\181\000\181\000\181\000\181\000\181\000\181\000\ \181\000\181\000\181\000\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\100\000\100\000\100\000\100\000\255\255\ \100\000\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\182\000\255\255\255\255\182\000\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\100\000\100\000\100\000\100\000\100\000\ \255\255\255\255\182\000\255\255\255\255\255\255\101\000\101\000\ \101\000\101\000\101\000\101\000\101\000\101\000\101\000\101\000\ \101\000\101\000\101\000\101\000\101\000\101\000\101\000\101\000\ \101\000\101\000\101\000\101\000\101\000\101\000\101\000\101\000\ \101\000\101\000\101\000\101\000\101\000\101\000\101\000\101\000\ \101\000\101\000\101\000\101\000\101\000\255\255\101\000\101\000\ \101\000\101\000\101\000\101\000\101\000\101\000\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \101\000\101\000\101\000\101\000\101\000\101\000\101\000\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\101\000\101\000\101\000\101\000\255\255\101\000\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \100\000\101\000\101\000\101\000\101\000\101\000\101\000\101\000\ \101\000\101\000\101\000\101\000\101\000\101\000\101\000\101\000\ \101\000\101\000\101\000\101\000\101\000\101\000\101\000\101\000\ \101\000\101\000\101\000\101\000\101\000\101\000\101\000\101\000\ \101\000\101\000\101\000\101\000\101\000\101\000\101\000\101\000\ \101\000\101\000\101\000\101\000\101\000\101\000\101\000\101\000\ \101\000\101\000\101\000\101\000\101\000\101\000\101\000\101\000\ \101\000\101\000\101\000\101\000\101\000\101\000\101\000\101\000\ \101\000\101\000\101\000\101\000\101\000\101\000\104\000\104\000\ \104\000\104\000\104\000\104\000\104\000\104\000\104\000\104\000\ \104\000\104\000\104\000\104\000\104\000\104\000\104\000\104\000\ \104\000\104\000\104\000\104\000\104\000\104\000\104\000\104\000\ \182\000\255\255\255\255\255\255\104\000\255\255\104\000\104\000\ \104\000\104\000\104\000\104\000\104\000\104\000\104\000\104\000\ \104\000\104\000\104\000\104\000\104\000\104\000\104\000\104\000\ \104\000\104\000\104\000\104\000\104\000\104\000\104\000\104\000\ \255\255\255\255\255\255\255\255\255\255\255\255\101\000\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\104\000\104\000\104\000\ \104\000\104\000\104\000\104\000\104\000\104\000\104\000\104\000\ \104\000\104\000\104\000\104\000\104\000\104\000\104\000\104\000\ \104\000\104\000\104\000\104\000\104\000\104\000\104\000\104\000\ \104\000\104\000\104\000\104\000\104\000\104\000\104\000\104\000\ \104\000\104\000\104\000\104\000\104\000\104\000\104\000\104\000\ \104\000\104\000\104\000\104\000\104\000\104\000\104\000\104\000\ \104\000\104\000\104\000\104\000\104\000\104\000\104\000\104\000\ \104\000\104\000\104\000\104\000\104\000\105\000\105\000\105\000\ \105\000\105\000\105\000\105\000\105\000\105\000\105\000\105\000\ \105\000\105\000\105\000\105\000\105\000\105\000\105\000\105\000\ \105\000\105\000\105\000\105\000\105\000\105\000\105\000\105\000\ \105\000\105\000\105\000\105\000\105\000\105\000\105\000\105\000\ \105\000\105\000\105\000\105\000\255\255\105\000\105\000\105\000\ \105\000\105\000\105\000\105\000\105\000\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\105\000\ \105\000\105\000\105\000\105\000\105\000\105\000\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \105\000\105\000\105\000\105\000\255\255\105\000\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \105\000\105\000\105\000\105\000\105\000\106\000\106\000\106\000\ \106\000\106\000\106\000\106\000\106\000\106\000\106\000\106\000\ \106\000\106\000\106\000\106\000\106\000\106\000\106\000\106\000\ \106\000\106\000\106\000\106\000\106\000\106\000\106\000\106\000\ \106\000\106\000\106\000\106\000\106\000\106\000\106\000\106\000\ \106\000\106\000\106\000\106\000\255\255\106\000\106\000\106\000\ \106\000\106\000\106\000\106\000\106\000\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\106\000\ \106\000\106\000\106\000\106\000\106\000\106\000\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \106\000\106\000\106\000\106\000\255\255\106\000\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \106\000\106\000\106\000\106\000\106\000\105\000\255\255\255\255\ \255\255\255\255\255\255\107\000\107\000\107\000\107\000\107\000\ \107\000\107\000\107\000\107\000\107\000\107\000\107\000\107\000\ \107\000\107\000\107\000\107\000\107\000\107\000\107\000\107\000\ \107\000\107\000\107\000\107\000\107\000\107\000\107\000\107\000\ \107\000\107\000\107\000\107\000\107\000\107\000\107\000\107\000\ \107\000\107\000\255\255\107\000\107\000\107\000\107\000\107\000\ \107\000\107\000\107\000\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\107\000\107\000\107\000\ \107\000\107\000\107\000\107\000\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\107\000\107\000\ \107\000\107\000\255\255\107\000\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\106\000\107\000\107\000\ \107\000\107\000\107\000\107\000\107\000\107\000\107\000\107\000\ \107\000\107\000\107\000\107\000\107\000\107\000\107\000\107\000\ \107\000\107\000\107\000\107\000\107\000\107\000\107\000\107\000\ \107\000\107\000\107\000\107\000\107\000\107\000\107\000\107\000\ \107\000\107\000\107\000\107\000\107\000\107\000\107\000\107\000\ \107\000\107\000\107\000\107\000\107\000\107\000\107\000\107\000\ \107\000\107\000\107\000\107\000\107\000\107\000\107\000\107\000\ \107\000\107\000\107\000\107\000\107\000\107\000\107\000\107\000\ \107\000\107\000\107\000\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\108\000\108\000\108\000\108\000\108\000\108\000\ \108\000\108\000\108\000\108\000\108\000\108\000\108\000\108\000\ \108\000\108\000\108\000\108\000\108\000\108\000\108\000\108\000\ \108\000\108\000\108\000\108\000\108\000\108\000\108\000\108\000\ \108\000\108\000\108\000\108\000\108\000\108\000\108\000\108\000\ \108\000\255\255\108\000\108\000\108\000\108\000\108\000\108\000\ \108\000\108\000\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\107\000\108\000\108\000\108\000\108\000\ \108\000\108\000\108\000\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\108\000\108\000\108\000\ \108\000\255\255\108\000\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\108\000\108\000\108\000\ \108\000\108\000\112\000\112\000\112\000\112\000\112\000\112\000\ \112\000\112\000\112\000\112\000\112\000\112\000\112\000\112\000\ \112\000\112\000\112\000\112\000\112\000\112\000\112\000\112\000\ \112\000\112\000\112\000\112\000\112\000\112\000\112\000\112\000\ \112\000\112\000\112\000\112\000\112\000\112\000\112\000\112\000\ \112\000\255\255\112\000\112\000\112\000\112\000\112\000\112\000\ \112\000\112\000\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\112\000\112\000\112\000\112\000\ \112\000\112\000\112\000\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\112\000\112\000\112\000\ \112\000\255\255\112\000\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\112\000\112\000\112\000\ \112\000\112\000\108\000\255\255\255\255\255\255\255\255\255\255\ \113\000\113\000\113\000\113\000\113\000\113\000\113\000\113\000\ \113\000\113\000\113\000\113\000\113\000\113\000\113\000\113\000\ \113\000\113\000\113\000\113\000\113\000\113\000\113\000\113\000\ \113\000\113\000\113\000\113\000\113\000\113\000\113\000\113\000\ \113\000\113\000\113\000\113\000\113\000\113\000\113\000\255\255\ \113\000\113\000\113\000\113\000\113\000\113\000\113\000\113\000\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\113\000\113\000\113\000\113\000\113\000\113\000\ \113\000\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\113\000\113\000\113\000\113\000\255\255\ \113\000\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\112\000\113\000\113\000\113\000\113\000\113\000\ \113\000\113\000\113\000\113\000\113\000\113\000\113\000\113\000\ \113\000\113\000\113\000\113\000\113\000\113\000\113\000\113\000\ \113\000\113\000\113\000\113\000\113\000\113\000\113\000\113\000\ \113\000\113\000\113\000\113\000\113\000\113\000\113\000\113\000\ \113\000\113\000\113\000\113\000\113\000\113\000\113\000\113\000\ \113\000\113\000\113\000\113\000\113\000\113\000\113\000\113\000\ \113\000\113\000\113\000\113\000\113\000\113\000\113\000\113\000\ \113\000\113\000\113\000\113\000\113\000\113\000\113\000\113\000\ \116\000\116\000\116\000\116\000\116\000\116\000\116\000\116\000\ \116\000\116\000\116\000\116\000\116\000\116\000\116\000\116\000\ \116\000\116\000\116\000\116\000\116\000\116\000\116\000\116\000\ \116\000\116\000\255\255\255\255\255\255\255\255\116\000\255\255\ \116\000\116\000\116\000\116\000\116\000\116\000\116\000\116\000\ \116\000\116\000\116\000\116\000\116\000\116\000\116\000\116\000\ \116\000\116\000\116\000\116\000\116\000\116\000\116\000\116\000\ \116\000\116\000\255\255\255\255\255\255\255\255\255\255\255\255\ \113\000\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\116\000\ \116\000\116\000\116\000\116\000\116\000\116\000\116\000\116\000\ \116\000\116\000\116\000\116\000\116\000\116\000\116\000\116\000\ \116\000\116\000\116\000\116\000\116\000\116\000\116\000\116\000\ \116\000\116\000\116\000\116\000\116\000\116\000\116\000\116\000\ \116\000\116\000\116\000\116\000\116\000\116\000\116\000\116\000\ \116\000\116\000\116\000\116\000\116\000\116\000\116\000\116\000\ \116\000\116\000\116\000\116\000\116\000\116\000\116\000\116\000\ \116\000\116\000\116\000\116\000\116\000\116\000\116\000\117\000\ \117\000\117\000\117\000\117\000\117\000\117\000\117\000\117\000\ \117\000\117\000\117\000\117\000\117\000\117\000\117\000\117\000\ \117\000\117\000\117\000\117\000\117\000\117\000\117\000\117\000\ \117\000\117\000\117\000\117\000\117\000\117\000\117\000\117\000\ \117\000\117\000\117\000\117\000\117\000\117\000\255\255\117\000\ \117\000\117\000\117\000\117\000\117\000\117\000\117\000\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\117\000\117\000\117\000\117\000\117\000\117\000\117\000\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\117\000\117\000\117\000\117\000\255\255\117\000\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\117\000\117\000\117\000\117\000\117\000\118\000\ \118\000\118\000\118\000\118\000\118\000\118\000\118\000\118\000\ \118\000\118\000\118\000\118\000\118\000\118\000\118\000\118\000\ \118\000\118\000\118\000\118\000\118\000\118\000\118\000\118\000\ \118\000\118\000\118\000\118\000\118\000\118\000\118\000\118\000\ \118\000\118\000\118\000\118\000\118\000\118\000\255\255\118\000\ \118\000\118\000\118\000\118\000\118\000\118\000\118\000\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\118\000\118\000\118\000\118\000\118\000\118\000\118\000\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\118\000\118\000\118\000\118\000\255\255\118\000\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\118\000\118\000\118\000\118\000\118\000\117\000\ \255\255\255\255\255\255\255\255\255\255\119\000\119\000\119\000\ \119\000\119\000\119\000\119\000\119\000\119\000\119\000\119\000\ \119\000\119\000\119\000\119\000\119\000\119\000\119\000\119\000\ \119\000\119\000\119\000\119\000\119\000\119\000\119\000\119\000\ \119\000\119\000\119\000\119\000\119\000\119\000\119\000\119\000\ \119\000\119\000\119\000\119\000\255\255\119\000\119\000\119\000\ \119\000\119\000\119\000\119\000\119\000\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\119\000\ \119\000\119\000\119\000\119\000\119\000\119\000\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \119\000\119\000\119\000\119\000\255\255\119\000\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\118\000\ \119\000\119\000\119\000\119\000\119\000\119\000\119\000\119\000\ \119\000\119\000\119\000\119\000\119\000\119\000\119\000\119\000\ \119\000\119\000\119\000\119\000\119\000\119\000\119\000\119\000\ \119\000\119\000\119\000\119\000\119\000\119\000\119\000\119\000\ \119\000\119\000\119\000\119\000\119\000\119\000\119\000\119\000\ \119\000\119\000\119\000\119\000\119\000\119\000\119\000\119\000\ \119\000\119\000\119\000\119\000\119\000\119\000\119\000\119\000\ \119\000\119\000\119\000\119\000\119\000\119\000\119\000\119\000\ \119\000\119\000\119\000\119\000\119\000\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\120\000\120\000\120\000\120\000\ \120\000\120\000\120\000\120\000\120\000\120\000\120\000\120\000\ \120\000\120\000\120\000\120\000\120\000\120\000\120\000\120\000\ \120\000\120\000\120\000\120\000\120\000\120\000\120\000\120\000\ \120\000\120\000\120\000\120\000\120\000\120\000\120\000\120\000\ \120\000\120\000\120\000\255\255\120\000\120\000\120\000\120\000\ \120\000\120\000\120\000\120\000\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\119\000\120\000\120\000\ \120\000\120\000\120\000\120\000\120\000\202\000\202\000\202\000\ \202\000\202\000\202\000\202\000\202\000\202\000\202\000\202\000\ \202\000\202\000\202\000\202\000\202\000\202\000\202\000\202\000\ \202\000\202\000\202\000\202\000\202\000\202\000\202\000\120\000\ \120\000\120\000\120\000\202\000\120\000\202\000\202\000\202\000\ \202\000\202\000\202\000\202\000\202\000\202\000\202\000\202\000\ \202\000\202\000\202\000\202\000\202\000\202\000\202\000\202\000\ \202\000\202\000\202\000\202\000\202\000\202\000\202\000\120\000\ \120\000\120\000\120\000\120\000\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\202\000\202\000\202\000\202\000\ \202\000\202\000\202\000\202\000\202\000\202\000\202\000\202\000\ \202\000\202\000\202\000\202\000\202\000\202\000\202\000\202\000\ \202\000\202\000\202\000\202\000\202\000\202\000\202\000\202\000\ \202\000\202\000\202\000\202\000\202\000\202\000\202\000\202\000\ \202\000\202\000\202\000\202\000\202\000\202\000\202\000\202\000\ \202\000\202\000\202\000\202\000\202\000\202\000\202\000\202\000\ \202\000\202\000\202\000\202\000\202\000\202\000\202\000\202\000\ \202\000\202\000\202\000\202\000\120\000\203\000\203\000\203\000\ \203\000\203\000\203\000\203\000\203\000\203\000\255\255\203\000\ \203\000\255\255\203\000\203\000\203\000\203\000\203\000\203\000\ \203\000\203\000\203\000\203\000\203\000\203\000\203\000\203\000\ \203\000\203\000\203\000\203\000\203\000\255\255\203\000\203\000\ \203\000\203\000\203\000\203\000\255\255\203\000\203\000\203\000\ \203\000\203\000\203\000\203\000\203\000\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\203\000\ \203\000\203\000\203\000\203\000\203\000\203\000\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\204\000\ \255\255\255\255\204\000\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \203\000\203\000\203\000\203\000\255\255\203\000\204\000\255\255\ \255\255\255\255\255\255\255\255\255\255\204\000\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\204\000\204\000\ \204\000\204\000\204\000\204\000\204\000\204\000\204\000\204\000\ \203\000\203\000\203\000\203\000\203\000\255\255\255\255\204\000\ \204\000\204\000\204\000\204\000\204\000\204\000\204\000\204\000\ \204\000\204\000\204\000\204\000\204\000\204\000\204\000\204\000\ \204\000\204\000\204\000\204\000\204\000\204\000\204\000\204\000\ \204\000\255\255\255\255\255\255\255\255\204\000\255\255\204\000\ \204\000\204\000\204\000\204\000\204\000\204\000\204\000\204\000\ \204\000\204\000\204\000\204\000\204\000\204\000\204\000\204\000\ \204\000\204\000\204\000\204\000\204\000\204\000\204\000\204\000\ \204\000\255\255\255\255\255\255\255\255\203\000\203\000\203\000\ \203\000\203\000\203\000\203\000\203\000\203\000\203\000\203\000\ \203\000\203\000\203\000\203\000\203\000\203\000\203\000\203\000\ \203\000\203\000\203\000\203\000\203\000\203\000\203\000\203\000\ \203\000\203\000\203\000\203\000\203\000\203\000\203\000\203\000\ \203\000\203\000\203\000\203\000\203\000\203\000\203\000\203\000\ \203\000\203\000\203\000\203\000\203\000\203\000\203\000\203\000\ \203\000\203\000\203\000\203\000\203\000\203\000\203\000\203\000\ \203\000\203\000\203\000\203\000\203\000\203\000\204\000\204\000\ \204\000\204\000\204\000\204\000\204\000\204\000\204\000\204\000\ \204\000\204\000\204\000\204\000\204\000\204\000\204\000\204\000\ \204\000\204\000\204\000\204\000\204\000\204\000\204\000\204\000\ \204\000\204\000\204\000\204\000\204\000\204\000\204\000\204\000\ \204\000\204\000\204\000\204\000\204\000\204\000\204\000\204\000\ \204\000\204\000\204\000\204\000\204\000\204\000\204\000\204\000\ \204\000\204\000\204\000\204\000\204\000\204\000\204\000\204\000\ \204\000\204\000\204\000\204\000\204\000\204\000\205\000\205\000\ \205\000\205\000\205\000\205\000\205\000\205\000\205\000\205\000\ \205\000\205\000\205\000\205\000\205\000\205\000\205\000\205\000\ \205\000\205\000\205\000\205\000\205\000\205\000\205\000\205\000\ \255\255\255\255\255\255\255\255\205\000\255\255\205\000\205\000\ \205\000\205\000\205\000\205\000\205\000\205\000\205\000\205\000\ \205\000\205\000\205\000\205\000\205\000\205\000\205\000\205\000\ \205\000\205\000\205\000\205\000\205\000\205\000\205\000\205\000\ \255\255\255\255\255\255\255\255\255\255\255\255\207\000\207\000\ \207\000\207\000\207\000\207\000\207\000\207\000\207\000\207\000\ \207\000\207\000\207\000\207\000\207\000\207\000\207\000\207\000\ \207\000\207\000\207\000\207\000\207\000\207\000\207\000\207\000\ \255\255\255\255\255\255\255\255\207\000\255\255\207\000\207\000\ \207\000\207\000\207\000\207\000\207\000\207\000\207\000\207\000\ \207\000\207\000\207\000\207\000\207\000\207\000\207\000\207\000\ \207\000\207\000\207\000\207\000\207\000\207\000\207\000\207\000\ \255\255\255\255\255\255\255\255\255\255\205\000\205\000\205\000\ \205\000\205\000\205\000\205\000\205\000\205\000\205\000\205\000\ \205\000\205\000\205\000\205\000\205\000\205\000\205\000\205\000\ \205\000\205\000\205\000\205\000\205\000\205\000\205\000\205\000\ \205\000\205\000\205\000\205\000\205\000\205\000\205\000\205\000\ \205\000\205\000\205\000\205\000\205\000\205\000\205\000\205\000\ \205\000\205\000\205\000\205\000\205\000\205\000\205\000\205\000\ \205\000\205\000\205\000\205\000\205\000\205\000\205\000\205\000\ \205\000\205\000\205\000\205\000\205\000\207\000\207\000\207\000\ \207\000\207\000\207\000\207\000\207\000\207\000\207\000\207\000\ \207\000\207\000\207\000\207\000\207\000\207\000\207\000\207\000\ \207\000\207\000\207\000\207\000\207\000\207\000\207\000\207\000\ \207\000\207\000\207\000\207\000\207\000\207\000\207\000\207\000\ \207\000\207\000\207\000\207\000\207\000\207\000\207\000\207\000\ \207\000\207\000\207\000\207\000\207\000\207\000\207\000\207\000\ \207\000\207\000\207\000\207\000\207\000\207\000\207\000\207\000\ \207\000\207\000\207\000\207\000\207\000\208\000\208\000\208\000\ \208\000\208\000\208\000\208\000\208\000\208\000\255\255\208\000\ \208\000\255\255\208\000\208\000\208\000\208\000\208\000\208\000\ \208\000\208\000\208\000\208\000\208\000\208\000\208\000\208\000\ \208\000\208\000\208\000\208\000\208\000\255\255\208\000\208\000\ \208\000\208\000\208\000\208\000\255\255\208\000\208\000\208\000\ \208\000\208\000\208\000\208\000\208\000\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\208\000\ \208\000\208\000\208\000\208\000\208\000\208\000\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \208\000\208\000\208\000\208\000\255\255\208\000\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \208\000\208\000\208\000\208\000\208\000\208\000\208\000\208\000\ \208\000\208\000\208\000\208\000\208\000\208\000\208\000\208\000\ \208\000\208\000\208\000\208\000\208\000\208\000\208\000\208\000\ \208\000\208\000\208\000\208\000\208\000\208\000\208\000\208\000\ \208\000\208\000\208\000\208\000\208\000\208\000\208\000\208\000\ \208\000\208\000\208\000\208\000\208\000\208\000\208\000\208\000\ \208\000\208\000\208\000\208\000\208\000\208\000\208\000\208\000\ \208\000\208\000\208\000\208\000\208\000\208\000\208\000\208\000\ \208\000\208\000\208\000\208\000\208\000\208\000\208\000\208\000\ \208\000\208\000\208\000\208\000\208\000\208\000\208\000\208\000\ \208\000\208\000\208\000\208\000\208\000\208\000\208\000\208\000\ \208\000\208\000\208\000\208\000\208\000\208\000\208\000\208\000\ \208\000\208\000\208\000\208\000\208\000\208\000\208\000\208\000\ \208\000\208\000\208\000\208\000\208\000\208\000\208\000\208\000\ \208\000\208\000\208\000\208\000\208\000\208\000\208\000\208\000\ \208\000\208\000\208\000\208\000\208\000\208\000\208\000\208\000\ \208\000\208\000\208\000\208\000\208\000\208\000\209\000\209\000\ \209\000\209\000\209\000\209\000\209\000\209\000\209\000\255\255\ \209\000\209\000\255\255\209\000\209\000\209\000\209\000\209\000\ \209\000\209\000\209\000\209\000\209\000\209\000\209\000\209\000\ \209\000\209\000\209\000\209\000\209\000\209\000\255\255\209\000\ \209\000\209\000\209\000\209\000\209\000\255\255\209\000\209\000\ \209\000\209\000\209\000\209\000\209\000\209\000\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \209\000\209\000\209\000\209\000\209\000\209\000\209\000\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \210\000\255\255\255\255\210\000\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\209\000\209\000\209\000\209\000\255\255\209\000\210\000\ \255\255\255\255\255\255\255\255\255\255\255\255\210\000\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\210\000\ \210\000\210\000\210\000\210\000\210\000\210\000\210\000\210\000\ \210\000\209\000\209\000\209\000\209\000\209\000\255\255\255\255\ \210\000\210\000\210\000\210\000\210\000\210\000\210\000\210\000\ \210\000\210\000\210\000\210\000\210\000\210\000\210\000\210\000\ \210\000\210\000\210\000\210\000\210\000\210\000\210\000\210\000\ \210\000\210\000\255\255\255\255\255\255\255\255\210\000\255\255\ \210\000\210\000\210\000\210\000\210\000\210\000\210\000\210\000\ \210\000\210\000\210\000\210\000\210\000\210\000\210\000\210\000\ \210\000\210\000\210\000\210\000\210\000\210\000\210\000\210\000\ \210\000\210\000\255\255\255\255\255\255\255\255\209\000\209\000\ \209\000\209\000\209\000\209\000\209\000\209\000\209\000\209\000\ \209\000\209\000\209\000\209\000\209\000\209\000\209\000\209\000\ \209\000\209\000\209\000\209\000\209\000\209\000\209\000\209\000\ \209\000\209\000\209\000\209\000\209\000\209\000\209\000\209\000\ \209\000\209\000\209\000\209\000\209\000\209\000\209\000\209\000\ \209\000\209\000\209\000\209\000\209\000\209\000\209\000\209\000\ \209\000\209\000\209\000\209\000\209\000\209\000\209\000\209\000\ \209\000\209\000\209\000\209\000\209\000\209\000\209\000\210\000\ \210\000\210\000\210\000\210\000\210\000\210\000\210\000\210\000\ \210\000\210\000\210\000\210\000\210\000\210\000\210\000\210\000\ \210\000\210\000\210\000\210\000\210\000\210\000\210\000\210\000\ \210\000\210\000\210\000\210\000\210\000\210\000\210\000\210\000\ \210\000\210\000\210\000\210\000\210\000\210\000\210\000\210\000\ \210\000\210\000\210\000\210\000\210\000\210\000\210\000\210\000\ \210\000\210\000\210\000\210\000\210\000\210\000\210\000\210\000\ \210\000\210\000\210\000\210\000\210\000\210\000\210\000\211\000\ \211\000\211\000\211\000\211\000\211\000\211\000\211\000\211\000\ \255\255\211\000\211\000\255\255\211\000\211\000\211\000\211\000\ \211\000\211\000\211\000\211\000\211\000\211\000\211\000\211\000\ \211\000\211\000\211\000\211\000\211\000\211\000\211\000\255\255\ \211\000\211\000\211\000\211\000\211\000\211\000\255\255\211\000\ \211\000\211\000\211\000\211\000\211\000\211\000\211\000\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\211\000\211\000\211\000\211\000\211\000\211\000\211\000\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\211\000\211\000\211\000\211\000\255\255\211\000\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\211\000\211\000\211\000\211\000\211\000\211\000\ \211\000\211\000\211\000\211\000\211\000\211\000\211\000\211\000\ \211\000\211\000\211\000\211\000\211\000\211\000\211\000\211\000\ \211\000\211\000\211\000\211\000\211\000\211\000\211\000\211\000\ \211\000\211\000\211\000\211\000\211\000\211\000\211\000\211\000\ \211\000\211\000\211\000\211\000\211\000\211\000\211\000\211\000\ \211\000\211\000\211\000\211\000\211\000\211\000\211\000\211\000\ \211\000\211\000\211\000\211\000\211\000\211\000\211\000\211\000\ \211\000\211\000\211\000\211\000\211\000\211\000\211\000\211\000\ \211\000\211\000\211\000\211\000\211\000\211\000\211\000\211\000\ \211\000\211\000\211\000\211\000\211\000\211\000\211\000\211\000\ \211\000\211\000\211\000\211\000\211\000\211\000\211\000\211\000\ \211\000\211\000\211\000\211\000\211\000\211\000\211\000\211\000\ \211\000\211\000\211\000\211\000\211\000\211\000\211\000\211\000\ \211\000\211\000\211\000\211\000\211\000\211\000\211\000\211\000\ \211\000\211\000\211\000\211\000\211\000\211\000\211\000\211\000\ \211\000\211\000\211\000\211\000\211\000\211\000\211\000\211\000\ "; Lexing.lex_code = "\255\003\255\255\004\255\255\000\002\255\002\255\255\000\004\255\ \000\003\255\005\255\255\007\255\255\006\255\255\000\005\001\006\ \255\008\255\255\000\007\001\008\255\007\255\006\255\255\006\255\ \007\255\255\000\004\001\005\002\006\003\007\255\001\255\255\000\ \001\255\001\002\255\001\002\002\255\255"; } let rec token lexbuf = lexbuf.Lexing.lex_mem <- Array.make 9 (-1);(* L=1 [2] <- p ; *) lexbuf.Lexing.lex_mem.(2) <- lexbuf.Lexing.lex_curr_pos ; __ocaml_lex_token_rec lexbuf 0 and __ocaml_lex_token_rec lexbuf __ocaml_lex_state = match Lexing.new_engine __ocaml_lex_tables __ocaml_lex_state lexbuf with | 0 -> let # 504 "parsing/lexer.mll" bs # 5881 "parsing/lexer.ml" = Lexing.sub_lexeme_char lexbuf lexbuf.Lexing.lex_start_pos in # 504 "parsing/lexer.mll" ( if not !escaped_newlines then error lexbuf (Illegal_character bs); update_loc lexbuf None 1 false 0; token lexbuf ) # 5888 "parsing/lexer.ml" | 1 -> # 509 "parsing/lexer.mll" ( update_loc lexbuf None 1 false 0; EOL ) # 5894 "parsing/lexer.ml" | 2 -> # 512 "parsing/lexer.mll" ( token lexbuf ) # 5899 "parsing/lexer.ml" | 3 -> # 514 "parsing/lexer.mll" ( UNDERSCORE ) # 5904 "parsing/lexer.ml" | 4 -> # 516 "parsing/lexer.mll" ( TILDE ) # 5909 "parsing/lexer.ml" | 5 -> # 518 "parsing/lexer.mll" ( error lexbuf (Reserved_sequence (".~", Some "is reserved for use in MetaOCaml")) ) # 5915 "parsing/lexer.ml" | 6 -> let # 520 "parsing/lexer.mll" name # 5921 "parsing/lexer.ml" = Lexing.sub_lexeme lexbuf (lexbuf.Lexing.lex_start_pos + 1) (lexbuf.Lexing.lex_curr_pos + -1) in # 521 "parsing/lexer.mll" ( check_label_name lexbuf name; LABEL name ) # 5926 "parsing/lexer.ml" | 7 -> let # 523 "parsing/lexer.mll" escape # 5932 "parsing/lexer.ml" = Lexing.sub_lexeme lexbuf (lexbuf.Lexing.lex_start_pos + 1) lexbuf.Lexing.lex_mem.(0) and # 523 "parsing/lexer.mll" raw_name # 5937 "parsing/lexer.ml" = Lexing.sub_lexeme lexbuf lexbuf.Lexing.lex_mem.(0) (lexbuf.Lexing.lex_curr_pos + -1) in # 524 "parsing/lexer.mll" ( let name = ident_for_extended lexbuf raw_name in check_label_name ~raw_escape:(escape<>"") lexbuf name; LABEL name ) # 5943 "parsing/lexer.ml" | 8 -> # 528 "parsing/lexer.mll" ( QUESTION ) # 5948 "parsing/lexer.ml" | 9 -> let # 529 "parsing/lexer.mll" name # 5954 "parsing/lexer.ml" = Lexing.sub_lexeme lexbuf (lexbuf.Lexing.lex_start_pos + 1) (lexbuf.Lexing.lex_curr_pos + -1) in # 530 "parsing/lexer.mll" ( check_label_name lexbuf name; OPTLABEL name ) # 5959 "parsing/lexer.ml" | 10 -> let # 532 "parsing/lexer.mll" escape # 5965 "parsing/lexer.ml" = Lexing.sub_lexeme lexbuf (lexbuf.Lexing.lex_start_pos + 1) lexbuf.Lexing.lex_mem.(0) and # 532 "parsing/lexer.mll" raw_name # 5970 "parsing/lexer.ml" = Lexing.sub_lexeme lexbuf lexbuf.Lexing.lex_mem.(0) (lexbuf.Lexing.lex_curr_pos + -1) in # 533 "parsing/lexer.mll" ( let name = ident_for_extended lexbuf raw_name in check_label_name ~raw_escape:(escape<>"") lexbuf name; OPTLABEL name ) # 5977 "parsing/lexer.ml" | 11 -> let # 537 "parsing/lexer.mll" name # 5983 "parsing/lexer.ml" = Lexing.sub_lexeme lexbuf lexbuf.Lexing.lex_start_pos lexbuf.Lexing.lex_curr_pos in # 538 "parsing/lexer.mll" ( find_keyword lexbuf name ) # 5987 "parsing/lexer.ml" | 12 -> let # 539 "parsing/lexer.mll" name # 5993 "parsing/lexer.ml" = Lexing.sub_lexeme lexbuf lexbuf.Lexing.lex_start_pos lexbuf.Lexing.lex_curr_pos in # 540 "parsing/lexer.mll" ( UIDENT name ) # 5997 "parsing/lexer.ml" | 13 -> let # 541 "parsing/lexer.mll" escape # 6003 "parsing/lexer.ml" = Lexing.sub_lexeme lexbuf lexbuf.Lexing.lex_start_pos lexbuf.Lexing.lex_mem.(0) and # 541 "parsing/lexer.mll" raw_name # 6008 "parsing/lexer.ml" = Lexing.sub_lexeme lexbuf lexbuf.Lexing.lex_mem.(0) lexbuf.Lexing.lex_curr_pos in # 542 "parsing/lexer.mll" ( let name = ident_for_extended lexbuf raw_name in if Utf8_lexeme.is_capitalized name then begin if escape="" then UIDENT name else (* we don't have capitalized keywords, and thus no needs for capitalized raw identifiers. *) error lexbuf (Capitalized_raw_identifier name) end else LIDENT name ) # 6021 "parsing/lexer.ml" | 14 -> let # 552 "parsing/lexer.mll" lit # 6027 "parsing/lexer.ml" = Lexing.sub_lexeme lexbuf lexbuf.Lexing.lex_start_pos lexbuf.Lexing.lex_curr_pos in # 552 "parsing/lexer.mll" ( INT (lit, None) ) # 6031 "parsing/lexer.ml" | 15 -> let # 553 "parsing/lexer.mll" lit # 6037 "parsing/lexer.ml" = Lexing.sub_lexeme lexbuf lexbuf.Lexing.lex_start_pos (lexbuf.Lexing.lex_curr_pos + -1) and # 553 "parsing/lexer.mll" modif # 6042 "parsing/lexer.ml" = Lexing.sub_lexeme_char lexbuf (lexbuf.Lexing.lex_curr_pos + -1) in # 554 "parsing/lexer.mll" ( INT (lit, Some modif) ) # 6046 "parsing/lexer.ml" | 16 -> let # 555 "parsing/lexer.mll" lit # 6052 "parsing/lexer.ml" = Lexing.sub_lexeme lexbuf lexbuf.Lexing.lex_start_pos lexbuf.Lexing.lex_curr_pos in # 556 "parsing/lexer.mll" ( FLOAT (lit, None) ) # 6056 "parsing/lexer.ml" | 17 -> let # 557 "parsing/lexer.mll" lit # 6062 "parsing/lexer.ml" = Lexing.sub_lexeme lexbuf lexbuf.Lexing.lex_start_pos (lexbuf.Lexing.lex_curr_pos + -1) and # 557 "parsing/lexer.mll" modif # 6067 "parsing/lexer.ml" = Lexing.sub_lexeme_char lexbuf (lexbuf.Lexing.lex_curr_pos + -1) in # 558 "parsing/lexer.mll" ( FLOAT (lit, Some modif) ) # 6071 "parsing/lexer.ml" | 18 -> let # 559 "parsing/lexer.mll" invalid # 6077 "parsing/lexer.ml" = Lexing.sub_lexeme lexbuf lexbuf.Lexing.lex_start_pos lexbuf.Lexing.lex_curr_pos in # 560 "parsing/lexer.mll" ( error lexbuf (Invalid_literal invalid) ) # 6081 "parsing/lexer.ml" | 19 -> # 562 "parsing/lexer.mll" ( let s, loc = wrap_string_lexer string lexbuf in STRING (s, loc, None) ) # 6087 "parsing/lexer.ml" | 20 -> let # 564 "parsing/lexer.mll" raw_name # 6093 "parsing/lexer.ml" = Lexing.sub_lexeme lexbuf (lexbuf.Lexing.lex_start_pos + 1) (lexbuf.Lexing.lex_curr_pos + -1) in # 565 "parsing/lexer.mll" ( let delim = validate_delim lexbuf raw_name in let s, loc = wrap_string_lexer (quoted_string delim) lexbuf in STRING (s, loc, Some delim) ) # 6100 "parsing/lexer.ml" | 21 -> let # 569 "parsing/lexer.mll" raw_id # 6106 "parsing/lexer.ml" = Lexing.sub_lexeme lexbuf (lexbuf.Lexing.lex_start_pos + 2) (lexbuf.Lexing.lex_curr_pos + -1) in # 570 "parsing/lexer.mll" ( let orig_loc = Location.curr lexbuf in let id = validate_ext lexbuf raw_id in let s, loc = wrap_string_lexer (quoted_string "") lexbuf in let idloc = compute_quoted_string_idloc orig_loc 2 id in QUOTED_STRING_EXPR (id, idloc, s, loc, Some "") ) # 6114 "parsing/lexer.ml" | 22 -> let # 575 "parsing/lexer.mll" raw_id # 6120 "parsing/lexer.ml" = Lexing.sub_lexeme lexbuf (lexbuf.Lexing.lex_start_pos + 2) lexbuf.Lexing.lex_mem.(0) and # 575 "parsing/lexer.mll" raw_delim # 6125 "parsing/lexer.ml" = Lexing.sub_lexeme lexbuf lexbuf.Lexing.lex_mem.(1) (lexbuf.Lexing.lex_curr_pos + -1) in # 576 "parsing/lexer.mll" ( let orig_loc = Location.curr lexbuf in let id = validate_ext lexbuf raw_id in let delim = validate_delim lexbuf raw_delim in let s, loc = wrap_string_lexer (quoted_string delim) lexbuf in let idloc = compute_quoted_string_idloc orig_loc 2 id in QUOTED_STRING_EXPR (id, idloc, s, loc, Some delim) ) # 6134 "parsing/lexer.ml" | 23 -> let # 582 "parsing/lexer.mll" raw_id # 6140 "parsing/lexer.ml" = Lexing.sub_lexeme lexbuf (lexbuf.Lexing.lex_start_pos + 3) (lexbuf.Lexing.lex_curr_pos + -1) in # 583 "parsing/lexer.mll" ( let orig_loc = Location.curr lexbuf in let id = validate_ext lexbuf raw_id in let s, loc = wrap_string_lexer (quoted_string "") lexbuf in let idloc = compute_quoted_string_idloc orig_loc 3 id in QUOTED_STRING_ITEM (id, idloc, s, loc, Some "") ) # 6148 "parsing/lexer.ml" | 24 -> let # 588 "parsing/lexer.mll" raw_id # 6154 "parsing/lexer.ml" = Lexing.sub_lexeme lexbuf (lexbuf.Lexing.lex_start_pos + 3) lexbuf.Lexing.lex_mem.(0) and # 588 "parsing/lexer.mll" raw_delim # 6159 "parsing/lexer.ml" = Lexing.sub_lexeme lexbuf lexbuf.Lexing.lex_mem.(1) (lexbuf.Lexing.lex_curr_pos + -1) in # 589 "parsing/lexer.mll" ( let orig_loc = Location.curr lexbuf in let id = validate_ext lexbuf raw_id in let delim = validate_delim lexbuf raw_delim in let s, loc = wrap_string_lexer (quoted_string delim) lexbuf in let idloc = compute_quoted_string_idloc orig_loc 3 id in QUOTED_STRING_ITEM (id, idloc, s, loc, Some delim) ) # 6168 "parsing/lexer.ml" | 25 -> # 596 "parsing/lexer.mll" ( update_loc lexbuf None 1 false 1; (* newline is ('\013'* '\010') *) CHAR '\n' ) # 6175 "parsing/lexer.ml" | 26 -> let # 599 "parsing/lexer.mll" c # 6181 "parsing/lexer.ml" = Lexing.sub_lexeme_char lexbuf (lexbuf.Lexing.lex_start_pos + 1) in # 600 "parsing/lexer.mll" ( CHAR c ) # 6185 "parsing/lexer.ml" | 27 -> let # 601 "parsing/lexer.mll" c # 6191 "parsing/lexer.ml" = Lexing.sub_lexeme_char lexbuf (lexbuf.Lexing.lex_start_pos + 2) in # 602 "parsing/lexer.mll" ( CHAR (char_for_backslash c) ) # 6195 "parsing/lexer.ml" | 28 -> # 604 "parsing/lexer.mll" ( CHAR(char_for_decimal_code lexbuf 2) ) # 6200 "parsing/lexer.ml" | 29 -> # 606 "parsing/lexer.mll" ( CHAR(char_for_octal_code lexbuf 3) ) # 6205 "parsing/lexer.ml" | 30 -> # 608 "parsing/lexer.mll" ( CHAR(char_for_hexadecimal_code lexbuf 3) ) # 6210 "parsing/lexer.ml" | 31 -> let # 609 "parsing/lexer.mll" esc # 6216 "parsing/lexer.ml" = Lexing.sub_lexeme lexbuf (lexbuf.Lexing.lex_start_pos + 1) (lexbuf.Lexing.lex_start_pos + 3) in # 610 "parsing/lexer.mll" ( error lexbuf (Illegal_escape (esc, None)) ) # 6220 "parsing/lexer.ml" | 32 -> # 612 "parsing/lexer.mll" ( error lexbuf Empty_character_literal ) # 6225 "parsing/lexer.ml" | 33 -> # 614 "parsing/lexer.mll" ( let s, loc = wrap_comment_lexer comment lexbuf in COMMENT (s, loc) ) # 6231 "parsing/lexer.ml" | 34 -> # 617 "parsing/lexer.mll" ( let s, loc = wrap_comment_lexer comment lexbuf in if !handle_docstrings then DOCSTRING (Docstrings.docstring s loc) else COMMENT ("*" ^ s, loc) ) # 6241 "parsing/lexer.ml" | 35 -> let # 623 "parsing/lexer.mll" stars # 6247 "parsing/lexer.ml" = Lexing.sub_lexeme lexbuf (lexbuf.Lexing.lex_start_pos + 3) lexbuf.Lexing.lex_curr_pos in # 624 "parsing/lexer.mll" ( let s, loc = wrap_comment_lexer (fun lexbuf -> store_string ("*" ^ stars); comment lexbuf) lexbuf in COMMENT (s, loc) ) # 6258 "parsing/lexer.ml" | 36 -> # 633 "parsing/lexer.mll" ( if !print_warnings then Location.prerr_warning (Location.curr lexbuf) Warnings.Comment_start; let s, loc = wrap_comment_lexer comment lexbuf in COMMENT (s, loc) ) # 6266 "parsing/lexer.ml" | 37 -> let # 637 "parsing/lexer.mll" stars # 6272 "parsing/lexer.ml" = Lexing.sub_lexeme lexbuf (lexbuf.Lexing.lex_start_pos + 2) (lexbuf.Lexing.lex_curr_pos + -2) in # 638 "parsing/lexer.mll" ( if !handle_docstrings && stars="" then (* (**) is an empty docstring *) DOCSTRING(Docstrings.docstring "" (Location.curr lexbuf)) else COMMENT (stars, Location.curr lexbuf) ) # 6280 "parsing/lexer.ml" | 38 -> # 644 "parsing/lexer.mll" ( let loc = Location.curr lexbuf in Location.prerr_warning loc Warnings.Comment_not_end; lexbuf.Lexing.lex_curr_pos <- lexbuf.Lexing.lex_curr_pos - 1; let curpos = lexbuf.lex_curr_p in lexbuf.lex_curr_p <- { curpos with pos_cnum = curpos.pos_cnum - 1 }; STAR ) # 6291 "parsing/lexer.ml" | 39 -> # 652 "parsing/lexer.mll" ( let at_beginning_of_line pos = (pos.pos_cnum = pos.pos_bol) in if not (at_beginning_of_line lexbuf.lex_start_p) then HASH else try directive lexbuf with Failure _ -> HASH ) # 6300 "parsing/lexer.ml" | 40 -> # 657 "parsing/lexer.mll" ( AMPERSAND ) # 6305 "parsing/lexer.ml" | 41 -> # 658 "parsing/lexer.mll" ( AMPERAMPER ) # 6310 "parsing/lexer.ml" | 42 -> # 659 "parsing/lexer.mll" ( BACKQUOTE ) # 6315 "parsing/lexer.ml" | 43 -> # 660 "parsing/lexer.mll" ( QUOTE ) # 6320 "parsing/lexer.ml" | 44 -> # 661 "parsing/lexer.mll" ( LPAREN ) # 6325 "parsing/lexer.ml" | 45 -> # 662 "parsing/lexer.mll" ( RPAREN ) # 6330 "parsing/lexer.ml" | 46 -> # 663 "parsing/lexer.mll" ( STAR ) # 6335 "parsing/lexer.ml" | 47 -> # 664 "parsing/lexer.mll" ( COMMA ) # 6340 "parsing/lexer.ml" | 48 -> # 665 "parsing/lexer.mll" ( MINUSGREATER ) # 6345 "parsing/lexer.ml" | 49 -> # 666 "parsing/lexer.mll" ( DOT ) # 6350 "parsing/lexer.ml" | 50 -> # 667 "parsing/lexer.mll" ( DOTDOT ) # 6355 "parsing/lexer.ml" | 51 -> let # 668 "parsing/lexer.mll" op # 6361 "parsing/lexer.ml" = Lexing.sub_lexeme lexbuf (lexbuf.Lexing.lex_start_pos + 1) lexbuf.Lexing.lex_curr_pos in # 668 "parsing/lexer.mll" ( DOTOP op ) # 6365 "parsing/lexer.ml" | 52 -> # 669 "parsing/lexer.mll" ( COLON ) # 6370 "parsing/lexer.ml" | 53 -> # 670 "parsing/lexer.mll" ( COLONCOLON ) # 6375 "parsing/lexer.ml" | 54 -> # 671 "parsing/lexer.mll" ( COLONEQUAL ) # 6380 "parsing/lexer.ml" | 55 -> # 672 "parsing/lexer.mll" ( COLONGREATER ) # 6385 "parsing/lexer.ml" | 56 -> # 673 "parsing/lexer.mll" ( SEMI ) # 6390 "parsing/lexer.ml" | 57 -> # 674 "parsing/lexer.mll" ( SEMISEMI ) # 6395 "parsing/lexer.ml" | 58 -> # 675 "parsing/lexer.mll" ( LESS ) # 6400 "parsing/lexer.ml" | 59 -> # 676 "parsing/lexer.mll" ( LESSMINUS ) # 6405 "parsing/lexer.ml" | 60 -> # 677 "parsing/lexer.mll" ( EQUAL ) # 6410 "parsing/lexer.ml" | 61 -> # 678 "parsing/lexer.mll" ( LBRACKET ) # 6415 "parsing/lexer.ml" | 62 -> # 679 "parsing/lexer.mll" ( LBRACKETBAR ) # 6420 "parsing/lexer.ml" | 63 -> # 680 "parsing/lexer.mll" ( LBRACKETLESS ) # 6425 "parsing/lexer.ml" | 64 -> # 681 "parsing/lexer.mll" ( LBRACKETGREATER ) # 6430 "parsing/lexer.ml" | 65 -> # 682 "parsing/lexer.mll" ( RBRACKET ) # 6435 "parsing/lexer.ml" | 66 -> # 683 "parsing/lexer.mll" ( LBRACE ) # 6440 "parsing/lexer.ml" | 67 -> # 684 "parsing/lexer.mll" ( LBRACELESS ) # 6445 "parsing/lexer.ml" | 68 -> # 685 "parsing/lexer.mll" ( BAR ) # 6450 "parsing/lexer.ml" | 69 -> # 686 "parsing/lexer.mll" ( BARBAR ) # 6455 "parsing/lexer.ml" | 70 -> # 687 "parsing/lexer.mll" ( BARRBRACKET ) # 6460 "parsing/lexer.ml" | 71 -> # 688 "parsing/lexer.mll" ( GREATER ) # 6465 "parsing/lexer.ml" | 72 -> # 689 "parsing/lexer.mll" ( GREATERRBRACKET ) # 6470 "parsing/lexer.ml" | 73 -> # 690 "parsing/lexer.mll" ( RBRACE ) # 6475 "parsing/lexer.ml" | 74 -> # 691 "parsing/lexer.mll" ( GREATERRBRACE ) # 6480 "parsing/lexer.ml" | 75 -> # 692 "parsing/lexer.mll" ( LBRACKETAT ) # 6485 "parsing/lexer.ml" | 76 -> # 693 "parsing/lexer.mll" ( LBRACKETATAT ) # 6490 "parsing/lexer.ml" | 77 -> # 694 "parsing/lexer.mll" ( LBRACKETATATAT ) # 6495 "parsing/lexer.ml" | 78 -> # 695 "parsing/lexer.mll" ( LBRACKETPERCENT ) # 6500 "parsing/lexer.ml" | 79 -> # 696 "parsing/lexer.mll" ( LBRACKETPERCENTPERCENT ) # 6505 "parsing/lexer.ml" | 80 -> # 697 "parsing/lexer.mll" ( BANG ) # 6510 "parsing/lexer.ml" | 81 -> # 698 "parsing/lexer.mll" ( INFIXOP0 "!=" ) # 6515 "parsing/lexer.ml" | 82 -> # 699 "parsing/lexer.mll" ( PLUS ) # 6520 "parsing/lexer.ml" | 83 -> # 700 "parsing/lexer.mll" ( PLUSDOT ) # 6525 "parsing/lexer.ml" | 84 -> # 701 "parsing/lexer.mll" ( PLUSEQ ) # 6530 "parsing/lexer.ml" | 85 -> # 702 "parsing/lexer.mll" ( MINUS ) # 6535 "parsing/lexer.ml" | 86 -> # 703 "parsing/lexer.mll" ( MINUSDOT ) # 6540 "parsing/lexer.ml" | 87 -> let # 705 "parsing/lexer.mll" op # 6546 "parsing/lexer.ml" = Lexing.sub_lexeme lexbuf lexbuf.Lexing.lex_start_pos lexbuf.Lexing.lex_curr_pos in # 706 "parsing/lexer.mll" ( PREFIXOP op ) # 6550 "parsing/lexer.ml" | 88 -> let # 707 "parsing/lexer.mll" op # 6556 "parsing/lexer.ml" = Lexing.sub_lexeme lexbuf lexbuf.Lexing.lex_start_pos lexbuf.Lexing.lex_curr_pos in # 708 "parsing/lexer.mll" ( PREFIXOP op ) # 6560 "parsing/lexer.ml" | 89 -> let # 709 "parsing/lexer.mll" op # 6566 "parsing/lexer.ml" = Lexing.sub_lexeme lexbuf lexbuf.Lexing.lex_start_pos lexbuf.Lexing.lex_curr_pos in # 710 "parsing/lexer.mll" ( INFIXOP0 op ) # 6570 "parsing/lexer.ml" | 90 -> let # 711 "parsing/lexer.mll" op # 6576 "parsing/lexer.ml" = Lexing.sub_lexeme lexbuf lexbuf.Lexing.lex_start_pos lexbuf.Lexing.lex_curr_pos in # 712 "parsing/lexer.mll" ( INFIXOP1 op ) # 6580 "parsing/lexer.ml" | 91 -> let # 713 "parsing/lexer.mll" op # 6586 "parsing/lexer.ml" = Lexing.sub_lexeme lexbuf lexbuf.Lexing.lex_start_pos lexbuf.Lexing.lex_curr_pos in # 714 "parsing/lexer.mll" ( INFIXOP2 op ) # 6590 "parsing/lexer.ml" | 92 -> let # 715 "parsing/lexer.mll" op # 6596 "parsing/lexer.ml" = Lexing.sub_lexeme lexbuf lexbuf.Lexing.lex_start_pos lexbuf.Lexing.lex_curr_pos in # 716 "parsing/lexer.mll" ( INFIXOP4 op ) # 6600 "parsing/lexer.ml" | 93 -> # 717 "parsing/lexer.mll" ( PERCENT ) # 6605 "parsing/lexer.ml" | 94 -> let # 718 "parsing/lexer.mll" op # 6611 "parsing/lexer.ml" = Lexing.sub_lexeme lexbuf lexbuf.Lexing.lex_start_pos lexbuf.Lexing.lex_curr_pos in # 719 "parsing/lexer.mll" ( INFIXOP3 op ) # 6615 "parsing/lexer.ml" | 95 -> let # 720 "parsing/lexer.mll" op # 6621 "parsing/lexer.ml" = Lexing.sub_lexeme lexbuf lexbuf.Lexing.lex_start_pos lexbuf.Lexing.lex_curr_pos in # 721 "parsing/lexer.mll" ( HASHOP op ) # 6625 "parsing/lexer.ml" | 96 -> let # 722 "parsing/lexer.mll" op # 6631 "parsing/lexer.ml" = Lexing.sub_lexeme lexbuf lexbuf.Lexing.lex_start_pos lexbuf.Lexing.lex_curr_pos in # 723 "parsing/lexer.mll" ( LETOP op ) # 6635 "parsing/lexer.ml" | 97 -> let # 724 "parsing/lexer.mll" op # 6641 "parsing/lexer.ml" = Lexing.sub_lexeme lexbuf lexbuf.Lexing.lex_start_pos lexbuf.Lexing.lex_curr_pos in # 725 "parsing/lexer.mll" ( ANDOP op ) # 6645 "parsing/lexer.ml" | 98 -> # 726 "parsing/lexer.mll" ( EOF ) # 6650 "parsing/lexer.ml" | 99 -> let # 727 "parsing/lexer.mll" illegal_char # 6656 "parsing/lexer.ml" = Lexing.sub_lexeme_char lexbuf lexbuf.Lexing.lex_start_pos in # 728 "parsing/lexer.mll" ( error lexbuf (Illegal_character illegal_char) ) # 6660 "parsing/lexer.ml" | __ocaml_lex_state -> lexbuf.Lexing.refill_buff lexbuf; __ocaml_lex_token_rec lexbuf __ocaml_lex_state and directive lexbuf = lexbuf.Lexing.lex_mem <- Array.make 8 (-1);(* L=1 [4] <- p ; *) lexbuf.Lexing.lex_mem.(4) <- lexbuf.Lexing.lex_curr_pos ; __ocaml_lex_directive_rec lexbuf 180 and __ocaml_lex_directive_rec lexbuf __ocaml_lex_state = match Lexing.new_engine __ocaml_lex_tables __ocaml_lex_state lexbuf with | 0 -> let # 731 "parsing/lexer.mll" num # 6675 "parsing/lexer.ml" = Lexing.sub_lexeme lexbuf lexbuf.Lexing.lex_mem.(0) lexbuf.Lexing.lex_mem.(1) and # 732 "parsing/lexer.mll" name # 6680 "parsing/lexer.ml" = Lexing.sub_lexeme lexbuf lexbuf.Lexing.lex_mem.(2) lexbuf.Lexing.lex_mem.(3) and # 732 "parsing/lexer.mll" directive # 6685 "parsing/lexer.ml" = Lexing.sub_lexeme lexbuf lexbuf.Lexing.lex_start_pos (lexbuf.Lexing.lex_mem.(3) + 1) in # 734 "parsing/lexer.mll" ( match int_of_string num with | exception _ -> (* PR#7165 *) let explanation = "line number out of range" in error lexbuf (Invalid_directive ("#" ^ directive, Some explanation)) | line_num -> (* Documentation says that the line number should be positive, but we have never guarded against this and it might have useful hackish uses. *) update_loc lexbuf (Some name) (line_num - 1) true 0; token lexbuf ) # 6701 "parsing/lexer.ml" | __ocaml_lex_state -> lexbuf.Lexing.refill_buff lexbuf; __ocaml_lex_directive_rec lexbuf __ocaml_lex_state and comment lexbuf = lexbuf.Lexing.lex_mem <- Array.make 3 (-1); __ocaml_lex_comment_rec lexbuf 185 and __ocaml_lex_comment_rec lexbuf __ocaml_lex_state = match Lexing.new_engine __ocaml_lex_tables __ocaml_lex_state lexbuf with | 0 -> # 749 "parsing/lexer.mll" ( comment_start_loc := (Location.curr lexbuf) :: !comment_start_loc; store_lexeme lexbuf; comment lexbuf ) # 6716 "parsing/lexer.ml" | 1 -> # 754 "parsing/lexer.mll" ( match !comment_start_loc with | [] -> assert false | [_] -> comment_start_loc := []; Location.curr lexbuf | _ :: l -> comment_start_loc := l; store_lexeme lexbuf; comment lexbuf ) # 6727 "parsing/lexer.ml" | 2 -> # 762 "parsing/lexer.mll" ( string_start_loc := Location.curr lexbuf; store_string_char '\"'; is_in_string := true; let _loc = try string lexbuf with Error (Unterminated_string, str_start) -> match !comment_start_loc with | [] -> assert false | loc :: _ -> let start = List.hd (List.rev !comment_start_loc) in comment_start_loc := []; error_loc loc (Unterminated_string_in_comment (start, str_start)) in is_in_string := false; store_string_char '\"'; comment lexbuf ) # 6747 "parsing/lexer.ml" | 3 -> let # 778 "parsing/lexer.mll" raw_delim # 6753 "parsing/lexer.ml" = Lexing.sub_lexeme lexbuf lexbuf.Lexing.lex_mem.(0) (lexbuf.Lexing.lex_curr_pos + -1) in # 779 "parsing/lexer.mll" ( match lax_delim raw_delim with | None -> store_lexeme lexbuf; comment lexbuf | Some delim -> string_start_loc := Location.curr lexbuf; store_lexeme lexbuf; is_in_string := true; let _loc = try quoted_string delim lexbuf with Error (Unterminated_string, str_start) -> match !comment_start_loc with | [] -> assert false | loc :: _ -> let start = List.hd (List.rev !comment_start_loc) in comment_start_loc := []; error_loc loc (Unterminated_string_in_comment (start, str_start)) in is_in_string := false; store_string_char '|'; store_string delim; store_string_char '}'; comment lexbuf ) # 6776 "parsing/lexer.ml" | 4 -> # 800 "parsing/lexer.mll" ( store_lexeme lexbuf; comment lexbuf ) # 6781 "parsing/lexer.ml" | 5 -> let # 801 "parsing/lexer.mll" nl # 6787 "parsing/lexer.ml" = Lexing.sub_lexeme lexbuf (lexbuf.Lexing.lex_start_pos + 1) (lexbuf.Lexing.lex_curr_pos + -1) in # 802 "parsing/lexer.mll" ( update_loc lexbuf None 1 false 1; store_string_char '\''; store_normalized_newline nl; store_string_char '\''; comment lexbuf ) # 6796 "parsing/lexer.ml" | 6 -> # 809 "parsing/lexer.mll" ( store_lexeme lexbuf; comment lexbuf ) # 6801 "parsing/lexer.ml" | 7 -> # 811 "parsing/lexer.mll" ( store_lexeme lexbuf; comment lexbuf ) # 6806 "parsing/lexer.ml" | 8 -> # 813 "parsing/lexer.mll" ( store_lexeme lexbuf; comment lexbuf ) # 6811 "parsing/lexer.ml" | 9 -> # 815 "parsing/lexer.mll" ( store_lexeme lexbuf; comment lexbuf ) # 6816 "parsing/lexer.ml" | 10 -> # 817 "parsing/lexer.mll" ( store_lexeme lexbuf; comment lexbuf ) # 6821 "parsing/lexer.ml" | 11 -> # 819 "parsing/lexer.mll" ( match !comment_start_loc with | [] -> assert false | loc :: _ -> let start = List.hd (List.rev !comment_start_loc) in comment_start_loc := []; error_loc loc (Unterminated_comment start) ) # 6832 "parsing/lexer.ml" | 12 -> let # 826 "parsing/lexer.mll" nl # 6838 "parsing/lexer.ml" = Lexing.sub_lexeme lexbuf lexbuf.Lexing.lex_start_pos lexbuf.Lexing.lex_curr_pos in # 827 "parsing/lexer.mll" ( update_loc lexbuf None 1 false 0; store_normalized_newline nl; comment lexbuf ) # 6845 "parsing/lexer.ml" | 13 -> # 832 "parsing/lexer.mll" ( store_lexeme lexbuf; comment lexbuf ) # 6850 "parsing/lexer.ml" | 14 -> # 834 "parsing/lexer.mll" ( store_lexeme lexbuf; comment lexbuf ) # 6855 "parsing/lexer.ml" | __ocaml_lex_state -> lexbuf.Lexing.refill_buff lexbuf; __ocaml_lex_comment_rec lexbuf __ocaml_lex_state and string lexbuf = lexbuf.Lexing.lex_mem <- Array.make 2 (-1); __ocaml_lex_string_rec lexbuf 236 and __ocaml_lex_string_rec lexbuf __ocaml_lex_state = match Lexing.new_engine __ocaml_lex_tables __ocaml_lex_state lexbuf with | 0 -> # 838 "parsing/lexer.mll" ( lexbuf.lex_start_p ) # 6867 "parsing/lexer.ml" | 1 -> let # 839 "parsing/lexer.mll" nl # 6873 "parsing/lexer.ml" = Lexing.sub_lexeme lexbuf (lexbuf.Lexing.lex_start_pos + 1) lexbuf.Lexing.lex_mem.(0) and # 839 "parsing/lexer.mll" space # 6878 "parsing/lexer.ml" = Lexing.sub_lexeme lexbuf lexbuf.Lexing.lex_mem.(0) lexbuf.Lexing.lex_curr_pos in # 840 "parsing/lexer.mll" ( update_loc lexbuf None 1 false (String.length space); if in_comment () then begin store_string_char '\\'; store_normalized_newline nl; store_string space; end; string lexbuf ) # 6889 "parsing/lexer.ml" | 2 -> let # 848 "parsing/lexer.mll" c # 6895 "parsing/lexer.ml" = Lexing.sub_lexeme_char lexbuf (lexbuf.Lexing.lex_start_pos + 1) in # 849 "parsing/lexer.mll" ( store_escaped_char lexbuf (char_for_backslash c); string lexbuf ) # 6900 "parsing/lexer.ml" | 3 -> # 852 "parsing/lexer.mll" ( store_escaped_char lexbuf (char_for_decimal_code lexbuf 1); string lexbuf ) # 6906 "parsing/lexer.ml" | 4 -> # 855 "parsing/lexer.mll" ( store_escaped_char lexbuf (char_for_octal_code lexbuf 2); string lexbuf ) # 6912 "parsing/lexer.ml" | 5 -> # 858 "parsing/lexer.mll" ( store_escaped_char lexbuf (char_for_hexadecimal_code lexbuf 2); string lexbuf ) # 6918 "parsing/lexer.ml" | 6 -> # 861 "parsing/lexer.mll" ( store_escaped_uchar lexbuf (uchar_for_uchar_escape lexbuf); string lexbuf ) # 6924 "parsing/lexer.ml" | 7 -> # 864 "parsing/lexer.mll" ( if not (in_comment ()) then begin (* Should be an error, but we are very lax. error lexbuf (Illegal_escape (Lexing.lexeme lexbuf, None)) *) let loc = Location.curr lexbuf in Location.prerr_warning loc Warnings.Illegal_backslash; end; store_lexeme lexbuf; string lexbuf ) # 6938 "parsing/lexer.ml" | 8 -> let # 874 "parsing/lexer.mll" nl # 6944 "parsing/lexer.ml" = Lexing.sub_lexeme lexbuf lexbuf.Lexing.lex_start_pos lexbuf.Lexing.lex_curr_pos in # 875 "parsing/lexer.mll" ( update_loc lexbuf None 1 false 0; store_normalized_newline nl; string lexbuf ) # 6951 "parsing/lexer.ml" | 9 -> # 880 "parsing/lexer.mll" ( is_in_string := false; error_loc !string_start_loc Unterminated_string ) # 6957 "parsing/lexer.ml" | 10 -> let # 882 "parsing/lexer.mll" c # 6963 "parsing/lexer.ml" = Lexing.sub_lexeme_char lexbuf lexbuf.Lexing.lex_start_pos in # 883 "parsing/lexer.mll" ( store_string_char c; string lexbuf ) # 6968 "parsing/lexer.ml" | __ocaml_lex_state -> lexbuf.Lexing.refill_buff lexbuf; __ocaml_lex_string_rec lexbuf __ocaml_lex_state and quoted_string delim lexbuf = __ocaml_lex_quoted_string_rec delim lexbuf 263 and __ocaml_lex_quoted_string_rec delim lexbuf __ocaml_lex_state = match Lexing.engine __ocaml_lex_tables __ocaml_lex_state lexbuf with | 0 -> let # 887 "parsing/lexer.mll" nl # 6981 "parsing/lexer.ml" = Lexing.sub_lexeme lexbuf lexbuf.Lexing.lex_start_pos lexbuf.Lexing.lex_curr_pos in # 888 "parsing/lexer.mll" ( update_loc lexbuf None 1 false 0; store_normalized_newline nl; quoted_string delim lexbuf ) # 6988 "parsing/lexer.ml" | 1 -> # 893 "parsing/lexer.mll" ( is_in_string := false; error_loc !string_start_loc Unterminated_string ) # 6994 "parsing/lexer.ml" | 2 -> let # 895 "parsing/lexer.mll" raw_edelim # 7000 "parsing/lexer.ml" = Lexing.sub_lexeme lexbuf (lexbuf.Lexing.lex_start_pos + 1) (lexbuf.Lexing.lex_curr_pos + -1) in # 896 "parsing/lexer.mll" ( let edelim = validate_encoding lexbuf raw_edelim in if delim = edelim then lexbuf.lex_start_p else (store_lexeme lexbuf; quoted_string delim lexbuf) ) # 7008 "parsing/lexer.ml" | 3 -> let # 901 "parsing/lexer.mll" c # 7014 "parsing/lexer.ml" = Lexing.sub_lexeme_char lexbuf lexbuf.Lexing.lex_start_pos in # 902 "parsing/lexer.mll" ( store_string_char c; quoted_string delim lexbuf ) # 7019 "parsing/lexer.ml" | __ocaml_lex_state -> lexbuf.Lexing.refill_buff lexbuf; __ocaml_lex_quoted_string_rec delim lexbuf __ocaml_lex_state and skip_hash_bang lexbuf = __ocaml_lex_skip_hash_bang_rec lexbuf 274 and __ocaml_lex_skip_hash_bang_rec lexbuf __ocaml_lex_state = match Lexing.engine __ocaml_lex_tables __ocaml_lex_state lexbuf with | 0 -> # 907 "parsing/lexer.mll" ( update_loc lexbuf None 3 false 0 ) # 7031 "parsing/lexer.ml" | 1 -> # 909 "parsing/lexer.mll" ( update_loc lexbuf None 1 false 0 ) # 7036 "parsing/lexer.ml" | 2 -> # 910 "parsing/lexer.mll" ( () ) # 7041 "parsing/lexer.ml" | __ocaml_lex_state -> lexbuf.Lexing.refill_buff lexbuf; __ocaml_lex_skip_hash_bang_rec lexbuf __ocaml_lex_state ;; # 912 "parsing/lexer.mll" let token_with_comments lexbuf = match !preprocessor with | None -> token lexbuf | Some (_init, preprocess) -> preprocess token lexbuf type newline_state = | NoLine (* There have been no blank lines yet. *) | NewLine (* There have been no blank lines, and the previous token was a newline. *) | BlankLine (* There have been blank lines. *) type doc_state = | Initial (* There have been no docstrings yet *) | After of docstring list (* There have been docstrings, none of which were preceded by a blank line *) | Before of docstring list * docstring list * docstring list (* There have been docstrings, some of which were preceded by a blank line *) and docstring = Docstrings.docstring let token lexbuf = let post_pos = lexeme_end_p lexbuf in let attach lines docs pre_pos = let open Docstrings in match docs, lines with | Initial, _ -> () | After a, (NoLine | NewLine) -> set_post_docstrings post_pos (List.rev a); set_pre_docstrings pre_pos a; | After a, BlankLine -> set_post_docstrings post_pos (List.rev a); set_pre_extra_docstrings pre_pos (List.rev a) | Before(a, f, b), (NoLine | NewLine) -> set_post_docstrings post_pos (List.rev a); set_post_extra_docstrings post_pos (List.rev_append f (List.rev b)); set_floating_docstrings pre_pos (List.rev f); set_pre_extra_docstrings pre_pos (List.rev a); set_pre_docstrings pre_pos b | Before(a, f, b), BlankLine -> set_post_docstrings post_pos (List.rev a); set_post_extra_docstrings post_pos (List.rev_append f (List.rev b)); set_floating_docstrings pre_pos (List.rev_append f (List.rev b)); set_pre_extra_docstrings pre_pos (List.rev a) in let rec loop lines docs lexbuf = match token_with_comments lexbuf with | COMMENT (s, loc) -> add_comment (s, loc); let lines' = match lines with | NoLine -> NoLine | NewLine -> NoLine | BlankLine -> BlankLine in loop lines' docs lexbuf | EOL -> let lines' = match lines with | NoLine -> NewLine | NewLine -> BlankLine | BlankLine -> BlankLine in loop lines' docs lexbuf | DOCSTRING doc -> Docstrings.register doc; add_docstring_comment doc; let docs' = if Docstrings.docstring_body doc = "/*" then match docs with | Initial -> Before([], [doc], []) | After a -> Before (a, [doc], []) | Before(a, f, b) -> Before(a, doc :: b @ f, []) else match docs, lines with | Initial, (NoLine | NewLine) -> After [doc] | Initial, BlankLine -> Before([], [], [doc]) | After a, (NoLine | NewLine) -> After (doc :: a) | After a, BlankLine -> Before (a, [], [doc]) | Before(a, f, b), (NoLine | NewLine) -> Before(a, f, doc :: b) | Before(a, f, b), BlankLine -> Before(a, b @ f, [doc]) in loop NoLine docs' lexbuf | tok -> attach lines docs (lexeme_start_p lexbuf); tok in loop NoLine Initial lexbuf let init ?(keyword_edition=None,[]) () = populate_keywords keyword_edition; is_in_string := false; comment_start_loc := []; comment_list := []; match !preprocessor with | None -> () | Some (init, _preprocess) -> init () let set_preprocessor init preprocess = escaped_newlines := true; preprocessor := Some (init, preprocess) # 7159 "parsing/lexer.ml"