(* 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 Error of int * int * string let regexp number = xml_digit+ let regexp ident_decoration = '\'' | '!' | '?' | '`' let regexp ident_cont = xml_letter | xml_digit | '_' let regexp ident = xml_letter ident_cont* ident_decoration* let regexp tex_token = '\\' ident let regexp keyword = '"' ident '"' let regexp implicit = '?' let regexp meta = implicit number let regexp uri = ("cic:/" | "theory:/") (* schema *) ident ('/' ident)* (* path *) ('.' ident)+ (* ext *) ("#xpointer(" number ('/' number)+ ")")? (* xpointer *) let error lexbuf msg = let begin_cnum, end_cnum = Ulexing.loc lexbuf in raise (Error (begin_cnum, end_cnum, msg)) let error_at_end lexbuf msg = let begin_cnum, end_cnum = Ulexing.loc lexbuf in raise (Error (begin_cnum, end_cnum, msg)) let return lexbuf token = let begin_cnum, end_cnum = Ulexing.loc lexbuf in (* TODO handle line/column numbers *) let flocation_begin = { Lexing.pos_fname = ""; Lexing.pos_lnum = -1; Lexing.pos_bol = -1; Lexing.pos_cnum = begin_cnum } in let flocation_end = { flocation_begin with Lexing.pos_cnum = end_cnum } in (token, (flocation_begin, flocation_end)) let return_lexeme lexbuf name = return lexbuf (name, Ulexing.utf8_lexeme lexbuf) let remove_quotes s = String.sub s 1 (String.length s - 2) let mk_lexer token = let tok_func stream = let lexbuf = Ulexing.from_utf8_stream stream in Token.make_stream_and_flocation (fun () -> try token lexbuf with | Ulexing.Error -> error_at_end lexbuf "Unexpected character" | Ulexing.InvalidCodepoint p -> error_at_end lexbuf (sprintf "Invalid code point: %d" p)) in { Token.tok_func = tok_func; Token.tok_using = (fun _ -> ()); Token.tok_removing = (fun _ -> ()); Token.tok_match = Token.default_match; Token.tok_text = Token.lexer_text; Token.tok_comm = None; } let expand_macro lexbuf = let macro = Ulexing.utf8_sub_lexeme lexbuf 1 (Ulexing.lexeme_length lexbuf - 1) in try ("SYMBOL", Utf8Macro.expand macro) with Utf8Macro.Macro_not_found _ -> "SYMBOL", Ulexing.utf8_lexeme lexbuf let keyword lexbuf = "KEYWORD", remove_quotes (Ulexing.utf8_lexeme lexbuf) let rec token = lexer | xml_blank+ -> token lexbuf | meta -> return lexbuf ("META", Ulexing.utf8_lexeme lexbuf) | implicit -> return lexbuf ("IMPLICIT", Ulexing.utf8_lexeme lexbuf) | ident -> return lexbuf ("IDENT", Ulexing.utf8_lexeme lexbuf) | number -> return lexbuf ("NUMBER", Ulexing.utf8_lexeme lexbuf) | keyword -> return lexbuf (keyword lexbuf) | tex_token -> return lexbuf (expand_macro lexbuf) | uri -> return lexbuf ("URI", Ulexing.utf8_lexeme lexbuf) | eof -> return lexbuf ("EOI", "") | _ -> return lexbuf ("SYMBOL", Ulexing.utf8_lexeme lexbuf) (* API implementation *) let notation_lexer = mk_lexer token