]> matita.cs.unibo.it Git - helm.git/blob - helm/ocaml/cic_notation/cicNotationPres.ml
snapshot, notably:
[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 let binder_attributes = [None, "mathcolor", "blue"]
33 let indent_attributes = [None, "indent", "1em"]
34 let keyword_attributes = [None, "mathcolor", "blue"]
35
36 let to_unicode s =
37   try
38     if s.[0] = '\\' then
39       Utf8Macro.expand (String.sub s 1 (String.length s - 1))
40     else s
41   with Utf8Macro.Macro_not_found _ -> s
42
43 let rec make_attributes l1 = function
44   | [] -> []
45   | None :: tl -> make_attributes (List.tl l1) tl
46   | Some s :: tl ->
47       let p,n = List.hd l1 in
48       (p,n,s) :: make_attributes (List.tl l1) tl
49
50 let box_of_mpres =
51   function
52     Mpresentation.Mobject (_, box) -> box
53   | mpres -> Box.Object ([], mpres)
54
55 let mpres_of_box =
56   function
57     Box.Object (_, mpres) -> mpres
58   | box -> Mpresentation.Mobject ([], box)
59
60 let genuine_math =
61   function
62   | Mpresentation.Mobject _ -> false
63   | _ -> true
64
65 let box_of mathonly spec attrs children =
66   match children with
67     | [t] -> t
68     | _ ->
69         let kind, spacing, indent = spec in
70         let dress children =
71           if spacing then
72             CicNotationUtil.dress (Mpresentation.Mtext ([], " ")) children
73           else
74             children
75         in
76           if mathonly then Mpresentation.Mrow (attrs, dress children)
77           else
78             let attrs' =
79               (if spacing then [None, "spacing", "0.5em"] else [])
80                 @ (if indent then [None, "indent", "0em 0.5em"] else [])
81                   @ attrs
82             in
83               match kind with
84                 | CicNotationPt.H when List.for_all genuine_math children ->
85                     Mpresentation.Mrow (attrs', dress children)
86                 | CicNotationPt.H ->
87                     mpres_of_box (Box.H (attrs', List.map box_of_mpres children))
88                 | CicNotationPt.V ->
89                     mpres_of_box (Box.V (attrs', List.map box_of_mpres children))
90                 | CicNotationPt.HV ->
91                     mpres_of_box (Box.HV (attrs', List.map box_of_mpres children))
92                 | CicNotationPt.HOV ->
93                     mpres_of_box (Box.HOV (attrs', List.map box_of_mpres children))
94
95 let open_paren   = Mpresentation.Mo ([], "(")
96 let closed_paren = Mpresentation.Mo ([], ")")
97 let open_box_paren = Box.Text ([], "(")
98 let closed_box_paren = Box.Text ([], ")")
99
100 type child_pos = [ `None | `Left | `Right | `Inner ]
101
102 let pp_assoc =
103   function
104   | Gramext.LeftA -> "LeftA"
105   | Gramext.RightA -> "RightA"
106   | Gramext.NonA -> "NonA"
107
108 let pp_pos =
109   function
110       `None -> "`None"
111     | `Left -> "`Left"
112     | `Right -> "`Right"
113     | `Inner -> "`Inner"
114
115 let is_atomic t =
116   let module P = Mpresentation in
117   let rec aux_mpres = function
118     | P.Mi _
119     | P.Mo _
120     | P.Mn _
121     | P.Ms _
122     | P.Mtext _
123     | P.Mspace _ -> true
124     | P.Mobject (_, box) -> aux_box box
125     | P.Maction (_, [mpres])
126     | P.Mrow (_, [mpres]) -> aux_mpres mpres
127     | _ -> false
128   and aux_box = function
129     | Box.Space _
130     | Box.Ink _
131     | Box.Text _ -> true
132     | Box.Object (_, mpres) -> aux_mpres mpres
133     | Box.H (_, [box])
134     | Box.V (_, [box])
135     | Box.HV (_, [box])
136     | Box.HOV (_, [box])
137     | Box.Action (_, [box]) -> aux_box box
138     | _ -> false
139   in
140   aux_mpres t
141
142 let add_parens child_prec child_assoc child_pos curr_prec t =
143 (*  prerr_endline (Printf.sprintf "add_parens %d %s %s %d" child_prec
144     (pp_assoc child_assoc) (pp_pos child_pos) (curr_prec)); *)
145   if is_atomic t then t
146   else if child_prec < curr_prec
147     || (child_prec = curr_prec &&
148         child_assoc = Gramext.LeftA &&
149         child_pos <> `Left)
150     || (child_prec = curr_prec &&
151         child_assoc = Gramext.RightA &&
152         child_pos <> `Right)
153   then  (* parens should be added *)
154     match t with
155     | Mpresentation.Mobject (_, box) ->
156         mpres_of_box (Box.H ([], [ open_box_paren; box; closed_box_paren ]))
157     | mpres -> Mpresentation.Mrow ([], [open_paren; t; closed_paren])
158   else
159     t
160
161 let render ids_to_uris =
162   let module A = CicNotationPt in
163   let module P = Mpresentation in
164   let use_unicode = true in
165   let lookup_uri = function
166     | None -> None
167     | Some id -> (try Some (Hashtbl.find ids_to_uris id) with Not_found -> None)
168   in
169   let make_href xmlattrs xref uris =
170     let xref_uri = lookup_uri xref in
171     let raw_uris = List.map UriManager.string_of_uri uris in
172     let uri =
173       match xref_uri, raw_uris with
174       | None, [] -> None
175       | Some uri, [] -> Some uri
176       | None, raw_uris -> Some (String.concat " " raw_uris)
177       | Some uri, raw_uris -> Some (String.concat " " (uri :: raw_uris))
178     in
179     xmlattrs
180     @ make_attributes [Some "helm", "xref"; Some "xlink", "href"] [xref; uri]
181   in
182   let make_xref xref = make_attributes [Some "helm","xref"] [xref] in
183   let make_box = function
184     | P.Mobject (attrs, box) ->
185         assert (attrs = []);
186         box
187     | m -> Box.Object ([], m)
188   in
189   (* when mathonly is true no boxes should be generated, only mrows *)
190   let rec aux xmlattrs mathonly xref pos prec uris t =
191     match t with
192     | A.AttributedTerm (attr, t) ->
193         aux_attribute xmlattrs mathonly xref pos prec uris t attr
194     | A.Ident (literal, _) ->
195         P.Mi (make_href xmlattrs xref [], to_unicode literal)
196     | A.Num (literal, _) ->
197         P.Mn (make_href xmlattrs xref [], to_unicode literal)
198     | A.Symbol (literal, _) ->
199         P.Mo (make_href xmlattrs xref uris, to_unicode literal)
200     | A.Uri (literal, _) ->
201         P.Mi (make_href xmlattrs xref [], to_unicode literal)
202     | A.Literal l -> aux_literal xmlattrs xref prec uris l
203     | A.Layout l -> aux_layout mathonly xref pos prec uris l
204     | A.Magic _
205     | A.Variable _ -> assert false  (* should have been instantiated *)
206     | t ->
207         prerr_endline (CicNotationPp.pp_term t);
208         assert false
209   and aux_attribute xmlattrs mathonly xref pos prec uris t =
210     function
211     | `Loc _ -> aux xmlattrs mathonly xref pos prec uris t
212     | `Level (child_prec, child_assoc) ->
213         let t' = aux xmlattrs mathonly xref pos child_prec uris t in
214         add_parens child_prec child_assoc pos prec t'
215     | `IdRef xref -> aux xmlattrs mathonly (Some xref) pos prec uris t
216     | `Href uris' -> aux xmlattrs mathonly xref pos prec uris' t
217     | `XmlAttrs xmlattrs -> aux xmlattrs mathonly xref pos prec uris t
218   and aux_literal xmlattrs xref prec uris l =
219     let attrs = make_href xmlattrs xref uris in
220       match l with
221         | `Symbol s -> P.Mo (attrs, to_unicode s)
222         | `Keyword s -> P.Mo (attrs, to_unicode s)
223         | `Number s  -> P.Mn (attrs, to_unicode s)
224   and aux_layout mathonly xref pos prec uris l =
225     let attrs = make_xref xref in
226     let invoke' t = aux [] true None pos prec uris t in
227     match l with
228     | A.Sub (t1, t2) -> P.Msub (attrs, invoke' t1, invoke' t2)
229     | A.Sup (t1, t2) -> P.Msup (attrs, invoke' t1, invoke' t2)
230     | A.Below (t1, t2) -> P.Munder (attrs, invoke' t1, invoke' t2)
231     | A.Above (t1, t2) -> P.Mover (attrs, invoke' t1, invoke' t2)
232     | A.Frac (t1, t2)
233     | A.Over (t1, t2) -> P.Mfrac (attrs, invoke' t1, invoke' t2)
234     | A.Atop (t1, t2) ->
235         P.Mfrac (atop_attributes @ attrs, invoke' t1, invoke' t2)
236     | A.Sqrt t -> P.Msqrt (attrs, invoke' t)
237     | A.Root (t1, t2) -> P.Mroot (attrs, invoke' t1, invoke' t2)
238     | A.Box ((_, spacing, _) as kind, terms) ->
239         let children = aux_children mathonly spacing xref pos prec uris (CicNotationUtil.ungroup terms) in
240           box_of mathonly kind attrs children
241     | A.Group terms ->
242         let children = aux_children false mathonly xref pos prec uris (CicNotationUtil.ungroup terms) in
243           box_of mathonly (A.H, false, false) attrs children
244     | A.Break -> assert false (* TODO? *)
245   and aux_children mathonly spacing xref pos prec uris terms =
246     let find_clusters =
247       let rec aux_list first clusters acc =
248         function
249             [] when acc = [] -> List.rev clusters
250           | [] -> aux_list first (List.rev acc :: clusters) [] []
251           | (A.Layout A.Break) :: tl when acc = [] -> aux_list first clusters [] tl
252           | (A.Layout A.Break) :: tl -> aux_list first (List.rev acc :: clusters) [] tl
253           | [hd] ->
254               let pos' = 
255                 if first then
256                   pos
257                 else
258                   match pos with
259                       `None -> `Right
260                     | `Inner -> `Inner
261                     | `Right -> `Right
262                     | `Left -> `Inner
263               in
264                 aux_list false clusters (aux [] mathonly xref pos' prec uris hd :: acc) []
265           | hd :: tl ->
266               let pos' =
267                 match pos, first with
268                     `None, true -> `Left
269                   | `None, false -> `Inner
270                   | `Left, true -> `Left
271                   | `Left, false -> `Inner
272                   | `Right, _ -> `Inner
273                   | `Inner, _ -> `Inner
274               in
275                 aux_list false clusters (aux [] mathonly xref pos' prec uris hd :: acc) tl
276       in
277         aux_list true [] []
278     in
279     let boxify_pres =
280       function
281           [t] -> t
282         | tl -> box_of mathonly (A.H, spacing, false) [] tl
283     in
284       List.map boxify_pres (find_clusters terms)
285   in
286   aux [] false None `None 0 []
287
288 let render_to_boxml id_to_uri t =
289   let rec print_box (t: CicNotationPres.boxml_markup) =
290     Box.box2xml print_mpres t
291   and print_mpres (t: CicNotationPres.mathml_markup) =
292     Mpresentation.print_mpres print_box t
293   in
294   let xml_stream = print_box (box_of_mpres (render id_to_uri t)) in
295   Ast2pres.add_xml_declaration xml_stream
296