]> matita.cs.unibo.it Git - helm.git/blob - helm/ocaml/urimanager/uriManager.ml
many strings that are supposed to be URIs are now UriManager.uri
[helm.git] / helm / ocaml / urimanager / uriManager.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 * "cic:/a/b/c.con" => [| "cic:/a" ; "cic:/a/b" ; "cic:/a/b/c.con" ; "c"; "" |]
28 * "cic:/a/b/c.ind#xpointer(1/1)" =>
29 *   [| "cic:/a" ; "cic:/a/b" ; "cic:/a/b/c.con" ; "c"; "#xpointer(1/1)" |]
30 * "cic:/a/b/c.ind#xpointer(1/1/1)" =>
31 *   [| "cic:/a" ; "cic:/a/b" ; "cic:/a/b/c.con" ; "c"; "#xpointer(1/1/1)" |]
32 *)
33
34 let fresh_id =
35  let id = ref 0 in
36   function () ->
37     incr id;
38     !id
39
40 type uri = string array * int;;
41
42 let eq uri1 uri2 =
43   uri1 == uri2 
44 ;;
45
46 let string_of_uri (uri,_) =
47   match  uri.(Array.length uri - 1) with
48   | "" -> 
49       uri.(Array.length uri - 3)
50   | _ -> 
51       String.concat "#" 
52         [ uri.(Array.length uri - 3); uri.(Array.length uri - 1) ]
53
54 let name_of_uri (uri,_) = uri.(Array.length uri - 2);;
55 let buri_of_uri (uri,_) = uri.(Array.length uri - 4);;
56 let depth_of_uri (uri,_) = Array.length uri - 3;;
57
58 module OrderedStrings =
59  struct
60   type t = string
61   let compare (s1 : t) (s2 : t) = compare s1 s2
62  end
63 ;;
64
65 module SetOfStrings = Map.Make(OrderedStrings);;
66
67 (*CSC: commento obsoleto ed errato *)
68 (* Invariant: the map is the identity function,      *)
69 (*  i.e. (SetOfStrings.find str !set_of_uri) == str  *)
70 let set_of_uri = ref SetOfStrings.empty;;
71 let set_of_prefixes = ref SetOfStrings.empty;;
72
73  
74 (* hash conses an uri *)
75 let add_to_uriset ?suri uri =
76   let lookup_suri suri =
77     try
78       SetOfStrings.find suri !set_of_uri
79     with Not_found -> assert false
80   in
81   let suri = 
82     match suri with 
83     | None -> string_of_uri uri
84     | Some suri -> suri 
85   in
86   if not(SetOfStrings.mem suri !set_of_uri) then
87     set_of_uri := SetOfStrings.add suri uri !set_of_uri;
88   lookup_suri suri  
89     
90
91 (* similar to uri_of_string, but used for prefixes of uris *)
92 let normalize prefix =
93  try
94   SetOfStrings.find prefix !set_of_prefixes
95  with
96   Not_found ->
97    set_of_prefixes := SetOfStrings.add prefix prefix !set_of_prefixes ;
98    prefix
99 ;;
100
101 exception IllFormedUri of string;;
102
103 let mk_prefixes str xpointer =
104  let rec aux curi =
105   function
106      [he] ->
107       let prefix_uri = curi ^ "/" ^ he
108       and name = List.hd (Str.split (Str.regexp "\\.") he) in
109        [ normalize prefix_uri ; name ]
110    | he::tl ->
111       let prefix_uri = curi ^ "/" ^ he in
112        (normalize prefix_uri)::(aux prefix_uri tl)
113    | _ -> raise (IllFormedUri str)
114  in
115   let tokens = (Str.split (Str.regexp "/") str) in
116    (* ty = "cic:" *)
117    let (ty, sp) =
118     (try (List.hd tokens, List.tl tokens)
119      with Failure "hd" | Failure "tl" ->
120       raise (IllFormedUri str))
121     in
122     (aux ty sp) @ [xpointer]
123 ;;
124
125
126 let sharp_rex = 
127   Str.regexp "#"
128 ;;
129
130 let uri_of_string str =
131   let base, xpointer =
132     match Str.split sharp_rex str with
133     | [base] -> base,""
134     | [base; xpointer] -> base,xpointer 
135     | _ -> raise (IllFormedUri str)
136   in
137    try
138     SetOfStrings.find str !set_of_uri
139    with
140     Not_found ->
141       let uri = Array.of_list (mk_prefixes base xpointer), fresh_id () in
142       add_to_uriset ~suri:str uri
143 ;;
144
145 let strip_xpointer (uri,_) =
146   let stripped_uri = Array.copy uri in
147   stripped_uri.(Array.length uri - 1) <- "";  (* reset xpointer field *)
148   let new_uri = stripped_uri,fresh_id () in
149   let suri = string_of_uri new_uri in
150   add_to_uriset ~suri new_uri
151
152   
153 let cicuri_of_uri uri =
154  let completeuri = string_of_uri uri in
155   let newcompleteuri = 
156    (Str.replace_first (Str.regexp "\\.types$") ""
157     (Str.replace_first (Str.regexp "\\.ann$") "" completeuri))
158   in
159    if completeuri = newcompleteuri then
160     uri
161    else
162     let uri = fst uri in
163     let newuri = Array.copy uri in
164      newuri.(Array.length uri - 3) <- newcompleteuri ;
165      add_to_uriset (newuri,fresh_id ())
166 ;;
167
168 let annuri_of_uri uri =
169  let completeuri = string_of_uri uri in
170   if Str.string_match (Str.regexp ".*\\.ann$") completeuri 0 then
171    uri
172   else
173    let uri = fst uri in
174    let newuri = Array.copy uri in
175     newuri.(Array.length uri - 3) <- completeuri ^ ".ann" ;
176     add_to_uriset (newuri,fresh_id ())
177 ;;
178
179 let uri_is_annuri uri =
180  Str.string_match (Str.regexp ".*\\.ann$") (string_of_uri uri) 0
181 ;;
182
183 let bodyuri_of_uri uri =
184  let struri = string_of_uri uri in
185   if Str.string_match (Str.regexp ".*\\.con$") (string_of_uri uri) 0 then
186    let uri = fst uri in
187    let newuri = Array.copy uri in
188     newuri.(Array.length uri - 3) <- struri ^ ".body" ;
189     Some (add_to_uriset (newuri,fresh_id ()))
190   else
191    None
192 ;;
193
194 let innertypesuri_of_uri uri =
195  let cicuri = cicuri_of_uri uri in
196   let newuri = Array.copy (fst cicuri) in
197    newuri.(Array.length (fst cicuri) - 3) <- (string_of_uri cicuri) ^ ".types" ;
198    add_to_uriset (newuri,fresh_id ())
199 ;;
200
201 type uriref = uri * (int list)
202
203 let string_of_uriref (uri, fi) =
204    let str = string_of_uri uri in
205    let xp t = "#xpointer(1/" ^ string_of_int (t + 1) in
206    match fi with
207       | []          -> str 
208       | [t]         -> str ^ xp t ^ ")" 
209       | t :: c :: _ -> str ^ xp t ^ "/" ^ string_of_int c ^ ")" 
210
211 let compare (_,id1) (_,id2) = id1 - id2
212
213 module OrderedUri =
214 struct
215   type t = uri
216   let compare = compare (* the one above, not Pervasives.compare *)
217 end
218
219 module UriSet = Set.Make (OrderedUri)
220