(* 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 keyword_attributes = [None, "mathcolor", "blue"] 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 = [ `None | `Left | `Right | `Inner ] let pp_assoc = function | Gramext.LeftA -> "LeftA" | Gramext.RightA -> "RightA" | Gramext.NonA -> "NonA" let pp_pos = function `None -> "`None" | `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 = 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 xmlattrs xref uris = let xref_uri = lookup_uri xref in let raw_uris = List.map UriManager.string_of_uri uris in let uri = match xref_uri, raw_uris with | None, [] -> None | Some uri, [] -> Some uri | None, raw_uris -> Some (String.concat " " raw_uris) | Some uri, raw_uris -> Some (String.concat " " (uri :: raw_uris)) in xmlattrs @ 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 (* when mathonly is true no boxes should be generated, only mrows *) let rec aux xmlattrs mathonly xref pos prec uris t = match t with | A.AttributedTerm (attr, t) -> aux_attribute xmlattrs mathonly xref pos prec uris t attr | A.Ident (literal, _) -> P.Mi (make_href xmlattrs xref [], to_unicode literal) | A.Num (literal, _) -> P.Mn (make_href xmlattrs xref [], to_unicode literal) | A.Symbol (literal, _) -> P.Mo (make_href xmlattrs xref uris, to_unicode literal) | A.Uri (literal, _) -> P.Mi (make_href xmlattrs xref [], to_unicode literal) | A.Literal l -> aux_literal xmlattrs xref prec uris l | A.Layout l -> aux_layout mathonly xref pos prec uris l | A.Magic _ | A.Variable _ -> assert false (* should have been instantiated *) | t -> prerr_endline (CicNotationPp.pp_term t); assert false and aux_attribute xmlattrs mathonly xref pos prec uris t = function | `Loc _ -> aux xmlattrs mathonly xref pos prec uris t | `Level (child_prec, child_assoc) -> let t' = aux xmlattrs mathonly xref pos child_prec uris t in add_parens child_prec child_assoc pos prec t' | `IdRef xref -> aux xmlattrs mathonly (Some xref) pos prec uris t | `Href uris' -> aux xmlattrs mathonly xref pos prec uris' t | `XmlAttrs xmlattrs -> aux xmlattrs mathonly xref pos prec uris t and aux_literal xmlattrs xref prec uris l = let attrs = make_href xmlattrs xref uris in match l with | `Symbol s -> P.Mo (attrs, to_unicode s) | `Keyword s -> P.Mo (attrs, to_unicode s) | `Number s -> P.Mn (attrs, to_unicode s) and aux_layout mathonly xref pos prec uris l = let attrs = make_xref xref in let invoke' t = aux [] true None pos prec uris t in match l with | A.Sub (t1, t2) -> P.Msub (attrs, invoke' t1, invoke' t2) | A.Sup (t1, t2) -> P.Msup (attrs, invoke' t1, invoke' t2) | A.Below (t1, t2) -> P.Munder (attrs, invoke' t1, invoke' t2) | A.Above (t1, t2) -> P.Mover (attrs, invoke' t1, invoke' t2) | A.Frac (t1, t2) | A.Over (t1, t2) -> P.Mfrac (attrs, invoke' t1, invoke' t2) | A.Atop (t1, t2) -> P.Mfrac (atop_attributes @ attrs, invoke' t1, invoke' t2) | A.Sqrt t -> P.Msqrt (attrs, invoke' t) | A.Root (t1, t2) -> P.Mroot (attrs, invoke' t1, invoke' t2) | A.Box (kind, terms) -> let children = aux_children mathonly xref pos prec uris terms in box_of mathonly kind attrs children | A.Break -> assert false (* TODO? *) and aux_children mathonly xref pos prec uris terms = let rec aux_list first = function [] -> [] | [t] -> assert (not first); let pos' = match pos with `None -> `Right | `Inner -> `Inner | `Right -> `Right | `Left -> `Inner in [aux [] mathonly xref pos' prec uris t] | t :: tl -> let pos' = match pos, first with `None, true -> `Left | `None, false -> `Inner | `Left, true -> `Left | `Left, false -> `Inner | `Right, _ -> `Inner | `Inner, _ -> `Inner in (aux [] mathonly xref pos' prec uris t) :: aux_list false tl in match terms with | [t] -> [aux [] mathonly xref pos prec uris t] | tl -> aux_list true tl in aux [] false None `None 0 [] 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