]> 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 map_tex use_unicode texcmd =
40   let default_map_tex = Printf.sprintf "\\%s " in
41   if use_unicode then
42     try
43       Utf8Macro.expand texcmd
44     with Utf8Macro.Macro_not_found _ -> default_map_tex texcmd
45   else
46     default_map_tex texcmd
47
48 let resolve_binder use_unicode = function
49   | `Lambda -> map_tex use_unicode "lambda"
50   | `Pi -> map_tex use_unicode "Pi"
51   | `Forall -> map_tex use_unicode "forall"
52   | `Exists -> map_tex use_unicode "exists"
53
54 let rec make_attributes l1 = function
55   | [] -> []
56   | None :: tl -> make_attributes (List.tl l1) tl
57   | Some s :: tl ->
58       let p,n = List.hd l1 in
59       (p,n,s) :: make_attributes (List.tl l1) tl
60
61 let box_of_mpres =
62   function
63     Mpresentation.Mobject (_, box) -> box
64   | mpres -> Box.Object ([], mpres)
65
66 let mpres_of_box =
67   function
68     Box.Object (_, mpres) -> mpres
69   | box -> Mpresentation.Mobject ([], box)
70
71 let genuine_math =
72   function
73   | Mpresentation.Mobject _ -> false
74   | _ -> true
75
76 let box_of mathonly kind attrs children =
77   if mathonly then Mpresentation.Mrow (attrs, children)
78   else
79     match kind with
80     | CicNotationPt.H when List.for_all genuine_math children ->
81         Mpresentation.Mrow (attrs, children)
82     | CicNotationPt.H ->
83         mpres_of_box (Box.H (attrs, List.map box_of_mpres children))
84     | CicNotationPt.V ->
85         mpres_of_box (Box.V (attrs, List.map box_of_mpres children))
86     | CicNotationPt.HV ->
87         mpres_of_box (Box.HV (attrs, List.map box_of_mpres children))
88     | CicNotationPt.HOV ->
89         mpres_of_box (Box.HOV (attrs, List.map box_of_mpres children))
90
91 let open_paren   = Mpresentation.Mo ([], "(")
92 let closed_paren = Mpresentation.Mo ([], ")")
93 let open_box_paren = Box.Text ([], "(")
94 let closed_box_paren = Box.Text ([], ")")
95
96 type child_pos = [ `Left | `Right | `Inner ]
97
98 let add_parens child_prec child_assoc child_pos curr_prec t =
99   if child_prec < curr_prec
100     || (child_prec = curr_prec &&
101         child_assoc = Gramext.LeftA &&
102         child_pos <> `Left)
103     || (child_prec = curr_prec &&
104         child_assoc = Gramext.RightA &&
105         child_pos <> `Right)
106   then  (* parens should be added *)
107     match t with
108     | Mpresentation.Mobject (_, box) ->
109         mpres_of_box (Box.H ([], [ open_box_paren; box; closed_box_paren ]))
110     | mpres -> Mpresentation.Mrow ([], [open_paren; t; closed_paren])
111   else
112     t
113
114 let render ids_to_uris t =
115   let module A = CicNotationPt in
116   let module P = Mpresentation in
117   let use_unicode = true in
118   let lookup_uri = function
119     | None -> None
120     | Some id -> (try Some (Hashtbl.find ids_to_uris id) with Not_found -> None)
121   in
122   let make_href xref =
123     let uri = lookup_uri xref in
124     make_attributes [Some "helm","xref"; Some "xlink","href"] [xref;uri]
125   in
126   let make_xref xref = make_attributes [Some "helm","xref"] [xref] in
127   let make_box = function
128     | P.Mobject (attrs, box) ->
129         assert (attrs = []);
130         box
131     | m -> Box.Object ([], m)
132   in
133   let make_hv xref children =
134     let attrs = indent_attributes @ make_href xref in
135     P.Mobject ([], Box.HV (indent_attributes, List.map make_box children))
136   in
137   let rec invoke mathonly xref prec assoc t =
138     fst (aux mathonly xref prec assoc t)
139   (* when mathonly is true no boxes should be generated, only mrows *)
140   and aux mathonly xref prec assoc t =
141     let return t = t, (prec, assoc) in
142     match t with
143     | A.AttributedTerm (`Loc _, t) -> return (invoke mathonly xref prec assoc t)
144     | A.AttributedTerm (`Level (prec, assoc), t) ->
145         return (invoke mathonly xref prec assoc t)
146     | A.AttributedTerm (`IdRef xref, t) ->
147         return (invoke mathonly (Some xref) prec assoc t)
148
149     | A.Ident (literal, None) -> return (P.Mi (make_href xref, literal))
150     | A.Num (literal, _)      -> return (P.Mn (make_href xref, literal))
151     | A.Symbol (literal, _)   -> return (P.Mo (make_href xref, literal))
152     | A.Uri (literal, None)   -> return (P.Mi (make_href xref, literal))
153
154     (* default pretty printing shant' be implemented here *)
155 (*     | A.Appl terms ->
156         let children = aux_children mathonly xref prec assoc terms in
157         make_hv xref children
158     | A.Binder (`Pi, (A.Ident ("_", None), ty_opt), body)
159     | A.Binder (`Forall, (A.Ident ("_", None), ty_opt), body) ->
160         let ty' =
161           match ty_opt with
162           | None -> mpres_implicit
163           | Some ty -> invoke mathonly None prec assoc ty
164         in
165         let body' = invoke mathonly None prec assoc body in
166         return (make_hv xref [ty'; make_h None [mpres_arrow; body']]) *)
167
168     | A.Literal l -> aux_literal xref prec assoc l
169     | A.Layout l -> aux_layout mathonly xref prec assoc l
170     | A.Magic _
171     | A.Variable _ -> assert false  (* should have been instantiated *)
172
173     | _ -> assert false
174
175   and aux_literal xref prec assoc l =
176     let return t = t, (prec, assoc) in
177     let attrs = make_href xref in
178     match l with
179     | `Symbol s
180     | `Keyword s -> return (P.Mo (attrs, s))
181     | `Number s  -> return (P.Mn (attrs, s))
182   and aux_layout mathonly xref prec assoc l =
183     let return t = t, (prec, assoc) in
184     let attrs = make_xref xref in
185     let invoke' t = invoke true None prec assoc t in
186     match l with
187     | A.Sub (t1, t2) -> return (P.Msub (attrs, invoke' t1, invoke' t2))
188     | A.Sup (t1, t2) -> return (P.Msup (attrs, invoke' t1, invoke' t2))
189     | A.Below (t1, t2) -> return (P.Munder (attrs, invoke' t1, invoke' t2))
190     | A.Above (t1, t2) -> return (P.Mover (attrs, invoke' t1, invoke' t2))
191     | A.Frac (t1, t2)
192     | A.Over (t1, t2) -> return (P.Mfrac (attrs, invoke' t1, invoke' t2))
193     | A.Atop (t1, t2) ->
194         return (P.Mfrac (atop_attributes @ attrs, invoke' t1, invoke' t2))
195     | A.Sqrt t -> return (P.Msqrt (attrs, invoke' t))
196     | A.Root (t1, t2) -> return (P.Mroot (attrs, invoke' t1, invoke' t2))
197     | A.Box (kind, terms) ->
198         let children = aux_children mathonly xref prec assoc terms in
199         return (box_of mathonly kind attrs children)
200   and aux_children mathonly xref prec assoc terms =
201     let rec aux_list first =
202       function
203         [] -> []
204       | [t] ->
205           let t', (child_prec, child_assoc) = aux mathonly xref prec assoc t in
206             [add_parens child_prec child_assoc `Right prec t']
207       | t :: tl ->
208           let t', (child_prec, child_assoc) = aux mathonly xref prec assoc t in
209           let child_pos = if first then `Left else `Inner in
210             add_parens child_prec child_assoc child_pos prec t' :: aux_list false tl
211     in
212       match terms with
213         [t] -> [invoke mathonly xref prec assoc t]
214       | tl -> aux_list true tl
215   in
216   fst (aux false None 0 Gramext.NonA t)
217