Prolog "noise"
Admin User, created Mar 15. 2025
/**
* Warranty & Liability
* To the extent permitted by applicable law and unless explicitly
* otherwise agreed upon, XLOG Technologies AG makes no warranties
* regarding the provided information. XLOG Technologies AG assumes
* no liability that any problems might be solved with the information
* provided by XLOG Technologies AG.
*
* Rights & License
* All industrial property rights regarding the information - copyright
* and patent rights in particular - are the sole property of XLOG
* Technologies AG. If the company was not the originator of some
* excerpts, XLOG Technologies AG has at least obtained the right to
* reproduce, change and translate the information.
*
* Reproduction is restricted to the whole unaltered document. Reproduction
* of the information is only allowed for non-commercial uses. Selling,
* giving away or letting of the execution of the library is prohibited.
* The library can be distributed as part of your applications and libraries
* for execution provided this comment remains unchanged.
*
* Restrictions
* Only to be distributed with programs that add significant and primary
* functionality to the library. Not to be distributed with additional
* software intended to replace any components of the library.
*
* Trademarks
* Jekejeke is a registered trademark of XLOG Technologies AG.
*/
:- ensure_loaded(library(util/math)).
:- ensure_loaded(library(sequence)).
:- ensure_loaded(library(edge/zero)).
/************************************************************/
/* Transformer */
/************************************************************/
/**
* noise_train(E, Z, N, I, T, B):
* The predicate succeeds in B with the binary decision diagram and in T
* with the failure score, for the transformer encoder of the mapping
* P-Q from data(Z,P,Q). The parameter N gives the ensemble size, the
* parameter E the initial encoder and I the number of iterations.
*/
% noise_train(+List, +Atom, +Integer, +Integer, -List, -List)
noise_train(E, Z, N, I, T, B) :-
noise_recon(N, E, Z, S, C),
sys_noise_improve(I, N, E, Z, S, C, T, B).
% sys_noise_improve(+Integer, +Integer, +List, +Atom, +Integer, +List, -List, -List)
sys_noise_improve(0, _, E, _, S, _, S, E) :- !.
sys_noise_improve(_, _, E, _, 0, _, 0, E) :- !.
sys_noise_improve(I, N, E, Z, S, C, R, G) :-
sys_noise_blame(E, Z, S, C, F),
J is I-1,
noise_recon(N, F, Z, T, D),
sys_noise_improve(J, N, F, Z, T, D, R, G).
/* Blame Noise */
% sys_noise_blame(+List, +Atom, +Integer, +List, -List)
sys_noise_blame(E, Z, S, C, F) :-
random(V), K is floor(V*S)+1,
sys_noise_pick(E, Z, C, K, P, H),
maplist(sys_noise_neighbour(0.5), H, W),
maplist(tree_set(P, 0), E, W, F).
% sys_noise_pick(+List, +Atom, +Tree, +Integer, -List, -List)
sys_noise_pick(E, Z, C, K, P, H) :-
call_nth((
sys_noise_upsample(E, Z, P, H, Q),
maplist(tree_current(H, 0), C, W),
Q \== W), K).
% sys_noise_neighbour(+Float, +Integer, -Integer)
sys_noise_neighbour(P, X, Y) :-
random(V), V =< P, !,
Y is 1-X.
sys_noise_neighbour(_, X, X).
/* Blame Recon */
/**
* noise_recon(N, E, Z, S, C):
* The predicate succeeds in C with the binary decision diagram and
* in S with the failure score, for the transformer decoder of the
* encoder E and the mapping P-Q from data(Z,P,Q). The parameter N
* gives the ensemble size.
*/
% noise_recon(+Integer, +List, +Atom, -Integer, -List)
noise_recon(N, E, Z, S, C) :-
zero_bayes(N, H-Q, sys_noise_upsample(E, Z, _, H, Q), C),
zero_failure(H-Q, sys_noise_upsample(E, Z, _, H, Q), C, S).
% sys_noise_upsample(+List, +Atom, -List, -List, -List)
sys_noise_upsample(E, Z, P, H, Q) :-
data(Z, P, Q),
maplist(tree_current(P, 0), E, H).