]> matita.cs.unibo.it Git - helm.git/blob - helm/ocaml/cic_notation/cicNotationPres.ml
added homepage URL, now we have one
[helm.git] / helm / ocaml / cic_notation / cicNotationPres.ml
1 (* Copyright (C) 2004-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 module P = Mpresentation
27
28 type mathml_markup = boxml_markup Mpresentation.mpres
29 and boxml_markup = mathml_markup Box.box
30
31 type markup = mathml_markup
32
33 let atop_attributes = [None, "linethickness", "0pt"]
34
35 let to_unicode = Utf8Macro.unicode_of_tex
36
37 let rec make_attributes l1 = function
38   | [] -> []
39   | None :: tl -> make_attributes (List.tl l1) tl
40   | Some s :: tl ->
41       let p,n = List.hd l1 in
42       (p,n,s) :: make_attributes (List.tl l1) tl
43
44 let box_of_mpres =
45   function
46     Mpresentation.Mobject (_, box) -> box
47   | mpres -> Box.Object ([], mpres)
48
49 let mpres_of_box =
50   function
51     Box.Object (_, mpres) -> mpres
52   | box -> Mpresentation.Mobject ([], box)
53
54 let rec genuine_math =
55   function
56   | Mpresentation.Mobject ([], obj) -> not (genuine_box obj)
57   | _ -> true
58 and genuine_box =
59   function
60   | Box.Object ([], mpres) -> not (genuine_math mpres)
61   | _ -> true
62
63 let rec eligible_math =
64   function
65   | Mpresentation.Mobject ([], Box.Object ([], mpres)) -> eligible_math mpres
66   | Mpresentation.Mobject ([], _) -> false
67   | _ -> true
68
69 let rec promote_to_math =
70   function
71   | Mpresentation.Mobject ([], Box.Object ([], mpres)) -> promote_to_math mpres
72   | math -> math
73
74 let small_skip =
75   Mpresentation.Mspace (RenderingAttrs.small_skip_attributes `MathML)
76
77 let box_of mathonly spec attrs children =
78   match children with
79     | [t] -> t
80     | _ ->
81         let kind, spacing, indent = spec in
82         let dress children =
83           if spacing then
84             CicNotationUtil.dress small_skip children
85           else
86             children
87         in
88           if mathonly then Mpresentation.Mrow (attrs, dress children)
89           else
90             let attrs' =
91               (if spacing then RenderingAttrs.spacing_attributes `BoxML else [])
92               @ (if indent then RenderingAttrs.indent_attributes `BoxML else [])
93               @ attrs
94             in
95               match kind with
96                 | CicNotationPt.H ->
97                     if List.for_all eligible_math children then
98                       Mpresentation.Mrow (attrs',
99                         dress (List.map promote_to_math children))
100                     else
101                       mpres_of_box (Box.H (attrs',
102                         List.map box_of_mpres children))
103 (*                 | CicNotationPt.H when List.for_all genuine_math children ->
104                     Mpresentation.Mrow (attrs', dress children) *)
105                 | CicNotationPt.V ->
106                     mpres_of_box (Box.V (attrs',
107                       List.map box_of_mpres children))
108                 | CicNotationPt.HV ->
109                     mpres_of_box (Box.HV (attrs',
110                       List.map box_of_mpres children))
111                 | CicNotationPt.HOV ->
112                     mpres_of_box (Box.HOV (attrs',
113                       List.map box_of_mpres children))
114
115 let open_paren        = Mpresentation.Mo ([], "(")
116 let closed_paren      = Mpresentation.Mo ([], ")")
117 let open_brace        = Mpresentation.Mo ([], "{")
118 let closed_brace      = Mpresentation.Mo ([], "}")
119 let hidden_substs     = Mpresentation.Mtext ([], "{...}")
120 let open_box_paren    = Box.Text ([], "(")
121 let closed_box_paren  = Box.Text ([], ")")
122 let semicolon         = Mpresentation.Mo ([], ";")
123 let toggle_action children =
124   Mpresentation.Maction ([None, "actiontype", "toggle"], children)
125
126 type child_pos = [ `None | `Left | `Right | `Inner ]
127
128 let pp_assoc =
129   function
130   | Gramext.LeftA -> "LeftA"
131   | Gramext.RightA -> "RightA"
132   | Gramext.NonA -> "NonA"
133
134 let pp_pos =
135   function
136       `None -> "`None"
137     | `Left -> "`Left"
138     | `Right -> "`Right"
139     | `Inner -> "`Inner"
140
141 let is_atomic t =
142   let rec aux_mpres = function
143     | P.Mi _
144     | P.Mo _
145     | P.Mn _
146     | P.Ms _
147     | P.Mtext _
148     | P.Mspace _ -> true
149     | P.Mobject (_, box) -> aux_box box
150     | P.Maction (_, [mpres])
151     | P.Mrow (_, [mpres]) -> aux_mpres mpres
152     | _ -> false
153   and aux_box = function
154     | Box.Space _
155     | Box.Ink _
156     | Box.Text _ -> true
157     | Box.Object (_, mpres) -> aux_mpres mpres
158     | Box.H (_, [box])
159     | Box.V (_, [box])
160     | Box.HV (_, [box])
161     | Box.HOV (_, [box])
162     | Box.Action (_, [box]) -> aux_box box
163     | _ -> false
164   in
165   aux_mpres t
166
167 let add_parens child_prec child_assoc child_pos curr_prec t =
168   if is_atomic t then t
169   else if child_prec < curr_prec
170     || (child_prec = curr_prec &&
171         child_assoc = Gramext.LeftA &&
172         child_pos <> `Left)
173     || (child_prec = curr_prec &&
174         child_assoc = Gramext.RightA &&
175         child_pos <> `Right)
176   then  (* parens should be added *)
177     match t with
178     | Mpresentation.Mobject (_, box) ->
179         mpres_of_box (Box.H ([], [ open_box_paren; box; closed_box_paren ]))
180     | mpres -> Mpresentation.Mrow ([], [open_paren; t; closed_paren])
181   else
182     t
183
184 let render ids_to_uris =
185   let module A = CicNotationPt in
186   let module P = Mpresentation in
187   let use_unicode = true in
188   let lookup_uri = function
189     | None -> None
190     | Some id -> (try Some (Hashtbl.find ids_to_uris id) with Not_found -> None)
191   in
192   let make_href xmlattrs xref uris =
193     let xref_uri = lookup_uri xref in
194     let raw_uris = List.map UriManager.string_of_uri uris in
195     let uri =
196       match xref_uri, raw_uris with
197       | None, [] -> None
198       | Some uri, [] -> Some uri
199       | None, raw_uris -> Some (String.concat " " raw_uris)
200       | Some uri, raw_uris -> Some (String.concat " " (uri :: raw_uris))
201     in
202     xmlattrs
203     @ make_attributes [Some "helm", "xref"; Some "xlink", "href"] [xref; uri]
204   in
205   let make_xref xref = make_attributes [Some "helm","xref"] [xref] in
206   (* when mathonly is true no boxes should be generated, only mrows *)
207   let rec aux xmlattrs mathonly xref pos prec uris t =
208     match t with
209     | A.AttributedTerm _ ->
210         aux_attributes xmlattrs mathonly xref pos prec uris t
211     | A.Num (literal, _) ->
212         let attrs =
213           (RenderingAttrs.number_attributes `MathML)
214           @ make_href xmlattrs xref uris
215         in
216         P.Mn (attrs, literal)
217     | A.Symbol (literal, _) ->
218         let attrs =
219           (RenderingAttrs.symbol_attributes `MathML)
220           @ make_href xmlattrs xref uris
221         in
222         P.Mo (attrs, to_unicode literal)
223     | A.Ident (literal, subst)
224     | A.Uri (literal, subst) ->
225         let attrs =
226           (RenderingAttrs.ident_attributes `MathML)
227           @ make_href xmlattrs xref []
228         in
229         let name = P.Mi (attrs, to_unicode literal) in
230         (match subst with
231         | Some []
232         | None -> name
233         | Some substs ->
234             let substs' =
235               box_of mathonly (A.H, false, false) []
236                 (open_brace
237                 :: (CicNotationUtil.dress semicolon
238                     (List.map
239                       (fun (name, t) ->
240                         box_of mathonly (A.H, false, false) [] [
241                           P.Mi ([], name);
242                           P.Mo ([], to_unicode "\\def");
243                           aux [] mathonly xref pos prec uris t ])
244                       substs))
245                 @ [ closed_brace ])
246 (*                 (CicNotationUtil.dress semicolon
247                   (List.map
248                     (fun (var, t) ->
249                       let var_uri = UriManager.uri_of_string var in
250                       let var_name = UriManager.name_of_uri var_uri in
251                       let href_attr = Some "xlink", "href", var in
252                       box_of mathonly (A.H, false, false) [] [
253                         P.Mi ([href_attr], var_name);
254                         P.Mo ([], to_unicode "\\def");
255                         aux [] mathonly xref pos prec uris t ])
256                     substs)) *)
257             in
258             let substs_maction = toggle_action [ hidden_substs; substs' ] in
259             box_of mathonly (A.H, false, false) [] [ name; substs_maction ])
260     | A.Literal l -> aux_literal xmlattrs xref prec uris l
261     | A.UserInput -> P.Mtext ([], "%")
262     | A.Layout l -> aux_layout mathonly xref pos prec uris l
263     | A.Magic _
264     | A.Variable _ -> assert false  (* should have been instantiated *)
265     | t ->
266         prerr_endline ("unexpected ast: " ^ CicNotationPp.pp_term t);
267         assert false
268   and aux_attributes xmlattrs mathonly xref pos prec uris t =
269     let new_level = ref None in
270     let new_xref = ref None in
271     let new_uris = ref [] in
272     let new_xmlattrs = ref [] in
273     let rec aux_attribute =
274       function
275       | A.AttributedTerm (attr, t) ->
276           (match attr with
277           | `Loc _
278           | `Raw _ -> ()
279           | `Level (child_prec, child_assoc) ->
280               new_level := Some (child_prec, child_assoc)
281           | `IdRef xref -> new_xref := Some xref
282           | `Href hrefs -> new_uris := hrefs
283           | `XmlAttrs attrs -> new_xmlattrs := attrs);
284           aux_attribute t
285       | t ->
286           (match !new_level with
287           | None -> aux !new_xmlattrs mathonly !new_xref pos prec !new_uris t
288           | Some (child_prec, child_assoc) ->
289               let t' = 
290                 aux !new_xmlattrs mathonly !new_xref pos child_prec !new_uris t
291               in
292               add_parens child_prec child_assoc pos prec t')
293     in
294     aux_attribute t
295 (*     function
296     | `Loc _
297     | `Raw _ -> aux xmlattrs mathonly xref pos prec uris t
298     | `Level (child_prec, child_assoc) ->
299         let t' = aux xmlattrs mathonly xref pos child_prec uris t in
300         add_parens child_prec child_assoc pos prec t'
301     | `IdRef xref -> aux xmlattrs mathonly (Some xref) pos prec uris t
302     | `Href uris' -> aux xmlattrs mathonly xref pos prec uris' t
303     | `XmlAttrs xmlattrs -> aux xmlattrs mathonly xref pos prec uris t *)
304   and aux_literal xmlattrs xref prec uris l =
305     let attrs = make_href xmlattrs xref uris in
306     (match l with
307     | `Symbol s -> P.Mo (attrs, to_unicode s)
308     | `Keyword s -> P.Mo (attrs, to_unicode s)
309     | `Number s  -> P.Mn (attrs, to_unicode s))
310   and aux_layout mathonly xref pos prec uris l =
311     let attrs = make_xref xref in
312     let invoke' t = aux [] true None pos prec uris t in
313     match l with
314     | A.Sub (t1, t2) -> P.Msub (attrs, invoke' t1, invoke' t2)
315     | A.Sup (t1, t2) -> P.Msup (attrs, invoke' t1, invoke' t2)
316     | A.Below (t1, t2) -> P.Munder (attrs, invoke' t1, invoke' t2)
317     | A.Above (t1, t2) -> P.Mover (attrs, invoke' t1, invoke' t2)
318     | A.Frac (t1, t2)
319     | A.Over (t1, t2) -> P.Mfrac (attrs, invoke' t1, invoke' t2)
320     | A.Atop (t1, t2) ->
321         P.Mfrac (atop_attributes @ attrs, invoke' t1, invoke' t2)
322     | A.Sqrt t -> P.Msqrt (attrs, invoke' t)
323     | A.Root (t1, t2) -> P.Mroot (attrs, invoke' t1, invoke' t2)
324     | A.Box ((_, spacing, _) as kind, terms) ->
325         let children =
326           aux_children mathonly spacing xref pos prec uris
327             (CicNotationUtil.ungroup terms)
328         in
329         box_of mathonly kind attrs children
330     | A.Group terms ->
331         let children =
332           aux_children mathonly false xref pos prec uris
333             (CicNotationUtil.ungroup terms)
334         in
335         box_of mathonly (A.H, false, false) attrs children
336     | A.Break -> assert false (* TODO? *)
337   and aux_children mathonly spacing xref pos prec uris terms =
338     let find_clusters =
339       let rec aux_list first clusters acc =
340         function
341             [] when acc = [] -> List.rev clusters
342           | [] -> aux_list first (List.rev acc :: clusters) [] []
343           | (A.Layout A.Break) :: tl when acc = [] ->
344               aux_list first clusters [] tl
345           | (A.Layout A.Break) :: tl ->
346               aux_list first (List.rev acc :: clusters) [] tl
347           | [hd] ->
348               let pos' = 
349                 if first then
350                   pos
351                 else
352                   match pos with
353                       `None -> `Right
354                     | `Inner -> `Inner
355                     | `Right -> `Right
356                     | `Left -> `Inner
357               in
358                 aux_list false clusters
359                   (aux [] mathonly xref pos' prec uris hd :: acc) []
360           | hd :: tl ->
361               let pos' =
362                 match pos, first with
363                     `None, true -> `Left
364                   | `None, false -> `Inner
365                   | `Left, true -> `Left
366                   | `Left, false -> `Inner
367                   | `Right, _ -> `Inner
368                   | `Inner, _ -> `Inner
369               in
370                 aux_list false clusters
371                   (aux [] mathonly xref pos' prec uris hd :: acc) tl
372       in
373         aux_list true [] []
374     in
375     let boxify_pres =
376       function
377           [t] -> t
378         | tl -> box_of mathonly (A.H, spacing, false) [] tl
379     in
380       List.map boxify_pres (find_clusters terms)
381   in
382   aux [] false None `None 0 []
383
384 let rec print_box (t: CicNotationPres.boxml_markup) =
385   Box.box2xml print_mpres t
386 and print_mpres (t: CicNotationPres.mathml_markup) =
387   Mpresentation.print_mpres print_box t
388
389 let print_xml = print_mpres
390
391 (* let render_to_boxml id_to_uri t =
392   let xml_stream = print_box (box_of_mpres (render id_to_uri t)) in
393   Xml.add_xml_declaration xml_stream *)
394