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