1 (* Copyright (C) 2005, HELM Team.
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.
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.
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.
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,
22 * For details, see the HELM World-Wide-Web page,
23 * http://helm.cs.unibo.it/
26 (* $Id: cicNotationLexer.ml 11231 2011-03-30 11:52:27Z ricciott $ *)
30 exception Error of int * int * string
32 module StringSet = Set.Make(String)
35 let regexp number = xml_digit+
36 let regexp utf8_blank = " " | "\r\n" | "\n" | "\t" | [160] (* this is a nbsp *)
37 let regexp percentage =
38 ('-' | "") [ '0' - '9' ] + '%'
39 let regexp floatwithunit =
40 ('-' | "") [ '0' - '9' ] + ["."] [ '0' - '9' ] + ([ 'a' - 'z' ] + | "" )
41 let regexp color = "#" [ '0' - '9' 'a' - 'f' 'A' - 'F' ] [ '0' - '9' 'a' - 'f'
42 'A' - 'F' ] [ '0' - '9' 'a' - 'f' 'A' - 'F' ] [ '0' - '9' 'a' - 'f' 'A' - 'F' ]
43 [ '0' - '9' 'a' - 'f' 'A' - 'F' ] [ '0' - '9' 'a' - 'f' 'A' - 'F' ]
45 (* ZACK: breaks unicode's binder followed by an ascii letter without blank *)
46 (* let regexp ident_letter = xml_letter *)
48 let regexp ident_letter = [ 'a' - 'z' 'A' - 'Z' ]
50 (* must be in sync with "is_ligature_char" below *)
51 let regexp ligature_char = [ "'`~!?@*()[]<>-+=|:;.,/\"" ]
52 let regexp ligature = ligature_char ligature_char+
54 let regexp we_proved = "we" utf8_blank+ "proved"
55 let regexp we_have = "we" utf8_blank+ "have"
56 let regexp let_rec = "let" utf8_blank+ "rec"
57 let regexp let_corec = "let" utf8_blank+ "corec"
58 let regexp ident_decoration = '\'' | '?' | '`'
59 let regexp ident_cont = ident_letter | xml_digit | '_'
60 let regexp ident_start = ident_letter
61 let regexp ident = ident_letter ident_cont* ident_decoration*
62 let regexp variable_ident = '_' '_' number
63 let regexp pident = '_' ident
65 let regexp uri_step = [ 'a' - 'z' 'A' - 'Z' '0' - '9' '_' '-' ''' ]+
68 ("cic:/" | "theory:/") (* schema *)
69 (* ident ('/' ident)* |+ path +| *)
70 uri_step ('/' uri_step)* (* path *)
71 ('.' ident)+ (* ext *)
72 (* ("#xpointer(" number ('/' number)+ ")")? (* xpointer *) *)
73 ("(" number (',' number)* ")")? (* reference spec *)
75 let regexp qstring = '"' [^ '"']* '"'
76 let regexp hreftag = "<" [ 'A' 'a' ]
77 let regexp href = "href=\"" uri "\""
78 let regexp hreftitle = "title=" qstring
79 let regexp hrefclose = "</" [ 'A' 'a' ] ">"
81 let regexp tex_token = '\\' ident
83 let regexp delim_begin = "\\["
84 let regexp delim_end = "\\]"
86 let regexp qkeyword = "'" ( ident | pident ) "'"
88 let regexp implicit = '?'
89 let regexp placeholder = '%'
90 let regexp meta = implicit number
92 let regexp csymbol = '\'' ident
94 let regexp begin_group = "@{" | "${"
95 let regexp end_group = '}'
96 let regexp wildcard = "$_"
97 let regexp ast_ident = "@" ident
98 let regexp ast_csymbol = "@" csymbol
99 let regexp meta_ident = "$" ident
100 let regexp meta_anonymous = "$_"
102 let regexp begincom = "(*"
103 let regexp endcom = "*)"
104 (* let regexp comment_char = [^'*'] | '*'[^')']
105 let regexp note = "|+" ([^'*'] | "**") comment_char* "+|" *)
110 "over"; "atop"; "frac";
111 "sqrt"; "root"; "mstyle" ; "mpadded"; "maction"
115 let level1_keywords =
116 [ "hbox"; "hvbox"; "hovbox"; "vbox";
118 "list0"; "list1"; "sep";
120 "term"; "ident"; "number";
123 let level2_meta_keywords =
124 [ "if"; "then"; "elCicNotationParser.se";
125 "fold"; "left"; "right"; "rec";
128 "anonymous"; "ident"; "number"; "term"; "fresh"
131 (* (string, int) Hashtbl.t, with multiple bindings.
132 * int is the unicode codepoint *)
133 let ligatures = Hashtbl.create 23
137 (fun (ligature, symbol) -> Hashtbl.add ligatures ligature symbol)
138 [ ("->", <:unicode<to>>); ("=>", <:unicode<Rightarrow>>);
139 (":=", <:unicode<def>>);
142 let regexp nreference =
144 uri_step ('/' uri_step)* (* path *)
147 | "def" "(" number ")"
148 | "fix" "(" number "," number "," number ")"
149 | "cfx" "(" number ")"
150 | "ind" "(" number "," number "," number ")"
151 | "con" "(" number "," number "," number ")") (* ext + reference *)
153 let error lexbuf msg =
154 let begin_cnum, end_cnum = Ulexing.loc lexbuf in
155 raise (Error (begin_cnum, end_cnum, msg))
156 let error_at_end lexbuf msg =
157 let begin_cnum, end_cnum = Ulexing.loc lexbuf in
158 raise (Error (begin_cnum, end_cnum, msg))
160 let loc_of_buf lexbuf =
161 HExtlib.floc_of_loc (Ulexing.loc lexbuf)
163 let return_with_loc token begin_cnum end_cnum =
164 let flocation = HExtlib.floc_of_loc (begin_cnum,end_cnum) in
167 let return lexbuf token =
168 let begin_cnum, end_cnum = Ulexing.loc lexbuf in
169 return_with_loc token begin_cnum end_cnum
171 let return_lexeme lexbuf name = return lexbuf (name, Ulexing.utf8_lexeme lexbuf)
173 let return_symbol lexbuf s = return lexbuf ("SYMBOL", s)
174 let return_eoi lexbuf = return lexbuf ("EOI", "")
176 let remove_quotes s = String.sub s 1 (String.length s - 2)
179 let tok_func stream =
180 (* let lexbuf = Ulexing.from_utf8_stream stream in *)
181 (** XXX Obj.magic rationale.
183 * camlp5 constraints the tok_func field of Token.glexer to have type:
184 * Stream.t char -> (Stream.t 'te * flocation_function)
185 * In order to use ulex we have (in theory) to instantiate a new lexbuf each
186 * time a char Stream.t is passed, destroying the previous lexbuf which may
187 * have consumed a character from the old stream which is lost forever :-(
189 * Instead of passing to camlp5 a char Stream.t we pass a lexbuf, casting it to
190 * char Stream.t with Obj.magic where needed.
192 let lexbuf = Obj.magic stream in
193 Token.make_stream_and_location
198 | Ulexing.Error -> error_at_end lexbuf "Unexpected character"
199 | Ulexing.InvalidCodepoint p ->
200 error_at_end lexbuf (sprintf "Invalid code point: %d" p))
203 Token.tok_func = tok_func;
204 Token.tok_using = (fun _ -> ());
205 Token.tok_removing = (fun _ -> ());
206 Token.tok_match = Token.default_match;
207 Token.tok_text = Token.lexer_text;
208 Token.tok_comm = None;
211 let expand_macro lexbuf =
213 Ulexing.utf8_sub_lexeme lexbuf 1 (Ulexing.lexeme_length lexbuf - 1)
216 ("SYMBOL", Utf8Macro.expand macro)
217 with Utf8Macro.Macro_not_found _ ->
218 (* FG: unexpanded TeX macros are terminated by a space for rendering *)
219 "SYMBOL", (Ulexing.utf8_lexeme lexbuf ^ " ")
221 let remove_quotes s = String.sub s 1 (String.length s - 2)
222 let remove_left_quote s = String.sub s 1 (String.length s - 1)
224 let rec level2_pattern_token_group counter buffer =
227 if (counter > 0) then
228 Buffer.add_string buffer (Ulexing.utf8_lexeme lexbuf) ;
229 snd (Ulexing.loc lexbuf)
231 Buffer.add_string buffer (Ulexing.utf8_lexeme lexbuf) ;
232 ignore (level2_pattern_token_group (counter + 1) buffer lexbuf) ;
233 level2_pattern_token_group counter buffer lexbuf
235 Buffer.add_string buffer (Ulexing.utf8_lexeme lexbuf) ;
236 level2_pattern_token_group counter buffer lexbuf
238 let read_unparsed_group token_name lexbuf =
239 let buffer = Buffer.create 16 in
240 let begin_cnum, _ = Ulexing.loc lexbuf in
241 let end_cnum = level2_pattern_token_group 0 buffer lexbuf in
242 return_with_loc (token_name, Buffer.contents buffer) begin_cnum end_cnum
244 let handle_keywords lexbuf k name =
245 let s = Ulexing.utf8_lexeme lexbuf in
247 return lexbuf ("", s)
249 return lexbuf (name, s)
252 let rec level2_meta_token =
254 | utf8_blank+ -> level2_meta_token lexbuf
255 | hreftag -> return lexbuf ("ATAG","")
256 | hrefclose -> return lexbuf ("ATAGEND","")
258 handle_keywords lexbuf (fun x -> List.mem x level2_meta_keywords) "IDENT"
259 | variable_ident -> return lexbuf ("IDENT", Ulexing.utf8_lexeme lexbuf)
261 handle_keywords lexbuf (fun x -> List.mem x level2_meta_keywords) "PIDENT"
262 | "@{" -> read_unparsed_group "UNPARSED_AST" lexbuf
264 return lexbuf ("UNPARSED_AST",
265 remove_left_quote (Ulexing.utf8_lexeme lexbuf))
267 return lexbuf ("UNPARSED_AST",
268 remove_left_quote (Ulexing.utf8_lexeme lexbuf))
269 | eof -> return_eoi lexbuf
272 (** @param k continuation to be invoked when no ligature has been found *)
273 let ligatures_token k =
276 let lexeme = Ulexing.utf8_lexeme lexbuf in
277 (match List.rev (Hashtbl.find_all ligatures lexeme) with
278 | [] -> (* ligature not found, rollback and try default lexer *)
279 Ulexing.rollback lexbuf;
281 | default_lig :: _ -> (* ligatures found, use the default one *)
282 return_symbol lexbuf default_lig)
283 | eof -> return_eoi lexbuf
284 | _ -> (* not a ligature, rollback and try default lexer *)
285 Ulexing.rollback lexbuf;
294 (* let update_table loc desc href loctable =
295 if desc <> None || href <> None
297 (let s,e = HExtlib.loc_of_floc loc in
298 prerr_endline (Printf.sprintf "*** [%d,%d] \"%s\",\"%s\""
299 s e (so_pp href) (so_pp desc));
300 CicNotationLexer.LocalizeEnv.add loc (href,desc) loctable)
306 (* k = lexing continuation *)
307 let rec aux nesting k =
309 | begincom -> aux (nesting+1) k lexbuf
310 | endcom -> aux (max 0 (nesting-1)) k lexbuf
312 | _ -> if nesting > 0
313 then aux nesting k lexbuf
314 else (Ulexing.rollback lexbuf;
316 and aux_basic loc1 desc href =
318 | hreftag -> aux 0 (aux_in_tag (Ulexing.loc lexbuf) None None) lexbuf
321 let loc1 = HExtlib.floc_of_loc (HExtlib.unopt loc1) in
322 let loc2 = HExtlib.floc_of_loc (Ulexing.loc lexbuf) in
323 (loc1,loc2,href,desc) :: aux 0 (aux_basic None None None) lexbuf
324 with Failure _ -> aux 0 (aux_basic None None None) lexbuf)
326 | _ -> aux 0 (aux_basic loc1 desc href) lexbuf
327 and aux_in_tag loc1 desc href = lexer
328 | utf8_blank+ -> aux 0 (aux_in_tag loc1 desc href) lexbuf
330 aux 0 (aux_in_tag loc1 desc (Some (Ulexing.utf8_sub_lexeme
331 lexbuf 6 (Ulexing.lexeme_length lexbuf - 7))))
334 aux 0 (aux_in_tag loc1 (Some (Ulexing.utf8_sub_lexeme lexbuf 7
335 (Ulexing.lexeme_length lexbuf - 8))) href)
338 let merge (a,b) (c,d) = (a,d) in
340 (aux_basic (Some (merge loc1 (Ulexing.loc lexbuf))) desc href) lexbuf
341 | _ -> aux 0 (aux_basic None None None) lexbuf
342 in aux 0 (aux_basic None None None)
344 let get_hot_spots s = get_hot_spots (Ulexing.from_utf8_string s)
346 (*let xmarkup = "\005"
348 let regexp tag_cont = ident_letter | xml_digit | "_" | "-"
349 let regexp tagname = ident_letter tag_cont*
350 let regexp opentag = xmarkup tagname
351 let regexp closetag = xmarkup "/" tagname ymarkup
352 let regexp attribute = tagname "=" qstring
356 | closetag -> xmarkup ^ ymarkup ^ xmarkup ^ to_xy lexbuf
359 Ulexing.utf8_sub_lexeme lexbuf 1
360 (Ulexing.lexeme_length lexbuf - 1) in
361 xmarkup ^ ymarkup ^ tag ^ to_xy_inner lexbuf
363 | _ -> let lexeme = Ulexing.utf8_lexeme lexbuf in
364 prerr_endline ("matched " ^ lexeme); lexeme ^ to_xy lexbuf
368 | utf8_blank+ -> to_xy_inner lexbuf
369 | attribute -> let lexeme = Ulexing.utf8_lexeme lexbuf in
370 ymarkup ^ lexeme ^ to_xy_inner lexbuf
371 | ">" -> xmarkup ^ to_xy lexbuf
376 let to_xy s = to_xy (Ulexing.from_utf8_string s)*)