1995-08-09 08:06:35 -07:00
|
|
|
(***********************************************************************)
|
|
|
|
(* *)
|
1996-04-30 07:53:58 -07:00
|
|
|
(* Objective Caml *)
|
1995-08-09 08:06:35 -07:00
|
|
|
(* *)
|
|
|
|
(* Xavier Leroy, projet Cristal, INRIA Rocquencourt *)
|
|
|
|
(* *)
|
1996-04-30 07:53:58 -07:00
|
|
|
(* Copyright 1996 Institut National de Recherche en Informatique et *)
|
1999-11-17 10:59:06 -08:00
|
|
|
(* en Automatique. All rights reserved. This file is distributed *)
|
|
|
|
(* under the terms of the Q Public License version 1.0. *)
|
1995-08-09 08:06:35 -07:00
|
|
|
(* *)
|
|
|
|
(***********************************************************************)
|
|
|
|
|
|
|
|
(* $Id$ *)
|
|
|
|
|
1996-02-25 06:45:47 -08:00
|
|
|
(* Output the DFA tables and its entry points *)
|
1995-05-04 03:15:53 -07:00
|
|
|
|
1996-02-25 06:45:47 -08:00
|
|
|
open Printf
|
1995-05-04 03:15:53 -07:00
|
|
|
open Syntax
|
1996-02-25 06:45:47 -08:00
|
|
|
open Lexgen
|
|
|
|
open Compact
|
2002-10-28 08:46:50 -08:00
|
|
|
open Common
|
1996-12-10 06:45:58 -08:00
|
|
|
|
1996-02-25 06:45:47 -08:00
|
|
|
(* To output an array of short ints, encoded as a string *)
|
|
|
|
|
|
|
|
let output_byte oc b =
|
|
|
|
output_char oc '\\';
|
|
|
|
output_char oc (Char.chr(48 + b / 100));
|
|
|
|
output_char oc (Char.chr(48 + (b / 10) mod 10));
|
|
|
|
output_char oc (Char.chr(48 + b mod 10))
|
|
|
|
|
|
|
|
let output_array oc v =
|
|
|
|
output_string oc " \"";
|
|
|
|
for i = 0 to Array.length v - 1 do
|
|
|
|
output_byte oc (v.(i) land 0xFF);
|
|
|
|
output_byte oc ((v.(i) asr 8) land 0xFF);
|
|
|
|
if i land 7 = 7 then output_string oc "\\\n "
|
1995-05-04 03:15:53 -07:00
|
|
|
done;
|
1996-02-25 06:45:47 -08:00
|
|
|
output_string oc "\""
|
|
|
|
|
2002-10-28 08:46:50 -08:00
|
|
|
let output_byte_array oc v =
|
|
|
|
output_string oc " \"";
|
|
|
|
for i = 0 to Array.length v - 1 do
|
|
|
|
output_byte oc (v.(i) land 0xFF);
|
|
|
|
if i land 15 = 15 then output_string oc "\\\n "
|
|
|
|
done;
|
|
|
|
output_string oc "\""
|
|
|
|
|
1996-02-25 06:45:47 -08:00
|
|
|
(* Output the tables *)
|
|
|
|
|
|
|
|
let output_tables oc tbl =
|
|
|
|
output_string oc "let lex_tables = {\n";
|
2002-10-28 08:46:50 -08:00
|
|
|
|
1996-02-25 06:45:47 -08:00
|
|
|
fprintf oc " Lexing.lex_base = \n%a;\n" output_array tbl.tbl_base;
|
|
|
|
fprintf oc " Lexing.lex_backtrk = \n%a;\n" output_array tbl.tbl_backtrk;
|
|
|
|
fprintf oc " Lexing.lex_default = \n%a;\n" output_array tbl.tbl_default;
|
|
|
|
fprintf oc " Lexing.lex_trans = \n%a;\n" output_array tbl.tbl_trans;
|
2002-10-28 08:46:50 -08:00
|
|
|
fprintf oc " Lexing.lex_check = \n%a;\n" output_array tbl.tbl_check;
|
|
|
|
fprintf oc " Lexing.lex_base_code = \n%a;\n" output_array tbl.tbl_base_code;
|
|
|
|
|
|
|
|
fprintf oc " Lexing.lex_backtrk_code = \n%a;\n"
|
|
|
|
output_array tbl.tbl_backtrk_code;
|
|
|
|
fprintf oc " Lexing.lex_default_code = \n%a;\n"
|
|
|
|
output_array tbl.tbl_default_code;
|
|
|
|
fprintf oc " Lexing.lex_trans_code = \n%a;\n"
|
|
|
|
output_array tbl.tbl_trans_code;
|
|
|
|
fprintf oc " Lexing.lex_check_code = \n%a;\n"
|
|
|
|
output_array tbl.tbl_check_code;
|
|
|
|
fprintf oc " Lexing.lex_code = \n%a;\n" output_byte_array tbl.tbl_code;
|
|
|
|
|
1996-02-25 06:45:47 -08:00
|
|
|
output_string oc "}\n\n"
|
|
|
|
|
2002-12-09 02:44:46 -08:00
|
|
|
|
1996-02-25 06:45:47 -08:00
|
|
|
(* Output the entries *)
|
|
|
|
|
2002-11-02 14:36:46 -08:00
|
|
|
let output_entry sourcefile ic oc oci e =
|
2002-10-28 08:46:50 -08:00
|
|
|
let init_num, init_moves = e.auto_initial_state in
|
2002-12-10 01:14:30 -08:00
|
|
|
fprintf oc "%s %alexbuf =
|
2002-12-09 02:44:46 -08:00
|
|
|
%a%a __ocaml_lex_%s_rec %alexbuf %d\n"
|
2002-10-30 09:20:04 -08:00
|
|
|
e.auto_name
|
2002-12-09 02:44:46 -08:00
|
|
|
output_args e.auto_args
|
2002-10-30 09:20:04 -08:00
|
|
|
(fun oc x ->
|
|
|
|
if x > 0 then
|
|
|
|
fprintf oc "lexbuf.Lexing.lex_mem <- Array.create %d (-1) ; " x)
|
|
|
|
e.auto_mem_size
|
2002-12-09 02:44:46 -08:00
|
|
|
(output_memory_actions " ") init_moves
|
|
|
|
e.auto_name
|
|
|
|
output_args e.auto_args
|
|
|
|
init_num;
|
2003-07-26 12:13:15 -07:00
|
|
|
fprintf oc "and __ocaml_lex_%s_rec %alexbuf __ocaml_lex_state =\n"
|
2002-12-09 02:44:46 -08:00
|
|
|
e.auto_name output_args e.auto_args ;
|
2003-07-26 12:13:15 -07:00
|
|
|
fprintf oc
|
|
|
|
" match Lexing.%sengine lex_tables __ocaml_lex_state lexbuf with\n "
|
2002-10-28 08:46:50 -08:00
|
|
|
(if e.auto_mem_size == 0 then "" else "new_") ;
|
1996-02-25 06:45:47 -08:00
|
|
|
List.iter
|
2002-10-28 08:46:50 -08:00
|
|
|
(fun (num, env, loc) ->
|
|
|
|
fprintf oc " | ";
|
2003-07-26 14:06:21 -07:00
|
|
|
fprintf oc "%d ->\n" num;
|
|
|
|
output_env oc env;
|
|
|
|
copy_chunk sourcefile ic oc oci loc true;
|
|
|
|
fprintf oc "\n")
|
1996-02-25 06:45:47 -08:00
|
|
|
e.auto_actions;
|
1999-10-15 11:37:55 -07:00
|
|
|
fprintf oc " | n -> lexbuf.Lexing.refill_buff lexbuf; \
|
2002-12-09 02:44:46 -08:00
|
|
|
__ocaml_lex_%s_rec %alexbuf n\n\n"
|
|
|
|
e.auto_name output_args e.auto_args
|
1996-02-25 06:45:47 -08:00
|
|
|
|
|
|
|
(* Main output function *)
|
|
|
|
|
1998-05-26 02:56:41 -07:00
|
|
|
exception Table_overflow
|
|
|
|
|
2002-11-02 14:36:46 -08:00
|
|
|
let output_lexdef sourcefile ic oc oci header tables entry_points trailer =
|
1996-02-25 06:45:47 -08:00
|
|
|
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));
|
2002-10-28 08:46:50 -08:00
|
|
|
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
|
|
|
|
Printf.printf "%d additional bytes used for bindings\n" size_groups ;
|
1996-02-25 06:45:47 -08:00
|
|
|
flush stdout;
|
1998-05-26 02:56:41 -07:00
|
|
|
if Array.length tables.tbl_trans > 0x8000 then raise Table_overflow;
|
2003-07-26 14:06:21 -07:00
|
|
|
copy_chunk sourcefile ic oc oci header false;
|
1996-02-25 06:45:47 -08:00
|
|
|
output_tables oc tables;
|
|
|
|
begin match entry_points with
|
|
|
|
[] -> ()
|
|
|
|
| entry1 :: entries ->
|
2002-11-02 14:36:46 -08:00
|
|
|
output_string oc "let rec "; output_entry sourcefile ic oc oci entry1;
|
1996-02-25 06:45:47 -08:00
|
|
|
List.iter
|
2002-11-02 14:36:46 -08:00
|
|
|
(fun e -> output_string oc "and "; output_entry sourcefile ic oc oci e)
|
1999-10-15 11:37:55 -07:00
|
|
|
entries;
|
|
|
|
output_string oc ";;\n\n";
|
1996-02-25 06:45:47 -08:00
|
|
|
end;
|
2003-07-26 14:06:21 -07:00
|
|
|
copy_chunk sourcefile ic oc oci trailer false
|