]> matita.cs.unibo.it Git - helm.git/blob - helm/ocaml/mathql/mQueryUtil.ml
textual parser fixed
[helm.git] / helm / ocaml / mathql / mQueryUtil.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 (******************************************************************************)
27 (*                                                                            *)
28 (*                               PROJECT HELM                                 *)
29 (*                                                                            *)
30 (*                     Ferruccio Guidi <fguidi@cs.unibo.it>                   *)
31 (*                                 30/04/2002                                 *)
32 (*                                                                            *)
33 (*                                                                            *)
34 (******************************************************************************)
35
36 open MathQL
37 open MQueryHTML
38
39 (* string linearization of a reference **************************************)
40
41 let str_btoken = function
42    | MQBC s -> s
43    | MQBD   -> "/"
44    | MQBQ   -> "?"
45    | MQBS   -> "*"
46    | MQBSS  -> "**"
47
48 let str_ftoken = function
49    | MQFC i -> string_of_int i
50    | MQFS   -> "*"
51    | MQFSS  -> "**"
52
53 let str_prot = function
54    | Some s -> s
55    | None   -> "*"
56
57 let rec str_body = function
58    | [] -> ""
59    | head :: tail -> str_btoken head ^ str_body tail 
60
61 let str_frag xpointer f l = 
62    let sfi = List.fold_left (fun l0 t0 -> l0 ^ "/" ^ f t0) "" l in
63    if sfi = "" then "" else
64    if xpointer then "#xpointer(1" ^ sfi ^ ")" else
65                     "#1" ^ sfi
66
67 let str_tref (p, b, i) = 
68    str_prot p ^ ":/" ^ str_body b ^ str_frag false str_ftoken i
69
70 let xp_str_tref (p, b, i) = 
71    str_prot p ^ ":/" ^ str_body b ^ str_frag true str_ftoken i
72
73 let str_uref (u, i) =
74    UriManager.string_of_uri u ^ str_frag false string_of_int i
75
76 let xp_str_uref (u, i) =
77    UriManager.string_of_uri u ^ str_frag true string_of_int i
78
79 (* HTML representation of a query ********************************************)
80
81 let out_rvar s = sym s
82
83 let out_svar s = sep "$" ^ sym s
84
85 let out_lvar s = sep "%" ^ sym s
86
87 let out_tref r = pat (str_tref r) 
88
89 let rec out_sequence f = function
90   | []        -> sep "."
91   | [s]       -> f s
92   | s :: tail -> f s ^ sep ", " ^ out_sequence f tail
93
94 let out_order = function
95    | MQAsc  -> sub2 "asc"
96    | MQDesc -> sub2 "desc"
97
98 let out_func = function
99    | MQName         -> key "name"
100    | MQTheory       -> key "theory"
101    | MQTitle        -> key "title"
102    | MQContributor  -> key "contributor"
103    | MQCreator      -> key "creator"
104    | MQPublisher    -> key "publisher"
105    | MQSubject      -> key "subject"
106    | MQDescription  -> key "description"
107    | MQDate         -> key "date"
108    | MQType         -> key "type"
109    | MQFormat       -> key "format"
110    | MQIdentifier   -> key "identifier"
111    | MQLanguage     -> key "language"
112    | MQRelation     -> key "relation"
113    | MQSource       -> key "source"
114    | MQCoverage     -> key "coverage"
115    | MQRights       -> key "rights"
116    | MQInstitution  -> key "institution"
117    | MQContact      -> key "contact"
118    | MQFirstVersion -> key "firstversion"
119    | MQModified     -> key "modified"
120
121 let out_str = function
122    | MQCons s       -> str s
123    | MQStringRVar s -> out_rvar s
124    | MQStringSVar s -> out_svar s
125    | MQFunc (f, r)  -> out_func f ^ out_rvar r
126    | MQMConclusion  -> key "mainconclusion" 
127    | MQConclusion   -> key "inconclusion" 
128
129 let rec out_bool = function
130    | MQTrue -> key "true"
131    | MQFalse -> key "false"
132    | MQIs (s, t) -> out_str s ^ sub "is" ^ out_str t
133    | MQNot b -> key "not" ^ out_bool b 
134    | MQAnd (b1, b2) -> sep "(" ^ out_bool b1 ^ sub "and" ^ out_bool b2 ^ sep ")"
135    | MQOr (b1, b2) -> sep "(" ^ out_bool b1 ^ sub "or" ^ out_bool b2 ^ sep ")"
136    | MQSubset (l1, l2) -> sep "(" ^ out_list l1 ^ sub "subset" ^ out_list l2 ^ sep ")"
137    | MQSetEqual (l1, l2) -> sep "(" ^ out_list l1 ^ sub "setequal" ^ out_list l2 ^ sep ")"
138
139 and out_list = function
140    | MQSelect (r, l, b) -> 
141       key "select" ^ out_rvar r ^ sub "in" ^ out_list l ^ sub "where" ^ out_bool b
142    | MQUse (l, v) -> key "use" ^ out_list l ^ sub "position" ^ out_svar v
143    | MQUsedBy (l, v) -> key "usedby" ^ out_list l ^ sub "position" ^ out_svar v
144    | MQPattern p -> key "pattern" ^ out_tref p
145    | MQUnion (l1, l2) -> sep "(" ^ out_list l1 ^ sub "union" ^ out_list l2 ^ sep ")"
146    | MQIntersect (l1, l2) -> sep "(" ^ out_list l1 ^ sub "intersect" ^ out_list l2 ^ sep ")"
147    | MQDiff (l1, l2) -> sep "(" ^ out_list l1 ^ sub "diff" ^ out_list l2 ^ sep ")"
148    | MQListRVar v -> out_rvar v
149    | MQSortedBy (l, o, f) -> sep "(" ^ out_list l ^ sub "sortedby" ^ out_func f ^ out_order o ^ sep ")"
150    | MQListLVar v -> out_lvar v
151    | MQLetIn (v, l1, l2) -> key "let" ^ out_lvar v ^ sub "be" ^ out_list l1 ^ sub "in" ^ out_list l2
152    | MQReference s -> key "reference" ^ out_sequence str s
153
154 let out_query = function
155    | MQList l -> out_list l
156
157 (* HTML representation of a query result ************************************)
158
159 let rec out_res_list = function 
160    | []     -> ""
161    | u :: l -> res u ^ nl () ^ out_res_list l 
162
163 let out_result qr =
164    par () ^ "Result:" ^ nl () ^
165    match qr with
166       | MQRefs l -> out_res_list l
167
168 (* Converting functions *****************************************************)
169
170 let tref_uref u =
171    let s = str_uref u in
172    MQueryTParser.ref MQueryTLexer.rtoken (Lexing.from_string s) 
173
174 let parse_text ch =
175    let lexbuf = Lexing.from_channel ch in
176    MQueryTParser.query MQueryTLexer.qtoken lexbuf
177
178 (* implementazione manuale di tref_uref da controllare 
179
180 let split s =
181    try 
182       let i = Str.search_forward (Str.regexp_string ":/") s 0 in
183       let p = Str.string_before s i in
184       let q = Str.string_after s (i + 2) in
185          (p, q)
186    with 
187       Not_found -> (s, "")
188
189 let encode = function
190    | Str.Text s  -> MQBC s
191    | Str.Delim s ->  
192       if s = "?"  then MQBQ else
193       if s = "*"  then MQBS else
194       if s = "**" then MQBSS else
195       if s = "/"  then MQBD  else MQBC s
196
197 let tref_uref (u, i) =
198    let s = UriManager.string_of_uri u in
199    match split s with
200       | (p, q) -> 
201          let rx = Str.regexp "\?\|\*\*\|\*\|/" in
202          let l = Str.full_split rx q in
203          (Some p, List.map encode l, i) 
204
205 *)