]> matita.cs.unibo.it Git - helm.git/blob - helm/ocaml/cic/helmLibraryObjects.ml
moved here term_of_uri
[helm.git] / helm / ocaml / cic / helmLibraryObjects.ml
1 (** {2 Auxiliary functions} *)
2
3 let uri = UriManager.uri_of_string
4
5 let const ?(subst = []) uri = Cic.Const (uri, subst)
6 let var ?(subst = []) uri = Cic.Var (uri, subst)
7 let mutconstruct ?(subst = []) uri typeno consno =
8   Cic.MutConstruct (uri, typeno, consno, subst)
9 let mutind ?(subst = []) uri typeno = Cic.MutInd (uri, typeno, subst)
10
11 let indtyuri_of_uri uri =
12   let index_sharp =  String.index uri '#' in
13   let index_num = index_sharp + 3 in
14   (UriManager.uri_of_string (String.sub uri 0 index_sharp),
15    int_of_string(String.sub uri index_num (String.length uri - index_num)) - 1)
16
17 let indconuri_of_uri uri =
18   let index_sharp =  String.index uri '#' in
19   let index_div = String.rindex uri '/' in
20   let index_con = index_div + 1 in
21     (UriManager.uri_of_string (String.sub uri 0 index_sharp),
22     int_of_string
23       (String.sub uri (index_sharp + 3) (index_div - index_sharp - 3)) - 1,
24     int_of_string
25       (String.sub uri index_con (String.length uri - index_con)))
26
27 let term_of_uri uri =
28   let s = UriManager.string_of_uri uri in
29   try
30   (* Constant *)
31   (* TODO explicit substitutions? *)
32   let len = String.length s in
33   let sub = String.sub s (len -4) 4 in
34   if sub = ".con" then
35     const uri
36   else if sub = ".var" then
37     var uri
38   else
39     (try
40       (* Inductive Type *)
41       let (uri, typeno) = indtyuri_of_uri s in
42       mutind uri typeno
43      with
44       | UriManager.IllFormedUri _ | Failure _ | Invalid_argument _ ->
45           (* Constructor of an Inductive Type *)
46           let (uri, typeno, consno) = indconuri_of_uri s in
47           mutconstruct uri typeno consno)
48  with
49  | Invalid_argument _ -> raise (UriManager.IllFormedUri s)
50
51 (** {2 Helm's objects shorthands} *)
52
53 module Logic =
54   struct
55     let eq_URI = uri "cic:/Coq/Init/Logic/eq.ind"
56     let true_URI = uri "cic:/Coq/Init/Logic/True.ind"
57     let false_URI = uri "cic:/Coq/Init/Logic/False.ind"
58   end
59
60 module Logic_Type =
61   struct
62     let eqt_URI = uri "cic:/Coq/Init/Logic_Type/eqT.ind"
63     let sym_eqt_URI = uri "cic:/Coq/Init/Logic_Type/sym_eqT.con"
64
65     let refl_eqt = mutconstruct eqt_URI 0 1
66     let sym_eqt = const sym_eqt_URI
67   end
68
69 module Datatypes =
70   struct
71     let bool_URI = uri "cic:/Coq/Init/Datatypes/bool.ind"
72     let nat_URI = uri "cic:/Coq/Init/Datatypes/nat.ind"
73
74     let trueb = mutconstruct bool_URI 0 1
75     let falseb = mutconstruct bool_URI 0 2
76     let zero = mutconstruct nat_URI 0 1
77     let succ = mutconstruct nat_URI 0 2
78   end
79
80 module Reals =
81   struct
82     let r_URI = uri "cic:/Coq/Reals/Rdefinitions/R.con"
83     let rplus_URI = uri "cic:/Coq/Reals/Rdefinitions/Rplus.con"
84     let rmult_URI = uri "cic:/Coq/Reals/Rdefinitions/Rmult.con"
85     let ropp_URI = uri "cic:/Coq/Reals/Rdefinitions/Ropp.con"
86     let r0_URI = uri "cic:/Coq/Reals/Rdefinitions/R0.con"
87     let r1_URI = uri "cic:/Coq/Reals/Rdefinitions/R1.con"
88     let rtheory_URI = uri "cic:/Coq/Reals/Rbase/RTheory.con"
89
90     let r = const r_URI
91     let rplus = const rplus_URI
92     let rmult = const rmult_URI
93     let ropp = const ropp_URI
94     let r0 = const r0_URI
95     let r1 = const r1_URI
96     let rtheory = const rtheory_URI
97   end
98
99 module Peano =
100   struct
101     let plus_URI = uri "cic:/Coq/Init/Peano/plus.con"
102     let mult_URI = uri "cic:/Coq/Init/Peano/mult.con"
103     let pred_URI = uri "cic:/Coq/Init/Peano/pred.con"
104
105     let plus = const plus_URI
106     let mult = const mult_URI
107     let pred = const pred_URI
108   end
109
110 (** {2 Helpers for creating common terms}
111  *  (e.g. numbers)} *)
112
113 exception NegativeInteger
114
115 let build_nat n =
116   if n < 0 then raise NegativeInteger;
117   let rec aux = function
118     | 0 -> Datatypes.zero
119     | n -> Cic.Appl [ Datatypes.succ; (aux (n - 1)) ]
120   in
121   aux n
122
123 let build_real n =
124   if n < 0 then raise NegativeInteger;
125   let rec aux = function
126     | 0 -> Reals.r0
127     | 1 -> Reals.r1 (* to avoid trailing "+ 0" *)
128     | n -> Cic.Appl [ Reals.rplus; Reals.r1; (aux (n - 1)) ]
129   in
130   aux n
131