]> matita.cs.unibo.it Git - helm.git/blob - helm/ocaml/cic_notation/cicNotationParser.ml
snapshot, notably:
[helm.git] / helm / ocaml / cic_notation / cicNotationParser.ml
1 (* Copyright (C) 2005, HELM Team.
2  * 
3  * This file is part of HELM, an Hypertextual, Electronic
4  * Library of Mathematics, developed at the Computer Science
5  * Department, University of Bologna, Italy.
6  * 
7  * HELM is free software; you can redistribute it and/or
8  * modify it under the terms of the GNU General Public License
9  * as published by the Free Software Foundation; either version 2
10  * of the License, or (at your option) any later version.
11  * 
12  * HELM is distributed in the hope that it will be useful,
13  * but WITHOUT ANY WARRANTY; without even the implied warranty of
14  * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
15  * GNU General Public License for more details.
16  *
17  * You should have received a copy of the GNU General Public License
18  * along with HELM; if not, write to the Free Software
19  * Foundation, Inc., 59 Temple Place - Suite 330, Boston,
20  * MA  02111-1307, USA.
21  * 
22  * For details, see the HELM World-Wide-Web page,
23  * http://helm.cs.unibo.it/
24  *)
25
26 open Printf
27
28 exception Parse_error of Token.flocation * string
29
30 module Level1Lexer =
31 struct
32   type te = string * string
33   let lexer = CicNotationLexer.syntax_pattern_lexer
34 end
35 module Level1Parser = Grammar.GMake (Level1Lexer)
36
37 module Level2Lexer =
38 struct
39   type te = string * string
40   let lexer = CicNotationLexer.ast_pattern_lexer
41 end
42 module Level2Parser = Grammar.GMake (Level2Lexer)
43
44 let level1_pattern = Level1Parser.Entry.create "level1_pattern"
45 let level2_pattern = Level2Parser.Entry.create "level2_pattern"
46
47 let return_term loc term = ()
48
49 (*let fail floc msg =*)
50 (*  let (x, y) = CicAst.loc_of_floc floc in*)
51 (*  failwith (sprintf "Error at characters %d - %d: %s" x y msg)*)
52
53 let int_of_string s =
54   try
55     Pervasives.int_of_string s
56   with Failure _ ->
57     failwith (sprintf "Lexer failure: string_of_int \"%s\" failed" s)
58
59 (* {{{ Grammar for concrete syntax patterns, notation level 1 *)
60 GEXTEND Level1Parser
61   GLOBAL: level1_pattern;
62   level1_pattern: [ [ p = pattern -> () ] ];
63
64   pattern: [ [ p = LIST1 simple_pattern -> () ] ];
65
66   literal: [
67     [ s = SYMBOL -> ()
68     | k = KEYWORD -> ()
69     ]
70   ];
71
72   sep:       [ [ SYMBOL "\\SEP";      sep = literal -> () ] ];
73   row_sep:   [ [ SYMBOL "\\ROWSEP";   sep = literal -> () ] ];
74   field_sep: [ [ SYMBOL "\\FIELDSEP"; sep = literal -> () ] ];
75
76   box_token: [
77     [ SYMBOL "\\HBOX"; p = simple_pattern -> ()
78     | SYMBOL "\\VBOX"; p = simple_pattern -> ()
79     | SYMBOL "\\BREAK" -> ()
80     ]
81   ];
82
83   simple_pattern:
84     [ "infix" LEFTA
85        (* TODO XXX many issues here:
86         * - "^^" is lexed as two "^" symbols
87         * - "a_b" is lexed as IDENT "a_b" *)
88       [ p1 = SELF; SYMBOL "^"; p2 = SELF -> ()
89       | p1 = SELF; SYMBOL "^"; SYMBOL "^"; p2 = SELF -> ()
90       | p1 = SELF; SYMBOL "_"; p2 = SELF -> ()
91       | p1 = SELF; SYMBOL "_"; SYMBOL "_"; p2 = SELF -> ()
92       ]
93     | "simple" NONA
94       [ SYMBOL "\\LIST0"; p = SELF; sep = OPT sep -> ()
95       | SYMBOL "\\LIST1"; p = SELF; sep = OPT sep -> ()
96       | b = box_token -> ()
97       | id = IDENT -> ()
98       | SYMBOL "\\NUM"; id = IDENT -> ()
99       | SYMBOL "\\IDENT"; id = IDENT -> ()
100       | SYMBOL "\\OPT"; p = SELF -> ()
101       | SYMBOL "\\ARRAY"; p = SELF; fsep = OPT field_sep; rsep = OPT row_sep ->
102           ()
103       | SYMBOL "\\FRAC"; p1 = SELF; p2 = SELF -> ()
104       | SYMBOL "\\SQRT"; p = SELF -> ()
105       | SYMBOL "\\ROOT"; p1 = SELF; SYMBOL "\\OF"; p2 = SELF ->
106           ()
107       | SYMBOL "["; p = pattern; SYMBOL "]" -> ()
108       ]
109     ];
110 END
111 (* }}} *)
112
113 (* {{{ Grammar for ast patterns, notation level 2 *)
114 GEXTEND Level2Parser
115   GLOBAL: level2_pattern;
116   level2_pattern: [ [ p = pattern -> () ] ];
117
118   pattern: [ [ a = ast -> () ] ];
119
120   ast: [ [ SYMBOL "\\FOO" -> () ] ];
121 END
122 (* }}} *)
123
124 let exc_located_wrapper f =
125   try
126     f ()
127   with
128   | Stdpp.Exc_located (floc, Stream.Error msg) ->
129       raise (Parse_error (floc, msg))
130   | Stdpp.Exc_located (floc, exn) ->
131       raise (Parse_error (floc, (Printexc.to_string exn)))
132
133 let parse_syntax_pattern stream =
134   exc_located_wrapper
135     (fun () ->
136       (Level1Parser.Entry.parse level1_pattern (Level1Parser.parsable stream)))
137
138 let parse_ast_pattern stream =
139   exc_located_wrapper
140     (fun () ->
141       (Level2Parser.Entry.parse level2_pattern (Level2Parser.parsable stream)))
142
143 (* vim:set encoding=utf8 foldmethod=marker: *)