# 35 "omake_ast_lex.mll" open Lm_printf open Lm_debug open Lm_symbol open Lm_location open Omake_ast open Omake_env open Omake_ast_util open Omake_ast_parse open Omake_ast_print open Omake_exn_print module Pos = MakePos (struct let name = "Omake_ast_lex" end) open Pos let debug_lex = create_debug (**) { debug_name = "debug-ast-lex"; debug_description = "Print tokens as they are scanned"; debug_value = false } (* * Current mode: * ModeNormal: normal lexing mode * ModeString s: parsing a literal string, dollar sequences are still expanded, * s is the quotation delimiter * ModeQuote s: parsing a literal string, dollar sequences are still expanded, * escape sequences are allowed, s is the quotation delimiter. *) type mode = ModeNormal | ModeString of string | ModeQuote of string (* * The lexing mode. * ModeInitial: lexbuf is ready to be used * ModeIndent i: initial indentation has been scanned * ModeNormal: normal processing *) type lexmode = LexModeInitial | LexModeNormal of int (* * Parsing results. *) type parse_item = ParseExp of exp list | ParseError | ParseEOF (* * This is the info for each indentation level. *) type info = { info_mode : mode; info_indent : int; info_parens : int option } (* * State of the lexer. *) type session = { (* The current location *) current_file : symbol; mutable current_line : int; mutable current_off : int; mutable current_loc : loc; (* The current input buffer *) mutable current_buffer : string; mutable current_index : int; mutable current_prompt : string; mutable current_fill_ok : bool; mutable current_eof : bool; readline : (string -> string); mutable is_interactive : bool; (* The current lexbuf *) mutable current_lexbuf : Lexing.lexbuf; mutable current_lexmode : lexmode; mutable current_token : token; (* The current mode *) mutable current_mode : mode; mutable current_parens : int option; mutable current_indent : int; mutable current_stack : info list } (************************************************************************ * Printing. NOTICE: if new tokens are added, please update * the token list in omake_gen_parse.ml!!! *) let pp_print_token buf = function TokEof _ -> pp_print_string buf "" | TokEol _ -> pp_print_string buf "" | TokWhite (s, _) -> fprintf buf "whitespace: \"%s\"" s | TokLeftParen (s, _) -> fprintf buf "left parenthesis: %s" s | TokRightParen (s, _) -> fprintf buf "right parenthesis: %s" s | TokComma (s, _) -> fprintf buf "comma: %s" s | TokColon (s, _) -> fprintf buf "colon: %s" s | TokDoubleColon (s, _) -> fprintf buf "doublecolon: %s" s | TokNamedColon (s, _) -> fprintf buf "named colon: %s" s | TokDollar (s, strategy, _) -> fprintf buf "dollar: %s%a" s pp_print_strategy strategy | TokEq (s, _) -> fprintf buf "equals: %s" s | TokArray (s, _) -> fprintf buf "array: %s" s | TokDot (s, _) -> fprintf buf "dot: %s" s | TokId (s, _) -> fprintf buf "id: %s" s | TokKeyword (s, _) -> fprintf buf "keyword: %s" s | TokCatch (s, _) -> fprintf buf "catch: %s" s | TokClass (s, _) -> fprintf buf "class: %s" s | TokVar (_, s, _) -> fprintf buf "var: %s" s | TokString (s, _) -> fprintf buf "string: %s" s | TokBeginQuote (s, _) -> fprintf buf "begin-quote: %s" s | TokEndQuote (s, _) -> fprintf buf "end-quote: %s" s | TokBeginQuoteString (s, _) -> fprintf buf "begin-quote-string: %s" s | TokEndQuoteString (s, _) -> fprintf buf "end-quote-string: %s" s | TokStringQuote (s, _) -> fprintf buf "quote: %s" s | TokVarQuote (_, s, _) -> fprintf buf "key: %s" s (* * Set state. *) let create name readline = let loc = Lm_location.bogus_loc name in { current_file = Lm_symbol.add name; current_line = 1; current_off = 0; current_loc = loc; current_buffer = ""; current_index = 0; current_prompt = ">"; current_fill_ok = true; current_eof = true; readline = readline; is_interactive = false; current_lexbuf = Lexing.from_string ""; current_lexmode = LexModeInitial; current_token = TokEof loc; current_mode = ModeNormal; current_parens = None; current_indent = 0; current_stack = [] } let set_current_loc state loc = state.current_loc <- loc let current_location state = state.current_loc (* * Advance a line. *) let set_next_line state lexbuf = let { current_line = line; current_file = file } = state in let line = succ line in state.current_line <- line; state.current_off <- Lexing.lexeme_start lexbuf; state.current_loc <- create_loc file line 0 line 0 (* * Save the state. *) let save_mode state = let { current_mode = mode'; current_parens = parens; current_indent = indent; current_stack = stack } = state in let info = { info_mode = mode'; info_parens = parens; info_indent = indent } in info :: stack (* * Restore the state. *) let restore_mode state stack = match stack with info :: stack -> state.current_mode <- info.info_mode; state.current_parens <- info.info_parens; state.current_indent <- info.info_indent; state.current_stack <- stack | [] -> () (* * Push the new mode. *) let push_mode state mode = let stack = save_mode state in state.current_mode <- mode; state.current_parens <- None; state.current_stack <- stack (* * Pop the mode. *) let pop_mode state = restore_mode state state.current_stack (* * We are moving from a quotation to normal mode. * Start collecting parentheses. *) let push_dollar state mode = push_mode state mode; state.current_parens <- Some 0 (* * Push a paren. *) let push_paren state = let { current_parens = parens } = state in match parens with Some i -> state.current_parens <- Some (succ i) | None -> () (* * When a paren is popped, if the level becomes zero, * then return to the previous mode. *) let pop_paren state = let { current_parens = parens } = state in match parens with Some i -> let i = pred i in if i = 0 then pop_mode state else state.current_parens <- Some i | None -> () (* * Get the location of the current lexeme. * We assume it is all on one line. *) let lexeme_loc state lexbuf = let { current_line = line; current_off = off; current_file = file } = state in let schar = Lexing.lexeme_start lexbuf - off in let echar = Lexing.lexeme_end lexbuf - off in let loc = create_loc file line schar line echar in state.current_loc <- loc; loc (* * Raise a syntax error exception. *) let parse_error state = let lexbuf = state.current_lexbuf in let loc = lexeme_loc state lexbuf in let print_error buf = fprintf buf "unexpected token: %a" pp_print_token state.current_token in raise (OmakeException (loc_exp_pos loc, LazyError print_error)) let syntax_error state s lexbuf = let loc = lexeme_loc state lexbuf in raise (OmakeException (loc_exp_pos loc, SyntaxError s)) (* * Get the string in the lexbuf. *) let lexeme_string state lexbuf = let loc = lexeme_loc state lexbuf in let s = Lexing.lexeme lexbuf in s, loc (* * Process a name. *) let lexeme_name state lexbuf = let id, loc = lexeme_string state lexbuf in match id with "if" | "elseif" | "else" | "switch" | "match" | "case" | "default" | "section" | "include" | "extends" | "import" | "try" | "when" | "finally" | "raise" | "return" | "export" | "open" | "declare" | "value" | "while" | "do" -> TokKeyword (id, loc) | "catch" -> TokCatch (id, loc) | "class" -> TokClass (id, loc) | _ -> TokId (id, loc) (* * Get the escaped char. *) let lexeme_esc state lexbuf = let s, loc = lexeme_string state lexbuf in String.make 1 s.[1], loc (* * Single character variable. *) let lexeme_var state lexbuf = let s, loc = lexeme_string state lexbuf in let strategy, s = match s.[1] with '`' -> LazyApply, String.sub s 2 1 | ',' -> EagerApply, String.sub s 2 1 | _ -> NormalApply, String.sub s 1 1 in TokVar (strategy, s, loc) (* * Dollar sequence. *) let lexeme_dollar_pipe state lexbuf = let s, loc = lexeme_string state lexbuf in let len = String.length s in let strategy, off = if len >= 2 then match s.[1] with '`' -> LazyApply, 2 | ',' -> EagerApply, 2 | '|' -> NormalApply, 1 | _ -> syntax_error state ("illegal character: " ^ s) lexbuf else NormalApply, 1 in let s = String.sub s off (String.length s - off) in strategy, s, loc let lexeme_dollar state lexbuf = let s, loc = lexeme_string state lexbuf in let len = String.length s in if len >= 2 then match s.[1] with '`' -> TokDollar (s, LazyApply, loc) | ',' -> TokDollar (s, EagerApply, loc) | '$' -> TokString ("$", loc) | _ -> syntax_error state ("illegal character: " ^ s) lexbuf else TokDollar (s, NormalApply, loc) (* * Special character. * Keep track of paren nesting. *) let lexeme_char state lexbuf = let s, loc = lexeme_string state lexbuf in match s.[0] with '$' -> TokDollar (s, NormalApply, loc) | ':' -> TokColon (s, loc) | ',' -> TokComma (s, loc) | '=' -> TokEq (s, loc) | '(' -> push_paren state; TokLeftParen (s, loc) | ')' -> pop_paren state; TokRightParen (s, loc) | _ -> syntax_error state ("illegal character: " ^ s) lexbuf (* * Count the indentation in a string of characters. *) let indent_of_string s = let len = String.length s in let rec loop col i = if i = len then col else match s.[i] with '\r' | '\n' -> loop 0 (succ i) | '\t' -> loop ((col + 8) land (lnot 7)) (succ i) | _ -> loop (succ col) (succ i) in loop 0 0 (* * Use lexer positions. *) let lexeme_pos lexbuf = let s = Lexing.lexeme lexbuf in let pos1 = Lexing.lexeme_start_p lexbuf in let pos2 = Lexing.lexeme_end_p lexbuf in let { Lexing.pos_fname = file; Lexing.pos_lnum = line1; Lexing.pos_bol = bol1; Lexing.pos_cnum = cnum1 } = pos1 in let { Lexing.pos_lnum = line2; Lexing.pos_bol = bol2; Lexing.pos_cnum = cnum2 } = pos2 in let loc = create_loc (Lm_symbol.add file) line1 (cnum1 - bol1) line2 (cnum2 - bol2) in s, loc # 470 "omake_ast_lex.ml" let __ocaml_lex_tables = { Lexing.lex_base = "\000\000\235\255\114\000\161\000\241\255\018\001\245\255\098\001\ \213\001\251\255\252\255\253\255\001\000\037\002\116\002\006\000\ \001\000\255\255\006\000\049\000\050\000\049\000\240\255\246\255\ \247\255\001\000\201\002\003\000\013\000\070\000\025\003\244\255\ \243\255\139\003\242\255\084\000\236\255\007\000\237\255\252\003\ \047\004\000\004\013\004\009\000\248\255\010\000\249\255\211\004\ \211\004\042\005\095\000\091\000\014\004\156\005\157\000\011\000\ \012\000\219\005\183\004\008\000\099\000\095\000\187\005\013\000\ \127\000\014\000\131\001\212\001\093\006\240\001\015\000\165\004\ \133\000\172\006\255\006\088\000\016\000\250\255\254\255\085\002\ \086\002\229\003\233\003\104\000"; Lexing.lex_backtrk = "\255\255\255\255\017\000\016\000\255\255\016\000\255\255\010\000\ \010\000\255\255\255\255\255\255\002\000\002\000\002\000\001\000\ \021\000\255\255\000\000\255\255\000\000\255\255\255\255\255\255\ \255\255\007\000\009\000\006\000\005\000\255\255\255\255\255\255\ \255\255\016\000\255\255\255\255\255\255\019\000\255\255\255\255\ \005\000\001\000\001\000\000\000\255\255\007\000\255\255\005\000\ \255\255\005\000\002\000\002\000\001\000\001\000\001\000\000\000\ \006\000\005\000\255\255\002\000\002\000\002\000\001\000\000\000\ \001\000\000\000\255\255\000\000\255\255\007\000\004\000\000\000\ \000\000\000\000\000\000\255\255\006\000\255\255\255\255\255\255\ \004\000\255\255\000\000\000\000"; Lexing.lex_default = "\003\000\000\000\255\255\003\000\000\000\003\000\000\000\255\255\ \255\255\000\000\000\000\000\000\255\255\255\255\255\255\255\255\ \019\000\000\000\255\255\019\000\019\000\255\255\000\000\000\000\ \000\000\255\255\255\255\255\255\255\255\255\255\255\255\000\000\ \000\000\003\000\000\000\255\255\000\000\255\255\000\000\041\000\ \255\255\041\000\255\255\255\255\000\000\255\255\000\000\255\255\ \052\000\255\255\255\255\255\255\052\000\052\000\255\255\255\255\ \255\255\255\255\062\000\255\255\255\255\255\255\062\000\255\255\ \255\255\255\255\066\000\066\000\044\000\079\000\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\000\000\000\000\079\000\ \079\000\082\000\082\000\255\255"; Lexing.lex_trans = "\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\015\000\017\000\017\000\015\000\018\000\020\000\015\000\ \017\000\036\000\015\000\017\000\044\000\017\000\046\000\017\000\ \017\000\009\000\046\000\000\000\000\000\000\000\000\000\000\000\ \015\000\000\000\009\000\016\000\008\000\010\000\015\000\009\000\ \006\000\006\000\027\000\005\000\006\000\013\000\004\000\028\000\ \013\000\013\000\013\000\013\000\013\000\013\000\013\000\013\000\ \013\000\013\000\007\000\017\000\017\000\006\000\020\000\020\000\ \013\000\014\000\014\000\014\000\014\000\014\000\014\000\014\000\ \014\000\014\000\014\000\014\000\014\000\014\000\014\000\014\000\ \014\000\014\000\014\000\014\000\014\000\014\000\014\000\014\000\ \014\000\014\000\014\000\012\000\002\000\011\000\022\000\013\000\ \003\000\014\000\014\000\014\000\014\000\014\000\014\000\014\000\ \014\000\014\000\014\000\014\000\014\000\014\000\014\000\014\000\ \014\000\014\000\014\000\014\000\014\000\014\000\014\000\014\000\ \014\000\014\000\014\000\038\000\036\000\025\000\013\000\037\000\ \032\000\050\000\051\000\003\000\059\000\060\000\061\000\017\000\ \064\000\017\000\017\000\064\000\065\000\003\000\072\000\017\000\ \000\000\072\000\038\000\000\000\038\000\038\000\038\000\000\000\ \000\000\038\000\038\000\038\000\000\000\000\000\038\000\064\000\ \000\000\000\000\066\000\000\000\000\000\072\000\000\000\046\000\ \000\000\000\000\056\000\255\255\038\000\000\000\255\255\038\000\ \003\000\000\000\000\000\000\000\017\000\000\000\000\000\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\255\255\255\255\000\000\000\000\255\255\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\255\255\000\000\000\000\255\255\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\255\255\255\255\255\255\000\000\ \001\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\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\255\255\255\255\000\000\255\255\255\255\255\255\255\255\ \000\000\255\255\255\255\255\255\000\000\000\000\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\255\255\000\000\000\000\034\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\255\255\255\255\255\255\ \000\000\000\000\036\000\033\000\033\000\033\000\033\000\033\000\ \033\000\033\000\033\000\033\000\033\000\033\000\033\000\033\000\ \033\000\033\000\033\000\033\000\033\000\033\000\033\000\033\000\ \033\000\033\000\033\000\033\000\033\000\017\000\000\000\030\000\ \067\000\000\000\030\000\030\000\030\000\030\000\030\000\030\000\ \030\000\030\000\030\000\030\000\031\000\046\000\000\000\000\000\ \000\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\030\000\029\000\000\000\029\000\ \000\000\030\000\000\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\030\000\000\000\017\000\000\000\ \030\000\067\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\028\000\ \000\000\023\000\009\000\024\000\027\000\080\000\000\000\024\000\ \024\000\026\000\000\000\000\000\000\000\024\000\024\000\024\000\ \024\000\024\000\024\000\024\000\024\000\024\000\024\000\000\000\ \000\000\024\000\255\255\024\000\024\000\024\000\024\000\024\000\ \024\000\024\000\024\000\024\000\024\000\024\000\024\000\024\000\ \024\000\024\000\024\000\024\000\024\000\024\000\024\000\024\000\ \024\000\024\000\024\000\024\000\024\000\024\000\024\000\024\000\ \024\000\000\000\024\000\024\000\024\000\026\000\024\000\024\000\ \024\000\024\000\024\000\024\000\024\000\024\000\024\000\024\000\ \024\000\024\000\024\000\024\000\024\000\024\000\024\000\024\000\ \024\000\024\000\024\000\024\000\024\000\024\000\024\000\024\000\ \000\000\025\000\013\000\024\000\000\000\013\000\013\000\013\000\ \013\000\013\000\013\000\013\000\013\000\013\000\013\000\009\000\ \009\000\000\000\080\000\080\000\000\000\013\000\013\000\013\000\ \013\000\013\000\013\000\013\000\013\000\013\000\013\000\013\000\ \013\000\013\000\013\000\013\000\013\000\013\000\013\000\013\000\ \013\000\013\000\013\000\013\000\013\000\013\000\013\000\013\000\ \000\000\000\000\000\000\017\000\013\000\000\000\013\000\013\000\ \013\000\013\000\013\000\013\000\013\000\013\000\013\000\013\000\ \013\000\013\000\013\000\013\000\013\000\013\000\013\000\013\000\ \013\000\013\000\013\000\013\000\013\000\013\000\013\000\013\000\ \000\000\013\000\000\000\013\000\013\000\013\000\013\000\013\000\ \013\000\013\000\013\000\013\000\013\000\013\000\021\000\000\000\ \000\000\000\000\000\000\000\000\013\000\013\000\013\000\013\000\ \013\000\013\000\013\000\013\000\013\000\013\000\013\000\013\000\ \013\000\013\000\013\000\013\000\013\000\013\000\013\000\013\000\ \013\000\013\000\013\000\013\000\013\000\013\000\013\000\000\000\ \000\000\000\000\000\000\013\000\017\000\013\000\013\000\013\000\ \013\000\013\000\013\000\013\000\013\000\013\000\013\000\013\000\ \013\000\013\000\013\000\013\000\013\000\013\000\013\000\013\000\ \013\000\013\000\013\000\013\000\013\000\013\000\013\000\024\000\ \255\255\000\000\013\000\024\000\024\000\000\000\000\000\000\000\ \000\000\024\000\024\000\024\000\024\000\024\000\024\000\024\000\ \024\000\024\000\024\000\000\000\000\000\024\000\000\000\024\000\ \024\000\024\000\024\000\024\000\024\000\024\000\024\000\024\000\ \024\000\024\000\024\000\024\000\024\000\024\000\024\000\024\000\ \024\000\024\000\024\000\024\000\024\000\024\000\024\000\024\000\ \024\000\024\000\024\000\024\000\024\000\000\000\024\000\024\000\ \024\000\000\000\024\000\024\000\024\000\024\000\024\000\024\000\ \024\000\024\000\024\000\024\000\024\000\024\000\024\000\024\000\ \024\000\024\000\024\000\024\000\024\000\024\000\024\000\024\000\ \024\000\024\000\024\000\024\000\000\000\025\000\030\000\024\000\ \000\000\030\000\030\000\030\000\030\000\030\000\030\000\030\000\ \030\000\030\000\030\000\032\000\000\000\255\255\255\255\000\000\ \000\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\030\000\030\000\000\000\000\000\000\000\000\000\ \030\000\000\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\030\000\000\000\255\255\000\000\030\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\255\255\255\255\255\255\ \255\255\000\000\255\255\255\255\255\255\000\000\000\000\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\035\000\000\000\000\000\ \255\255\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\255\255\255\255\ \255\255\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\017\000\078\000\ \000\000\043\000\255\255\255\255\078\000\255\255\000\000\000\000\ \255\255\000\000\000\000\000\000\000\000\000\000\000\000\044\000\ \255\255\000\000\045\000\255\255\000\000\000\000\011\000\000\000\ \040\000\000\000\255\255\011\000\255\255\000\000\000\000\255\255\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\046\000\ \255\255\000\000\255\255\000\000\046\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\083\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\010\000\000\000\009\000\000\000\000\000\ \042\000\009\000\009\000\047\000\255\255\000\000\000\000\009\000\ \009\000\009\000\009\000\009\000\009\000\009\000\009\000\009\000\ \009\000\046\000\255\255\009\000\000\000\009\000\009\000\009\000\ \009\000\009\000\009\000\009\000\009\000\009\000\009\000\009\000\ \009\000\009\000\009\000\009\000\009\000\009\000\009\000\009\000\ \009\000\009\000\009\000\009\000\009\000\009\000\009\000\009\000\ \009\000\009\000\009\000\255\255\009\000\009\000\009\000\047\000\ \009\000\009\000\009\000\009\000\009\000\009\000\009\000\009\000\ \009\000\009\000\009\000\009\000\009\000\009\000\009\000\009\000\ \009\000\009\000\009\000\009\000\009\000\009\000\009\000\009\000\ \009\000\009\000\000\000\000\000\000\000\009\000\077\000\046\000\ \000\000\000\000\076\000\000\000\000\000\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\000\000\000\000\000\063\000\077\000\000\000\077\000\ \077\000\077\000\000\000\000\000\077\000\077\000\077\000\000\000\ \000\000\077\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\060\000\000\000\000\000\000\000\017\000\061\000\078\000\ \055\000\000\000\077\000\000\000\000\000\011\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\050\000\000\000\049\000\ \000\000\009\000\051\000\000\000\024\000\009\000\009\000\000\000\ \255\255\077\000\000\000\009\000\009\000\009\000\009\000\009\000\ \009\000\009\000\009\000\009\000\009\000\044\000\255\255\009\000\ \000\000\009\000\009\000\009\000\009\000\009\000\009\000\009\000\ \009\000\009\000\009\000\009\000\009\000\009\000\009\000\009\000\ \009\000\009\000\009\000\009\000\009\000\009\000\009\000\009\000\ \009\000\009\000\009\000\009\000\009\000\009\000\009\000\054\000\ \009\000\009\000\009\000\059\000\009\000\009\000\009\000\009\000\ \009\000\009\000\009\000\009\000\009\000\009\000\009\000\009\000\ \009\000\009\000\009\000\009\000\009\000\009\000\009\000\009\000\ \009\000\009\000\009\000\009\000\009\000\009\000\010\000\053\000\ \009\000\009\000\000\000\000\000\009\000\009\000\057\000\000\000\ \000\000\000\000\009\000\009\000\009\000\009\000\009\000\009\000\ \009\000\009\000\009\000\009\000\000\000\000\000\009\000\000\000\ \009\000\009\000\009\000\009\000\009\000\009\000\009\000\009\000\ \009\000\009\000\009\000\009\000\009\000\009\000\009\000\009\000\ \009\000\009\000\009\000\009\000\009\000\009\000\009\000\009\000\ \009\000\009\000\009\000\009\000\009\000\009\000\000\000\009\000\ \009\000\009\000\057\000\009\000\009\000\009\000\009\000\009\000\ \009\000\009\000\009\000\009\000\009\000\009\000\009\000\009\000\ \009\000\009\000\009\000\009\000\009\000\009\000\009\000\009\000\ \009\000\009\000\009\000\009\000\009\000\046\000\255\255\000\000\ \009\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\010\000\ \000\000\000\000\000\000\000\000\000\000\000\000\255\255\000\000\ \255\255\000\000\000\000\255\255\000\000\255\255\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\044\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\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\ \255\255\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\009\000\000\000\000\000\000\000\009\000\009\000\000\000\ \000\000\000\000\000\000\009\000\009\000\009\000\009\000\009\000\ \009\000\009\000\009\000\009\000\009\000\000\000\000\000\009\000\ \053\000\009\000\009\000\009\000\009\000\009\000\009\000\009\000\ \009\000\009\000\009\000\009\000\009\000\009\000\009\000\009\000\ \009\000\009\000\009\000\009\000\009\000\009\000\009\000\009\000\ \009\000\009\000\009\000\009\000\009\000\009\000\009\000\255\255\ \009\000\009\000\009\000\000\000\009\000\009\000\009\000\009\000\ \009\000\009\000\009\000\009\000\009\000\009\000\009\000\009\000\ \009\000\009\000\009\000\009\000\009\000\009\000\009\000\009\000\ \009\000\009\000\009\000\009\000\009\000\009\000\000\000\000\000\ \000\000\009\000\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\009\000\ \000\000\072\000\070\000\000\000\000\000\000\000\000\000\000\000\ \000\000\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\000\000\010\000\ \069\000\000\000\000\000\000\000\010\000\000\000\000\000\000\000\ \000\000\000\000\073\000\000\000\000\000\073\000\073\000\073\000\ \073\000\073\000\073\000\073\000\073\000\073\000\073\000\011\000\ \000\000\000\000\000\000\000\000\255\255\073\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\ \017\000\071\000\017\000\255\255\073\000\000\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\ \000\000\073\000\000\000\073\000\073\000\073\000\073\000\073\000\ \073\000\073\000\073\000\073\000\073\000\073\000\000\000\000\000\ \000\000\000\000\000\000\000\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\000\000\ \000\000\000\000\000\000\073\000\000\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\000\000\ \000\000\000\000\073\000\000\000\073\000\000\000\000\000\073\000\ \073\000\073\000\073\000\073\000\073\000\073\000\073\000\073\000\ \073\000\075\000\000\000\000\000\000\000\000\000\000\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\000\000\000\000\000\000\024\000\073\000\000\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\000\000\000\000\000\000\073\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\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\016\000\000\000\000\000\016\000\015\000\ \018\000\037\000\015\000\043\000\045\000\055\000\056\000\063\000\ \065\000\070\000\076\000\255\255\255\255\255\255\255\255\255\255\ \000\000\255\255\000\000\000\000\000\000\000\000\015\000\000\000\ \000\000\000\000\027\000\000\000\000\000\000\000\000\000\028\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\020\000\000\000\019\000\020\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\012\000\000\000\ \021\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\ \000\000\000\000\000\000\000\000\000\000\000\000\000\000\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\002\000\025\000\000\000\002\000\ \029\000\050\000\051\000\035\000\059\000\060\000\061\000\075\000\ \064\000\064\000\083\000\064\000\064\000\021\000\072\000\083\000\ \255\255\072\000\002\000\255\255\002\000\002\000\002\000\255\255\ \255\255\002\000\002\000\002\000\255\255\255\255\002\000\064\000\ \255\255\255\255\064\000\255\255\255\255\072\000\255\255\054\000\ \255\255\255\255\054\000\003\000\002\000\255\255\003\000\002\000\ \035\000\255\255\255\255\255\255\075\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\003\000\003\000\003\000\255\255\ \003\000\003\000\003\000\255\255\255\255\003\000\002\000\003\000\ \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\003\000\003\000\003\000\003\000\003\000\003\000\ \003\000\003\000\003\000\003\000\003\000\003\000\003\000\003\000\ \003\000\003\000\003\000\003\000\003\000\003\000\003\000\003\000\ \003\000\003\000\003\000\003\000\003\000\003\000\003\000\255\255\ \000\000\016\000\003\000\003\000\003\000\003\000\003\000\003\000\ \003\000\003\000\003\000\003\000\003\000\003\000\003\000\003\000\ \003\000\003\000\003\000\003\000\003\000\003\000\003\000\003\000\ \003\000\003\000\003\000\003\000\005\000\255\255\255\255\005\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\019\000\020\000\255\255\005\000\005\000\005\000\005\000\ \255\255\005\000\005\000\005\000\255\255\255\255\005\000\255\255\ \005\000\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\005\000\255\255\255\255\005\000\ \255\255\255\255\255\255\005\000\005\000\005\000\005\000\005\000\ \005\000\005\000\005\000\005\000\005\000\005\000\005\000\005\000\ \005\000\005\000\005\000\005\000\005\000\005\000\005\000\005\000\ \005\000\005\000\005\000\005\000\005\000\005\000\005\000\005\000\ \255\255\255\255\002\000\005\000\005\000\005\000\005\000\005\000\ \005\000\005\000\005\000\005\000\005\000\005\000\005\000\005\000\ \005\000\005\000\005\000\005\000\005\000\005\000\005\000\005\000\ \005\000\005\000\005\000\005\000\005\000\066\000\255\255\007\000\ \066\000\255\255\007\000\007\000\007\000\007\000\007\000\007\000\ \007\000\007\000\007\000\007\000\007\000\054\000\255\255\255\255\ \255\255\003\000\007\000\007\000\007\000\007\000\007\000\007\000\ \007\000\007\000\007\000\007\000\007\000\007\000\007\000\007\000\ \007\000\007\000\007\000\007\000\007\000\007\000\007\000\007\000\ \007\000\007\000\007\000\007\000\007\000\007\000\255\255\007\000\ \255\255\007\000\255\255\007\000\007\000\007\000\007\000\007\000\ \007\000\007\000\007\000\007\000\007\000\007\000\007\000\007\000\ \007\000\007\000\007\000\007\000\007\000\007\000\007\000\007\000\ \007\000\007\000\007\000\007\000\007\000\255\255\067\000\255\255\ \007\000\067\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\008\000\ \255\255\008\000\069\000\008\000\008\000\069\000\255\255\008\000\ \008\000\008\000\255\255\255\255\255\255\008\000\008\000\008\000\ \008\000\008\000\008\000\008\000\008\000\008\000\008\000\255\255\ \255\255\008\000\005\000\008\000\008\000\008\000\008\000\008\000\ \008\000\008\000\008\000\008\000\008\000\008\000\008\000\008\000\ \008\000\008\000\008\000\008\000\008\000\008\000\008\000\008\000\ \008\000\008\000\008\000\008\000\008\000\008\000\008\000\008\000\ \008\000\255\255\008\000\008\000\008\000\008\000\008\000\008\000\ \008\000\008\000\008\000\008\000\008\000\008\000\008\000\008\000\ \008\000\008\000\008\000\008\000\008\000\008\000\008\000\008\000\ \008\000\008\000\008\000\008\000\008\000\008\000\008\000\008\000\ \255\255\008\000\013\000\008\000\255\255\013\000\013\000\013\000\ \013\000\013\000\013\000\013\000\013\000\013\000\013\000\079\000\ \080\000\255\255\079\000\080\000\255\255\013\000\013\000\013\000\ \013\000\013\000\013\000\013\000\013\000\013\000\013\000\013\000\ \013\000\013\000\013\000\013\000\013\000\013\000\013\000\013\000\ \013\000\013\000\013\000\013\000\013\000\013\000\013\000\013\000\ \255\255\255\255\255\255\066\000\013\000\255\255\013\000\013\000\ \013\000\013\000\013\000\013\000\013\000\013\000\013\000\013\000\ \013\000\013\000\013\000\013\000\013\000\013\000\013\000\013\000\ \013\000\013\000\013\000\013\000\013\000\013\000\013\000\013\000\ \255\255\014\000\255\255\013\000\014\000\014\000\014\000\014\000\ \014\000\014\000\014\000\014\000\014\000\014\000\014\000\255\255\ \255\255\255\255\255\255\255\255\014\000\014\000\014\000\014\000\ \014\000\014\000\014\000\014\000\014\000\014\000\014\000\014\000\ \014\000\014\000\014\000\014\000\014\000\014\000\014\000\014\000\ \014\000\014\000\014\000\014\000\014\000\014\000\014\000\255\255\ \255\255\255\255\255\255\014\000\067\000\014\000\014\000\014\000\ \014\000\014\000\014\000\014\000\014\000\014\000\014\000\014\000\ \014\000\014\000\014\000\014\000\014\000\014\000\014\000\014\000\ \014\000\014\000\014\000\014\000\014\000\014\000\014\000\026\000\ \069\000\255\255\014\000\026\000\026\000\255\255\255\255\255\255\ \255\255\026\000\026\000\026\000\026\000\026\000\026\000\026\000\ \026\000\026\000\026\000\255\255\255\255\026\000\255\255\026\000\ \026\000\026\000\026\000\026\000\026\000\026\000\026\000\026\000\ \026\000\026\000\026\000\026\000\026\000\026\000\026\000\026\000\ \026\000\026\000\026\000\026\000\026\000\026\000\026\000\026\000\ \026\000\026\000\026\000\026\000\026\000\255\255\026\000\026\000\ \026\000\255\255\026\000\026\000\026\000\026\000\026\000\026\000\ \026\000\026\000\026\000\026\000\026\000\026\000\026\000\026\000\ \026\000\026\000\026\000\026\000\026\000\026\000\026\000\026\000\ \026\000\026\000\026\000\026\000\255\255\026\000\030\000\026\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\255\255\079\000\080\000\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\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\255\255\033\000\255\255\030\000\ \033\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\033\000\033\000\033\000\ \033\000\255\255\033\000\033\000\033\000\255\255\255\255\033\000\ \255\255\033\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\255\255\ \033\000\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\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\039\000\081\000\ \255\255\039\000\041\000\082\000\081\000\041\000\255\255\255\255\ \082\000\255\255\255\255\255\255\255\255\255\255\255\255\042\000\ \052\000\255\255\042\000\052\000\255\255\255\255\039\000\255\255\ \039\000\255\255\041\000\039\000\041\000\255\255\255\255\041\000\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\042\000\ \052\000\255\255\052\000\255\255\042\000\052\000\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\081\000\255\255\255\255\255\255\082\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\040\000\255\255\040\000\255\255\255\255\ \039\000\040\000\040\000\040\000\041\000\255\255\255\255\040\000\ \040\000\040\000\040\000\040\000\040\000\040\000\040\000\040\000\ \040\000\042\000\052\000\040\000\255\255\040\000\040\000\040\000\ \040\000\040\000\040\000\040\000\040\000\040\000\040\000\040\000\ \040\000\040\000\040\000\040\000\040\000\040\000\040\000\040\000\ \040\000\040\000\040\000\040\000\040\000\040\000\040\000\040\000\ \040\000\040\000\040\000\033\000\040\000\040\000\040\000\040\000\ \040\000\040\000\040\000\040\000\040\000\040\000\040\000\040\000\ \040\000\040\000\040\000\040\000\040\000\040\000\040\000\040\000\ \040\000\040\000\040\000\040\000\040\000\040\000\040\000\040\000\ \040\000\040\000\255\255\255\255\255\255\040\000\071\000\071\000\ \255\255\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\058\000\255\255\255\255\058\000\071\000\255\255\071\000\ \071\000\071\000\255\255\255\255\071\000\071\000\071\000\255\255\ \255\255\071\000\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\058\000\255\255\255\255\255\255\048\000\058\000\071\000\ \048\000\255\255\071\000\255\255\255\255\081\000\255\255\255\255\ \255\255\082\000\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\048\000\255\255\048\000\ \255\255\047\000\048\000\255\255\039\000\047\000\047\000\255\255\ \041\000\071\000\255\255\047\000\047\000\047\000\047\000\047\000\ \047\000\047\000\047\000\047\000\047\000\042\000\052\000\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\047\000\047\000\047\000\047\000\048\000\ \047\000\047\000\047\000\058\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\049\000\048\000\ \049\000\047\000\255\255\255\255\049\000\049\000\049\000\255\255\ \255\255\255\255\049\000\049\000\049\000\049\000\049\000\049\000\ \049\000\049\000\049\000\049\000\255\255\255\255\049\000\255\255\ \049\000\049\000\049\000\049\000\049\000\049\000\049\000\049\000\ \049\000\049\000\049\000\049\000\049\000\049\000\049\000\049\000\ \049\000\049\000\049\000\049\000\049\000\049\000\049\000\049\000\ \049\000\049\000\049\000\049\000\049\000\049\000\255\255\049\000\ \049\000\049\000\049\000\049\000\049\000\049\000\049\000\049\000\ \049\000\049\000\049\000\049\000\049\000\049\000\049\000\049\000\ \049\000\049\000\049\000\049\000\049\000\049\000\049\000\049\000\ \049\000\049\000\049\000\049\000\049\000\071\000\053\000\255\255\ \049\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\058\000\ \255\255\255\255\255\255\255\255\255\255\255\255\053\000\255\255\ \053\000\255\255\255\255\053\000\255\255\062\000\255\255\255\255\ \062\000\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\048\000\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\062\000\255\255\255\255\ \255\255\255\255\062\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\ \053\000\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\057\000\255\255\255\255\255\255\057\000\057\000\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\255\255\255\255\057\000\ \053\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\062\000\ \057\000\057\000\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\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\068\000\068\000\ \255\255\068\000\068\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\068\000\255\255\068\000\ \068\000\255\255\255\255\255\255\068\000\255\255\255\255\255\255\ \255\255\255\255\068\000\255\255\255\255\068\000\068\000\068\000\ \068\000\068\000\068\000\068\000\068\000\068\000\068\000\068\000\ \255\255\255\255\255\255\255\255\053\000\068\000\068\000\068\000\ \068\000\068\000\068\000\068\000\068\000\068\000\068\000\068\000\ \068\000\068\000\068\000\068\000\068\000\068\000\068\000\068\000\ \068\000\068\000\068\000\068\000\068\000\068\000\068\000\068\000\ \068\000\068\000\068\000\062\000\068\000\255\255\068\000\068\000\ \068\000\068\000\068\000\068\000\068\000\068\000\068\000\068\000\ \068\000\068\000\068\000\068\000\068\000\068\000\068\000\068\000\ \068\000\068\000\068\000\068\000\068\000\068\000\068\000\068\000\ \255\255\073\000\255\255\068\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\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\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\073\000\255\255\074\000\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\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\255\255\255\255\255\255\068\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\255\255\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\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\255\ \255\255\255\255\255\255\255\255\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 lex_main state lexbuf = __ocaml_lex_lex_main_rec state lexbuf 0 and __ocaml_lex_lex_main_rec state lexbuf __ocaml_lex_state = match Lexing.engine __ocaml_lex_tables __ocaml_lex_state lexbuf with | 0 -> # 582 "omake_ast_lex.mll" ( let loc = state.current_loc in let _ = lexeme_loc state lexbuf in set_next_line state lexbuf; TokEol (loc) ) # 1049 "omake_ast_lex.ml" | 1 -> # 588 "omake_ast_lex.mll" ( let s, loc = lexeme_string state lexbuf in TokWhite (s, loc) ) # 1056 "omake_ast_lex.ml" | 2 -> # 592 "omake_ast_lex.mll" ( lexeme_name state lexbuf ) # 1061 "omake_ast_lex.ml" | 3 -> # 594 "omake_ast_lex.mll" ( let s, loc = lexeme_string state lexbuf in TokVar (NormalApply, s, loc) ) # 1068 "omake_ast_lex.ml" | 4 -> # 598 "omake_ast_lex.mll" ( let id, loc = lexeme_string state lexbuf in let mode = ModeQuote id in push_mode state mode; TokBeginQuoteString (id, loc) ) # 1077 "omake_ast_lex.ml" | 5 -> # 604 "omake_ast_lex.mll" ( let id, loc = lexeme_string state lexbuf in let id = String.sub id 1 (pred (String.length id)) in let mode = ModeString id in push_mode state mode; TokBeginQuote ("", loc) ) # 1087 "omake_ast_lex.ml" | 6 -> # 611 "omake_ast_lex.mll" ( let id, loc = lexeme_string state lexbuf in let id = String.sub id 1 (pred (String.length id)) in let s, loc = lex_literal state (Buffer.create 32) id lexbuf in TokStringQuote (s, loc) ) # 1096 "omake_ast_lex.ml" | 7 -> # 617 "omake_ast_lex.mll" ( let strategy, id, loc = lexeme_dollar_pipe state lexbuf in let s, loc = lex_literal state (Buffer.create 32) id lexbuf in TokVarQuote (strategy, s, loc) ) # 1104 "omake_ast_lex.ml" | 8 -> # 622 "omake_ast_lex.mll" ( lexeme_var state lexbuf ) # 1109 "omake_ast_lex.ml" | 9 -> # 624 "omake_ast_lex.mll" ( lexeme_dollar state lexbuf ) # 1114 "omake_ast_lex.ml" | 10 -> # 626 "omake_ast_lex.mll" ( lexeme_char state lexbuf ) # 1119 "omake_ast_lex.ml" | 11 -> # 628 "omake_ast_lex.mll" ( let s, loc = lexeme_string state lexbuf in TokDoubleColon (s, loc) ) # 1126 "omake_ast_lex.ml" | 12 -> # 632 "omake_ast_lex.mll" ( let s, loc = lexeme_string state lexbuf in TokNamedColon (s, loc) ) # 1133 "omake_ast_lex.ml" | 13 -> # 636 "omake_ast_lex.mll" ( let s, loc = lexeme_string state lexbuf in TokEq (s, loc) ) # 1140 "omake_ast_lex.ml" | 14 -> # 640 "omake_ast_lex.mll" ( let s, loc = lexeme_string state lexbuf in TokDot (s, loc) ) # 1147 "omake_ast_lex.ml" | 15 -> # 644 "omake_ast_lex.mll" ( let s, loc = lexeme_string state lexbuf in TokArray (s, loc) ) # 1154 "omake_ast_lex.ml" | 16 -> # 648 "omake_ast_lex.mll" ( let s, loc = lexeme_string state lexbuf in TokString (s, loc) ) # 1161 "omake_ast_lex.ml" | 17 -> # 652 "omake_ast_lex.mll" ( let s, loc = lexeme_string state lexbuf in TokString (s, loc) ) # 1168 "omake_ast_lex.ml" | 18 -> # 656 "omake_ast_lex.mll" ( let s, loc = lexeme_esc state lexbuf in TokStringQuote (s, loc) ) # 1175 "omake_ast_lex.ml" | 19 -> # 660 "omake_ast_lex.mll" ( let loc = lexeme_loc state lexbuf in set_next_line state lexbuf; state.current_prompt <- "\\"; state.current_fill_ok <- true; TokString (" ", loc) ) # 1185 "omake_ast_lex.ml" | 20 -> # 667 "omake_ast_lex.mll" ( let loc = lexeme_loc state lexbuf in match state.current_token with TokEol _ | TokEof _ -> TokEof loc | _ -> TokEol loc ) # 1197 "omake_ast_lex.ml" | 21 -> # 676 "omake_ast_lex.mll" ( let s, loc = lexeme_string state lexbuf in syntax_error state ("illegal character: " ^ String.escaped s) lexbuf ) # 1204 "omake_ast_lex.ml" | __ocaml_lex_state -> lexbuf.Lexing.refill_buff lexbuf; __ocaml_lex_lex_main_rec state lexbuf __ocaml_lex_state and lex_quote state lexbuf = __ocaml_lex_lex_quote_rec state lexbuf 39 and __ocaml_lex_lex_quote_rec state lexbuf __ocaml_lex_state = match Lexing.engine __ocaml_lex_tables __ocaml_lex_state lexbuf with | 0 -> # 688 "omake_ast_lex.mll" ( set_next_line state lexbuf; syntax_error state "unterminated string" lexbuf ) # 1217 "omake_ast_lex.ml" | 1 -> # 693 "omake_ast_lex.mll" ( let s, loc = lexeme_string state lexbuf in TokString (s, loc) ) # 1224 "omake_ast_lex.ml" | 2 -> # 697 "omake_ast_lex.mll" ( let s, loc = lexeme_string state lexbuf in match state.current_mode with ModeQuote s' when s' = s -> pop_mode state; TokEndQuoteString (s, loc) | _ -> TokString (s, loc) ) # 1236 "omake_ast_lex.ml" | 3 -> # 706 "omake_ast_lex.mll" ( let loc = lexeme_loc state lexbuf in TokString ("$", loc) ) # 1243 "omake_ast_lex.ml" | 4 -> # 710 "omake_ast_lex.mll" ( lexeme_var state lexbuf ) # 1248 "omake_ast_lex.ml" | 5 -> # 712 "omake_ast_lex.mll" ( push_dollar state ModeNormal; lexeme_dollar state lexbuf ) # 1255 "omake_ast_lex.ml" | 6 -> # 716 "omake_ast_lex.mll" ( let s, loc = lexeme_esc state lexbuf in TokString (s, loc) ) # 1262 "omake_ast_lex.ml" | 7 -> # 720 "omake_ast_lex.mll" ( let loc = lexeme_loc state lexbuf in set_next_line state lexbuf; state.current_fill_ok <- true; TokString ("", loc) ) # 1271 "omake_ast_lex.ml" | 8 -> # 726 "omake_ast_lex.mll" ( syntax_error state "unterminated string" lexbuf ) # 1276 "omake_ast_lex.ml" | 9 -> # 728 "omake_ast_lex.mll" ( let s, loc = lexeme_string state lexbuf in syntax_error state ("illegal character in string constant: " ^ String.escaped s) lexbuf ) # 1283 "omake_ast_lex.ml" | __ocaml_lex_state -> lexbuf.Lexing.refill_buff lexbuf; __ocaml_lex_lex_quote_rec state lexbuf __ocaml_lex_state and lex_string state lexbuf = __ocaml_lex_lex_string_rec state lexbuf 48 and __ocaml_lex_lex_string_rec state lexbuf __ocaml_lex_state = match Lexing.engine __ocaml_lex_tables __ocaml_lex_state lexbuf with | 0 -> # 739 "omake_ast_lex.mll" ( let s, loc = lexeme_string state lexbuf in set_next_line state lexbuf; state.current_fill_ok <- true; TokString (s, loc) ) # 1298 "omake_ast_lex.ml" | 1 -> # 746 "omake_ast_lex.mll" ( let s, loc = lexeme_string state lexbuf in TokString (s, loc) ) # 1305 "omake_ast_lex.ml" | 2 -> # 750 "omake_ast_lex.mll" ( let s, loc = lexeme_string state lexbuf in match state.current_mode with ModeString s' when s' = s -> pop_mode state; TokEndQuote ("", loc) | _ -> TokString (s, loc) ) # 1317 "omake_ast_lex.ml" | 3 -> # 759 "omake_ast_lex.mll" ( let loc = lexeme_loc state lexbuf in TokString ("$", loc) ) # 1324 "omake_ast_lex.ml" | 4 -> # 763 "omake_ast_lex.mll" ( lexeme_var state lexbuf ) # 1329 "omake_ast_lex.ml" | 5 -> # 765 "omake_ast_lex.mll" ( push_dollar state ModeNormal; lexeme_dollar state lexbuf ) # 1336 "omake_ast_lex.ml" | 6 -> # 769 "omake_ast_lex.mll" ( let loc = lexeme_loc state lexbuf in set_next_line state lexbuf; state.current_fill_ok <- true; TokString ("", loc) ) # 1345 "omake_ast_lex.ml" | 7 -> # 775 "omake_ast_lex.mll" ( syntax_error state "unterminated string" lexbuf ) # 1350 "omake_ast_lex.ml" | 8 -> # 777 "omake_ast_lex.mll" ( let s, loc = lexeme_string state lexbuf in syntax_error state ("illegal character: " ^ String.escaped s) lexbuf ) # 1357 "omake_ast_lex.ml" | __ocaml_lex_state -> lexbuf.Lexing.refill_buff lexbuf; __ocaml_lex_lex_string_rec state lexbuf __ocaml_lex_state and lex_literal state buf equote lexbuf = __ocaml_lex_lex_literal_rec state buf equote lexbuf 58 and __ocaml_lex_lex_literal_rec state buf equote lexbuf __ocaml_lex_state = match Lexing.engine __ocaml_lex_tables __ocaml_lex_state lexbuf with | 0 -> # 786 "omake_ast_lex.mll" ( let s, loc = lexeme_string state lexbuf in set_next_line state lexbuf; state.current_fill_ok <- true; Buffer.add_string buf s; lex_literal state buf equote lexbuf ) # 1373 "omake_ast_lex.ml" | 1 -> # 793 "omake_ast_lex.mll" ( let s, loc = lexeme_string state lexbuf in Buffer.add_string buf s; lex_literal state buf equote lexbuf ) # 1381 "omake_ast_lex.ml" | 2 -> # 798 "omake_ast_lex.mll" ( let s, loc = lexeme_string state lexbuf in if s = equote then let s = Buffer.contents buf in s, loc else begin Buffer.add_string buf s; lex_literal state buf equote lexbuf end ) # 1395 "omake_ast_lex.ml" | 3 -> # 809 "omake_ast_lex.mll" ( syntax_error state "unterminated string" lexbuf ) # 1400 "omake_ast_lex.ml" | 4 -> # 811 "omake_ast_lex.mll" ( let s, loc = lexeme_string state lexbuf in syntax_error state ("illegal character: " ^ String.escaped s) lexbuf ) # 1407 "omake_ast_lex.ml" | __ocaml_lex_state -> lexbuf.Lexing.refill_buff lexbuf; __ocaml_lex_lex_literal_rec state buf equote lexbuf __ocaml_lex_state and lex_indent state lexbuf = __ocaml_lex_lex_indent_rec state lexbuf 64 and __ocaml_lex_lex_indent_rec state lexbuf __ocaml_lex_state = match Lexing.engine __ocaml_lex_tables __ocaml_lex_state lexbuf with | 0 -> # 821 "omake_ast_lex.mll" ( set_next_line state lexbuf; state.current_fill_ok <- true; lex_indent state lexbuf ) # 1421 "omake_ast_lex.ml" | 1 -> # 826 "omake_ast_lex.mll" ( let s, loc = lexeme_string state lexbuf in let indent = indent_of_string s in indent ) # 1429 "omake_ast_lex.ml" | __ocaml_lex_state -> lexbuf.Lexing.refill_buff lexbuf; __ocaml_lex_lex_indent_rec state lexbuf __ocaml_lex_state and lex_deps lexbuf = __ocaml_lex_lex_deps_rec lexbuf 68 and __ocaml_lex_lex_deps_rec lexbuf __ocaml_lex_state = match Lexing.engine __ocaml_lex_tables __ocaml_lex_state lexbuf with | 0 -> # 839 "omake_ast_lex.mll" ( let s, loc = lexeme_pos lexbuf in TokString (s, loc) ) # 1442 "omake_ast_lex.ml" | 1 -> # 843 "omake_ast_lex.mll" ( let _, loc = lexeme_pos lexbuf in TokString (":", loc) ) # 1449 "omake_ast_lex.ml" | 2 -> # 847 "omake_ast_lex.mll" ( let s, loc = lexeme_pos lexbuf in TokColon (s, loc) ) # 1456 "omake_ast_lex.ml" | 3 -> # 851 "omake_ast_lex.mll" ( let s, loc = lexeme_pos lexbuf in let buf = Buffer.create 64 in Buffer.add_string buf s; lex_deps_quote s buf lexbuf; TokString (Buffer.contents buf, loc) ) # 1466 "omake_ast_lex.ml" | 4 -> # 859 "omake_ast_lex.mll" ( let _, loc = lexeme_pos lexbuf in TokEol loc ) # 1473 "omake_ast_lex.ml" | 5 -> # 863 "omake_ast_lex.mll" ( let s, loc = lexeme_pos lexbuf in let s = String.make 1 s.[1] in TokStringQuote (s, loc) ) # 1481 "omake_ast_lex.ml" | 6 -> # 868 "omake_ast_lex.mll" ( let _, loc = lexeme_pos lexbuf in TokWhite (" ", loc) ) # 1488 "omake_ast_lex.ml" | 7 -> # 872 "omake_ast_lex.mll" ( let s, loc = lexeme_pos lexbuf in TokString (s, loc) ) # 1495 "omake_ast_lex.ml" | 8 -> # 876 "omake_ast_lex.mll" ( let _, loc = lexeme_pos lexbuf in TokEof loc ) # 1502 "omake_ast_lex.ml" | __ocaml_lex_state -> lexbuf.Lexing.refill_buff lexbuf; __ocaml_lex_lex_deps_rec lexbuf __ocaml_lex_state and lex_deps_quote term buf lexbuf = __ocaml_lex_lex_deps_quote_rec term buf lexbuf 81 and __ocaml_lex_lex_deps_quote_rec term buf lexbuf __ocaml_lex_state = match Lexing.engine __ocaml_lex_tables __ocaml_lex_state lexbuf with | 0 -> # 884 "omake_ast_lex.mll" ( let s, loc = lexeme_pos lexbuf in Buffer.add_string buf s; lex_deps_quote term buf lexbuf ) # 1516 "omake_ast_lex.ml" | 1 -> # 889 "omake_ast_lex.mll" ( let s, loc = lexeme_pos lexbuf in Buffer.add_string buf s; if s <> term then lex_deps_quote term buf lexbuf ) # 1525 "omake_ast_lex.ml" | 2 -> # 896 "omake_ast_lex.mll" ( raise Parsing.Parse_error ) # 1530 "omake_ast_lex.ml" | __ocaml_lex_state -> lexbuf.Lexing.refill_buff lexbuf; __ocaml_lex_lex_deps_quote_rec term buf lexbuf __ocaml_lex_state ;; # 898 "omake_ast_lex.mll" (************************************************************************ * Prompts. *) (* * Lex and parse a line for the shell. *) let tabstop = 3 let prompt_ext s = s ^ "> " (* Prune the prompt to a reasonable length *) let prompt_prune prompt indent = let max_len = 8 in let s = String.make (indent * tabstop + max_len + 2) ' ' in let length = String.length prompt in if length > max_len then begin String.blit prompt 0 s 0 max_len; s.[max_len] <- '>' end else String.blit prompt 0 s 0 length; s let prompt_indent prompt root indent = if root then prompt else prompt_prune prompt indent let prompt_string state root nest e = let prompt = prompt_ext (key_of_exp e) in if state.is_interactive && root then printf "%s%s@?" (prompt_prune prompt nest) state.current_buffer; prompt (* * Parser for the body of an expression. *) let body_parser state body = match body with NoBody -> None | OptBody -> if state.is_interactive then None else Some Omake_ast_parse.shell | ColonBody -> Some Omake_ast_parse.shell | OptStringBody -> Some Omake_ast_parse.string (************************************************************************ * Lexing input. *) (* * Copy into the lexbuf. *) let lex_fill state buf len = let { current_mode = mode; current_buffer = buffer; current_index = index } = state in let length = String.length buffer in let amount = min (length - index) len in if amount = 0 then state.current_eof <- true else begin String.blit buffer index buf 0 amount; state.current_index <- index + amount end; amount (* * Refill the buffer using the readline function. *) let state_refill state = let { current_fill_ok = fill_ok; current_prompt = prompt; readline = readline; } = state in if fill_ok then let line = readline prompt in let line = if state.is_interactive && line = ".\n" then "" else line in state.current_buffer <- line; state.current_index <- 0; state.current_fill_ok <- false (* * Lexer function to refill the buffer. *) let lex_refill state buf len = let { current_buffer = buffer; current_index = index } = state in let length = String.length buffer in let amount = length - index in if amount = 0 then state_refill state; lex_fill state buf len (************************************************************************ * Main lexer. *) (* * Get the input. *) let lex_line state lexbuf = let tok = match state.current_mode with ModeNormal -> lex_main state lexbuf | ModeString _ -> lex_string state lexbuf | ModeQuote _ -> lex_quote state lexbuf in if !debug_lex then eprintf "Token: %a@." pp_print_token tok; state.current_token <- tok; tok (************************************************************************ * Parse main loop. *) (* * Make sure the lexbuf is valid. *) let parse_refill state prompt root nest = if state.current_eof then begin let lexbuf = Lexing.from_function (lex_refill state) in state.current_eof <- false; state.current_fill_ok <- true; state.current_prompt <- prompt_indent prompt root nest; state.current_lexbuf <- lexbuf; state.current_lexmode <- LexModeInitial; state.current_off <- 0 end (* * Get the current indentation level. *) let parse_indent state prompt root nest = parse_refill state prompt root nest; match state.current_lexmode with LexModeInitial -> let indent = (* Interactive shell ignores indentation *) if state.is_interactive then nest else lex_indent state state.current_lexbuf in if !debug_lex then eprintf "indent: %d@." indent; state.current_lexmode <- LexModeNormal indent; indent | LexModeNormal indent -> indent (* * Parse a single expression. *) let rec parse_exp state parse prompt root nest = let indent = parse_indent state prompt root nest in if indent > state.current_indent then syntax_error state "illegal indentation" state.current_lexbuf else if indent < state.current_indent then raise End_of_file else parse_exp_indent state parse prompt root nest and parse_exp_indent state parse prompt root nest = let body, e = try parse (lex_line state) state.current_lexbuf with Parsing.Parse_error -> parse_error state in let parse = body_parser state body in match parse with Some parse -> let prompt = prompt_string state root nest e in let body = parse_body state parse prompt nest in let e = update_body e body in (match can_continue e with Some prompt -> (try e :: parse_exp state parse (prompt_ext prompt) false nest with End_of_file -> [e]) | None -> [e]) | None -> [e] and parse_body state parse prompt nest = let nest = succ nest in let indent = parse_indent state prompt false nest in if indent > state.current_indent then begin push_mode state ModeNormal; state.current_indent <- indent; parse_body_indent state parse prompt nest [] end else [] and parse_body_indent state parse prompt nest el = let e = try ParseExp (parse_exp state parse prompt false nest) with End_of_file -> if state.is_interactive then printf ".@."; pop_mode state; ParseEOF | OmakeException _ as exn when state.is_interactive -> eprintf "%a@." pp_print_exn exn; ParseError in match e with ParseExp e -> parse_body_indent state parse prompt nest (List.rev_append e el) | ParseError -> parse_body_indent state parse prompt nest el | ParseEOF -> List.rev el (* * Parse a file. *) let parse_ast name = let inx = open_in name in let readline prompt = try input_line inx ^ "\n" with End_of_file -> "" in let state = create name readline in let el = parse_body_indent state Omake_ast_parse.shell "" 0 [] in close_in inx; el (* * Parse a string. *) let parse_string s = let len = String.length s in let index = ref 0 in let readline prompt = let start = !index in let rec search i = if i = len then if start < i then begin index := i; String.sub s start (i - start) ^ "\n" end else raise End_of_file else if s.[i] = '\n' then begin index := i + 1; String.sub s start (i - start + 1) end else search (succ i) in search start in let state = create "-" readline in parse_body_indent state Omake_ast_parse.shell "" 0 [] (* * Parse an expression. *) let create_shell () = let state = create "-" Omake_readline.readline in state.is_interactive <- Omake_readline.is_interactive (); state (* * Copy the state, if an exception happens, then * restore the initial state. *) let parse_shell state prompt = let stack = save_mode state in state.current_fill_ok <- true; try parse_exp state Omake_ast_parse.shell prompt true 0 with exn -> Omake_readline.flush (); restore_mode state stack; state.current_buffer <- ""; state.current_index <- 0; raise exn (* * Just dependency analysis. *) let parse_deps name = let inx = open_in name in let lexbuf = Lexing.from_channel inx in let deps = try Omake_ast_parse.deps lex_deps lexbuf with exn -> close_in inx; eprintf "%s: char %d: scanner dependency syntax error@." name (Lexing.lexeme_end lexbuf); raise exn in close_in inx; deps # 1864 "omake_ast_lex.ml"