]> matita.cs.unibo.it Git - helm.git/blob - helm/ocaml/cic_disambiguation/make_table.ml
removed dependency on netclient, use http_client module from ocaml-http
[helm.git] / helm / ocaml / cic_disambiguation / make_table.ml
1
2 open Printf
3 open Pxp_types
4 open Pxp_ev_parser
5
6 (* Usage: make_table <hashtbls_dump_file> *)
7
8 let debug = false
9 let debug_print s = if debug then prerr_endline s
10
11 let tables = [
12 (*
13   `Entities, "/usr/share/gtkmathview/entities-table.xml";
14   `Dictionary, "/usr/share/editex/dictionary-tex.xml"
15 *)
16   `Entities, "macros/entities-table.xml";
17   `Dictionary, "macros/dictionary-tex.xml";
18   `Entities, "macros/extra-entities.xml";
19 ]
20
21 let macro2utf8 = Hashtbl.create 2000
22 let utf82macro = Hashtbl.create 2000
23
24 let add_macro macro utf8 =
25   debug_print (sprintf "Adding macro %s = '%s'" macro utf8);
26   Hashtbl.add macro2utf8 macro utf8;
27   Hashtbl.add utf82macro utf8 macro
28
29 let rec find_first_tag pull_parser =
30   match pull_parser () with
31   | Some (E_start_tag _ as e) -> e
32   | None -> assert false
33   | _ -> find_first_tag pull_parser
34
35 let iter_entities_file f pull_parser =
36   ignore (find_first_tag pull_parser); (* <entities-table> *)
37   let rec aux () =
38     match pull_parser () with
39     | Some (E_start_tag ("entity", attrs, _)) ->
40         (try
41           let name = List.assoc "name" attrs in
42           let value = List.assoc "value" attrs in
43           f name value
44         with Not_found -> ());
45         aux ()
46     | None -> ()
47     | _ -> aux ()
48   in
49   aux ()
50
51 let iter_dictionary_file f pull_parser =
52   ignore (find_first_tag pull_parser); (* <dictionary> *)
53   let rec aux () =
54     match pull_parser () with
55     | Some (E_start_tag ("entry", attrs, _)) ->
56         (try
57           let name = List.assoc "name" attrs in
58           let value = List.assoc "val" attrs in
59           f name value
60         with Not_found -> ());
61         aux ()
62     | None -> ()
63     | _ -> aux ()
64   in
65   aux ()
66
67 let fill_table () =
68   List.iter
69     (fun (typ, fname) ->
70       let entry = `Entry_document [ `Extend_dtd_fully; `Parse_xml_decl ] in
71       let config = { default_config with encoding = `Enc_utf8 } in
72       let entity_manager =
73         create_entity_manager ~is_document:true config (from_file fname)
74       in
75       let pull_parser = create_pull_parser config entry entity_manager in
76       match typ with
77       | `Entities -> iter_entities_file add_macro pull_parser
78       | `Dictionary -> iter_dictionary_file add_macro pull_parser)
79     tables
80
81 let main () =
82   let oc = open_out Sys.argv.(1) in
83   fill_table ();
84   Marshal.to_channel oc (macro2utf8, utf82macro) [];
85   close_out oc
86
87 let _ = main ()
88