1:- module(mathml, [pl_mathml/2, pl_mathml/3, pl_mathjax/2, pl_mathjax/3]). 2
3:- discontiguous math/2, math/3, math/4, current/3, paren/3, prec/3. 4:- discontiguous type/3, denoting/3, ml/3, jax/3. 5
6:- use_module(library(http/html_write)). 7:- use_module(library(rolog)). 8:- consult(['../inst/pl/lib/main.pl', '../inst/pl/lib/op.pl']). 9
18:- dynamic math_hook/2, math_hook/3, math_hook/4. 19:- multifile math_hook/2, math_hook/3, math_hook/4. 20
26:- multifile mlx/3. 27:- multifile jaxx/3. 28:- multifile precx/3. 29:- multifile parenx/3. 30:- multifile typex/3. 31
37pl_mathml(R, S)
38=> pl_mathml(R, S, []).
39
45pl_mathml(R, S, Flags0)
46 => digits_(Flags0, Flags1),
47 mathml(R, M, Flags1),
48 html(M, H, []),
49 maplist(atom_string, H, S).
50
52pl_mathjax(R, S)
53 => pl_mathjax(R, S, []).
54
55pl_mathjax(R, S, Flags0)
56 => digits_(Flags0, Flags1),
57 mathjax(R, S, Flags1).
58
59 60 digits_(Flags0, Flags1),
61 option(digits(_), Flags0)
62 => Flags1 = Flags0.
63
64 digits_(Flags0, Flags1)
65 => Flags1 = [digits(2) | Flags0]