(* Copyright (C) 2005, HELM Team. * * This file is part of HELM, an Hypertextual, Electronic * Library of Mathematics, developed at the Computer Science * Department, University of Bologna, Italy. * * HELM is free software; you can redistribute it and/or * modify it under the terms of the GNU General Public License * as published by the Free Software Foundation; either version 2 * of the License, or (at your option) any later version. * * HELM is distributed in the hope that it will be useful, * but WITHOUT ANY WARRANTY; without even the implied warranty of * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the * GNU General Public License for more details. * * You should have received a copy of the GNU General Public License * along with HELM; if not, write to the Free Software * Foundation, Inc., 59 Temple Place - Suite 330, Boston, * MA 02111-1307, USA. * * For details, see the HELM World-Wide-Web page, * http://helm.cs.unibo.it/ *) open Printf exception Parse_error of Token.flocation * string module Level1Lexer = struct type te = string * string let lexer = CicNotationLexer.syntax_pattern_lexer end module Level1Parser = Grammar.GMake (Level1Lexer) module Level2Lexer = struct type te = string * string let lexer = CicNotationLexer.ast_pattern_lexer end module Level2Parser = Grammar.GMake (Level2Lexer) let level1_pattern = Level1Parser.Entry.create "level1_pattern" let level2_pattern = Level2Parser.Entry.create "level2_pattern" let return_term loc term = () (*let fail floc msg =*) (* let (x, y) = CicAst.loc_of_floc floc in*) (* failwith (sprintf "Error at characters %d - %d: %s" x y msg)*) let int_of_string s = try Pervasives.int_of_string s with Failure _ -> failwith (sprintf "Lexer failure: string_of_int \"%s\" failed" s) (* {{{ Grammar for concrete syntax patterns, notation level 1 *) GEXTEND Level1Parser GLOBAL: level1_pattern; level1_pattern: [ [ p = pattern -> () ] ]; pattern: [ [ p = LIST1 simple_pattern -> () ] ]; literal: [ [ s = SYMBOL -> () | k = KEYWORD -> () ] ]; sep: [ [ SYMBOL "\\SEP"; sep = literal -> () ] ]; row_sep: [ [ SYMBOL "\\ROWSEP"; sep = literal -> () ] ]; field_sep: [ [ SYMBOL "\\FIELDSEP"; sep = literal -> () ] ]; box_token: [ [ SYMBOL "\\HBOX"; p = simple_pattern -> () | SYMBOL "\\VBOX"; p = simple_pattern -> () | SYMBOL "\\BREAK" -> () ] ]; simple_pattern: [ "infix" LEFTA (* TODO XXX many issues here: * - "^^" is lexed as two "^" symbols * - "a_b" is lexed as IDENT "a_b" *) [ p1 = SELF; SYMBOL "^"; p2 = SELF -> () | p1 = SELF; SYMBOL "^"; SYMBOL "^"; p2 = SELF -> () | p1 = SELF; SYMBOL "_"; p2 = SELF -> () | p1 = SELF; SYMBOL "_"; SYMBOL "_"; p2 = SELF -> () ] | "simple" NONA [ SYMBOL "\\LIST0"; p = SELF; sep = OPT sep -> () | SYMBOL "\\LIST1"; p = SELF; sep = OPT sep -> () | b = box_token -> () | id = IDENT -> () | SYMBOL "\\NUM"; id = IDENT -> () | SYMBOL "\\IDENT"; id = IDENT -> () | SYMBOL "\\OPT"; p = SELF -> () | SYMBOL "\\ARRAY"; p = SELF; fsep = OPT field_sep; rsep = OPT row_sep -> () | SYMBOL "\\FRAC"; p1 = SELF; p2 = SELF -> () | SYMBOL "\\SQRT"; p = SELF -> () | SYMBOL "\\ROOT"; p1 = SELF; SYMBOL "\\OF"; p2 = SELF -> () | SYMBOL "["; p = pattern; SYMBOL "]" -> () ] ]; END (* }}} *) (* {{{ Grammar for ast patterns, notation level 2 *) GEXTEND Level2Parser GLOBAL: level2_pattern; level2_pattern: [ [ p = pattern -> () ] ]; pattern: [ [ a = ast -> () ] ]; ast: [ [ SYMBOL "\\FOO" -> () ] ]; END (* }}} *) let exc_located_wrapper f = try f () with | Stdpp.Exc_located (floc, Stream.Error msg) -> raise (Parse_error (floc, msg)) | Stdpp.Exc_located (floc, exn) -> raise (Parse_error (floc, (Printexc.to_string exn))) let parse_syntax_pattern stream = exc_located_wrapper (fun () -> (Level1Parser.Entry.parse level1_pattern (Level1Parser.parsable stream))) let parse_ast_pattern stream = exc_located_wrapper (fun () -> (Level2Parser.Entry.parse level2_pattern (Level2Parser.parsable stream))) (* vim:set encoding=utf8 foldmethod=marker: *)