]> 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 = [ `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   | `Left -> "`Left"
113   | `Right -> "`Right"
114   | `Inner -> "`Inner"
115
116 let is_atomic t =
117   let module P = Mpresentation in
118   let rec aux_mpres = function
119     | P.Mi _
120     | P.Mo _
121     | P.Mn _
122     | P.Ms _
123     | P.Mtext _
124     | P.Mspace _ -> true
125     | P.Mobject (_, box) -> aux_box box
126     | P.Maction (_, [mpres])
127     | P.Mrow (_, [mpres]) -> aux_mpres mpres
128     | _ -> false
129   and aux_box = function
130     | Box.Space _
131     | Box.Ink _
132     | Box.Text _ -> true
133     | Box.Object (_, mpres) -> aux_mpres mpres
134     | Box.H (_, [box])
135     | Box.V (_, [box])
136     | Box.HV (_, [box])
137     | Box.HOV (_, [box])
138     | Box.Action (_, [box]) -> aux_box box
139     | _ -> false
140   in
141   aux_mpres t
142
143 let add_parens child_prec child_assoc child_pos curr_prec t =
144   prerr_endline (Printf.sprintf "add_parens %d %s %s %d" child_prec
145     (pp_assoc child_assoc) (pp_pos child_pos) (curr_prec));
146   if is_atomic t then t
147   else if child_prec < curr_prec
148     || (child_prec = curr_prec &&
149         child_assoc = Gramext.LeftA &&
150         child_pos <> `Left)
151     || (child_prec = curr_prec &&
152         child_assoc = Gramext.RightA &&
153         child_pos <> `Right)
154   then  (* parens should be added *)
155     match t with
156     | Mpresentation.Mobject (_, box) ->
157         mpres_of_box (Box.H ([], [ open_box_paren; box; closed_box_paren ]))
158     | mpres -> Mpresentation.Mrow ([], [open_paren; t; closed_paren])
159   else
160     t
161
162 let render ids_to_uris t =
163   let module A = CicNotationPt in
164   let module P = Mpresentation in
165   let use_unicode = true in
166   let lookup_uri = function
167     | None -> None
168     | Some id -> (try Some (Hashtbl.find ids_to_uris id) with Not_found -> None)
169   in
170   let make_href xref =
171     let uri = lookup_uri xref in
172     make_attributes [Some "helm","xref"; Some "xlink","href"] [xref;uri]
173   in
174   let make_xref xref = make_attributes [Some "helm","xref"] [xref] in
175   let make_box = function
176     | P.Mobject (attrs, box) ->
177         assert (attrs = []);
178         box
179     | m -> Box.Object ([], m)
180   in
181   let make_hv xref children =
182     let attrs = indent_attributes @ make_href xref in
183     P.Mobject ([], Box.HV (indent_attributes, List.map make_box children))
184   in
185   let rec invoke mathonly xref prec assoc t =
186     fst (aux mathonly xref prec assoc t)
187   (* when mathonly is true no boxes should be generated, only mrows *)
188   and aux mathonly xref prec assoc t =
189     let return t = t, (prec, assoc) in
190     match t with
191     | A.AttributedTerm (`Loc _, t) -> return (invoke mathonly xref prec assoc t)
192     | A.AttributedTerm (`Level (prec, assoc), t) ->
193         return (invoke mathonly xref prec assoc t)
194     | A.AttributedTerm (`IdRef xref, t) ->
195         return (invoke mathonly (Some xref) prec assoc t)
196
197     | A.Ident (literal, _) -> return (P.Mi (make_href xref, to_unicode literal))
198     | A.Num (literal, _) -> return (P.Mn (make_href xref, to_unicode literal))
199     | A.Symbol (literal, _) -> return (P.Mo (make_href xref,to_unicode literal))
200     | A.Uri (literal, _) -> return (P.Mi (make_href xref, to_unicode literal))
201
202     (* default pretty printing shant' be implemented here *)
203 (*     | A.Appl terms ->
204         let children = aux_children mathonly xref prec assoc terms in
205         make_hv xref children
206     | A.Binder (`Pi, (A.Ident ("_", None), ty_opt), body)
207     | A.Binder (`Forall, (A.Ident ("_", None), ty_opt), body) ->
208         let ty' =
209           match ty_opt with
210           | None -> mpres_implicit
211           | Some ty -> invoke mathonly None prec assoc ty
212         in
213         let body' = invoke mathonly None prec assoc body in
214         return (make_hv xref [ty'; make_h None [mpres_arrow; body']]) *)
215
216     | A.Literal l -> aux_literal xref prec assoc l
217     | A.Layout l -> aux_layout mathonly xref prec assoc l
218     | A.Magic _
219     | A.Variable _ -> assert false  (* should have been instantiated *)
220
221     | t ->
222         prerr_endline (CicNotationPp.pp_term t);
223         assert false
224
225   and aux_literal xref prec assoc l =
226     let return t = t, (prec, assoc) in
227     let attrs = make_href xref in
228     match l with
229     | `Symbol s
230     | `Keyword s -> return (P.Mo (attrs, to_unicode s))
231     | `Number s  -> return (P.Mn (attrs, to_unicode s))
232   and aux_layout mathonly xref prec assoc l =
233     let return t = t, (prec, assoc) in
234     let attrs = make_xref xref in
235     let invoke' t = invoke true None prec assoc t in
236     match l with
237     | A.Sub (t1, t2) -> return (P.Msub (attrs, invoke' t1, invoke' t2))
238     | A.Sup (t1, t2) -> return (P.Msup (attrs, invoke' t1, invoke' t2))
239     | A.Below (t1, t2) -> return (P.Munder (attrs, invoke' t1, invoke' t2))
240     | A.Above (t1, t2) -> return (P.Mover (attrs, invoke' t1, invoke' t2))
241     | A.Frac (t1, t2)
242     | A.Over (t1, t2) -> return (P.Mfrac (attrs, invoke' t1, invoke' t2))
243     | A.Atop (t1, t2) ->
244         return (P.Mfrac (atop_attributes @ attrs, invoke' t1, invoke' t2))
245     | A.Sqrt t -> return (P.Msqrt (attrs, invoke' t))
246     | A.Root (t1, t2) -> return (P.Mroot (attrs, invoke' t1, invoke' t2))
247     | A.Box (kind, terms) ->
248         let children = aux_children mathonly xref prec assoc terms in
249         return (box_of mathonly kind attrs children)
250   and aux_children mathonly xref prec assoc terms =
251     let rec aux_list first =
252       function
253         [] -> []
254       | [t] ->
255           let t', (child_prec, child_assoc) = aux mathonly xref prec assoc t in
256           prerr_endline ("T " ^ CicNotationPp.pp_term t);
257             [add_parens child_prec child_assoc `Right prec t']
258       | t :: tl ->
259           let t', (child_prec, child_assoc) = aux mathonly xref prec assoc t in
260           prerr_endline ( "T " ^ CicNotationPp.pp_term t);
261           let child_pos = if first then `Left else `Inner in
262           let hd = add_parens child_prec child_assoc child_pos prec t' in
263             hd :: aux_list false tl
264     in
265       match terms with
266         [t] -> [invoke mathonly xref prec assoc t]
267       | tl -> aux_list true tl
268   in
269   fst (aux false None 0 Gramext.NonA t)
270
271 let render_to_boxml id_to_uri t =
272   let rec print_box (t: CicNotationPres.boxml_markup) =
273     Box.box2xml print_mpres t
274   and print_mpres (t: CicNotationPres.mathml_markup) =
275     Mpresentation.print_mpres print_box t
276   in
277   let xml_stream = print_box (box_of_mpres (render id_to_uri t)) in
278   Ast2pres.add_xml_declaration xml_stream
279