(* Copyright (C) 2004-2005, HELM Team. * * This file is part of HELM, an Hypertextual, Electronic * Library of Mathematics, developed at the Computer Science * Department, University of Bologna, Italy. * * HELM is free software; you can redistribute it and/or * modify it under the terms of the GNU General Public License * as published by the Free Software Foundation; either version 2 * of the License, or (at your option) any later version. * * HELM is distributed in the hope that it will be useful, * but WITHOUT ANY WARRANTY; without even the implied warranty of * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the * GNU General Public License for more details. * * You should have received a copy of the GNU General Public License * along with HELM; if not, write to the Free Software * Foundation, Inc., 59 Temple Place - Suite 330, Boston, * MA 02111-1307, USA. * * For details, see the HELM World-Wide-Web page, * http://helm.cs.unibo.it/ *) type mathml_markup = boxml_markup Mpresentation.mpres and boxml_markup = mathml_markup Box.box type markup = mathml_markup let atop_attributes = [None, "linethickness", "0pt"] let binder_attributes = [None, "mathcolor", "blue"] let indent_attributes = [None, "indent", "1em"] let mpres_arrow = Mpresentation.Mo (binder_attributes, "->") (* TODO unicode symbol "to" *) let mpres_implicit = Mpresentation.Mtext ([], "?") let to_unicode s = try if s.[0] = '\\' then Utf8Macro.expand (String.sub s 1 (String.length s - 1)) else s with Utf8Macro.Macro_not_found _ -> s let rec make_attributes l1 = function | [] -> [] | None :: tl -> make_attributes (List.tl l1) tl | Some s :: tl -> let p,n = List.hd l1 in (p,n,s) :: make_attributes (List.tl l1) tl let box_of_mpres = function Mpresentation.Mobject (_, box) -> box | mpres -> Box.Object ([], mpres) let mpres_of_box = function Box.Object (_, mpres) -> mpres | box -> Mpresentation.Mobject ([], box) let genuine_math = function | Mpresentation.Mobject _ -> false | _ -> true let box_of mathonly spec attrs children = match children with | [t] -> t | _ -> let kind, spacing, indent = spec in let rec dress = function | [] -> [] | [hd] -> [hd] | hd :: tl -> hd :: Mpresentation.Mtext ([], " ") :: dress tl in if mathonly then Mpresentation.Mrow (attrs, dress children) else let attrs' = if spacing then [None, "spacing", "0.5em"] else [] @ if indent then [None, "indent", "0em 0.5em"] else [] @ attrs in match kind with | CicNotationPt.H when List.for_all genuine_math children -> Mpresentation.Mrow (attrs', children) | CicNotationPt.H -> mpres_of_box (Box.H (attrs', List.map box_of_mpres children)) | CicNotationPt.V -> mpres_of_box (Box.V (attrs', List.map box_of_mpres children)) | CicNotationPt.HV -> mpres_of_box (Box.HV (attrs', List.map box_of_mpres children)) | CicNotationPt.HOV -> mpres_of_box (Box.HOV (attrs', List.map box_of_mpres children)) let open_paren = Mpresentation.Mo ([], "(") let closed_paren = Mpresentation.Mo ([], ")") let open_box_paren = Box.Text ([], "(") let closed_box_paren = Box.Text ([], ")") type child_pos = [ `Left | `Right | `Inner ] let pp_assoc = function | Gramext.LeftA -> "LeftA" | Gramext.RightA -> "RightA" | Gramext.NonA -> "NonA" let pp_pos = function | `Left -> "`Left" | `Right -> "`Right" | `Inner -> "`Inner" let is_atomic t = let module P = Mpresentation in let rec aux_mpres = function | P.Mi _ | P.Mo _ | P.Mn _ | P.Ms _ | P.Mtext _ | P.Mspace _ -> true | P.Mobject (_, box) -> aux_box box | P.Maction (_, [mpres]) | P.Mrow (_, [mpres]) -> aux_mpres mpres | _ -> false and aux_box = function | Box.Space _ | Box.Ink _ | Box.Text _ -> true | Box.Object (_, mpres) -> aux_mpres mpres | Box.H (_, [box]) | Box.V (_, [box]) | Box.HV (_, [box]) | Box.HOV (_, [box]) | Box.Action (_, [box]) -> aux_box box | _ -> false in aux_mpres t let add_parens child_prec child_assoc child_pos curr_prec t = prerr_endline (Printf.sprintf "add_parens %d %s %s %d" child_prec (pp_assoc child_assoc) (pp_pos child_pos) (curr_prec)); if is_atomic t then t else if child_prec < curr_prec || (child_prec = curr_prec && child_assoc = Gramext.LeftA && child_pos <> `Left) || (child_prec = curr_prec && child_assoc = Gramext.RightA && child_pos <> `Right) then (* parens should be added *) match t with | Mpresentation.Mobject (_, box) -> mpres_of_box (Box.H ([], [ open_box_paren; box; closed_box_paren ])) | mpres -> Mpresentation.Mrow ([], [open_paren; t; closed_paren]) else t let render ids_to_uris t = let module A = CicNotationPt in let module P = Mpresentation in let use_unicode = true in let lookup_uri = function | None -> None | Some id -> (try Some (Hashtbl.find ids_to_uris id) with Not_found -> None) in let make_href xref = let uri = lookup_uri xref in make_attributes [Some "helm","xref"; Some "xlink","href"] [xref;uri] in let make_xref xref = make_attributes [Some "helm","xref"] [xref] in let make_box = function | P.Mobject (attrs, box) -> assert (attrs = []); box | m -> Box.Object ([], m) in let make_hv xref children = let attrs = indent_attributes @ make_href xref in P.Mobject ([], Box.HV (indent_attributes, List.map make_box children)) in let rec invoke mathonly xref prec assoc t = fst (aux mathonly xref prec assoc t) (* when mathonly is true no boxes should be generated, only mrows *) and aux mathonly xref prec assoc t = let return t = t, (prec, assoc) in match t with | A.AttributedTerm (`Loc _, t) -> return (invoke mathonly xref prec assoc t) | A.AttributedTerm (`Level (prec, assoc), t) -> return (invoke mathonly xref prec assoc t) | A.AttributedTerm (`IdRef xref, t) -> return (invoke mathonly (Some xref) prec assoc t) | A.Ident (literal, _) -> return (P.Mi (make_href xref, to_unicode literal)) | A.Num (literal, _) -> return (P.Mn (make_href xref, to_unicode literal)) | A.Symbol (literal, _) -> return (P.Mo (make_href xref,to_unicode literal)) | A.Uri (literal, _) -> return (P.Mi (make_href xref, to_unicode literal)) (* default pretty printing shant' be implemented here *) (* | A.Appl terms -> let children = aux_children mathonly xref prec assoc terms in make_hv xref children | A.Binder (`Pi, (A.Ident ("_", None), ty_opt), body) | A.Binder (`Forall, (A.Ident ("_", None), ty_opt), body) -> let ty' = match ty_opt with | None -> mpres_implicit | Some ty -> invoke mathonly None prec assoc ty in let body' = invoke mathonly None prec assoc body in return (make_hv xref [ty'; make_h None [mpres_arrow; body']]) *) | A.Literal l -> aux_literal xref prec assoc l | A.Layout l -> aux_layout mathonly xref prec assoc l | A.Magic _ | A.Variable _ -> assert false (* should have been instantiated *) | t -> prerr_endline (CicNotationPp.pp_term t); assert false and aux_literal xref prec assoc l = let return t = t, (prec, assoc) in let attrs = make_href xref in match l with | `Symbol s | `Keyword s -> return (P.Mo (attrs, to_unicode s)) | `Number s -> return (P.Mn (attrs, to_unicode s)) and aux_layout mathonly xref prec assoc l = let return t = t, (prec, assoc) in let attrs = make_xref xref in let invoke' t = invoke true None prec assoc t in match l with | A.Sub (t1, t2) -> return (P.Msub (attrs, invoke' t1, invoke' t2)) | A.Sup (t1, t2) -> return (P.Msup (attrs, invoke' t1, invoke' t2)) | A.Below (t1, t2) -> return (P.Munder (attrs, invoke' t1, invoke' t2)) | A.Above (t1, t2) -> return (P.Mover (attrs, invoke' t1, invoke' t2)) | A.Frac (t1, t2) | A.Over (t1, t2) -> return (P.Mfrac (attrs, invoke' t1, invoke' t2)) | A.Atop (t1, t2) -> return (P.Mfrac (atop_attributes @ attrs, invoke' t1, invoke' t2)) | A.Sqrt t -> return (P.Msqrt (attrs, invoke' t)) | A.Root (t1, t2) -> return (P.Mroot (attrs, invoke' t1, invoke' t2)) | A.Box (kind, terms) -> let children = aux_children mathonly xref prec assoc terms in return (box_of mathonly kind attrs children) and aux_children mathonly xref prec assoc terms = let rec aux_list first = function [] -> [] | [t] -> let t', (child_prec, child_assoc) = aux mathonly xref prec assoc t in prerr_endline ("T " ^ CicNotationPp.pp_term t); [add_parens child_prec child_assoc `Right prec t'] | t :: tl -> let t', (child_prec, child_assoc) = aux mathonly xref prec assoc t in prerr_endline ( "T " ^ CicNotationPp.pp_term t); let child_pos = if first then `Left else `Inner in let hd = add_parens child_prec child_assoc child_pos prec t' in hd :: aux_list false tl in match terms with [t] -> [invoke mathonly xref prec assoc t] | tl -> aux_list true tl in fst (aux false None 0 Gramext.NonA t) let render_to_boxml id_to_uri t = let rec print_box (t: CicNotationPres.boxml_markup) = Box.box2xml print_mpres t and print_mpres (t: CicNotationPres.mathml_markup) = Mpresentation.print_mpres print_box t in let xml_stream = print_box (box_of_mpres (render id_to_uri t)) in Ast2pres.add_xml_declaration xml_stream