# 1 "odoc_ocamlhtml.mll" (**************************************************************************) (* *) (* OCaml *) (* *) (* Maxence Guesdon, projet Cristal, INRIA Rocquencourt *) (* *) (* Copyright 2001 Institut National de Recherche en Informatique et *) (* en Automatique. *) (* *) (* All rights reserved. This file is distributed under the terms of *) (* the GNU Lesser General Public License version 2.1, with the *) (* special exception on linking described in the file LICENSE. *) (* *) (**************************************************************************) (** Generation of html code to display OCaml code. *) open Lexing exception Fatal_error let fatal_error msg = prerr_string ">> Fatal error: "; prerr_endline msg; raise Fatal_error type error = | Illegal_character of char | Unterminated_comment | Unterminated_string | Unterminated_string_in_comment | Keyword_as_label of string ;; exception Error of error * int * int let base_escape_strings = [ ("&", "&") ; ("<", "<") ; (">", ">") ; ] let prelike_escape_strings = [ (" ", " ") ; ("\t", "        ") ; ("\n", "
\n") ] let pre = ref false let fmt = ref Format.str_formatter (** Escape the strings which would clash with html syntax, and some other strings if we want to get a PRE style outside of
 
.*) let escape s = let escape_strings = if !pre then base_escape_strings else base_escape_strings @ prelike_escape_strings in List.fold_left (fun acc -> fun (s, s2) -> Str.global_replace (Str.regexp s) s2 acc) s escape_strings (** Escape the strings which would clash with html syntax. *) let escape_base s = List.fold_left (fun acc -> fun (s, s2) -> Str.global_replace (Str.regexp s) s2 acc) s base_escape_strings (** The output functions *) let print ?(esc=true) s = Format.pp_print_string !fmt (if esc then escape s else s) ;; let print_class ?(esc=true) cl s = print ~esc: false (""^ (if esc then escape s else s)^ "") ;; (** The table of keywords with colors *) let create_hashtable size init = let tbl = Hashtbl.create size in List.iter (fun (key, data) -> Hashtbl.add tbl key data) init; tbl (** The function used to return html code for the given comment body. *) let html_of_comment = ref (fun (_ : string) -> "Odoc_ocamlhtml.html_of_comment not initialized") let keyword_table = create_hashtable 149 [ "and", "keyword" ; "as", "keyword" ; "assert", "keyword" ; "begin", "keyword" ; "class", "keyword" ; "constraint", "keyword" ; "do", "keyword" ; "done", "keyword" ; "downto", "keyword" ; "else", "keyword" ; "end", "keyword" ; "exception", "keyword" ; "external", "keyword" ; "false", "keyword" ; "for", "keyword" ; "fun", "keyword" ; "function", "keyword" ; "functor", "keyword" ; "if", "keyword" ; "in", "keyword" ; "include", "keyword" ; "inherit", "keyword" ; "initializer", "keyword" ; "lazy", "keyword" ; "let", "keyword" ; "match", "keyword" ; "method", "keyword" ; "module", "keyword" ; "mutable", "keyword" ; "new", "keyword" ; "object", "keyword" ; "of", "keyword" ; "open", "keyword" ; "or", "keyword" ; "parser", "keyword" ; "private", "keyword" ; "rec", "keyword" ; "sig", "keyword" ; "struct", "keyword" ; "then", "keyword" ; "to", "keyword" ; "true", "keyword" ; "try", "keyword" ; "type", "keyword" ; "val", "keyword" ; "virtual", "keyword" ; "when", "keyword" ; "while", "keyword" ; "with", "keyword" ; "mod", "keyword" ; "land", "keyword" ; "lor", "keyword" ; "lxor", "keyword" ; "lsl", "keyword" ; "lsr", "keyword" ; "asr", "keyword" ; ] let kwsign_class = "keywordsign" let constructor_class = "constructor" let comment_class = "comment" let string_class = "string" let code_class = "code" (** To buffer and print comments *) let margin = ref 0 let comment_buffer = Buffer.create 32 let reset_comment_buffer () = Buffer.reset comment_buffer let store_comment_char = Buffer.add_char comment_buffer let add_comment_string = Buffer.add_string comment_buffer let make_margin () = let rec iter n = if n <= 0 then "" else " "^(iter (n-1)) in iter !margin let print_comment () = let s = Buffer.contents comment_buffer in let len = String.length s in let code = if len < 1 then "(*"^(escape s)^"*)" else match s.[0] with '*' -> ( try let html = !html_of_comment (String.sub s 1 (len-1)) in "
"^(make_margin ())^""^ ""^ "(**"^html^"*)"^ "
" with e -> prerr_endline (Printexc.to_string e); "(*"^(escape s)^"*)" ) | _ -> "(*"^(escape s)^"*)" in print ~esc: false code (** To buffer string literals *) let string_buffer = Buffer.create 32 let reset_string_buffer () = Buffer.reset string_buffer let store_string_char = Buffer.add_char string_buffer let get_stored_string () = Buffer.contents string_buffer (** To translate escape sequences *) let char_for_backslash = function | 'n' -> '\010' | 'r' -> '\013' | 'b' -> '\008' | 't' -> '\009' | c -> c let char_for_decimal_code lexbuf i = let c = 100 * (Char.code(Lexing.lexeme_char lexbuf i) - 48) + 10 * (Char.code(Lexing.lexeme_char lexbuf (i+1)) - 48) + (Char.code(Lexing.lexeme_char lexbuf (i+2)) - 48) in Char.chr(c land 0xFF) let char_for_hexa_code lexbuf i = let c = 16 * (Char.code(Lexing.lexeme_char lexbuf i) - 48) + (Char.code(Lexing.lexeme_char lexbuf (i+1)) - 48) in Char.chr(c land 0xFF) (** To store the position of the beginning of a string and comment *) let string_start_pos = ref 0;; let comment_start_pos = ref [];; let in_comment () = !comment_start_pos <> [];; (** Error report *) open Format let report_error ppf = function | Illegal_character c -> fprintf ppf "Illegal character (%s)" (Char.escaped c) | Unterminated_comment -> fprintf ppf "Comment not terminated" | Unterminated_string -> fprintf ppf "String literal not terminated" | Unterminated_string_in_comment -> fprintf ppf "This comment contains an unterminated string literal" | Keyword_as_label kwd -> fprintf ppf "`%s' is a keyword, it cannot be used as label name" kwd ;; # 259 "odoc_ocamlhtml.ml" let __ocaml_lex_tables = { Lexing.lex_base = "\000\000\190\255\191\255\224\000\003\001\038\001\073\001\108\001\ \204\255\143\001\180\001\032\000\212\255\067\000\217\001\252\001\ \069\000\071\000\084\000\031\002\229\255\231\255\234\255\066\002\ \122\000\101\002\092\000\123\000\245\255\089\000\120\002\193\002\ \145\003\112\004\204\004\156\005\255\255\123\006\153\006\252\255\ \120\007\150\007\250\255\017\003\224\000\099\000\132\000\220\003\ \064\005\003\001\101\000\027\003\037\003\147\004\097\000\244\255\ \047\003\112\000\243\255\057\003\113\000\242\255\112\000\240\255\ \117\008\239\255\020\006\019\004\001\000\238\255\007\000\152\008\ \187\008\222\008\001\009\225\255\221\255\222\255\223\255\219\255\ \036\009\213\255\214\255\210\255\207\255\071\009\203\255\205\255\ \106\009\141\009\117\000\252\255\253\255\114\000\114\000\255\255\ \254\255\224\000\249\255\250\255\162\009\255\255\235\009\067\003\ \253\255\156\000\003\001\243\003\252\255\054\010\251\255"; Lexing.lex_backtrk = "\255\255\255\255\255\255\063\000\060\000\059\000\054\000\057\000\ \255\255\049\000\046\000\044\000\255\255\040\000\039\000\037\000\ \035\000\031\000\029\000\055\000\255\255\255\255\255\255\019\000\ \018\000\025\000\023\000\022\000\255\255\008\000\008\000\007\000\ \006\000\004\000\002\000\001\000\255\255\058\000\255\255\255\255\ \027\000\255\255\255\255\255\255\009\000\255\255\255\255\255\255\ \008\000\008\000\008\000\009\000\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\014\000\255\255\ \062\000\255\255\255\255\255\255\017\000\255\255\255\255\020\000\ \061\000\056\000\028\000\255\255\255\255\255\255\255\255\255\255\ \038\000\255\255\255\255\255\255\255\255\047\000\255\255\255\255\ \057\000\053\000\255\255\255\255\255\255\003\000\003\000\255\255\ \255\255\255\255\255\255\255\255\006\000\255\255\255\255\255\255\ \255\255\001\000\001\000\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\ \000\000\255\255\255\255\255\255\000\000\255\255\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\054\000\000\000\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\000\000\255\255\255\255\000\000\ \255\255\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\000\000\255\255\255\255\000\000\255\255\000\000\ \255\255\000\000\070\000\255\255\255\255\000\000\070\000\255\255\ \255\255\255\255\255\255\000\000\000\000\000\000\000\000\000\000\ \255\255\000\000\000\000\000\000\000\000\255\255\000\000\000\000\ \255\255\255\255\091\000\000\000\000\000\255\255\255\255\000\000\ \000\000\098\000\000\000\000\000\255\255\000\000\255\255\255\255\ \000\000\255\255\255\255\255\255\000\000\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\036\000\036\000\069\000\036\000\036\000\000\000\000\000\ \000\000\069\000\000\000\000\000\068\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \036\000\007\000\028\000\024\000\005\000\003\000\023\000\027\000\ \026\000\021\000\025\000\006\000\020\000\019\000\018\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\009\000\033\000\ \004\000\031\000\031\000\031\000\031\000\031\000\031\000\031\000\ \031\000\031\000\031\000\031\000\031\000\031\000\031\000\031\000\ \031\000\031\000\031\000\031\000\031\000\031\000\031\000\031\000\ \031\000\031\000\031\000\013\000\083\000\012\000\004\000\035\000\ \022\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\011\000\010\000\008\000\034\000\081\000\ \079\000\078\000\075\000\067\000\077\000\076\000\062\000\044\000\ \055\000\029\000\029\000\029\000\029\000\029\000\029\000\029\000\ \029\000\029\000\029\000\050\000\050\000\050\000\050\000\058\000\ \061\000\063\000\067\000\096\000\095\000\094\000\043\000\093\000\ \000\000\000\000\255\255\000\000\000\000\106\000\106\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\049\000\049\000\049\000\049\000\ \049\000\049\000\049\000\049\000\106\000\000\000\043\000\082\000\ \031\000\031\000\031\000\031\000\031\000\031\000\031\000\031\000\ \031\000\031\000\031\000\031\000\031\000\031\000\031\000\031\000\ \031\000\031\000\031\000\031\000\031\000\031\000\031\000\053\000\ \031\000\031\000\031\000\031\000\031\000\031\000\031\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\ \032\000\032\000\032\000\032\000\032\000\032\000\032\000\032\000\ \002\000\003\000\101\000\000\000\003\000\003\000\003\000\255\255\ \000\000\000\000\003\000\003\000\106\000\003\000\003\000\003\000\ \044\000\044\000\044\000\044\000\044\000\044\000\044\000\044\000\ \044\000\044\000\003\000\000\000\003\000\003\000\003\000\003\000\ \003\000\000\000\000\000\106\000\004\000\043\000\000\000\004\000\ \004\000\004\000\000\000\000\000\000\000\004\000\004\000\000\000\ \004\000\004\000\004\000\049\000\049\000\049\000\049\000\049\000\ \049\000\049\000\049\000\000\000\100\000\004\000\003\000\004\000\ \004\000\004\000\004\000\004\000\000\000\043\000\000\000\005\000\ \000\000\000\000\005\000\005\000\005\000\000\000\000\000\000\000\ \005\000\005\000\000\000\005\000\005\000\005\000\000\000\000\000\ \000\000\000\000\000\000\000\000\003\000\000\000\003\000\000\000\ \005\000\004\000\005\000\005\000\005\000\005\000\005\000\000\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\092\000\072\000\072\000\ \072\000\000\000\000\000\255\255\000\000\000\000\000\000\004\000\ \000\000\004\000\000\000\072\000\005\000\072\000\072\000\072\000\ \072\000\072\000\000\000\000\000\000\000\088\000\000\000\000\000\ \088\000\088\000\088\000\000\000\000\000\000\000\088\000\088\000\ \000\000\088\000\088\000\088\000\000\000\000\000\000\000\000\000\ \000\000\000\000\005\000\000\000\005\000\000\000\088\000\072\000\ \088\000\089\000\088\000\088\000\088\000\000\000\000\000\000\000\ \005\000\000\000\000\000\005\000\005\000\005\000\000\000\000\000\ \000\000\005\000\005\000\000\000\005\000\005\000\005\000\000\000\ \000\000\000\000\000\000\000\000\000\000\072\000\000\000\072\000\ \000\000\005\000\088\000\005\000\005\000\005\000\005\000\005\000\ \000\000\000\000\000\000\000\000\000\000\005\000\000\000\000\000\ \005\000\005\000\005\000\000\000\000\000\000\000\005\000\005\000\ \099\000\005\000\005\000\005\000\000\000\000\000\000\000\000\000\ \088\000\000\000\088\000\000\000\087\000\005\000\005\000\000\000\ \005\000\005\000\005\000\005\000\005\000\000\000\000\000\000\000\ \000\000\000\000\005\000\000\000\000\000\005\000\005\000\005\000\ \000\000\000\000\000\000\005\000\005\000\000\000\005\000\005\000\ \005\000\000\000\000\000\005\000\086\000\005\000\000\000\000\000\ \000\000\084\000\005\000\005\000\000\000\005\000\005\000\005\000\ \005\000\005\000\000\000\000\000\000\000\005\000\000\000\000\000\ \005\000\005\000\005\000\000\000\000\000\000\000\005\000\005\000\ \000\000\080\000\005\000\005\000\000\000\000\000\000\000\000\000\ \085\000\000\000\005\000\000\000\000\000\000\000\005\000\005\000\ \005\000\005\000\005\000\005\000\005\000\000\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\073\000\072\000\000\000\ \000\000\000\000\000\000\000\000\000\000\005\000\000\000\005\000\ \000\000\072\000\005\000\072\000\072\000\074\000\072\000\072\000\ \000\000\000\000\000\000\005\000\000\000\000\000\005\000\005\000\ \071\000\000\000\000\000\000\000\005\000\005\000\000\000\005\000\ \005\000\005\000\000\000\000\000\000\000\000\000\000\000\000\000\ \005\000\000\000\005\000\000\000\005\000\072\000\005\000\005\000\ \005\000\005\000\005\000\000\000\000\000\000\000\003\000\000\000\ \000\000\003\000\003\000\003\000\000\000\000\000\065\000\064\000\ \003\000\000\000\003\000\003\000\003\000\000\000\000\000\000\000\ \000\000\000\000\000\000\072\000\000\000\072\000\000\000\003\000\ \005\000\003\000\003\000\003\000\003\000\003\000\044\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\000\000\045\000\000\000\000\000\043\000\005\000\000\000\ \005\000\000\000\000\000\003\000\000\000\000\000\000\000\046\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \047\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\045\000\000\000\000\000\043\000\000\000\000\000\ \000\000\003\000\000\000\003\000\000\000\000\000\000\000\046\000\ \031\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \047\000\031\000\031\000\031\000\031\000\031\000\031\000\031\000\ \031\000\031\000\031\000\000\000\000\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\000\000\000\000\000\000\000\000\ \031\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\052\000\000\000\052\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\059\000\ \059\000\059\000\059\000\059\000\059\000\059\000\059\000\059\000\ \059\000\060\000\060\000\060\000\060\000\060\000\060\000\060\000\ \060\000\060\000\060\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\031\000\031\000\031\000\031\000\031\000\031\000\031\000\ \031\000\031\000\031\000\031\000\031\000\031\000\031\000\031\000\ \031\000\031\000\031\000\031\000\031\000\031\000\031\000\031\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\ \032\000\031\000\031\000\031\000\031\000\031\000\031\000\031\000\ \031\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\048\000\048\000\048\000\048\000\ \048\000\048\000\048\000\048\000\048\000\048\000\000\000\000\000\ \000\000\000\000\000\000\000\000\067\000\048\000\048\000\048\000\ \048\000\048\000\048\000\108\000\108\000\108\000\108\000\108\000\ \108\000\108\000\108\000\108\000\108\000\000\000\000\000\000\000\ \000\000\000\000\000\000\067\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\066\000\066\000\066\000\066\000\066\000\ \066\000\066\000\066\000\066\000\066\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\ \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\032\000\032\000\032\000\032\000\032\000\ \000\000\032\000\032\000\032\000\032\000\032\000\032\000\032\000\ \032\000\037\000\000\000\000\000\037\000\037\000\037\000\000\000\ \000\000\000\000\037\000\037\000\000\000\037\000\037\000\037\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\037\000\000\000\037\000\037\000\037\000\040\000\ \037\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\057\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\056\000\056\000\056\000\056\000\056\000\ \056\000\056\000\056\000\056\000\056\000\000\000\037\000\041\000\ \000\000\041\000\041\000\041\000\041\000\041\000\041\000\041\000\ \041\000\041\000\041\000\041\000\041\000\041\000\041\000\041\000\ \041\000\041\000\041\000\041\000\041\000\041\000\041\000\041\000\ \041\000\041\000\041\000\000\000\037\000\037\000\037\000\057\000\ \037\000\037\000\037\000\000\000\000\000\057\000\037\000\037\000\ \000\000\037\000\037\000\037\000\000\000\000\000\000\000\000\000\ \000\000\057\000\000\000\000\000\000\000\057\000\037\000\057\000\ \037\000\037\000\037\000\037\000\037\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\037\000\038\000\000\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\000\000\ \037\000\000\000\037\000\000\000\000\000\000\000\000\000\041\000\ \041\000\041\000\041\000\041\000\041\000\041\000\041\000\041\000\ \041\000\041\000\041\000\041\000\041\000\041\000\041\000\041\000\ \041\000\041\000\041\000\041\000\041\000\041\000\041\000\000\000\ \041\000\041\000\041\000\041\000\041\000\041\000\041\000\041\000\ \048\000\048\000\048\000\048\000\048\000\048\000\048\000\048\000\ \048\000\048\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\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\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\000\000\ \000\000\000\000\000\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\032\000\038\000\038\000\038\000\038\000\ \038\000\038\000\038\000\038\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\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\069\000\000\000\ \000\000\068\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \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\000\000\000\000\ \000\000\000\000\000\000\000\000\000\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\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\032\000\032\000\ \032\000\032\000\032\000\000\000\032\000\032\000\032\000\032\000\ \032\000\032\000\032\000\032\000\037\000\000\000\000\000\037\000\ \037\000\037\000\000\000\000\000\000\000\037\000\037\000\000\000\ \037\000\037\000\037\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\037\000\000\000\037\000\ \037\000\037\000\037\000\037\000\000\000\000\000\000\000\000\000\ \038\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\038\000\038\000\038\000\038\000\038\000\038\000\038\000\ \038\000\038\000\038\000\039\000\000\000\000\000\000\000\000\000\ \000\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\000\000\000\000\000\000\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\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\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\ \000\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\ \000\000\038\000\038\000\038\000\038\000\038\000\038\000\038\000\ \038\000\037\000\000\000\000\000\037\000\037\000\037\000\000\000\ \000\000\000\000\037\000\037\000\000\000\037\000\037\000\037\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\037\000\000\000\037\000\037\000\037\000\037\000\ \037\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\041\000\041\000\ \041\000\041\000\041\000\041\000\041\000\041\000\041\000\041\000\ \042\000\000\000\000\000\000\000\000\000\000\000\037\000\041\000\ \041\000\041\000\041\000\041\000\041\000\041\000\041\000\041\000\ \041\000\041\000\041\000\041\000\041\000\041\000\041\000\041\000\ \041\000\041\000\041\000\041\000\041\000\041\000\041\000\041\000\ \041\000\000\000\000\000\000\000\037\000\041\000\037\000\041\000\ \041\000\041\000\041\000\041\000\041\000\041\000\041\000\041\000\ \041\000\041\000\041\000\041\000\041\000\041\000\041\000\041\000\ \041\000\041\000\041\000\041\000\041\000\041\000\041\000\041\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\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\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\041\000\ \041\000\041\000\041\000\041\000\041\000\041\000\041\000\041\000\ \041\000\041\000\041\000\041\000\041\000\041\000\041\000\041\000\ \041\000\041\000\041\000\041\000\041\000\000\000\041\000\041\000\ \041\000\041\000\041\000\041\000\041\000\041\000\041\000\041\000\ \041\000\041\000\041\000\041\000\041\000\041\000\041\000\041\000\ \041\000\041\000\041\000\041\000\041\000\041\000\041\000\041\000\ \041\000\041\000\041\000\041\000\041\000\000\000\041\000\041\000\ \041\000\041\000\041\000\041\000\041\000\041\000\064\000\000\000\ \000\000\064\000\064\000\064\000\000\000\000\000\000\000\064\000\ \064\000\000\000\064\000\064\000\064\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\064\000\ \000\000\064\000\064\000\064\000\064\000\064\000\000\000\000\000\ \000\000\005\000\000\000\000\000\005\000\005\000\005\000\000\000\ \000\000\000\000\005\000\005\000\000\000\005\000\005\000\005\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\005\000\064\000\005\000\005\000\005\000\005\000\ \005\000\000\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\072\000\072\000\000\000\000\000\000\000\000\000\000\000\ \000\000\064\000\000\000\064\000\000\000\072\000\005\000\072\000\ \072\000\072\000\072\000\072\000\000\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\072\000\072\000\000\000\000\000\ \000\000\000\000\000\000\000\000\005\000\000\000\005\000\000\000\ \072\000\072\000\072\000\072\000\072\000\072\000\072\000\000\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\072\000\ \072\000\000\000\000\000\000\000\000\000\000\000\000\000\072\000\ \000\000\072\000\000\000\072\000\072\000\072\000\072\000\072\000\ \072\000\072\000\000\000\000\000\000\000\005\000\000\000\000\000\ \005\000\005\000\005\000\000\000\000\000\000\000\005\000\005\000\ \000\000\005\000\005\000\005\000\000\000\000\000\000\000\000\000\ \000\000\000\000\072\000\000\000\072\000\000\000\005\000\072\000\ \005\000\005\000\005\000\005\000\005\000\000\000\000\000\000\000\ \005\000\000\000\000\000\005\000\005\000\005\000\000\000\000\000\ \000\000\005\000\005\000\000\000\005\000\005\000\005\000\000\000\ \000\000\000\000\000\000\000\000\000\000\072\000\000\000\072\000\ \000\000\005\000\005\000\005\000\005\000\005\000\005\000\005\000\ \000\000\000\000\000\000\088\000\000\000\000\000\088\000\088\000\ \088\000\000\000\000\000\000\000\088\000\088\000\000\000\088\000\ \088\000\088\000\000\000\000\000\000\000\000\000\000\000\000\000\ \005\000\000\000\005\000\000\000\088\000\005\000\088\000\088\000\ \088\000\088\000\088\000\000\000\106\000\000\000\088\000\105\000\ \000\000\088\000\088\000\088\000\000\000\000\000\000\000\088\000\ \088\000\000\000\088\000\088\000\088\000\000\000\000\000\000\000\ \000\000\000\000\000\000\005\000\104\000\005\000\000\000\088\000\ \088\000\088\000\088\000\088\000\088\000\088\000\000\000\000\000\ \000\000\000\000\103\000\103\000\103\000\103\000\103\000\103\000\ \103\000\103\000\103\000\103\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\088\000\000\000\ \088\000\000\000\000\000\088\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\104\000\000\000\ \000\000\000\000\000\000\000\000\104\000\000\000\000\000\000\000\ \000\000\088\000\000\000\088\000\000\000\000\000\000\000\000\000\ \104\000\000\000\000\000\000\000\104\000\000\000\104\000\000\000\ \000\000\000\000\102\000\109\000\109\000\109\000\109\000\109\000\ \109\000\109\000\109\000\109\000\109\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\109\000\109\000\109\000\109\000\ \109\000\109\000\109\000\109\000\109\000\109\000\109\000\109\000\ \109\000\109\000\109\000\109\000\109\000\109\000\109\000\109\000\ \109\000\109\000\109\000\109\000\109\000\109\000\000\000\000\000\ \000\000\000\000\000\000\000\000\109\000\109\000\109\000\109\000\ \109\000\109\000\109\000\109\000\109\000\109\000\109\000\109\000\ \109\000\109\000\109\000\109\000\109\000\109\000\109\000\109\000\ \109\000\109\000\109\000\109\000\109\000\109\000\110\000\110\000\ \110\000\110\000\110\000\110\000\110\000\110\000\110\000\110\000\ \000\000\000\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\000\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\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\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_check = "\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\000\000\000\000\068\000\000\000\000\000\255\255\255\255\ \255\255\070\000\255\255\255\255\070\000\255\255\255\255\255\255\ \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\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\011\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\013\000\ \016\000\017\000\018\000\024\000\017\000\017\000\026\000\029\000\ \054\000\029\000\029\000\029\000\029\000\029\000\029\000\029\000\ \029\000\029\000\029\000\045\000\045\000\050\000\050\000\057\000\ \060\000\062\000\024\000\093\000\094\000\090\000\029\000\090\000\ \255\255\255\255\027\000\255\255\255\255\105\000\105\000\255\255\ \255\255\255\255\024\000\024\000\024\000\024\000\024\000\024\000\ \024\000\024\000\024\000\024\000\046\000\046\000\046\000\046\000\ \046\000\046\000\046\000\046\000\105\000\255\255\029\000\013\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\027\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\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\003\000\097\000\255\255\003\000\003\000\003\000\070\000\ \255\255\255\255\003\000\003\000\106\000\003\000\003\000\003\000\ \044\000\044\000\044\000\044\000\044\000\044\000\044\000\044\000\ \044\000\044\000\003\000\255\255\003\000\003\000\003\000\003\000\ \003\000\255\255\255\255\106\000\004\000\044\000\255\255\004\000\ \004\000\004\000\255\255\255\255\255\255\004\000\004\000\255\255\ \004\000\004\000\004\000\049\000\049\000\049\000\049\000\049\000\ \049\000\049\000\049\000\255\255\097\000\004\000\003\000\004\000\ \004\000\004\000\004\000\004\000\255\255\044\000\255\255\005\000\ \255\255\255\255\005\000\005\000\005\000\255\255\255\255\255\255\ \005\000\005\000\255\255\005\000\005\000\005\000\255\255\255\255\ \255\255\255\255\255\255\255\255\003\000\255\255\003\000\255\255\ \005\000\004\000\005\000\005\000\005\000\005\000\005\000\255\255\ \255\255\255\255\006\000\255\255\255\255\006\000\006\000\006\000\ \255\255\255\255\255\255\006\000\006\000\090\000\006\000\006\000\ \006\000\255\255\255\255\027\000\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\ \009\000\255\255\255\255\009\000\009\000\009\000\255\255\255\255\ \255\255\009\000\009\000\255\255\009\000\009\000\009\000\255\255\ \255\255\255\255\255\255\255\255\255\255\006\000\255\255\006\000\ \255\255\009\000\007\000\009\000\009\000\009\000\009\000\009\000\ \255\255\255\255\255\255\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\ \097\000\010\000\010\000\010\000\255\255\255\255\255\255\255\255\ \007\000\255\255\007\000\255\255\009\000\009\000\010\000\255\255\ \010\000\010\000\010\000\010\000\010\000\255\255\255\255\255\255\ \255\255\255\255\014\000\255\255\255\255\014\000\014\000\014\000\ \255\255\255\255\255\255\014\000\014\000\255\255\014\000\014\000\ \014\000\255\255\255\255\009\000\009\000\009\000\255\255\255\255\ \255\255\010\000\010\000\014\000\255\255\014\000\014\000\014\000\ \014\000\014\000\255\255\255\255\255\255\015\000\255\255\255\255\ \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\255\255\255\255\ \010\000\255\255\010\000\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\ \019\000\255\255\255\255\019\000\019\000\019\000\255\255\255\255\ \255\255\019\000\019\000\255\255\019\000\019\000\019\000\255\255\ \255\255\255\255\255\255\255\255\255\255\014\000\255\255\014\000\ \255\255\019\000\015\000\019\000\019\000\019\000\019\000\019\000\ \255\255\255\255\255\255\023\000\255\255\255\255\023\000\023\000\ \023\000\255\255\255\255\255\255\023\000\023\000\255\255\023\000\ \023\000\023\000\255\255\255\255\255\255\255\255\255\255\255\255\ \015\000\255\255\015\000\255\255\023\000\019\000\023\000\023\000\ \023\000\023\000\023\000\255\255\255\255\255\255\025\000\255\255\ \255\255\025\000\025\000\025\000\255\255\255\255\025\000\025\000\ \025\000\255\255\025\000\025\000\025\000\255\255\255\255\255\255\ \255\255\255\255\255\255\019\000\255\255\019\000\255\255\025\000\ \023\000\025\000\025\000\025\000\025\000\025\000\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\255\255\030\000\255\255\255\255\030\000\023\000\255\255\ \023\000\255\255\255\255\025\000\255\255\255\255\255\255\030\000\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \030\000\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\030\000\255\255\255\255\030\000\255\255\255\255\ \255\255\025\000\255\255\025\000\255\255\255\255\255\255\030\000\ \031\000\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \030\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\043\000\255\255\043\000\255\255\ \255\255\043\000\043\000\043\000\043\000\043\000\043\000\043\000\ \043\000\043\000\043\000\051\000\051\000\051\000\051\000\051\000\ \051\000\051\000\051\000\051\000\051\000\052\000\052\000\052\000\ \052\000\052\000\052\000\052\000\052\000\052\000\052\000\056\000\ \056\000\056\000\056\000\056\000\056\000\056\000\056\000\056\000\ \056\000\059\000\059\000\059\000\059\000\059\000\059\000\059\000\ \059\000\059\000\059\000\103\000\103\000\103\000\103\000\103\000\ \103\000\103\000\103\000\103\000\103\000\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\ \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\ \032\000\031\000\031\000\031\000\031\000\031\000\031\000\031\000\ \031\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\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\067\000\047\000\047\000\047\000\ \047\000\047\000\047\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\067\000\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\067\000\067\000\067\000\067\000\067\000\ \067\000\067\000\067\000\067\000\067\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\ \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\ \255\255\032\000\032\000\032\000\032\000\032\000\032\000\032\000\ \032\000\033\000\255\255\255\255\033\000\033\000\033\000\255\255\ \255\255\255\255\033\000\033\000\255\255\033\000\033\000\033\000\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\033\000\255\255\033\000\033\000\033\000\033\000\ \033\000\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\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\255\255\033\000\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\255\255\033\000\034\000\033\000\053\000\ \034\000\034\000\034\000\255\255\255\255\053\000\034\000\034\000\ \255\255\034\000\034\000\034\000\255\255\255\255\255\255\255\255\ \255\255\053\000\255\255\255\255\255\255\053\000\034\000\053\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\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\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\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\ \034\000\255\255\034\000\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\255\255\ \033\000\033\000\033\000\033\000\033\000\033\000\033\000\033\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\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\048\000\048\000\048\000\048\000\048\000\048\000\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\035\000\034\000\034\000\034\000\034\000\ \034\000\034\000\034\000\034\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\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\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\066\000\255\255\ \255\255\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\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\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\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\255\255\035\000\035\000\035\000\035\000\ \035\000\035\000\035\000\035\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\037\000\ \037\000\037\000\037\000\037\000\255\255\255\255\255\255\255\255\ \038\000\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\255\255\255\255\255\255\255\255\ \255\255\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\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\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\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\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\ \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\ \255\255\038\000\038\000\038\000\038\000\038\000\038\000\038\000\ \038\000\040\000\255\255\255\255\040\000\040\000\040\000\255\255\ \255\255\255\255\040\000\040\000\255\255\040\000\040\000\040\000\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\040\000\255\255\040\000\040\000\040\000\040\000\ \040\000\255\255\255\255\255\255\255\255\041\000\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\041\000\041\000\ \041\000\041\000\041\000\041\000\041\000\041\000\041\000\041\000\ \041\000\255\255\255\255\255\255\255\255\255\255\040\000\041\000\ \041\000\041\000\041\000\041\000\041\000\041\000\041\000\041\000\ \041\000\041\000\041\000\041\000\041\000\041\000\041\000\041\000\ \041\000\041\000\041\000\041\000\041\000\041\000\041\000\041\000\ \041\000\255\255\255\255\255\255\040\000\041\000\040\000\041\000\ \041\000\041\000\041\000\041\000\041\000\041\000\041\000\041\000\ \041\000\041\000\041\000\041\000\041\000\041\000\041\000\041\000\ \041\000\041\000\041\000\041\000\041\000\041\000\041\000\041\000\ \041\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\041\000\041\000\ \041\000\041\000\041\000\041\000\041\000\041\000\041\000\041\000\ \041\000\041\000\041\000\041\000\041\000\041\000\041\000\041\000\ \041\000\041\000\041\000\041\000\041\000\255\255\041\000\041\000\ \041\000\041\000\041\000\041\000\041\000\041\000\041\000\041\000\ \041\000\041\000\041\000\041\000\041\000\041\000\041\000\041\000\ \041\000\041\000\041\000\041\000\041\000\041\000\041\000\041\000\ \041\000\041\000\041\000\041\000\041\000\255\255\041\000\041\000\ \041\000\041\000\041\000\041\000\041\000\041\000\064\000\255\255\ \255\255\064\000\064\000\064\000\255\255\255\255\255\255\064\000\ \064\000\255\255\064\000\064\000\064\000\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\064\000\ \255\255\064\000\064\000\064\000\064\000\064\000\255\255\255\255\ \255\255\071\000\255\255\255\255\071\000\071\000\071\000\255\255\ \255\255\255\255\071\000\071\000\255\255\071\000\071\000\071\000\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\071\000\064\000\071\000\071\000\071\000\071\000\ \071\000\255\255\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\072\000\072\000\255\255\255\255\255\255\255\255\255\255\ \255\255\064\000\255\255\064\000\255\255\072\000\071\000\072\000\ \072\000\072\000\072\000\072\000\255\255\255\255\255\255\073\000\ \255\255\255\255\073\000\073\000\073\000\255\255\255\255\255\255\ \073\000\073\000\255\255\073\000\073\000\073\000\255\255\255\255\ \255\255\255\255\255\255\255\255\071\000\255\255\071\000\255\255\ \073\000\072\000\073\000\073\000\073\000\073\000\073\000\255\255\ \255\255\255\255\074\000\255\255\255\255\074\000\074\000\074\000\ \255\255\255\255\255\255\074\000\074\000\255\255\074\000\074\000\ \074\000\255\255\255\255\255\255\255\255\255\255\255\255\072\000\ \255\255\072\000\255\255\074\000\073\000\074\000\074\000\074\000\ \074\000\074\000\255\255\255\255\255\255\080\000\255\255\255\255\ \080\000\080\000\080\000\255\255\255\255\255\255\080\000\080\000\ \255\255\080\000\080\000\080\000\255\255\255\255\255\255\255\255\ \255\255\255\255\073\000\255\255\073\000\255\255\080\000\074\000\ \080\000\080\000\080\000\080\000\080\000\255\255\255\255\255\255\ \085\000\255\255\255\255\085\000\085\000\085\000\255\255\255\255\ \255\255\085\000\085\000\255\255\085\000\085\000\085\000\255\255\ \255\255\255\255\255\255\255\255\255\255\074\000\255\255\074\000\ \255\255\085\000\080\000\085\000\085\000\085\000\085\000\085\000\ \255\255\255\255\255\255\088\000\255\255\255\255\088\000\088\000\ \088\000\255\255\255\255\255\255\088\000\088\000\255\255\088\000\ \088\000\088\000\255\255\255\255\255\255\255\255\255\255\255\255\ \080\000\255\255\080\000\255\255\088\000\085\000\088\000\088\000\ \088\000\088\000\088\000\255\255\100\000\255\255\089\000\100\000\ \255\255\089\000\089\000\089\000\255\255\255\255\255\255\089\000\ \089\000\255\255\089\000\089\000\089\000\255\255\255\255\255\255\ \255\255\255\255\255\255\085\000\100\000\085\000\255\255\089\000\ \088\000\089\000\089\000\089\000\089\000\089\000\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\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\088\000\255\255\ \088\000\255\255\255\255\089\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\100\000\255\255\ \255\255\255\255\255\255\255\255\100\000\255\255\255\255\255\255\ \255\255\089\000\255\255\089\000\255\255\255\255\255\255\255\255\ \100\000\255\255\255\255\255\255\100\000\255\255\100\000\255\255\ \255\255\255\255\100\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\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\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\109\000\109\000\ \109\000\109\000\109\000\109\000\109\000\109\000\109\000\109\000\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\109\000\ \109\000\109\000\109\000\109\000\109\000\109\000\109\000\109\000\ \109\000\109\000\109\000\109\000\109\000\109\000\109\000\109\000\ \109\000\109\000\109\000\109\000\109\000\109\000\109\000\109\000\ \109\000\255\255\255\255\255\255\255\255\255\255\255\255\109\000\ \109\000\109\000\109\000\109\000\109\000\109\000\109\000\109\000\ \109\000\109\000\109\000\109\000\109\000\109\000\109\000\109\000\ \109\000\109\000\109\000\109\000\109\000\109\000\109\000\109\000\ \109\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\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255"; Lexing.lex_base_code = ""; Lexing.lex_backtrk_code = ""; Lexing.lex_default_code = ""; Lexing.lex_trans_code = ""; Lexing.lex_check_code = ""; Lexing.lex_code = ""; } let rec token lexbuf = __ocaml_lex_token_rec lexbuf 0 and __ocaml_lex_token_rec lexbuf __ocaml_lex_state = match Lexing.engine __ocaml_lex_tables __ocaml_lex_state lexbuf with | 0 -> # 274 "odoc_ocamlhtml.mll" ( let s = Lexing.lexeme lexbuf in ( match s with " " -> incr margin | "\t" -> margin := !margin + 8 | "\n" -> margin := 0 | _ -> () ); print s; token lexbuf ) # 1058 "odoc_ocamlhtml.ml" | 1 -> # 287 "odoc_ocamlhtml.mll" ( print "_" ; token lexbuf ) # 1063 "odoc_ocamlhtml.ml" | 2 -> # 288 "odoc_ocamlhtml.mll" ( print "~" ; token lexbuf ) # 1068 "odoc_ocamlhtml.ml" | 3 -> # 290 "odoc_ocamlhtml.mll" ( let s = Lexing.lexeme lexbuf in let name = String.sub s 1 (String.length s - 2) in if Hashtbl.mem keyword_table name then raise (Error(Keyword_as_label name, Lexing.lexeme_start lexbuf, Lexing.lexeme_end lexbuf)); print s ; token lexbuf ) # 1078 "odoc_ocamlhtml.ml" | 4 -> # 296 "odoc_ocamlhtml.mll" ( print "?" ; token lexbuf ) # 1083 "odoc_ocamlhtml.ml" | 5 -> # 298 "odoc_ocamlhtml.mll" ( let s = Lexing.lexeme lexbuf in let name = String.sub s 1 (String.length s - 2) in if Hashtbl.mem keyword_table name then raise (Error(Keyword_as_label name, Lexing.lexeme_start lexbuf, Lexing.lexeme_end lexbuf)); print s ; token lexbuf ) # 1093 "odoc_ocamlhtml.ml" | 6 -> # 305 "odoc_ocamlhtml.mll" ( let s = Lexing.lexeme lexbuf in try let cl = Hashtbl.find keyword_table s in (print_class cl s ; token lexbuf ) with Not_found -> (print s ; token lexbuf )) # 1103 "odoc_ocamlhtml.ml" | 7 -> # 312 "odoc_ocamlhtml.mll" ( print_class constructor_class (Lexing.lexeme lexbuf) ; token lexbuf ) # 1108 "odoc_ocamlhtml.ml" | 8 -> # 314 "odoc_ocamlhtml.mll" ( print (Lexing.lexeme lexbuf) ; token lexbuf ) # 1113 "odoc_ocamlhtml.ml" | 9 -> # 316 "odoc_ocamlhtml.mll" ( print (Lexing.lexeme lexbuf) ; token lexbuf ) # 1118 "odoc_ocamlhtml.ml" | 10 -> # 318 "odoc_ocamlhtml.mll" ( reset_string_buffer(); let string_start = Lexing.lexeme_start lexbuf in string_start_pos := string_start; string lexbuf; lexbuf.Lexing.lex_start_pos <- string_start - lexbuf.Lexing.lex_abs_pos; print_class string_class ("\""^(get_stored_string())^"\"") ; token lexbuf ) # 1130 "odoc_ocamlhtml.ml" | 11 -> # 327 "odoc_ocamlhtml.mll" ( print_class string_class (Lexing.lexeme lexbuf) ; token lexbuf ) # 1136 "odoc_ocamlhtml.ml" | 12 -> # 330 "odoc_ocamlhtml.mll" ( print_class string_class (Lexing.lexeme lexbuf ) ; token lexbuf ) # 1142 "odoc_ocamlhtml.ml" | 13 -> # 333 "odoc_ocamlhtml.mll" ( print_class string_class (Lexing.lexeme lexbuf ) ; token lexbuf ) # 1148 "odoc_ocamlhtml.ml" | 14 -> # 336 "odoc_ocamlhtml.mll" ( reset_comment_buffer (); comment_start_pos := [Lexing.lexeme_start lexbuf]; comment lexbuf ; print_comment (); token lexbuf ) # 1158 "odoc_ocamlhtml.ml" | 15 -> # 343 "odoc_ocamlhtml.mll" ( reset_comment_buffer (); comment_start_pos := [Lexing.lexeme_start lexbuf]; comment lexbuf ; print_comment (); token lexbuf ) # 1168 "odoc_ocamlhtml.ml" | 16 -> # 350 "odoc_ocamlhtml.mll" ( lexbuf.Lexing.lex_curr_pos <- lexbuf.Lexing.lex_curr_pos - 1; lexbuf.Lexing.lex_curr_p <- { lexbuf.Lexing.lex_curr_p with pos_cnum = lexbuf.Lexing.lex_curr_p.pos_cnum - 1 } ; print (Lexing.lexeme lexbuf) ; token lexbuf ) # 1180 "odoc_ocamlhtml.ml" | 17 -> # 360 "odoc_ocamlhtml.mll" ( print (Lexing.lexeme lexbuf); token lexbuf ) # 1188 "odoc_ocamlhtml.ml" | 18 -> # 364 "odoc_ocamlhtml.mll" ( print_class kwsign_class (Lexing.lexeme lexbuf) ; token lexbuf ) # 1193 "odoc_ocamlhtml.ml" | 19 -> # 365 "odoc_ocamlhtml.mll" ( print_class kwsign_class (Lexing.lexeme lexbuf) ; token lexbuf ) # 1198 "odoc_ocamlhtml.ml" | 20 -> # 366 "odoc_ocamlhtml.mll" ( print_class kwsign_class (Lexing.lexeme lexbuf) ; token lexbuf ) # 1203 "odoc_ocamlhtml.ml" | 21 -> # 367 "odoc_ocamlhtml.mll" ( print_class kwsign_class (Lexing.lexeme lexbuf) ; token lexbuf ) # 1208 "odoc_ocamlhtml.ml" | 22 -> # 368 "odoc_ocamlhtml.mll" ( print_class kwsign_class (Lexing.lexeme lexbuf) ; token lexbuf ) # 1213 "odoc_ocamlhtml.ml" | 23 -> # 369 "odoc_ocamlhtml.mll" ( print (Lexing.lexeme lexbuf) ; token lexbuf ) # 1218 "odoc_ocamlhtml.ml" | 24 -> # 370 "odoc_ocamlhtml.mll" ( print (Lexing.lexeme lexbuf) ; token lexbuf ) # 1223 "odoc_ocamlhtml.ml" | 25 -> # 371 "odoc_ocamlhtml.mll" ( print (Lexing.lexeme lexbuf) ; token lexbuf ) # 1228 "odoc_ocamlhtml.ml" | 26 -> # 372 "odoc_ocamlhtml.mll" ( print (Lexing.lexeme lexbuf) ; token lexbuf ) # 1233 "odoc_ocamlhtml.ml" | 27 -> # 373 "odoc_ocamlhtml.mll" ( print_class kwsign_class (Lexing.lexeme lexbuf) ; token lexbuf ) # 1238 "odoc_ocamlhtml.ml" | 28 -> # 374 "odoc_ocamlhtml.mll" ( print_class kwsign_class (Lexing.lexeme lexbuf) ; token lexbuf ) # 1243 "odoc_ocamlhtml.ml" | 29 -> # 375 "odoc_ocamlhtml.mll" ( print (Lexing.lexeme lexbuf) ; token lexbuf ) # 1248 "odoc_ocamlhtml.ml" | 30 -> # 376 "odoc_ocamlhtml.mll" ( print (Lexing.lexeme lexbuf) ; token lexbuf ) # 1253 "odoc_ocamlhtml.ml" | 31 -> # 377 "odoc_ocamlhtml.mll" ( print (Lexing.lexeme lexbuf) ; token lexbuf ) # 1258 "odoc_ocamlhtml.ml" | 32 -> # 378 "odoc_ocamlhtml.mll" ( print (Lexing.lexeme lexbuf) ; token lexbuf ) # 1263 "odoc_ocamlhtml.ml" | 33 -> # 379 "odoc_ocamlhtml.mll" ( print (Lexing.lexeme lexbuf) ; token lexbuf ) # 1268 "odoc_ocamlhtml.ml" | 34 -> # 380 "odoc_ocamlhtml.mll" ( print (Lexing.lexeme lexbuf) ; token lexbuf ) # 1273 "odoc_ocamlhtml.ml" | 35 -> # 381 "odoc_ocamlhtml.mll" ( print (Lexing.lexeme lexbuf) ; token lexbuf ) # 1278 "odoc_ocamlhtml.ml" | 36 -> # 382 "odoc_ocamlhtml.mll" ( print (Lexing.lexeme lexbuf) ; token lexbuf ) # 1283 "odoc_ocamlhtml.ml" | 37 -> # 383 "odoc_ocamlhtml.mll" ( print (Lexing.lexeme lexbuf) ; token lexbuf ) # 1288 "odoc_ocamlhtml.ml" | 38 -> # 384 "odoc_ocamlhtml.mll" ( print (Lexing.lexeme lexbuf) ; token lexbuf ) # 1293 "odoc_ocamlhtml.ml" | 39 -> # 385 "odoc_ocamlhtml.mll" ( print (Lexing.lexeme lexbuf) ; token lexbuf ) # 1298 "odoc_ocamlhtml.ml" | 40 -> # 386 "odoc_ocamlhtml.mll" ( print (Lexing.lexeme lexbuf) ; token lexbuf ) # 1303 "odoc_ocamlhtml.ml" | 41 -> # 387 "odoc_ocamlhtml.mll" ( print (Lexing.lexeme lexbuf) ; token lexbuf ) # 1308 "odoc_ocamlhtml.ml" | 42 -> # 388 "odoc_ocamlhtml.mll" ( print (Lexing.lexeme lexbuf) ; token lexbuf ) # 1313 "odoc_ocamlhtml.ml" | 43 -> # 389 "odoc_ocamlhtml.mll" ( print (Lexing.lexeme lexbuf) ; token lexbuf ) # 1318 "odoc_ocamlhtml.ml" | 44 -> # 390 "odoc_ocamlhtml.mll" ( print (Lexing.lexeme lexbuf) ; token lexbuf ) # 1323 "odoc_ocamlhtml.ml" | 45 -> # 391 "odoc_ocamlhtml.mll" ( print (Lexing.lexeme lexbuf) ; token lexbuf ) # 1328 "odoc_ocamlhtml.ml" | 46 -> # 392 "odoc_ocamlhtml.mll" ( print_class kwsign_class (Lexing.lexeme lexbuf) ; token lexbuf ) # 1333 "odoc_ocamlhtml.ml" | 47 -> # 393 "odoc_ocamlhtml.mll" ( print_class kwsign_class (Lexing.lexeme lexbuf) ; token lexbuf ) # 1338 "odoc_ocamlhtml.ml" | 48 -> # 394 "odoc_ocamlhtml.mll" ( print (Lexing.lexeme lexbuf) ; token lexbuf ) # 1343 "odoc_ocamlhtml.ml" | 49 -> # 395 "odoc_ocamlhtml.mll" ( print (Lexing.lexeme lexbuf) ; token lexbuf ) # 1348 "odoc_ocamlhtml.ml" | 50 -> # 396 "odoc_ocamlhtml.mll" ( print (Lexing.lexeme lexbuf) ; token lexbuf ) # 1353 "odoc_ocamlhtml.ml" | 51 -> # 397 "odoc_ocamlhtml.mll" ( print (Lexing.lexeme lexbuf) ; token lexbuf ) # 1358 "odoc_ocamlhtml.ml" | 52 -> # 398 "odoc_ocamlhtml.mll" ( print (Lexing.lexeme lexbuf) ; token lexbuf ) # 1363 "odoc_ocamlhtml.ml" | 53 -> # 400 "odoc_ocamlhtml.mll" ( print (Lexing.lexeme lexbuf) ; token lexbuf ) # 1368 "odoc_ocamlhtml.ml" | 54 -> # 401 "odoc_ocamlhtml.mll" ( print (Lexing.lexeme lexbuf) ; token lexbuf ) # 1373 "odoc_ocamlhtml.ml" | 55 -> # 402 "odoc_ocamlhtml.mll" ( print (Lexing.lexeme lexbuf) ; token lexbuf ) # 1378 "odoc_ocamlhtml.ml" | 56 -> # 403 "odoc_ocamlhtml.mll" ( print (Lexing.lexeme lexbuf) ; token lexbuf ) # 1383 "odoc_ocamlhtml.ml" | 57 -> # 406 "odoc_ocamlhtml.mll" ( print (Lexing.lexeme lexbuf) ; token lexbuf ) # 1388 "odoc_ocamlhtml.ml" | 58 -> # 408 "odoc_ocamlhtml.mll" ( print_class kwsign_class (Lexing.lexeme lexbuf) ; token lexbuf ) # 1393 "odoc_ocamlhtml.ml" | 59 -> # 410 "odoc_ocamlhtml.mll" ( print (Lexing.lexeme lexbuf) ; token lexbuf ) # 1398 "odoc_ocamlhtml.ml" | 60 -> # 412 "odoc_ocamlhtml.mll" ( print (Lexing.lexeme lexbuf) ; token lexbuf ) # 1403 "odoc_ocamlhtml.ml" | 61 -> # 414 "odoc_ocamlhtml.mll" ( print (Lexing.lexeme lexbuf) ; token lexbuf ) # 1408 "odoc_ocamlhtml.ml" | 62 -> # 416 "odoc_ocamlhtml.mll" ( print (Lexing.lexeme lexbuf) ; token lexbuf ) # 1413 "odoc_ocamlhtml.ml" | 63 -> # 418 "odoc_ocamlhtml.mll" ( print (Lexing.lexeme lexbuf) ; token lexbuf ) # 1418 "odoc_ocamlhtml.ml" | 64 -> # 419 "odoc_ocamlhtml.mll" ( () ) # 1423 "odoc_ocamlhtml.ml" | 65 -> # 421 "odoc_ocamlhtml.mll" ( raise (Error(Illegal_character ((Lexing.lexeme lexbuf).[0]), Lexing.lexeme_start lexbuf, Lexing.lexeme_end lexbuf)) ) # 1429 "odoc_ocamlhtml.ml" | __ocaml_lex_state -> lexbuf.Lexing.refill_buff lexbuf; __ocaml_lex_token_rec lexbuf __ocaml_lex_state and comment lexbuf = __ocaml_lex_comment_rec lexbuf 90 and __ocaml_lex_comment_rec lexbuf __ocaml_lex_state = match Lexing.engine __ocaml_lex_tables __ocaml_lex_state lexbuf with | 0 -> # 426 "odoc_ocamlhtml.mll" ( comment_start_pos := Lexing.lexeme_start lexbuf :: !comment_start_pos; store_comment_char '('; store_comment_char '*'; comment lexbuf; ) # 1445 "odoc_ocamlhtml.ml" | 1 -> # 432 "odoc_ocamlhtml.mll" ( match !comment_start_pos with | [] -> assert false | [_] -> comment_start_pos := [] | _ :: l -> store_comment_char '*'; store_comment_char ')'; comment_start_pos := l; comment lexbuf; ) # 1458 "odoc_ocamlhtml.ml" | 2 -> # 481 "odoc_ocamlhtml.mll" ( let st = List.hd !comment_start_pos in raise (Error (Unterminated_comment, st, st + 2)); ) # 1465 "odoc_ocamlhtml.ml" | 3 -> # 485 "odoc_ocamlhtml.mll" ( store_comment_char(Lexing.lexeme_char lexbuf 0); comment lexbuf ) # 1471 "odoc_ocamlhtml.ml" | __ocaml_lex_state -> lexbuf.Lexing.refill_buff lexbuf; __ocaml_lex_comment_rec lexbuf __ocaml_lex_state and string lexbuf = __ocaml_lex_string_rec lexbuf 97 and __ocaml_lex_string_rec lexbuf __ocaml_lex_state = match Lexing.engine __ocaml_lex_tables __ocaml_lex_state lexbuf with | 0 -> # 490 "odoc_ocamlhtml.mll" ( () ) # 1483 "odoc_ocamlhtml.ml" | 1 -> # 492 "odoc_ocamlhtml.mll" ( string lexbuf ) # 1488 "odoc_ocamlhtml.ml" | 2 -> # 494 "odoc_ocamlhtml.mll" ( Buffer.add_string string_buffer (Lexing.lexeme lexbuf) ; string lexbuf ) # 1494 "odoc_ocamlhtml.ml" | 3 -> # 497 "odoc_ocamlhtml.mll" ( Buffer.add_string string_buffer (Lexing.lexeme lexbuf) ; string lexbuf ) # 1502 "odoc_ocamlhtml.ml" | 4 -> # 502 "odoc_ocamlhtml.mll" ( Buffer.add_string string_buffer (Lexing.lexeme lexbuf) ; string lexbuf ) # 1508 "odoc_ocamlhtml.ml" | 5 -> # 505 "odoc_ocamlhtml.mll" ( raise (Error (Unterminated_string, !string_start_pos, !string_start_pos+1)) ) # 1514 "odoc_ocamlhtml.ml" | 6 -> # 508 "odoc_ocamlhtml.mll" ( store_string_char(Lexing.lexeme_char lexbuf 0); string lexbuf ) # 1520 "odoc_ocamlhtml.ml" | __ocaml_lex_state -> lexbuf.Lexing.refill_buff lexbuf; __ocaml_lex_string_rec lexbuf __ocaml_lex_state ;; # 510 "odoc_ocamlhtml.mll" let html_of_code b ?(with_pre=true) code = let old_pre = !pre in let old_margin = !margin in let old_comment_buffer = Buffer.contents comment_buffer in let old_string_buffer = Buffer.contents string_buffer in let buf = Buffer.create 256 in let old_fmt = !fmt in fmt := Format.formatter_of_buffer buf ; pre := with_pre; margin := 0; let start = "" in let ending = "" in let html = ( try print ~esc: false start ; let lexbuf = Lexing.from_string code in token lexbuf; print ~esc: false ending ; Format.pp_print_flush !fmt () ; Buffer.contents buf with _ -> (* flush str_formatter because we already output something in it *) Format.pp_print_flush !fmt () ; start^code^ending ) in pre := old_pre; margin := old_margin ; Buffer.reset comment_buffer; Buffer.add_string comment_buffer old_comment_buffer ; Buffer.reset string_buffer; Buffer.add_string string_buffer old_string_buffer ; fmt := old_fmt ; Buffer.add_string b html # 1571 "odoc_ocamlhtml.ml"