1 % minimize ProB AST predicates for shrinking stage
2
3 :- use_module(library(lists)).
4 :- use_module(library(random),[random_member/2]).
5
6 minimize_pred(b(truth,pred,Info),b(truth,pred,Info)).
7
8 minimize_pred(b(falsity,pred,Info),b(falsity,pred,Info)).
9
10 % one argument predicates
11 minimize_pred(b(Pred,pred,Info),Shrunken) :-
12 Pred =.. [Type,Arg] ,
13 member(Type,[negation,finite]) ,
14 prob_is_ground(Arg,Res) ,
15 % if argument is ground interpret predicate
16 (Res = true
17 -> pint(b(Pred,pred,Info),Value) ,
18 (Value = true
19 -> Shrunken = b(truth,pred,Info)
20 ; Shrunken = b(falsity,pred,Info))
21 ; (Type = negation
22 -> minimize_pred(Arg,NewArg)
23 ; minimize_set_expr(Arg,NewArg)) ,
24 NewPred =.. [Type,NewArg] ,
25 Shrunken = b(NewPred,pred,Info)).
26
27 minimize_pred(b(exists(IDs,InnerPred),pred,Info),b(exists(IDs,NewInner),pred,Info)) :-
28 minimize_pred(InnerPred,NewInner).
29
30 minimize_pred(b(forall(IDs,Constraints,InnerPred),pred,Info),b(forall(IDs,NewConstraints,NewInner),pred,Info)) :-
31 minimize_pred(InnerPred,NewInner) ,
32 minimize_constraint_pred(Constraints,NewConstraints).
33
34 % two argument predicates
35 minimize_pred(b(Pred,pred,Info),Shrunken) :-
36 Pred =.. [Type,Arg1,Arg2] ,
37 member(Type,[conjunct,disjunct,implication,equivalence,equal,not_equal]) ,
38 prob_is_ground(Arg1,true) ,
39 prob_is_ground(Arg2,true) ,
40 pint(b(Pred,pred,Info),Value) ,
41 (Value = true
42 -> Shrunken = b(truth,pred,Info)
43 ; Shrunken = b(falsity,pred,Info)).
44 minimize_pred(b(Pred,pred,Info),Shrunken) :-
45 Pred =.. [Type,Arg1,Arg2] ,
46 member(Type,[conjunct,disjunct,implication,equivalence,equal,not_equal]) ,
47 prob_is_ground(Arg1,Res1) ,
48 prob_is_ground(Arg2,Res2) ,
49 % hold boolean value and minimize predicate
50 (Res1 = true , Res2 = false
51 -> minimize_pred(Arg2,NewArg2) ,
52 NewExpr =.. [Type,Arg1,NewArg2] ,
53 Shrunken = b(NewExpr,pred,Info)
54 ; Res1 = false , Res2 = true
55 -> minimize_pred(Arg1,NewArg1) ,
56 NewExpr =.. [Type,NewArg1,Arg2] ,
57 Shrunken = b(NewExpr,pred,Info)
58 ; % minimize both expressions
59 minimize_pred(Arg1,NewArg1) ,
60 minimize_pred(Arg2,NewArg2) ,
61 NewExpr =.. [Type,NewArg1,NewArg2] ,
62 Shrunken = b(NewExpr,pred,Info)).
63
64 % member, not_member
65 minimize_pred(b(Pred,pred,Info),Shrunken) :-
66 Pred =.. [Type,_,_] ,
67 member(Type,[member,not_member]) ,
68 pint(b(Pred,pred,Info),Value) ,
69 (Value = true
70 -> Shrunken = b(truth,pred,Info)
71 ; Shrunken = b(falsity,pred,Info)).
72
73 % skip identifier
74 minimize_pred(b(identifier(Name),Type,Info),b(identifier(Name),Type,Info)).
75
76 minimize_pred(b(Pred,pred,Info),Shrunken) :-
77 Pred =.. [_,Arg1,Arg2] ,
78 prob_is_ground(Arg1,true) ,
79 prob_is_ground(Arg2,true) ,
80 pint(b(Pred,pred,Info),Value) ,
81 (Value = true
82 -> Shrunken = b(truth,pred,Info)
83 ; Shrunken = b(falsity,pred,Info)).
84 minimize_pred(b(Pred,pred,Info),Shrunken) :-
85 Pred =.. [Type,Expr1,Expr2] ,
86 prob_is_ground(Expr1,Res1) , prob_is_ground(Expr2,Res2) ,
87 % hold boolean value and minimize integer expressions
88 ( Res1 = true , Res2 = false
89 -> (shrink(prob_ast_expr(_),Expr2,NewArg2) ; shrink(prob_ast_pred(_),Expr2,NewArg2)) ,
90 NewExpr =.. [Type,Expr1,NewArg2] ,
91 Shrunken = b(NewExpr,pred,Info)
92 ; Res1 = false , Res2 = true
93 -> (shrink(prob_ast_expr(_),Expr1,NewArg1) ; shrink(prob_ast_pred(_),Expr1,NewArg1)) ,
94 NewExpr =.. [Type,NewArg1,Expr2] ,
95 Shrunken = b(NewExpr,pred,Info)
96 ; % minimize both expressions
97 (shrink(prob_ast_expr(_),Expr1,NewArg1) ; shrink(prob_ast_pred(_),Expr1,NewArg1)) ,
98 (shrink(prob_ast_expr(_),Expr2,NewArg2) ; shrink(prob_ast_pred(_),Expr2,NewArg2)) ,
99 NewExpr =.. [Type,NewArg1,NewArg2] ,
100 Shrunken = b(NewExpr,pred,Info)).
101
102 % get one bottom predicate from an ast
103
104 % return exists or forall nodes, it's not reasonable to get their
105 % inner predicates because they need their IDs and Constraints
106 get_inner_pred(b(exists(ListOfIDs,Pred),pred,Info),b(exists(ListOfIDs,NewPred),pred,Info)) :-
107 minimize_pred(Pred,NewPred).
108 get_inner_pred(b(forall(ListOfIDs,IDConstraints,Pred),pred,Info),b(forall(ListOfIDs,IDConstraints,NewPred),pred,Info)) :-
109 minimize_pred(Pred,NewPred).
110
111 % two argument predicates
112 get_inner_pred(b(Pred,pred,Info),Shrunken) :-
113 Pred =.. [_,Arg1,Arg2] ,
114 (prob_is_ground(Arg1,Res1) ; Arg1 = b(_,integer,_)) , % only predicates
115 (prob_is_ground(Arg2,Res2) ; Arg2 = b(_,integer,_)) ,
116 ( Res1 = true , Res2 = true ->
117 % done
118 Shrunken = b(Pred,pred,Info)
119 ; % get inner predicate of second argument
120 Res1 = true , Res2 = false
121 -> get_inner_pred(Arg2,Shrunken)
122 ; % both arguments are predicates
123 Res1 = false , Res2 = false
124 -> % random choice heuristic
125 random_member(Argument,[Arg1,Arg2]) ,
126 get_inner_pred(Argument,Shrunken)
127 ; % get inner predicate of first argument
128 get_inner_pred(Arg1,Shrunken)).
129 % one argument predicates
130 get_inner_pred(b(Pred,pred,Info),Shrunken) :-
131 Pred =.. [_,Arg] ,
132 (prob_is_ground(Arg,Res) ; Arg = b(_,integer,_)) ,
133 (Res = true
134 -> Shrunken = b(Pred,pred,Info)
135 ; get_inner_pred(Arg,Shrunken)).
136
137 get_inner_pred(b(Pred,pred,Info),b(Pred,pred,Info)).
138
139 % addition to minimize constraints from forall node
140 % minimize domain from each side
141 minimize_constraint_int(b(Expr,pred,Info),b(NewExpr,pred,Info)) :-
142 Expr =.. [Type,IDNode,b(integer(Value),integer,IntInfo)] ,
143 member(Type,[less,less_equal]) ,
144 NewValue is Value - 1 ,
145 NewExpr =.. [Type,IDNode,b(integer(NewValue),integer,IntInfo)].
146 minimize_constraint_int(b(Expr,pred,Info),b(NewExpr,pred,Info)) :-
147 Expr =.. [Type,IDNode,b(integer(Value),integer,IntInfo)] ,
148 member(Type,[greater,greater_equal]) ,
149 NewValue is Value + 1 ,
150 NewExpr =.. [Type,IDNode,b(integer(NewValue),integer,IntInfo)].
151 minimize_constraint_int(b(equal(IDNode,Constraint),pred,Info),b(equal(IDNode,Constraint),pred,Info)).
152
153 % minimize cardinality of set constraints
154 minimize_constraint_pred(b(equal(Card,b(integer(Val),integer,[])),pred,Info),_,b(equal(Card,b(integer(NewVal),integer,[])),pred,Info)) :-
155 (Val = 0 -> NewVal = Val ; NewVal is Val - 1).
156 minimize_constraint_pred(Constraint,_,Constraint) :-
157 Constraint = b(member(_),_,_) , !.
158 % minimize constraints given as predicates less, less_equal, greater, greater_equal
159 % surrounded by conjunct
160 minimize_constraint_pred(b(conjunct(Constraint1,Constraint2),pred,Info),b(NewPred,pred,Info)) :-
161 minimize_constraint_int(Constraint1,NewConstraint1) ,
162 minimize_constraint_int(Constraint2,NewConstraint2) ,
163 % get identifier and integer node from the restricting predicate
164 NewConstraint1 = b(ConstrPred1,_,_) ,
165 ConstrPred1 =.. [_Pred1,IDNode,Val1] ,
166 NewConstraint2 = b(ConstrPred2,_,_) ,
167 ConstrPred2 =.. [_Pred2,IDNode,Val2] ,
168 % check if identifier node is still in use
169 %(member(IDNode,UsedIDs) ->
170 % return an equality constraint if domain is down to one value
171 (Val1 == Val2
172 -> NewPred = equal(IDNode,Val1)
173 ; NewPred = conjunct(NewConstraint1,NewConstraint2)).
174 %; NewPred = truth).
175 minimize_constraint_pred(b(conjunct(Constraint1,Constraint2),pred,Info),b(conjunct(NewConstraint1,NewConstraint2),pred,Info)) :-
176 minimize_constraint_pred(Constraint1,NewConstraint1) ,
177 minimize_constraint_pred(Constraint2,NewConstraint2).
178 % skip sequence constraints
179 minimize_constraint_pred(b(truth,pred,[]),b(truth,pred,[])) :- !.