]> matita.cs.unibo.it Git - helm.git/blob - helm/ocaml/cic_disambiguation/disambiguateTypes.ml
renamed modules so that they are more consistent with other cic modules
[helm.git] / helm / ocaml / cic_disambiguation / disambiguateTypes.ml
1
2 type domain_item =
3  | Id of string               (* literal *)
4  | Symbol of string * int     (* literal, instance num *)
5  | Num of int                 (* instance num *)
6
7 module OrderedDomain =
8   struct
9     type t = domain_item
10     let compare = Pervasives.compare
11   end
12
13 module Domain = Set.Make (OrderedDomain)
14 module Environment = Map.Make (OrderedDomain)
15
16 type codomain_item =
17   string *  (* description *)
18   (environment -> string -> Cic.term list -> Cic.term)
19     (* environment, literal number, arguments as needed *)
20
21 and environment = codomain_item Environment.t
22
23 module type Callbacks =
24   sig
25     val output_html : ?append_NL:bool -> Ui_logger.html_msg -> unit
26     val interactive_user_uri_choice :
27       selection_mode:[`SINGLE | `MULTIPLE] ->
28       ?ok:string ->
29       ?enable_button_for_non_vars:bool ->
30       title:string -> msg:string -> id:string -> string list -> string list
31     val interactive_interpretation_choice :
32       (string * string) list list -> int
33     val input_or_locate_uri : title:string -> UriManager.uri
34   end
35
36 let string_of_domain_item = function
37   | Id s -> Printf.sprintf "ID(%s)" s
38   | Symbol (s, i) -> Printf.sprintf "SYMBOL(%s,%d)" s i
39   | Num i -> Printf.sprintf "NUM(instance %d)" i
40
41 let string_of_domain dom =
42   let buf = Buffer.create 1024 in
43   Domain.iter
44     (fun item -> Buffer.add_string buf (string_of_domain_item item ^ "; "))
45     dom;
46   Buffer.contents buf
47
48 module EnvironmentP3 =
49   struct
50     type t = environment
51     let empty = ""
52
53     let to_string env =
54      Environment.fold
55       (fun i v s ->
56         match i with
57         | Id id ->s ^ Printf.sprintf "alias %s %s\n" id (fst v)
58         | _ -> "")
59       env ""
60
61     let of_string inputtext =
62      let regexpr =
63       let alfa = "[a-zA-Z_-]" in
64       let digit = "[0-9]" in
65       let ident = alfa ^ "\(" ^ alfa ^ "\|" ^ digit ^ "\)*" in
66       let blanks = "\( \|\t\|\n\)+" in
67       let nonblanks = "[^ \t\n]+" in
68       let uri = "/\(" ^ ident ^ "/\)*" ^ nonblanks in (* not very strict check *)
69        Str.regexp
70         ("alias" ^ blanks ^ "\(" ^ ident ^ "\)" ^ blanks ^ "\(" ^ uri ^ "\)")
71      in
72       let rec aux n =
73        try
74         let n' = Str.search_forward regexpr inputtext n in
75          let id = Id (Str.matched_group 2 inputtext) in
76          let uri = "cic:" ^ (Str.matched_group 5 inputtext) in
77           let resolve_id = aux (n' + 1) in
78            if Environment.mem id resolve_id then
79             resolve_id
80            else
81              let term =
82                HelmLibraryObjects.term_of_uri (UriManager.uri_of_string uri)
83              in
84              (Environment.add id (uri, (fun _ _ _ -> term))
85                resolve_id)
86        with
87         Not_found -> Environment.empty
88       in
89        aux 0
90   end
91