1:- module(pval, []). 2:- reexport(library(mathml)). 3
4:- multifile math_hook/2, math_hook/3, math_hook/4. 5
7mathml:math_hook(pval(A), M, Flags, Flags1) :-
8 mathml:type(A, T, Flags),
9 member(numeric(N), T),
10 N =< 1,
11 N >= 0.1,
12 !,
13 M = A,
14 Flags1 = [round(2) | Flags].
15
16mathml:math_hook(pval(A), M, Flags, Flags1) :-
17 mathml:type(A, T, Flags),
18 member(numeric(_N), T),
19 !,
20 M = A,
21 Flags1 = [round(3) | Flags].
22
23mathml:math_hook(pval(A), M, Flags, Flags1) :-
24 !,
25 M = A,
26 Flags1 = Flags.
27
28mathml:math_hook(pval(A, P), M, Flags) :-
29 mathml:type(A, T, Flags),
30 member(numeric(N), T),
31 N < 0.001,
32 !,
33 M = (P < pval(0.001)).
34
35mathml:math_hook(pval(A, P), M, _Flags) :-
36 !,
37 M = (P == pval(A))