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