This repository has been archived on 2023-08-20. You can view files and clone it, but cannot push or open issues or pull requests.
yap-6.3/packages/CLPBN/pfl.yap

145 lines
3.2 KiB
Plaintext
Raw Normal View History

2012-01-10 17:01:06 +00:00
%
% This module defines PFL, the prolog factor language.
%
%
2012-03-22 19:10:15 +00:00
:- module(pfl, [
2012-01-10 17:01:06 +00:00
factor/5,
skolem/2,
2012-03-22 19:10:15 +00:00
get_pfl_parameters/2, % given id return par factor parameter
new_pfl_parameters/2, % given id set new parameters
get_first_pvariable/2, % given id get firt pvar (useful in bayesian)
get_factor_pvariable/2, % given id get any pvar
2012-01-10 17:01:06 +00:00
op(550,yfx,::),
op(1150,fx,bayes),
2012-03-22 19:10:15 +00:00
op(1150,fx,markov),
2012-01-10 17:01:06 +00:00
op(1150,fx,parfactor)]).
:- use_module(library(lists),
[nth0/3,
2012-03-22 19:10:15 +00:00
append/3,
member/2]).
2012-01-10 17:01:06 +00:00
:- dynamic factor/5, skolem_in/2, skolem/2, preprocess/3, evidence/2, id/1.
:- reexport(library(clpbn),
2012-03-22 19:10:15 +00:00
[clpbn_flag/2,
clpbn_flag/2 as pfl_flag,
set_clpbn_flag/2,
set_clpbn_flag/2 as set_pfl_flag]).
2012-01-10 17:01:06 +00:00
2012-03-22 19:10:15 +00:00
:- set_pfl_flag(use_factors,on).
2012-01-10 17:01:06 +00:00
2012-03-22 19:10:15 +00:00
:- pfl_not_clpbn.
user:term_expansion( bayes((Formula ; Phi ; Constraints)), pfl:factor(Id,FList,FV,Phi,Constraints)) :-
!,
term_variables(Formula, FreeVars),
FV =.. [fv|FreeVars],
new_id(Id),
process_args(Formula, Id, 0, _, FList, []).
user:term_expansion( markov((Formula ; Phi ; Constraints)), pfl:factor(Id,FList,FV,Phi,Constraints)) :-
2012-01-10 17:01:06 +00:00
!,
term_variables(Formula, FreeVars),
FV =.. [fv|FreeVars],
new_id(Id),
process_args(Formula, Id, 0, _, FList, []).
user:term_expansion( Goal, [] ) :-
preprocess(Goal, Sk,Var), !,
(ground(Goal) -> true ; throw(error('non ground evidence',Goal))),
% prolog_load_context(module, M),
2012-03-22 19:10:15 +00:00
assert(pfl:evidence(Sk,Var)).
2012-01-10 17:01:06 +00:00
id(0).
new_id(Id) :-
retract(id(Id0)),
Id is Id0+1,
assert(id(Id)).
process_args((Arg1,Arg2), Id, I0, I ) --> !,
process_args(Arg1, Id, I0, I1),
process_args(Arg2, Id, I1, I).
process_args(Arg1, Id, I0, I ) -->
{ I is I0+1 },
process_arg(Arg1, Id, I).
process_arg(Sk::D, Id, _I) -->
!,
{
new_skolem(Sk,D),
assert(skolem_in(Sk, Id))
},
[Sk].
process_arg(Sk, Id, _I) -->
!,
{
assert(skolem_in(Sk, Id))
},
[Sk].
new_skolem(Sk,D) :-
copy_term(Sk, Sk1),
skolem(Sk1, D1),
Sk1 =@= Sk,
!,
D1 = D.
new_skolem(Sk,D) :-
interface_predicate(Sk),
assert(skolem(Sk, D)).
interface_predicate(Sk) :-
Sk =.. SKAs,
append(SKAs, [Var], ESKAs),
ESk =.. ESKAs,
assert(preprocess(ESk, Sk, Var)),
assert_static((user:ESk :-
2012-03-22 19:10:15 +00:00
evidence(Sk,Ev) -> Ev = Var;
var(Var) -> insert_atts(Var,Sk) ;
add_evidence(Sk,Var)
)
2012-01-10 17:01:06 +00:00
).
insert_atts(Var,Sk) :-
clpbn:put_atts(Var,[key(Sk)]).
add_evidence(Sk,Var) :-
skolem(Sk,D),
once(nth0(E,D,Var)),
clpbn:put_atts(_V,[key(Sk),evidence(E)]).
2012-03-22 19:10:15 +00:00
get_pfl_parameters(Id,Out) :-
factor(Id,_FList,_FV,Phi,_Constraints),
writeln(factor(Id,_FList,_FV,_Phi,_Constraints)),
( is_list(Phi) -> Out = Phi ; call(user:Phi, Out) ).
new_pfl_parameters(Id, NewPhi) :-
retract(factor(Id,FList,FV,_Phi,Constraints)),
assert(factor(Id,FList,FV,NewPhi,Constraints)),
fail.
new_pfl_parameters(_Id, _NewPhi).
get_pfl_factor_sizes(Id, DSizes) :-
factor(Id, FList, _FV, _Phi, _Constraints),
get_sizes(FList, DSizes).
get_sizes([], []).
get_sizes(Key.FList, Sz.DSizes) :-
skolem(Key, Domain),
length(Domain, Sz),
get_sizes(FList, DSizes).
% only makes sense for bayesian networks
get_first_pvariable(Id,Var) :-
factor(Id,Var._FList,_FV,_Phi,_Constraints).
% only makes sense for bayesian networks
get_factor_pvariable(Id,Var) :-
factor(Id,FList,_FV,_Phi,_Constraints),
member(Var, FList).