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