]> matita.cs.unibo.it Git - helm.git/blob - helm/ocaml/mathql_generator/mQGUtil.ml
- the mathql interpreter is not helm-dependent any more
[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
47 let string_of_depth = string_of_int
48
49 let mathql_of_position = function
50    | T.MainHypothesis -> "$MH"
51    | T.InHypothesis   -> "$IH"
52    | T.MainConclusion -> "$MC"
53    | T.InConclusion   -> "$IC"
54    | T.InBody         -> "$IB"
55       
56 let mathql_of_sort = function
57    | T.Set  -> "$SET"
58    | T.Prop -> "$PROP"
59    | T.Type -> "$TYPE"
60
61 let mathql_of_depth = string_of_int
62
63 let mathql_of_uri u = u
64
65 let mathql_of_specs out l =
66    let rec iter f = function 
67       | []        -> ()
68       | [s]       -> out "\""; out (f s); out "\""
69       | s :: tail -> out "\""; out (f s); out "\", "; iter f tail
70    in
71    let txt_uri l = out "{"; iter mathql_of_uri l; out "} " in
72    let txt_pos l = out "{"; iter mathql_of_position l; out "} " in
73    let txt_sort l = out "{"; iter mathql_of_sort l; out "} " in
74    let txt_depth l = out "{"; iter mathql_of_depth l; out "} " in
75    let txt_spec = function
76       | T.MustObj  (u, p, d) -> out "mustobj  "; txt_uri u; txt_pos p; txt_depth d; out "\n" 
77       | T.MustSort (s, p, d) -> out "mustsort "; txt_sort s; txt_pos p; txt_depth d; out "\n" 
78       | T.MustRel  (   p, d) -> out "mustrel  "; txt_pos p; txt_depth d; out "\n" 
79       | T.OnlyObj  (u, p, d) -> out "onlyobj  "; txt_uri u; txt_pos p; txt_depth d; out "\n" 
80       | T.OnlySort (s, p, d) -> out "onlysort "; txt_sort s; txt_pos p; txt_depth d; out "\n" 
81       | T.OnlyRel  (   p, d) -> out "onlyrel  "; txt_pos p; txt_depth d; out "\n" 
82       | T.Universe (   p   ) -> out "universe "; txt_pos p; out "\n" 
83    in   
84    List.iter txt_spec l  
85
86 let position_of_mathql = function
87    | "$MH" -> T.MainHypothesis 
88    | "$IH" -> T.InHypothesis
89    | "$MC" -> T.MainConclusion
90    | "$IC" -> T.InConclusion
91    | "$IB" -> T.InBody
92    | _     -> raise Parsing.Parse_error 
93
94 let sort_of_mathql = function
95    | "$SET"  -> T.Set 
96    | "$PROP" -> T.Prop
97    | "$TYPE" -> T.Type
98    | _       -> raise Parsing.Parse_error 
99
100 let depth_of_mathql s =
101    try 
102       let d = int_of_string s in
103       if d < 0 then raise (Failure "") else d
104    with Failure _ -> raise Parsing.Parse_error
105
106 let uri_of_mathql s = s
107
108 (* high level functions  ****************************************************)
109
110 let text_of_position = function
111    | `MainHypothesis _ -> "MainHypothesis"
112    | `MainConclusion _ -> "MainConclusion"
113    | `InHypothesis     -> "InHypothesis" 
114    | `InConclusion     -> "InConclusion" 
115    | `InBody           -> "InBody" 
116
117 let text_of_depth pos no_depth_text = match pos with
118    | `MainHypothesis (Some d)
119    | `MainConclusion (Some d) -> string_of_int d
120    | _                        -> no_depth_text
121
122 let text_of_sort = function
123    | T.Set  -> "Set"
124    | T.Prop -> "Prop"
125    | T.Type -> "Type"
126
127 let is_main_position = function
128    | `MainHypothesis _
129    | `MainConclusion _ -> true
130    | _                 -> false
131
132 let is_conclusion = function
133    | `MainConclusion _ 
134    | `InConclusion     -> true
135    | _                 -> false
136
137 let set_full_position pos depth = match pos with
138    | `MainHypothesis _ -> `MainHypothesis depth
139    | `MainConclusion _ -> `MainConclusion depth
140    | _                 -> pos
141
142 let set_main_position pos depth = match pos with
143    | `MainHypothesis _ -> `MainHypothesis depth
144    | `MainConclusion _ -> `MainConclusion depth
145
146 let universe_for_search_pattern =
147    [T.MainHypothesis; T.InHypothesis; T.MainConclusion; T.InConclusion]
148    
149 let universe_for_match_conclusion = [T.MainConclusion; T.InConclusion]