Skip to content

Commit

Permalink
PR#1803
Browse files Browse the repository at this point in the history
git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@5815 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
  • Loading branch information
Damien Doligez committed Aug 29, 2003
1 parent f5419d3 commit d200cf6
Show file tree
Hide file tree
Showing 4 changed files with 15 additions and 8 deletions.
2 changes: 2 additions & 0 deletions lex/common.ml
Original file line number Diff line number Diff line change
Expand Up @@ -149,3 +149,5 @@ let output_env oc env =
let output_args oc args =
List.iter (fun x -> (output_string oc x; output_char oc ' ')) args

(* quiet flag *)
let quiet_mode = ref false;;
2 changes: 2 additions & 0 deletions lex/common.mli
Original file line number Diff line number Diff line change
Expand Up @@ -21,3 +21,5 @@ val output_memory_actions :
string -> out_channel -> Lexgen.memory_action list -> unit
val output_env : out_channel -> (string * Lexgen.ident_info) list -> unit
val output_args : out_channel -> string list -> unit

val quiet_mode : bool ref;;
4 changes: 3 additions & 1 deletion lex/main.ml
Original file line number Diff line number Diff line change
Expand Up @@ -18,6 +18,7 @@ open Syntax
open Lexgen

let ml_automata = ref false
let quiet_mode = ref false
let source_name = ref None
let output_name = ref None

Expand All @@ -26,8 +27,9 @@ let usage = "usage: ocamlex [options] sourcefile"
let specs =
["-ml", Arg.Set ml_automata,
" Output code that does not use the Lexing module built-in automata interpreter";
"-o", Arg.String (fun x -> source_name := Some x),
"-o", Arg.String (fun x -> source_name := Some x),
" <file> Set output file name to <file>";
"-q", Arg.Set Common.quiet_mode, " Do not display informational messages";
]

let _ =
Expand Down
15 changes: 8 additions & 7 deletions lex/output.ml
Original file line number Diff line number Diff line change
Expand Up @@ -108,20 +108,21 @@ let output_entry sourcefile ic oc oci e =
exception Table_overflow

let output_lexdef sourcefile ic oc oci header tables entry_points trailer =
Printf.printf "%d states, %d transitions, table size %d bytes\n"
(Array.length tables.tbl_base)
(Array.length tables.tbl_trans)
(2 * (Array.length tables.tbl_base + Array.length tables.tbl_backtrk +
Array.length tables.tbl_default + Array.length tables.tbl_trans +
Array.length tables.tbl_check));
if not !Common.quiet_mode then
Printf.printf "%d states, %d transitions, table size %d bytes\n"
(Array.length tables.tbl_base)
(Array.length tables.tbl_trans)
(2 * (Array.length tables.tbl_base + Array.length tables.tbl_backtrk +
Array.length tables.tbl_default + Array.length tables.tbl_trans +
Array.length tables.tbl_check));
let size_groups =
(2 * (Array.length tables.tbl_base_code +
Array.length tables.tbl_backtrk_code +
Array.length tables.tbl_default_code +
Array.length tables.tbl_trans_code +
Array.length tables.tbl_check_code) +
Array.length tables.tbl_code) in
if size_groups > 0 then
if size_groups > 0 && not !Common.quiet_mode then
Printf.printf "%d additional bytes used for bindings\n" size_groups ;
flush stdout;
if Array.length tables.tbl_trans > 0x8000 then raise Table_overflow;
Expand Down

0 comments on commit d200cf6

Please sign in to comment.