]> matita.cs.unibo.it Git - helm.git/blob - helm/ocaml/cic_disambiguation/disambiguatePp.ml
ocaml 3.09 transition
[helm.git] / helm / ocaml / cic_disambiguation / disambiguatePp.ml
1 (* Copyright (C) 2005, HELM Team.
2  * 
3  * This file is part of HELM, an Hypertextual, Electronic
4  * Library of Mathematics, developed at the Computer Science
5  * Department, University of Bologna, Italy.
6  * 
7  * HELM is free software; you can redistribute it and/or
8  * modify it under the terms of the GNU General Public License
9  * as published by the Free Software Foundation; either version 2
10  * of the License, or (at your option) any later version.
11  * 
12  * HELM is distributed in the hope that it will be useful,
13  * but WITHOUT ANY WARRANTY; without even the implied warranty of
14  * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
15  * GNU General Public License for more details.
16  *
17  * You should have received a copy of the GNU General Public License
18  * along with HELM; if not, write to the Free Software
19  * Foundation, Inc., 59 Temple Place - Suite 330, Boston,
20  * MA  02111-1307, USA.
21  * 
22  * For details, see the HELM World-Wide-Web page,
23  * http://helm.cs.unibo.it/
24  *)
25
26 open DisambiguateTypes
27
28 let parse_environment str =
29  let stream = Ulexing.from_utf8_string str in
30  let environment = ref Environment.empty in
31  let multiple_environment = ref Environment.empty in
32   try
33     while true do
34      let alias =
35       match GrafiteParser.parse_statement stream with
36          GrafiteAst.Executable (_, GrafiteAst.Command (_, GrafiteAst.Alias (_,alias)))
37            -> alias
38        | _ -> assert false in
39      let key,value =
40       (*CSC: Warning: this code should be factorized with the corresponding
41              code in MatitaEngine *)
42       match alias with
43          GrafiteAst.Ident_alias (id,uri) ->
44           Id id,
45           (uri,(fun _ _ _-> CicUtil.term_of_uri (UriManager.uri_of_string uri)))
46        | GrafiteAst.Symbol_alias (symb,instance,desc) ->
47           Symbol (symb,instance),
48           DisambiguateChoices.lookup_symbol_by_dsc symb desc
49        | GrafiteAst.Number_alias (instance,desc) ->
50           Num instance,
51           DisambiguateChoices.lookup_num_by_dsc desc
52      in
53       environment := Environment.add key value !environment;
54       multiple_environment := Environment.cons key value !multiple_environment;
55     done;
56     assert false
57   with End_of_file ->
58    !environment, !multiple_environment
59
60 let alias_of_domain_and_codomain_items domain_item (dsc,_) =
61  match domain_item with
62     Id id -> GrafiteAst.Ident_alias (id, dsc)
63   | Symbol (symb, i) -> GrafiteAst.Symbol_alias (symb, i, dsc)
64   | Num i -> GrafiteAst.Number_alias (i, dsc)
65
66 let aliases_of_environment env =
67   Environment.fold
68     (fun domain_item codomain_item acc ->
69       alias_of_domain_and_codomain_items domain_item codomain_item::acc
70     ) env []
71
72 let aliases_of_domain_and_codomain_items_list l =
73   List.fold_left
74     (fun acc (domain_item,codomain_item) ->
75       alias_of_domain_and_codomain_items domain_item codomain_item::acc
76     ) [] l
77
78 let pp_environment env =
79   let aliases = aliases_of_environment env in
80   let strings =
81     List.map (fun alias -> GrafiteAstPp.pp_alias alias ^ ".") aliases
82   in
83   String.concat "\n" (List.sort compare strings)