1:- module(canny_maths,
    2          [   frem/3,
    3              fmod/3,
    4
    5              epsilon_equal/2,
    6              epsilon_equal/3,
    7
    8              frexp/3,
    9              ldexp/3
   10          ]).
 frem(+X:number, +Y:number, -Z:number) is det
Z is the remainder after dividing X by Y, calculated by X - N * Y where N is the nearest integral to X / Y.
   17frem(X, Y, Z) :- Z is X - round(X / Y) * Y.
 fmod(+X:number, +Y:number, -Z:number) is det
Z is the remainder after dividing X by Y, equal to X - N * Y where N is X over Y after truncating its fractional part.
   24fmod(X, Y, Z) :-
   25    X_ is abs(X),
   26    Y_ is abs(Y),
   27    frem(X_, Y_, Z_),
   28    (   sign(Z_) < 0
   29    ->  Z0 is Z_ + Y_
   30    ;   Z0 = Z_
   31    ),
   32    Z is copysign(Z0, X).
 epsilon_equal(+X:number, +Y:number) is semidet
 epsilon_equal(+Epsilons:number, +X:number, +Y:number) is semidet
Succeeds only when the absolute difference between the two given numbers X and Y is less than or equal to epsilon, or some factor (Epsilons) of epsilon according to rounding limitations.
   41epsilon_equal(X, Y) :- epsilon_equal(1, X, Y).
   42
   43epsilon_equal(Epsilons, X, Y) :- Epsilons * epsilon >= abs(X - Y).
 frexp(+X:number, -Y:number, -Exp:integer) is det
Answers mantissa Y and exponent Exp for floating-point number X.
Arguments:
Y- is the floating-point mantissa falling within the interval [0.5, 1.0). Note the non-inclusive upper bound.
   52frexp(X, Y, Exp) :- float_parts(X, Y, 2, Exp).
 ldexp(+X:number, -Y:number, +Exp:integer) is det
Loads exponent. Multiplies X by 2 to the power Exp giving Y. Mimics the C math ldexp(x, exp) function.

Uses an unusual argument order. Ordering aligns X, Y and Exp with frexp/3. Uses ** rather than ^ operator. Exp is an integer.

Arguments:
X- is some floating-point value.
Y- is X times 2 to the power Exp.
Exp- is the exponent, typically an integer.
   66ldexp(X, Y, Exp) :- Y is X * 2 ** Exp