syntax errors
This commit is contained in:
parent
125e676b64
commit
ef3a5754e6
@ -242,7 +242,8 @@ format_learning(_,_,_) :-
|
||||
format_learning_rule(D,'$atom'(A)):-
|
||||
format_learning(D,'~q',[A]).
|
||||
format_learning_rule(D,\+A):-
|
||||
format_learning(D,'\+',[]),
|
||||
functor( \+A, Name, _),
|
||||
format_learning(D, Name , []),
|
||||
format_learning_rule(D,A).
|
||||
|
||||
format_learning_rule(D,'true'):-
|
||||
|
@ -1,4 +1,4 @@
|
||||
%%% -*- Mode: Prolog; -*-
|
||||
%%% -*- mode: Prolog; -*-
|
||||
|
||||
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
|
||||
% ProbLog program describing a probabilistic graph
|
||||
@ -14,7 +14,7 @@
|
||||
% will run 20 iterations of learning with default settings
|
||||
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
|
||||
|
||||
%:- use_module(library(problog)).
|
||||
:- use_module(library(problog)).
|
||||
:- use_module(library(problog_learning_lbdd)).
|
||||
|
||||
%%%%
|
||||
|
@ -1,4 +1,4 @@
|
||||
:- module(clpfd, [
|
||||
:- module(gecode_clpfd, [
|
||||
op(100, yf, []),
|
||||
op(760, yfx, #<==>),
|
||||
op(750, xfy, #==>),
|
||||
@ -89,11 +89,16 @@
|
||||
|
||||
:- use_module(library(gecode)).
|
||||
:- use_module(library(maplist)).
|
||||
:- reexport(library(matrix), [(<==)/2, foreach/2, foreach/4, of/2]).
|
||||
:- reexport(library(matrix), [(<==)/2, op(600, xfx, '<=='),
|
||||
op(700, xfx, in),
|
||||
op(700, xfx, ins),
|
||||
op(450, xfx, ..), % should bind more tightly than \/
|
||||
op(710, xfx, of),
|
||||
foreach/2, foreach/4, of/2]).
|
||||
|
||||
% build array of constraints
|
||||
%
|
||||
matrix:array_extension(_.._ , clpfd:build).
|
||||
matrix:array_extension(_.._ , gecode_clpfd:build).
|
||||
|
||||
build( I..J, _, Size, L) :-
|
||||
length( L, Size ),
|
||||
@ -1035,7 +1040,7 @@ in_c(C, A, Space-Map) :-
|
||||
in_c_l(Env, V, IV) :-
|
||||
in_c(V, IV, Env).
|
||||
|
||||
user:term_expansion( ( H :- B), (H :- (clpfd:init_gecode(Space, Me), NB, clpfd:close_gecode(Space, Vs, Me)) ) ) :-
|
||||
user:term_expansion( ( H :- B), (H :- (gecode_clpfd:init_gecode(Space, Me), NB, gecode_clpfd:close_gecode(Space, Vs, Me)) ) ) :-
|
||||
process_constraints(B, NB, Env),
|
||||
term_variables(H, Vs),
|
||||
nonvar( Env ), !,
|
||||
@ -1080,7 +1085,7 @@ add_el(_G0, _El, Cs-Vs, Cs-Vs).
|
||||
attr_unify_hook(_, _) :-
|
||||
b_getval(gecode_done, true), !.
|
||||
attr_unify_hook(v(IV1,_,_), Y) :-
|
||||
( get_attr(Y, clpfd, v(IV2,_,_))
|
||||
( get_attr(Y, gecode_clpfd, v(IV2,_,_))
|
||||
->
|
||||
nb_getval(gecode_space, Space-_),
|
||||
( IV1 == IV2 -> true ;
|
||||
@ -1095,11 +1100,11 @@ attr_unify_hook(v(IV1,_,_), Y) :-
|
||||
% Translate attributes from this module to residual goals
|
||||
|
||||
attribute_goals(X) -->
|
||||
{ get_attr(X, clpfd, v(_,A,B)) },
|
||||
{ get_attr(X, gecode_clpfd, v(_,A,B)) },
|
||||
[X in A..B].
|
||||
|
||||
m(X, Y, A, B, _Map) :-
|
||||
put_attr(X, clpfd, v(Y, A, B)).
|
||||
put_attr(X, gecode_clpfd, v(Y, A, B)).
|
||||
/*
|
||||
m(NV, OV, NA, NB, Vs) :-
|
||||
var(Vs), !,
|
||||
@ -1112,7 +1117,7 @@ lm(A, B, Map, X, Y) :-
|
||||
m(X, Y, A, B, Map).
|
||||
|
||||
l(V, IV, _) :-
|
||||
get_attr(V, clpfd, v(IV, _, _)).
|
||||
get_attr(V, gecode_clpfd, v(IV, _, _)).
|
||||
/*
|
||||
l(_NV, _OV, Vs) :-
|
||||
var(Vs), !,
|
||||
@ -1127,7 +1132,7 @@ ll(Map, X, Y) :-
|
||||
l(X, Y, Map).
|
||||
|
||||
l(V, IV, A, B, _) :-
|
||||
get_attr(V, clpfd, v(IV, A, B)).
|
||||
get_attr(V, gecode_clpfd, v(IV, A, B)).
|
||||
|
||||
/*
|
||||
l(_NV, _OV, _, _, Vs) :-
|
||||
|
@ -21,9 +21,9 @@
|
||||
|
||||
:- style_check(all).
|
||||
|
||||
:- reexport(meld/meldi).
|
||||
%:- reexport(meld/meldi).
|
||||
|
||||
:- reexport(meld/meldc).
|
||||
%:- reexport(meld/meldc).
|
||||
|
||||
simulate(G) :-
|
||||
input_graph(G),
|
||||
|
@ -19,6 +19,8 @@
|
||||
sum/3
|
||||
]).
|
||||
|
||||
:- use_module(meld).
|
||||
|
||||
:- use_module(library(meld)).
|
||||
|
||||
:- use_module(library(terms), [
|
||||
|
@ -18,6 +18,8 @@
|
||||
run/1
|
||||
]).
|
||||
|
||||
:- use_module(meld).
|
||||
|
||||
|
||||
:- use_module(library(nb),
|
||||
[
|
||||
|
@ -11,6 +11,8 @@
|
||||
minval/3
|
||||
]).
|
||||
|
||||
:- use_module(meld).
|
||||
|
||||
:- dynamic extensional/3, translate/2.
|
||||
|
||||
meld_top_down_aggregate(S0, horn, _) :-
|
||||
|
@ -2,7 +2,7 @@
|
||||
% SEND + MORE = MONEY
|
||||
% Adapted from: http://en.wikipedia.org/wiki/Constraint_programming
|
||||
|
||||
:- use_module(library('bounds')).
|
||||
:- use_module(library('clpfd')).
|
||||
|
||||
sendmore(Digits) :-
|
||||
Digits = [S,E,N,D,M,O,R,Y], % Create variables
|
||||
|
Reference in New Issue
Block a user