. (utf8) 2:- module( 3 math_ext, 4 [ 5 avg_list/2, % +Numbers, -Avg 6 between/4, % +Low, +High, +Interval, ?Value 7 decimal_parts/3, % ?Decimal, ?Integer, ?Fractorial 8 fractional_integer/2, % +Number, -Fractorial 9 fractional_weights/2, % ?Fractional, ?Weights 10 inf_max/3, % +X, +Y, -Z 11 inf_min/3, % +X, +Y, -Z 12 integer_weights/2, % ?Integer, ?Weights 13 integer_weights/3 % ?Integer, +Base, ?Weights 14 ] 15).
21:- use_module(library(aggregate)). 22:- use_module(library(clpfd)). 23:- use_module(library(error)). 24:- use_module(library(lists)). 25:- use_module(library(plunit)).
?- avg_list([1 rdiv 3, 1 rdiv 6], X). X = 1 rdiv 4.
Avg is the integer 0 in case Numbers is the empty list. This is in line with how sum_list/2 works.
48avg_list([], 0):- !. 49avg_list(L, Avg):- 50 aggregate(count+sum(X), member(X, L), Len+Sum), 51 Avg is Sum / Len.
60between(Low, _, _, Low). 61between(Low1, High, Interval, Value):- 62 Low2 is Low1 + Interval, 63 (High == â -> true ; Low2 =< High), between(Low2, High, Interval, Value).
74decimal_parts(N, Int, Frac):- 75 ground(N), 76 must_be(number, N), !, 77 Int is floor(float_integer_part(N)), 78 fractional_integer(N, Frac). 79decimal_parts(N, Int, Frac):- 80 must_be(integer, Int), 81 must_be(nonneg, Frac), 82 number_length(Frac, Length), 83 N is copysign(abs(Int) + (Frac rdiv (10 ^ Length)), Int).
92fractional_integer(Frac, _) :- 93 \+ ground(Frac), !, 94 instantiation_error(Frac). 95fractional_integer(Frac, Int) :- 96 Frac = A rdiv B, !, 97 FloatFrac is A / B, 98 fractional_integer(FloatFrac, Int). 99fractional_integer(Frac, Int) :- 100 atom_number(FracAtom, Frac), 101 % We assume that there is at most one occurrence of `.'. 102 sub_atom(FracAtom, IndexOfDot, 1, _, .), !, 103 Skip is IndexOfDot + 1, 104 sub_atom(FracAtom, Skip, _, 0, IntAtom), 105 atom_number(IntAtom, Int). 106fractional_integer(_, 0).
113fractional_weights(Frac, Weights):- 114 ground(Weights), !, 115 aggregate_all( 116 sum(N), 117 ( 118 nth1(Position, Weights, Weight), 119 N is Weight rdiv (10 ^ Position) 120 ), 121 Frac 122 ). 123fractional_weights(Frac, Weights):- 124 ground(Frac), !, 125 fractional_integer(Frac, Int), 126 integer_weights(Int, Weights). 127fractional_weights(_, _):- 128 instantiation_error(_). 129 130 131 132%! inf_max(+X, +Y, -Z) is det. 133 134inf_max(â, _, â) :- !. 135inf_max(_, â, â) :- !. 136inf_max(-â, Y, Y) :- !. 137inf_max(X, -â, X) :- !. 138inf_max(X, Y, Z) :- 139 Z is max(X, Y). 140 141 142 143%! inf_min(+X, +Y, -Z) is det. 144 145inf_min(-â, _, -â) :- !. 146inf_min(_, -â, -â) :- !. 147inf_min(â, Y, Y) :- !. 148inf_min(X, â, X) :- !. 149inf_min(X, Y, Z) :- 150 Z is min(X, Y).
158integer_weights(Int, Weights):-
159 integer_weights(Int, 10, Weights).
168integer_weights(Int, Base, Weights):- 169 (nonvar(Int), nonvar(Base) ; nonvar(Weights)), !, 170 integer_weights0(Int, Base, Weights, 0, Int). 171 172integer_weights0(Int, _, [], Int, _) :- !. 173integer_weights0(Int, Base, [Weight|Weights], Int0, M):- 174 in_base(Weight, Base), 175 Int1 #= Weight + Base * Int0, 176 M #>= Int1, 177 integer_weights0(Int, Base, Weights, Int1, M). 178 179in_base(Weight, Base):- 180 Base #= Max + 1, 181 Weight in 0..Max. 182 183:- begin_tests('integer_weights/3'). 184 185test( 186 'integer_weights(+,+,+) is semidet. TRUE', 187 [forall(integer_weights_test(Int,Base,Weights))] 188):- 189 integer_weights(Int, Base, Weights). 190test( 191 'integer_weights(+,+,-) is multi. TRUE', 192 [forall(integer_weights_test(Int,Base,Weights)),nondet] 193):- 194 integer_weights(Int, Base, Weights0), 195 Weights0 = Weights. 196test( 197 'integer_weights(-,+,+) is multi. TRUE', 198 [forall(integer_weights_test(Int, Base, Weights)),nondet] 199):- 200 integer_weights(Int, Base, Weights0), 201 Weights0 = Weights. 202 203integer_weights_test(1226, 10, [1,2,2,6]). 204integer_weights_test(120, 60, [2,0]). 205 206:- end_tests('integer_weights/3').
224number_length(M, L):- 225 number_length(M, 10.0, L). 226 227 228number_length(N1, Radix, L1):- 229 N2 is N1 / Radix, 230 N2 >= 1.0, !, 231 number_length(N2, Radix, L2), 232 L1 is L2 + 1. 233number_length(_N, _Radix, 1):- !
Mathematics extensions
*/