我正在尝试编写一种天真寻找布尔公式(NNF,但不是CNF)模型的算法。
我所拥有的代码可以检查现有的模型,但是当被要求查找模型时它会失败(或者没有完成),因为它为member(X, Y)
生成无限多的[X|_], [_,X|_], [_,_,X|_]...
解决方案。 }
到目前为止我所拥有的是:
:- op(100, fy, ~).
:- op(200, xfx, /\).
:- op(200, xfx, \/).
:- op(300, xfx, =>).
:- op(300, xfx, <=>).
formula(X) :- atom(X).
formula(~X) :- formula(X).
formula(X /\ Y) :- formula(X), formula(Y).
formula(X \/ Y) :- formula(X), formula(Y).
formula(X => Y) :- formula(X), formula(Y).
formula(X <=> Y) :- formula(X), formula(Y).
model(1, _).
model(X, F) :- atom(X), member([X, 1], F).
model(~X, F) :- atom(X), member([X, 0], F). % NNF
model(A /\ B, F) :- model(A, F), model(B, F).
model(A \/ B, F) :- (model(A, F); model(B, F)).
model(A => B, F) :- model(~A \/ B, F).
model(A <=> B, F) :- model((A => B) /\ (B => A), F).
sat(A) :- model(A, F), \+ (member([X, 1], F), member([X, 0], F)).
%%% examples:
% formula(~(~ (a /\ b) \/ (c => d))).
% model(a, [[a,1]]).
F
是否有更好的数据结构,或者某些其他方式可以切断部分实例化的列表?
编辑:添加了定义和示例。
答案 0 :(得分:3)
使用clpb!
:- use_module(library(clpb)).
使用sat/1
进行示例查询:
?- sat(~(~ (A * B) + (C * D))). A = B, B = 1, sat(1#C*D).
某些变量(A
和B
)已经已经绑定到一个布尔值(在上面的查询中),但搜索尚未完成(已指示)通过剩余目标)。
要触发所有解决方案的智能强力枚举,请使用labeling/1
,如下所示:
?- sat(~(~ (A * B) + (C * D))), labeling([A,B,C,D]). A = B, B = 1, C = D, D = 0 ; A = B, B = D, D = 1, C = 0 ; A = B, B = C, C = 1, D = 0.
答案 1 :(得分:1)
我通过编写generate_model
谓词解决了这个问题,该谓词创建了一个预定义列表,每个变量只包含一个元素:
generate_model([], []).
generate_model([X|T], [[X,_]|T2]) :- generate_model(T, T2).
sat(A) :-
var_list(A, Vars),
generate_model(Vars, F),
model(A, F).
答案 2 :(得分:0)
我是否理解您,您对单一模型感到满意。您 不需要标签或sat_count。这是一个替代{{3}},与您的类似,但只会返回一致的模型。
由于它找到了计数器模型,因此需要提供公式的否定来查找模型。谓词迷宫/ 3被开发为正谓词证明/ 2的否定实现:
% Find a counter model.
% maze(+Norm,+List,-List)
maze(or(A,_),L,_) :- member(A,L), !, fail.
maze(or(A,B),L,R) :- !, inv(A,C), maze(B,[C|L],R).
maze(and(A,_),L,R) :- maze(A,L,R), !.
maze(and(_,B),L,R) :- !, maze(B,L,R).
maze(A,L,_) :- member(A,L), !, fail.
maze(A,L,M) :- oneof(L,B,R), connective(B), !,
inv(A,C), inv(B,D), maze(D,[C|R],M).
maze(A,L,[B|L]) :- inv(A,B).
它可以找到所有以下谬误的反模型:
Affirming a Disjunct: (p v q) & p => ~q.
Affirming the Consequent: (p => q) & q => p.
Commutation of Conditionals: (p => q) => (q => p).
Denying a Conjunct: ~(p & q) & ~p => q.
Denying the Antecedent: (p => q) & ~p => ~q.
Improper Transposition: (p => q) => (~p => ~q).
以下是一个示例运行:
Jekejeke Prolog 2, Runtime Library 1.2.5
(c) 1985-2017, XLOG Technologies GmbH, Switzerland
?- negcase(_,N,F), norm(F,G), maze(G,[],L),
write(N), write(': '), sort(L,R), write(R), nl, fail; true.
Affirming a Disjunct: [pos(p),pos(q)]
Affirming the Consequent: [neg(p),pos(q)]
Commutation of Conditionals: [neg(p),pos(q)]
Denying a Conjunct: [neg(p),neg(q)]
Denying the Antecedent: [neg(p),pos(q)]
Improper Transposition: [neg(p),pos(q)]
有趣的是,事情比CLP(B)快得多。以下是在CLP(B)和迷宫中运行相同问题的一些计时:
?- time((between(1,1000,_), negcaseclp(_,N,F,L),
sat(~F), once(labeling(L)), fail; true)).
% Up 296 ms, GC 3 ms, Thread Cpu 250 ms (Current 01/27/18 00:34:20)
Yes
?- time((between(1,1000,_), negcase(_,_,F),
norm(F,G), maze(G,[],_), fail; true)).
% Up 82 ms, GC 0 ms, Thread Cpu 78 ms (Current 01/27/18 00:30:21)
Yes