]> matita.cs.unibo.it Git - helm.git/blob - helm/ocaml/mathql_generator/mQGUtil.ml
ocaml 3.09 transition
[helm.git] / helm / ocaml / mathql_generator / mQGUtil.ml
1 (* Copyright (C) 2000, 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://cs.unibo.it/helm/.
24  *)
25
26 (*  AUTOR: Ferruccio Guidi <fguidi@cs.unibo.it>
27  *)
28
29 module T = MQGTypes
30
31 (* low level functions  *****************************************************)
32
33 let string_of_position p = 
34    let ns = "http://www.cs.unibo.it/helm/schemas/schema-helm#" in
35    match p with
36       | T.MainHypothesis -> ns ^ "MainHypothesis"
37       | T.InHypothesis   -> ns ^ "InHypothesis"
38       | T.MainConclusion -> ns ^ "MainConclusion"
39       | T.InConclusion   -> ns ^ "InConclusion"
40       | T.InBody         -> ns ^ "InBody"
41       
42 let string_of_sort = function
43    | T.Set   -> "Set"
44    | T.Prop  -> "Prop"
45    | T.Type  -> "Type"
46    | T.CProp -> "CProp"
47
48 let string_of_depth = string_of_int
49
50 let mathql_of_position = function
51    | T.MainHypothesis -> "$MH"
52    | T.InHypothesis   -> "$IH"
53    | T.MainConclusion -> "$MC"
54    | T.InConclusion   -> "$IC"
55    | T.InBody         -> "$IB"
56       
57 let mathql_of_sort = function
58    | T.Set   -> "$SET"
59    | T.Prop  -> "$PROP"
60    | T.Type  -> "$TYPE"
61    | T.CProp -> "$CPROP"
62
63 let mathql_of_depth = string_of_int
64
65 let mathql_of_uri u = u
66
67 let mathql_of_specs out l =
68    let rec iter f = function 
69       | []        -> ()
70       | [s]       -> out "\""; out (f s); out "\""
71       | s :: tail -> out "\""; out (f s); out "\", "; iter f tail
72    in
73    let txt_uri l = out "{"; iter mathql_of_uri l; out "} " in
74    let txt_pos l = out "{"; iter mathql_of_position l; out "} " in
75    let txt_sort l = out "{"; iter mathql_of_sort l; out "} " in
76    let txt_depth l = out "{"; iter mathql_of_depth l; out "} " in
77    let txt_spec = function
78       | T.MustObj  (u, p, d) -> out "mustobj  "; txt_uri u; txt_pos p; txt_depth d; out "\n" 
79       | T.MustSort (s, p, d) -> out "mustsort "; txt_sort s; txt_pos p; txt_depth d; out "\n" 
80       | T.MustRel  (   p, d) -> out "mustrel  "; txt_pos p; txt_depth d; out "\n" 
81       | T.OnlyObj  (u, p, d) -> out "onlyobj  "; txt_uri u; txt_pos p; txt_depth d; out "\n" 
82       | T.OnlySort (s, p, d) -> out "onlysort "; txt_sort s; txt_pos p; txt_depth d; out "\n" 
83       | T.OnlyRel  (   p, d) -> out "onlyrel  "; txt_pos p; txt_depth d; out "\n" 
84       | T.Universe (   p   ) -> out "universe "; txt_pos p; out "\n" 
85    in   
86    List.iter txt_spec l  
87
88 let position_of_mathql = function
89    | "$MH" -> T.MainHypothesis 
90    | "$IH" -> T.InHypothesis
91    | "$MC" -> T.MainConclusion
92    | "$IC" -> T.InConclusion
93    | "$IB" -> T.InBody
94    | _     -> raise Parsing.Parse_error 
95
96 let sort_of_mathql = function
97    | "$SET"   -> T.Set 
98    | "$PROP"  -> T.Prop
99    | "$TYPE"  -> T.Type
100    | "$CPROP" -> T.CProp
101    | _       -> raise Parsing.Parse_error 
102
103 let depth_of_mathql s =
104    try 
105       let d = int_of_string s in
106       if d < 0 then raise (Failure "") else d
107    with Failure _ -> raise Parsing.Parse_error
108
109 let uri_of_mathql s = s
110
111 (* high level functions  ****************************************************)
112
113 let text_of_position = function
114    | `MainHypothesis _ -> "MainHypothesis"
115    | `MainConclusion _ -> "MainConclusion"
116    | `InHypothesis     -> "InHypothesis" 
117    | `InConclusion     -> "InConclusion" 
118    | `InBody           -> "InBody" 
119
120 let text_of_depth pos no_depth_text = match pos with
121    | `MainHypothesis (Some d)
122    | `MainConclusion (Some d) -> string_of_int d
123    | _                        -> no_depth_text
124
125 let text_of_sort = function
126    | T.Set   -> "Set"
127    | T.Prop  -> "Prop"
128    | T.Type  -> "Type"
129    | T.CProp -> "CProp"
130
131 let is_main_position = function
132    | `MainHypothesis _
133    | `MainConclusion _ -> true
134    | _                 -> false
135
136 let is_conclusion = function
137    | `MainConclusion _ 
138    | `InConclusion     -> true
139    | _                 -> false
140
141 let set_full_position pos depth = match pos with
142    | `MainHypothesis _ -> `MainHypothesis depth
143    | `MainConclusion _ -> `MainConclusion depth
144    | _                 -> pos
145
146 let set_main_position pos depth = match pos with
147    | `MainHypothesis _ -> `MainHypothesis depth
148    | `MainConclusion _ -> `MainConclusion depth