1:- module(lazymath, [ add/3, sub/3, mul/3, max/3, min/3, stoch/2, exp/2, log/2, lse/2, pow/3, log_stoch/2
    2                    , patient/3, patient/4]).

Multimoded arithmetic operations

This module is here mostly because there are some numerical problems with library(clpr). */

    8:- use_module(library(math), [stoch/3]).    9:- use_module(library(callutils)).   10:- use_module(library(insist)).   11
   12% lazy arithmetic predicates
   13max(X,Y,Z) :- when(ground(X-Y), Z is max(X,Y)).
   14min(X,Y,Z) :- when(ground(X-Y), Z is min(X,Y)).
   15add(X,Y,Z) :- when(ground(X-Y), Z is X+Y).
   16sub(X,Y,Z) :- when(ground(X-Y), Z is Y-X).
   17mul(X,Y,Z) :- when(ground(X-Y), Z is X*Y).
   18stoch(X,Y) :- when(ground(X),   insist(stoch(X,Y,_))).
   19log(X,Y)   :- when(ground(X),   Y is log(X)).
   20exp(X,Y)   :- when(ground(X),   Y is exp(X)).
   21pow(1,X,X) :- !.
   22pow(B,X,Y) :- when(ground(X), Y is X^B).
   23log_stoch(X,Y) :- when(ground(X), log_stoch_strict(X,Y)).
   24
   25log_stoch_strict([_],[0.0]) :- !.
   26log_stoch_strict(LogWeights,LogProbs) :-
   27   log_sum_exp(LogWeights, LogTotal),
   28   maplist((math:sub(LogTotal)), LogWeights, LogProbs).
   29
   30lse(Xs,Z) :- when(ground(Xs), log_sum_exp(Xs,Z)).
   31
   32log_sum_exp([X],X) :- !.
   33log_sum_exp(Xs,Y) :-
   34   max_list(Xs,M),
   35   call(add_log(M)*sum_list*maplist(exp_sub(M)),Xs,Y).
   36exp_sub(M,X,Y) :- Y is exp(X-M).
   37add_log(M,X,Y) :- Y is M+log(X).
   38
   39:- meta_predicate patient(2,?,-), patient(3,?,?,-).   40patient(P,X,Y) :- when(ground(X),call(P,X,Y)).
   41patient(P,X,Y,Z) :- when(ground(X-Y),call(P,X,Y,Z)).
   42user:goal_expansion(patient(P,X,Y), when(ground(X),call(P,X,Y))).
   43user:goal_expansion(patient(P,X,Y,Z), when(ground(X-Y),call(P,X,Y,Z)))