]> matita.cs.unibo.it Git - helm.git/blob - helm/ocaml/getter/http_getter.ml
do not .body/.types/.proof_tree files from ls output
[helm.git] / helm / ocaml / getter / http_getter.ml
1 (* Copyright (C) 2005, 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://helm.cs.unibo.it/
24  *)
25
26 open Printf
27
28 open Http_getter_common
29 open Http_getter_misc
30 open Http_getter_types
31
32 exception Not_implemented of string
33 exception UnexpectedGetterOutput
34
35 type resolve_result =
36   | Unknown
37   | Exception of exn
38   | Resolved of string
39
40 type logger_callback = HelmLogger.html_tag -> unit
41
42 let stdout_logger tag = print_string (HelmLogger.string_of_html_tag tag)
43
44 let not_implemented s = raise (Not_implemented ("Http_getter." ^ s))
45
46 let index_line_sep_RE     = Pcre.regexp "[ \t]+"
47 let index_sep_RE          = Pcre.regexp "\r\n|\r|\n"
48 let trailing_types_RE     = Pcre.regexp "\\.types$"
49 let heading_cic_RE        = Pcre.regexp "^cic:"
50 let heading_theory_RE     = Pcre.regexp "^theory:"
51 let heading_nuprl_RE      = Pcre.regexp "^nuprl:"
52 let types_RE              = Pcre.regexp "\\.types$"
53 let types_ann_RE          = Pcre.regexp "\\.types\\.ann$"
54 let body_RE               = Pcre.regexp "\\.body$"
55 let body_ann_RE           = Pcre.regexp "\\.body\\.ann$"
56 let proof_tree_RE         = Pcre.regexp "\\.proof_tree$"
57 let proof_tree_ann_RE     = Pcre.regexp "\\.proof_tree\\.ann$"
58 let theory_RE             = Pcre.regexp "\\.theory$"
59 let basepart_RE           = Pcre.regexp
60   "^([^.]*\\.[^.]*)((\\.body)|(\\.proof_tree)|(\\.types))?(\\.ann)?$"
61 let slash_RE              = Pcre.regexp "/"
62 let pipe_RE               = Pcre.regexp "\\|"
63 let til_slash_RE          = Pcre.regexp "^.*/"
64 let no_slashes_RE         = Pcre.regexp "^[^/]*$"
65 let fix_regexp_RE         = Pcre.regexp ("^" ^ (Pcre.quote "(cic|theory)"))
66 let showable_file_RE      =
67   Pcre.regexp "(\\.con|\\.ind|\\.var|\\.body|\\.types|\\.proof_tree)$"
68
69 let xml_suffix = ".xml"
70 let theory_suffix = ".theory" ^ xml_suffix
71
72   (* global maps, shared by all threads *)
73
74 let ends_with_slash s =
75   try
76     s.[String.length s - 1] = '/'
77   with Invalid_argument _ -> false
78
79   (* should we use a remote getter or not *)
80 let remote () =
81   try
82     Helm_registry.get "getter.mode" = "remote"
83   with Helm_registry.Key_not_found _ -> false
84
85 let getter_url () = Helm_registry.get "getter.url"
86
87 (* Remote interface: getter methods implemented using a remote getter *)
88
89   (* <TODO> *)
90 let getxml_remote uri = not_implemented "getxml_remote"
91 let getxslt_remote ~patch_dtd uri = not_implemented "getxslt_remote"
92 let getdtd_remote uri = not_implemented "getdtd_remote"
93 let clean_cache_remote () = not_implemented "clean_cache_remote"
94 let list_servers_remote () = not_implemented "list_servers_remote"
95 let add_server_remote ~logger ~position name =
96   not_implemented "add_server_remote"
97 let remove_server_remote ~logger position =
98   not_implemented "remove_server_remote"
99 let getalluris_remote () = not_implemented "getalluris_remote"
100 let ls_remote lsuri = not_implemented "ls_remote"
101 let exists_remote uri = not_implemented "exists_remote"
102   (* </TODO> *)
103
104 let resolve_remote uri =
105   (* deliver resolve request to http_getter *)
106   let doc =
107     Http_getter_wget.get (sprintf "%sresolve?uri=%s" (getter_url ()) uri)
108   in
109   let res = ref Unknown in
110   let start_element tag attrs =
111     match tag with
112     | "url" ->
113         (try
114           res := Resolved (List.assoc "value" attrs)
115         with Not_found -> ())
116     | "unresolvable" -> res := Exception (Unresolvable_URI uri)
117     | "not_found" -> res := Exception (Key_not_found uri)
118     | _ -> ()
119   in
120   let callbacks = {
121     XmlPushParser.default_callbacks with
122       XmlPushParser.start_element = Some start_element
123   } in
124   let xml_parser = XmlPushParser.create_parser callbacks in
125   XmlPushParser.parse xml_parser (`String doc);
126   XmlPushParser.final xml_parser;
127   match !res with
128   | Unknown -> raise UnexpectedGetterOutput
129   | Exception e -> raise e
130   | Resolved url -> url
131
132 (* API *)
133
134 let help () = Http_getter_const.usage_string (Http_getter_env.env_to_string ())
135
136 let exists uri =
137   if remote () then
138     exists_remote uri
139   else
140     Http_getter_storage.exists (uri ^ xml_suffix)
141         
142 let resolve uri =
143   if remote () then
144     resolve_remote uri
145   else
146     try
147       Http_getter_storage.resolve (uri ^ xml_suffix)
148     with Http_getter_storage.Resource_not_found _ -> raise (Key_not_found uri)
149
150 let getxml uri =
151   if remote () then
152     getxml_remote uri
153   else begin
154     try
155       Http_getter_storage.filename (uri ^ xml_suffix)
156     with Http_getter_storage.Resource_not_found _ -> raise (Key_not_found uri)
157   end
158
159 let getxslt uri = assert false
160 (* let getxslt ?(patch_dtd = true) uri =
161   if remote () then
162     getxslt_remote ~patch_dtd uri
163   else begin
164     let url = resolve uri in
165     let (fname, outchan) = temp_file_of_uri uri in
166     Http_getter_cache.respond_xsl ~via_http:false ~url ~patch:patch_dtd outchan;
167     close_out outchan;
168     fname
169   end *)
170
171 let getdtd uri =
172   if remote () then
173     getdtd_remote uri
174   else begin
175     let fname = Lazy.force Http_getter_env.dtd_dir ^ "/" ^ uri in
176     if not (Sys.file_exists fname) then raise (Dtd_not_found uri);
177     fname
178   end
179
180 let clean_cache () =
181   if remote () then
182     clean_cache_remote ()
183   else
184     Http_getter_storage.clean_cache ()
185
186 let (++) (oldann, oldtypes, oldbody, oldtree)
187          (newann, newtypes, newbody, newtree) =
188   ((if newann   > oldann    then newann   else oldann),
189    (if newtypes > oldtypes  then newtypes else oldtypes),
190    (if newbody  > oldbody   then newbody  else oldbody),
191    (if newtree  > oldtree   then newtree  else oldtree))
192     
193 let store_obj tbl o =
194 (*   prerr_endline ("Http_getter.store_obj " ^ o); *)
195   if Pcre.pmatch ~rex:showable_file_RE o then begin
196     let basepart = Pcre.replace ~rex:basepart_RE ~templ:"$1" o in
197     let no_flags = false, No, No, No in
198     let oldflags =
199       try
200         Hashtbl.find tbl basepart
201       with Not_found -> (* no ann, no types, no body, no proof tree *)
202         no_flags
203     in
204     let newflags =
205       match o with
206       | s when Pcre.pmatch ~rex:types_RE s          -> (false, Yes, No, No)
207       | s when Pcre.pmatch ~rex:types_ann_RE s      -> (true,  Ann, No, No)
208       | s when Pcre.pmatch ~rex:body_RE s           -> (false, No, Yes, No)
209       | s when Pcre.pmatch ~rex:body_ann_RE s       -> (true,  No, Ann, No)
210       | s when Pcre.pmatch ~rex:proof_tree_RE s     -> (false, No, No, Yes)
211       | s when Pcre.pmatch ~rex:proof_tree_ann_RE s -> (true,  No, No, Ann)
212       | s -> no_flags
213     in
214     Hashtbl.replace tbl basepart (oldflags ++ newflags)
215   end
216   
217 let store_dir set_ref d =
218   set_ref := StringSet.add (List.hd (Pcre.split ~rex:slash_RE d)) !set_ref
219
220 let collect_ls_items dirs_set objs_tbl =
221   let items = ref [] in
222   StringSet.iter (fun dir -> items := Ls_section dir :: !items) dirs_set;
223   Http_getter_misc.hashtbl_sorted_iter
224     (fun uri (annflag, typesflag, bodyflag, treeflag) ->
225       items :=
226         Ls_object {
227           uri = uri; ann = annflag;
228           types = typesflag; body = bodyflag; proof_tree = treeflag
229         } :: !items)
230     objs_tbl;
231   List.rev !items
232
233   (** non regexp-aware version of ls *)
234 let dumb_ls uri_prefix =
235 (*   prerr_endline ("Http_getter.dumb_ls " ^ uri_prefix); *)
236   if is_cic_obj_uri uri_prefix then begin
237     let dirs = ref StringSet.empty in
238     let objs = Hashtbl.create 17 in
239     List.iter
240       (fun fname ->
241         if ends_with_slash fname then
242           store_dir dirs fname
243         else
244           try
245             store_obj objs (strip_suffix ~suffix:xml_suffix fname)
246           with Invalid_argument _ -> ())
247       (Http_getter_storage.ls uri_prefix);
248     collect_ls_items !dirs objs
249   end else if is_theory_uri uri_prefix then begin
250     let items = ref [] in
251     List.iter
252       (fun fname ->
253         if ends_with_slash fname then
254           items := Ls_section (strip_trailing_slash fname) :: !items
255         else
256           try
257             let obj =
258               { uri = strip_suffix theory_suffix fname;
259                 ann = false; types = No; body = No; proof_tree = No }
260             in
261             items := Ls_object obj :: !items
262           with Invalid_argument _ -> ())
263       (Http_getter_storage.ls uri_prefix);
264     !items
265   end else
266     raise (Invalid_URI uri_prefix)
267
268   (* handle simple regular expressions of the form "...(..|..|..)..." on cic
269    * uris, not meant to be a real implementation of regexp. The only we use is
270    * "(cic|theory):/..." *)
271 let explode_ls_regexp regexp =
272   try
273     let len = String.length regexp in
274     let lparen_idx = String.index regexp '(' in
275     let rparen_idx = String.index_from regexp lparen_idx ')' in
276     let choices_str = (* substring between parens, parens excluded *)
277       String.sub regexp (lparen_idx + 1) (rparen_idx - lparen_idx - 1)
278     in
279     let choices = Pcre.split ~rex:pipe_RE choices_str in
280     let prefix = String.sub regexp 0 lparen_idx in
281     let suffix = String.sub regexp (rparen_idx + 1) (len - (rparen_idx + 1)) in
282     List.map (fun choice -> prefix ^ choice ^ suffix) choices
283   with Not_found -> [regexp]
284
285 let merge_results results =
286   let rec aux objects_acc dirs_acc = function
287     | [] -> dirs_acc @ objects_acc
288     | Ls_object _ as obj :: tl -> aux (obj :: objects_acc) dirs_acc tl
289     | Ls_section _ as dir :: tl ->
290         if List.mem dir dirs_acc then (* filters out dir duplicates *)
291           aux objects_acc dirs_acc tl
292         else
293           aux objects_acc (dir :: dirs_acc) tl
294   in
295   aux [] [] (List.concat results)
296
297 let ls regexp =
298   if remote () then
299     ls_remote regexp
300   else
301     let prefixes = explode_ls_regexp regexp in
302     merge_results (List.map dumb_ls prefixes)
303
304 let getalluris () =
305   let rec aux acc = function
306     | [] -> acc
307     | dir :: todo ->
308         let acc', todo' =
309           List.fold_left
310             (fun (acc, subdirs) result ->
311               match result with
312               | Ls_object obj -> (dir ^ obj.uri) :: acc, subdirs
313               | Ls_section sect -> acc, (dir ^ sect ^ "/") :: subdirs)
314             (acc, todo)
315             (dumb_ls dir)
316         in
317         aux acc' todo'
318   in
319   aux [] ["cic:/"] (* trailing slash required *)
320
321 (* Shorthands from now on *)
322
323 let getxml' uri = getxml (UriManager.string_of_uri uri)
324 let resolve' uri = resolve (UriManager.string_of_uri uri)
325 let exists' uri = exists (UriManager.string_of_uri uri)
326
327 let init () =
328   Http_getter_logger.set_log_level
329     (Helm_registry.get_opt_default Helm_registry.int ~default:1
330       "getter.log_level");
331   Http_getter_logger.set_log_file
332     (Helm_registry.get_opt Helm_registry.string "getter.log_file")
333