directives #line pour lex et yacc

git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@6244 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
master
Damien Doligez 2004-04-21 23:26:06 +00:00
parent 2158b37ebd
commit 7405556404
9 changed files with 164 additions and 73 deletions

View File

@ -1,6 +1,12 @@
Objective Caml 3.08:
--------------------
Ocamllex:
- #line directives in the input file are now accepted
Ocamlyacc:
- #line directives in the input file are now accepted
Runtime System:
- All global identifiers are now prefixed with "caml" to avoid name clashes
with other libraries.

View File

@ -14,7 +14,9 @@
val main: Lexing.lexbuf -> Parser.token
exception Lexical_error of string * int * int
exception Lexical_error of string * string * int * int
(*n
val line_num: int ref
val line_start_pos: int ref
*)

View File

@ -25,7 +25,7 @@ and comment_depth = ref 0
let in_pattern () = !brace_depth = 0 && !comment_depth = 0
exception Lexical_error of string * int * int
exception Lexical_error of string * string * int * int
let string_buff = Buffer.create 256
@ -42,24 +42,32 @@ let char_for_backslash = function
| 'r' -> '\r'
| c -> c
let line_num = ref 1
let line_start_pos = ref 0
let raise_lexical_error lexbuf msg =
let p = Lexing.lexeme_start_p lexbuf in
raise (Lexical_error (msg,
p.Lexing.pos_fname,
p.Lexing.pos_lnum,
p.Lexing.pos_cnum - p.Lexing.pos_bol + 1))
;;
let handle_lexical_error fn lexbuf =
let line = !line_num
and column = Lexing.lexeme_start lexbuf - !line_start_pos + 1 in
let p = Lexing.lexeme_start_p lexbuf in
let line = p.Lexing.pos_lnum
and column = p.Lexing.pos_cnum - p.Lexing.pos_bol + 1
and file = p.Lexing.pos_fname
in
try
fn lexbuf
with Lexical_error (msg, 0, 0) ->
raise(Lexical_error(msg, line, column))
with Lexical_error (msg, "", 0, 0) ->
raise(Lexical_error(msg, file, line, column))
let get_input_name () = Sys.argv.(Array.length Sys.argv - 1)
let warning lexbuf msg =
let p = Lexing.lexeme_start_p lexbuf in
Printf.eprintf "ocamllex warning:\nFile \"%s\", line %d, character %d: %s.\n"
(get_input_name ()) !line_num
(Lexing.lexeme_start lexbuf - !line_start_pos+1) msg;
p.Lexing.pos_fname p.Lexing.pos_lnum
(p.Lexing.pos_cnum - p.Lexing.pos_bol + 1) msg;
flush stderr
let decimal_code c d u =
@ -78,6 +86,27 @@ let char_for_hexadecimal_code d u =
in
Char.chr (val1 * 16 + val2)
let incr_loc lexbuf delta =
let pos = lexbuf.Lexing.lex_curr_p in
lexbuf.Lexing.lex_curr_p <- { pos with
Lexing.pos_lnum = pos.Lexing.pos_lnum + 1;
Lexing.pos_bol = pos.Lexing.pos_cnum - delta;
}
;;
let update_loc lexbuf opt_file line =
let pos = lexbuf.Lexing.lex_curr_p in
let new_file = match opt_file with
| None -> pos.Lexing.pos_fname
| Some f -> f
in
lexbuf.Lexing.lex_curr_p <- { pos with
Lexing.pos_fname = new_file;
Lexing.pos_lnum = line;
Lexing.pos_bol = pos.Lexing.pos_cnum;
}
;;
}
let identstart =
@ -91,9 +120,14 @@ rule main = parse
[' ' '\013' '\009' '\012' ] +
{ main lexbuf }
| '\010'
{ line_start_pos := Lexing.lexeme_end lexbuf;
incr line_num;
{ incr_loc lexbuf 0;
main lexbuf }
| "#" [' ' '\t']* (['0'-'9']+ as num) [' ' '\t']*
('\"' ([^ '\010' '\013' '\"']* as name) '\"')?
[^ '\010' '\013']* '\010'
{ update_loc lexbuf name (int_of_string num);
main lexbuf
}
| "(*"
{ comment_depth := 1;
handle_lexical_error comment lexbuf;
@ -121,25 +155,22 @@ rule main = parse
| "'" '\\' (['0'-'9'] as c) (['0'-'9'] as d) (['0'-'9'] as u)"'"
{ let v = decimal_code c d u in
if v > 255 then
raise
(Lexical_error
(Printf.sprintf "illegal escape sequence \\%c%c%c" c d u,
!line_num, Lexing.lexeme_start lexbuf - !line_start_pos+1))
raise_lexical_error lexbuf
(Printf.sprintf "illegal escape sequence \\%c%c%c" c d u)
else
Tchar v }
| "'" '\\' 'x'
(['0'-'9' 'a'-'f' 'A'-'F'] as d) (['0'-'9' 'a'-'f' 'A'-'F'] as u) "'"
{ Tchar(Char.code(char_for_hexadecimal_code d u)) }
| "'" '\\' (_ as c)
{ raise
(Lexical_error
(Printf.sprintf "illegal escape sequence \\%c" c,
!line_num, Lexing.lexeme_start lexbuf - !line_start_pos+1))
{ raise_lexical_error lexbuf
(Printf.sprintf "illegal escape sequence \\%c" c)
}
| '{'
{ let n1 = Lexing.lexeme_end lexbuf
and l1 = !line_num
and s1 = !line_start_pos in
{ let p = Lexing.lexeme_end_p lexbuf in
let n1 = p.Lexing.pos_cnum
and l1 = p.Lexing.pos_lnum
and s1 = p.Lexing.pos_bol in
brace_depth := 1;
let n2 = handle_lexical_error action lexbuf in
Taction({start_pos = n1; end_pos = n2;
@ -157,18 +188,17 @@ rule main = parse
| '-' { Tdash }
| eof { Tend }
| _
{ raise(Lexical_error
("illegal character " ^ String.escaped(Lexing.lexeme lexbuf),
!line_num, Lexing.lexeme_start lexbuf - !line_start_pos+1)) }
{ raise_lexical_error lexbuf
("illegal character " ^ String.escaped(Lexing.lexeme lexbuf))
}
(* String parsing comes from the compiler lexer *)
and string = parse
'"'
{ () }
| '\\' ("\010" | "\013" | "\013\010") [' ' '\009'] *
{ line_start_pos := Lexing.lexeme_end lexbuf;
incr line_num;
| '\\' ("\010" | "\013" | "\013\010") ([' ' '\009'] * as spaces)
{ incr_loc lexbuf (String.length spaces);
string lexbuf }
| '\\' (backslash_escapes as c)
{ store_string_char(char_for_backslash c);
@ -192,11 +222,10 @@ and string = parse
store_string_char c ;
string lexbuf }
| eof
{ raise(Lexical_error("unterminated string", 0, 0)) }
{ raise(Lexical_error("unterminated string", "", 0, 0)) }
| '\010'
{ store_string_char '\010';
line_start_pos := Lexing.lexeme_end lexbuf;
incr line_num;
incr_loc lexbuf 0;
string lexbuf }
| _ as c
{ store_string_char c;
@ -223,10 +252,9 @@ and comment = parse
{ skip_char lexbuf ;
comment lexbuf }
| eof
{ raise(Lexical_error("unterminated comment", 0, 0)) }
{ raise(Lexical_error("unterminated comment", "", 0, 0)) }
| '\010'
{ line_start_pos := Lexing.lexeme_end lexbuf;
incr line_num;
{ incr_loc lexbuf 0;
comment lexbuf }
| _
{ comment lexbuf }
@ -251,18 +279,17 @@ and action = parse
comment lexbuf;
action lexbuf }
| eof
{ raise (Lexical_error("unterminated action", 0, 0)) }
{ raise (Lexical_error("unterminated action", "", 0, 0)) }
| '\010'
{ line_start_pos := Lexing.lexeme_end lexbuf;
incr line_num;
{ incr_loc lexbuf 0;
action lexbuf }
| _
{ action lexbuf }
and skip_char = parse
| '\\'? '\010' "'"
{ line_start_pos := Lexing.lexeme_end lexbuf;
incr line_num }
{ incr_loc lexbuf 1;
}
| [^ '\\' '\''] "'" (* regular character *)
(* one character and numeric escape sequences *)
| '\\' _ "'"

View File

@ -55,6 +55,9 @@ let main () =
let oc = open_out dest_name in
let tr = Common.open_tracker dest_name oc in
let lexbuf = Lexing.from_channel ic in
lexbuf.Lexing.lex_curr_p <-
{Lexing.pos_fname = source_name; Lexing.pos_lnum = 1;
Lexing.pos_bol = 0; Lexing.pos_cnum = 0};
try
let def = Parser.lexer_definition Lexer.main lexbuf in
let (entries, transitions) = Lexgen.make_dfa def.entrypoints in
@ -77,14 +80,15 @@ let main () =
Sys.remove dest_name;
begin match exn with
Parsing.Parse_error ->
let p = Lexing.lexeme_start_p lexbuf in
Printf.fprintf stderr
"File \"%s\", line %d, character %d: syntax error.\n"
source_name !Lexer.line_num
(Lexing.lexeme_start lexbuf - !Lexer.line_start_pos)
| Lexer.Lexical_error(msg, line, col) ->
p.Lexing.pos_fname p.Lexing.pos_lnum
(p.Lexing.pos_cnum - p.Lexing.pos_bol)
| Lexer.Lexical_error(msg, file, line, col) ->
Printf.fprintf stderr
"File \"%s\", line %d, character %d: %s.\n"
source_name line col msg
file line col msg
| Lexgen.Memory_overflow ->
Printf.fprintf stderr
"File \"%s\":\n Position memory overflow, too many bindings\n"

View File

@ -78,4 +78,4 @@ let catch_break on =
(* OCaml version string, must be in the format described in sys.mli. *)
let ocaml_version = "3.07+16 (2004-04-13)";;
let ocaml_version = "3.07+17 (2004-04-22)";;

View File

@ -215,6 +215,7 @@ extern char *myname;
extern char *cptr;
extern char *line;
extern int lineno;
extern char *virtual_input_file_name;
extern int outline;
extern char *action_file_name;

View File

@ -42,7 +42,7 @@ void open_error(char *filename)
void unexpected_EOF(void)
{
fprintf(stderr, "%s: e - line %d of \"%s\", unexpected end-of-file\n",
myname, lineno, input_file_name);
myname, lineno, virtual_input_file_name);
done(1);
}
@ -75,7 +75,7 @@ void print_pos(char *st_line, char *st_cptr)
void syntax_error(int st_lineno, char *st_line, char *st_cptr)
{
fprintf(stderr, "%s: e - line %d of \"%s\", syntax error\n",
myname, st_lineno, input_file_name);
myname, st_lineno, virtual_input_file_name);
print_pos(st_line, st_cptr);
done(1);
}
@ -84,7 +84,7 @@ void syntax_error(int st_lineno, char *st_line, char *st_cptr)
void unterminated_comment(int c_lineno, char *c_line, char *c_cptr)
{
fprintf(stderr, "%s: e - line %d of \"%s\", unmatched /*\n",
myname, c_lineno, input_file_name);
myname, c_lineno, virtual_input_file_name);
print_pos(c_line, c_cptr);
done(1);
}
@ -93,7 +93,7 @@ void unterminated_comment(int c_lineno, char *c_line, char *c_cptr)
void unterminated_string(int s_lineno, char *s_line, char *s_cptr)
{
fprintf(stderr, "%s: e - line %d of \"%s\", unterminated string\n",
myname, s_lineno, input_file_name);
myname, s_lineno, virtual_input_file_name);
print_pos(s_line, s_cptr);
done(1);
}
@ -102,7 +102,7 @@ void unterminated_string(int s_lineno, char *s_line, char *s_cptr)
void unterminated_text(int t_lineno, char *t_line, char *t_cptr)
{
fprintf(stderr, "%s: e - line %d of \"%s\", unmatched %%{\n",
myname, t_lineno, input_file_name);
myname, t_lineno, virtual_input_file_name);
print_pos(t_line, t_cptr);
done(1);
}
@ -111,7 +111,7 @@ void unterminated_text(int t_lineno, char *t_line, char *t_cptr)
void unterminated_union(int u_lineno, char *u_line, char *u_cptr)
{
fprintf(stderr, "%s: e - line %d of \"%s\", unterminated %%union \
declaration\n", myname, u_lineno, input_file_name);
declaration\n", myname, u_lineno, virtual_input_file_name);
print_pos(u_line, u_cptr);
done(1);
}
@ -120,7 +120,7 @@ declaration\n", myname, u_lineno, input_file_name);
void over_unionized(char *u_cptr)
{
fprintf(stderr, "%s: e - line %d of \"%s\", too many %%union \
declarations\n", myname, lineno, input_file_name);
declarations\n", myname, lineno, virtual_input_file_name);
print_pos(line, u_cptr);
done(1);
}
@ -129,7 +129,7 @@ declarations\n", myname, lineno, input_file_name);
void illegal_tag(int t_lineno, char *t_line, char *t_cptr)
{
fprintf(stderr, "%s: e - line %d of \"%s\", illegal tag\n",
myname, t_lineno, input_file_name);
myname, t_lineno, virtual_input_file_name);
print_pos(t_line, t_cptr);
done(1);
}
@ -138,7 +138,7 @@ void illegal_tag(int t_lineno, char *t_line, char *t_cptr)
void illegal_character(char *c_cptr)
{
fprintf(stderr, "%s: e - line %d of \"%s\", illegal character\n",
myname, lineno, input_file_name);
myname, lineno, virtual_input_file_name);
print_pos(line, c_cptr);
done(1);
}
@ -147,7 +147,7 @@ void illegal_character(char *c_cptr)
void used_reserved(char *s)
{
fprintf(stderr, "%s: e - line %d of \"%s\", illegal use of reserved symbol \
%s\n", myname, lineno, input_file_name, s);
%s\n", myname, lineno, virtual_input_file_name, s);
done(1);
}
@ -155,7 +155,7 @@ void used_reserved(char *s)
void tokenized_start(char *s)
{
fprintf(stderr, "%s: e - line %d of \"%s\", the start symbol %s cannot be \
declared to be a token\n", myname, lineno, input_file_name, s);
declared to be a token\n", myname, lineno, virtual_input_file_name, s);
done(1);
}
@ -163,35 +163,35 @@ declared to be a token\n", myname, lineno, input_file_name, s);
void retyped_warning(char *s)
{
fprintf(stderr, "%s: w - line %d of \"%s\", the type of %s has been \
redeclared\n", myname, lineno, input_file_name, s);
redeclared\n", myname, lineno, virtual_input_file_name, s);
}
void reprec_warning(char *s)
{
fprintf(stderr, "%s: w - line %d of \"%s\", the precedence of %s has been \
redeclared\n", myname, lineno, input_file_name, s);
redeclared\n", myname, lineno, virtual_input_file_name, s);
}
void revalued_warning(char *s)
{
fprintf(stderr, "%s: w - line %d of \"%s\", the value of %s has been \
redeclared\n", myname, lineno, input_file_name, s);
redeclared\n", myname, lineno, virtual_input_file_name, s);
}
void terminal_start(char *s)
{
fprintf(stderr, "%s: e - line %d of \"%s\", the entry point %s is a \
token\n", myname, lineno, input_file_name, s);
token\n", myname, lineno, virtual_input_file_name, s);
done(1);
}
void too_many_entries(void)
{
fprintf(stderr, "%s: e - line %d of \"%s\", more than 256 entry points\n",
myname, lineno, input_file_name);
myname, lineno, virtual_input_file_name);
done(1);
}
@ -199,7 +199,7 @@ void too_many_entries(void)
void no_grammar(void)
{
fprintf(stderr, "%s: e - line %d of \"%s\", no grammar has been \
specified\n", myname, lineno, input_file_name);
specified\n", myname, lineno, virtual_input_file_name);
done(1);
}
@ -207,7 +207,7 @@ specified\n", myname, lineno, input_file_name);
void terminal_lhs(int s_lineno)
{
fprintf(stderr, "%s: e - line %d of \"%s\", a token appears on the lhs \
of a production\n", myname, s_lineno, input_file_name);
of a production\n", myname, s_lineno, virtual_input_file_name);
done(1);
}
@ -215,14 +215,14 @@ of a production\n", myname, s_lineno, input_file_name);
void prec_redeclared(void)
{
fprintf(stderr, "%s: w - line %d of \"%s\", conflicting %%prec \
specifiers\n", myname, lineno, input_file_name);
specifiers\n", myname, lineno, virtual_input_file_name);
}
void unterminated_action(int a_lineno, char *a_line, char *a_cptr)
{
fprintf(stderr, "%s: e - line %d of \"%s\", unterminated action\n",
myname, a_lineno, input_file_name);
myname, a_lineno, virtual_input_file_name);
print_pos(a_line, a_cptr);
done(1);
}
@ -231,14 +231,14 @@ void unterminated_action(int a_lineno, char *a_line, char *a_cptr)
void dollar_warning(int a_lineno, int i)
{
fprintf(stderr, "%s: w - line %d of \"%s\", $%d references beyond the \
end of the current rule\n", myname, a_lineno, input_file_name, i);
end of the current rule\n", myname, a_lineno, virtual_input_file_name, i);
}
void dollar_error(int a_lineno, char *a_line, char *a_cptr)
{
fprintf(stderr, "%s: e - line %d of \"%s\", illegal $-name\n",
myname, a_lineno, input_file_name);
myname, a_lineno, virtual_input_file_name);
print_pos(a_line, a_cptr);
done(1);
}
@ -247,7 +247,7 @@ void dollar_error(int a_lineno, char *a_line, char *a_cptr)
void untyped_lhs(void)
{
fprintf(stderr, "%s: e - line %d of \"%s\", $$ is untyped\n",
myname, lineno, input_file_name);
myname, lineno, virtual_input_file_name);
done(1);
}
@ -255,7 +255,7 @@ void untyped_lhs(void)
void untyped_rhs(int i, char *s)
{
fprintf(stderr, "%s: e - line %d of \"%s\", $%d (%s) is untyped\n",
myname, lineno, input_file_name, i, s);
myname, lineno, virtual_input_file_name, i, s);
done(1);
}
@ -263,21 +263,21 @@ void untyped_rhs(int i, char *s)
void unknown_rhs(int i)
{
fprintf(stderr, "%s: e - line %d of \"%s\", $%d is unbound\n",
myname, lineno, input_file_name, i);
myname, lineno, virtual_input_file_name, i);
done(1);
}
void illegal_token_ref(int i, char *name)
{
fprintf(stderr, "%s: e - line %d of \"%s\", $%d refers to terminal `%s', which has no argument\n",
myname, lineno, input_file_name, i, name);
myname, lineno, virtual_input_file_name, i, name);
done(1);
}
void default_action_error(void)
{
fprintf(stderr, "%s: e - line %d of \"%s\", no action specified for this production\n",
myname, lineno, input_file_name);
myname, lineno, virtual_input_file_name);
done(1);
}

View File

@ -39,6 +39,7 @@ char temp_form[] = "yacc.XXXXXXX";
#endif
int lineno;
char *virtual_input_file_name = NULL;
int outline;
char *action_file_name;

View File

@ -155,6 +155,51 @@ void skip_comment(void)
}
}
char *substring (char *str, int start, int len)
{
int i;
char *buf = MALLOC (len+1);
if (buf == NULL) return NULL;
for (i = 0; i < len; i++){
buf[i] = str[start+i];
}
return buf;
}
void parse_line_directive (void)
{
int i = 0, j = 0;
int line_number = 0;
char *file_name = NULL;
again:
if (line == 0) return;
if (line[i] != '#') return;
++ i;
while (line[i] == ' ' || line[i] == '\t') ++ i;
if (line[i] < '0' || line[i] > '9') return;
while (line[i] >= '0' && line[i] <= '9'){
line_number = line_number * 10 + line[i] - '0';
++ i;
}
while (line[i] == ' ' || line[i] == '\t') ++ i;
if (line[i] == '"'){
++ i;
j = i;
while (line[j] != '"' && line[j] != '\0') ++j;
if (line[j] == '"'){
file_name = substring (line, i, j - i);
if (file_name == NULL) no_space ();
}
}
lineno = line_number - 1;
if (file_name != NULL){
if (virtual_input_file_name != NULL) FREE (virtual_input_file_name);
virtual_input_file_name = file_name;
}
get_line ();
goto again;
}
int
nextc(void)
@ -164,6 +209,7 @@ nextc(void)
if (line == 0)
{
get_line();
parse_line_directive ();
if (line == 0)
return (EOF);
}
@ -175,6 +221,7 @@ nextc(void)
{
case '\n':
get_line();
parse_line_directive ();
if (line == 0) return (EOF);
s = cptr;
break;
@ -204,6 +251,7 @@ nextc(void)
else if (s[1] == '/')
{
get_line();
parse_line_directive ();
if (line == 0) return (EOF);
s = cptr;
break;
@ -1823,6 +1871,8 @@ void print_grammar(void)
void reader(void)
{
virtual_input_file_name = substring (input_file_name, 0,
strlen (input_file_name));
create_symbol_table();
read_declarations();
output_token_type();