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