]> matita.cs.unibo.it Git - helm.git/blob - helm/ocaml/mathql/mQueryUtil.ml
2169564e42e33f817cc599fffd98b920f5554ffd
[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_ftoken = function
48    | MQFC i -> "/" ^ string_of_int i
49    | MQFS   -> "/*"
50    | MQFSS  -> "/**"
51
52 let str_prot = function
53    | Some s -> s
54    | None   -> "*"
55
56 let rec str_body = function
57    | [] -> ""
58    | head :: tail -> str_btoken head ^ str_body tail 
59
60 let str_frag l = 
61    let rec str_fi start = function 
62       | []     -> ""
63       | t :: l -> 
64          (if start then "#1" else "") ^ str_ftoken t ^ str_fi false l
65    in str_fi true l
66
67 let str_tref (p, b, i) = 
68    str_prot p ^ ":/" ^ str_body b ^ str_frag i
69
70 let str_uref (u, i) =
71    let rec str_fi start = function 
72       | []     -> ""
73       | i :: l -> 
74          (if start then "#1" else "") ^ string_of_int i ^ str_fi false l
75    in UriManager.string_of_uri u ^ str_fi true i
76
77 (* raw HTML representation *)
78
79 let key s = "<font color=\"blue\">" ^ s ^ " </font>"
80
81 let sub s = "<font color=\"blue\"> " ^ s ^ " </font>"
82
83 let sub2 s = "<font color=\"blue\">" ^ s ^ "</font>"
84
85 let sym s = s
86
87 let sep s = s
88
89 let str s = "<font color=\"red\">'" ^ s ^ "'</font>"
90
91 let pat s = "<font color=\"red\">\"" ^ s ^ "\"</font>"
92
93 let res s = "<font color=\"brown\">\"" ^ s ^ "\"</font>"
94
95 let nl () = "<br>"
96
97 let par () = "<p>"
98
99 (* HTML representation of a query *)
100
101 let out_rvar s = sym s
102
103 let out_svar s = sep "$" ^ sym s
104
105 let out_tref r = pat (str_tref r) 
106
107 let out_pat p = out_tref p
108
109 let out_order = function
110    | MQAsc  -> sub2 "asc"
111    | MQDesc -> sub2 "desc"
112
113 let out_func = function
114    | MQName         -> key "name"
115    | MQTheory       -> key "theory"
116    | MQTitle        -> key "title"
117    | MQContributor  -> key "contributor"
118    | MQCreator      -> key "creator"
119    | MQPublisher    -> key "publisher"
120    | MQSubject      -> key "subject"
121    | MQDescription  -> key "description"
122    | MQDate         -> key "date"
123    | MQType         -> key "type"
124    | MQFormat       -> key "format"
125    | MQIdentifier   -> key "identifier"
126    | MQLanguage     -> key "language"
127    | MQRelation     -> key "relation"
128    | MQSource       -> key "source"
129    | MQCoverage     -> key "coverage"
130    | MQRights       -> key "rights"
131    | MQInstitution  -> key "institution"
132    | MQContact      -> key "contact"
133    | MQFirstVersion -> key "firstversion"
134    | MQModified     -> key "modified"
135
136 let out_str = function
137    | MQCons s      -> str s
138    | MQSRVar s     -> out_rvar s
139    | MQSSVar s     -> out_svar s
140    | MQFunc (f, r) -> out_func f ^ out_rvar r
141    | MQMConclusion -> key "mainconclusion" 
142    | MQConclusion  -> key "inconclusion" 
143
144 let rec out_bool = function
145    | MQTrue -> key "true"
146    | MQFalse -> key "false"
147    | MQIs (s, t) -> out_str s ^ sub "is" ^ out_str t
148    | MQNot b -> key "not" ^ out_bool b 
149    | MQAnd (b1, b2) -> sep "(" ^ out_bool b1 ^ sub "and" ^ out_bool b2 ^ sep ")"
150    | MQOr (b1, b2) -> sep "(" ^ out_bool b1 ^ sub "or" ^ out_bool b2 ^ sep ")"
151    | MQSubset (l1, l2) -> sep "(" ^ out_list l1 ^ sub "subset" ^ out_list l2 ^ sep ")"
152    | MQSetEqual (l1, l2) -> sep "(" ^ out_list l1 ^ sub "setequal" ^ out_list l2 ^ sep ")"
153
154 and out_list = function
155    | MQSelect (r, l, b) -> 
156       key "select" ^ out_rvar r ^ sub "in" ^ out_list l ^ sub "where" ^ out_bool b
157    | MQUse (l, v) -> key "use" ^ out_list l ^ sub "position" ^ out_svar v
158    | MQUsedBy (l, v) -> key "usedby" ^ out_list l ^ sub "position" ^ out_svar v
159    | MQPattern p -> key "pattern" ^ out_pat p
160    | MQUnion (l1, l2) -> sep "(" ^ out_list l1 ^ sub "union" ^ out_list l2 ^ sep ")"
161    | MQIntersect (l1, l2) -> sep "(" ^ out_list l1 ^ sub "intersect" ^ out_list l2 ^ sep ")"
162    | MQDiff (l1, l2) -> sep "(" ^ out_list l1 ^ sub "diff" ^ out_list l2 ^ sep ")"
163    | MQLRVar s -> out_rvar s
164    | MQSortedBy (l, o, f) -> sep "(" ^ out_list l ^ sub "sortedby" ^ out_func f ^ out_order o ^ sep ")"
165
166 let out_query = function
167    | MQList l -> out_list l
168
169 (* HTML representation of a query result *)
170
171 let rec out_list = function 
172    | []     -> ""
173    | u :: l -> res u ^ nl () ^ out_list l 
174
175 let out_result qr =
176    par () ^ "Result:" ^ nl () ^
177    match qr with
178       | MQRefs l -> out_list l
179
180 (* Converting functions *)
181
182 let tref_uref u =
183    let s = str_uref u in
184    MQueryTParser.ref MQueryTLexer.rtoken (Lexing.from_string s) 
185
186 let parse_text ch =
187    let lexbuf = Lexing.from_channel ch in
188    MQueryTParser.query MQueryTLexer.qtoken lexbuf