summaryrefslogtreecommitdiffstats
diff options
context:
space:
mode:
-rw-r--r--lex/main.ml54
-rw-r--r--lex/output.ml3
-rw-r--r--lex/output.mli2
3 files changed, 35 insertions, 24 deletions
diff --git a/lex/main.ml b/lex/main.ml
index a56041602..b0129af28 100644
--- a/lex/main.ml
+++ b/lex/main.ml
@@ -31,30 +31,36 @@ let main () =
let ic = open_in_bin source_name in
let oc = open_out dest_name in
let lexbuf = Lexing.from_channel ic in
- let def =
- try
- Parser.lexer_definition Lexer.main lexbuf
- with exn ->
- close_out oc;
- Sys.remove dest_name;
- begin match exn with
- Parsing.Parse_error ->
- 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) ->
- Printf.fprintf stderr
- "File \"%s\", line %d, character %d: %s.\n"
- source_name line col msg
- | _ -> raise exn
- end;
- exit 2 in
- let (entries, transitions) = Lexgen.make_dfa def in
- let tables = Compact.compact_tables transitions in
- Output.output_lexdef source_name ic oc def.header tables entries def.trailer;
- close_in ic;
- close_out oc
+ try
+ let def = Parser.lexer_definition Lexer.main lexbuf in
+ let (entries, transitions) = Lexgen.make_dfa def in
+ let tables = Compact.compact_tables transitions in
+ Output.output_lexdef source_name ic oc
+ def.header tables entries def.trailer;
+ close_in ic;
+ close_out oc
+ with exn ->
+ close_in ic;
+ close_out oc;
+ Sys.remove dest_name;
+ begin match exn with
+ Parsing.Parse_error ->
+ 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) ->
+ Printf.fprintf stderr
+ "File \"%s\", line %d, character %d: %s.\n"
+ source_name line col msg
+ | Output.Table_overflow ->
+ Printf.fprintf stderr
+ "File \"%s\":\ntransition table overflow, automaton is too big\n"
+ source_name
+ | _ ->
+ raise exn
+ end;
+ exit 3
let _ = Printexc.catch main (); exit 0
diff --git a/lex/output.ml b/lex/output.ml
index 9e2504bcd..c272f776a 100644
--- a/lex/output.ml
+++ b/lex/output.ml
@@ -97,6 +97,8 @@ let output_entry sourcefile ic oc e =
(* Main output function *)
+exception Table_overflow
+
let output_lexdef sourcefile ic oc header tables entry_points trailer =
Printf.printf "%d states, %d transitions, table size %d bytes\n"
(Array.length tables.tbl_base)
@@ -105,6 +107,7 @@ let output_lexdef sourcefile ic oc header tables entry_points trailer =
Array.length tables.tbl_default + Array.length tables.tbl_trans +
Array.length tables.tbl_check));
flush stdout;
+ if Array.length tables.tbl_trans > 0x8000 then raise Table_overflow;
copy_chunk sourcefile ic oc header;
output_tables oc tables;
begin match entry_points with
diff --git a/lex/output.mli b/lex/output.mli
index 7df1eb50c..a226f2029 100644
--- a/lex/output.mli
+++ b/lex/output.mli
@@ -20,3 +20,5 @@ val output_lexdef:
Lexgen.automata_entry list ->
Syntax.location ->
unit
+
+exception Table_overflow