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