1 :- multifile generate/2.
2
3 % shrinking of all mutations defined in mutation.pl
4
5 :- use_module(library(lists),[is_list/1]).
6 :- use_module(library(sets),[subtract/3]).
7 :- use_module(library(random),[random_permutation/2,random_member/2,random/3]).
8
9 % mutation of ProB ast predicates
10 generate(mutation(Predicate:prob_ast_pred),NewPredicate) :-
11 \+is_list(Predicate) ,
12 random_pred_mutation(Predicate,NewPredicate).
13 % list of predicates, random concatenation of predicates then
14 % mutation of consisting integer and set expressions
15 generate(mutation(Predicates:prob_ast_pred),NewPredicate) :-
16 concatenate_ast(Predicates,[conjunct,disjunct,implication,equivalence],Predicate) ,
17 random_pred_mutation(Predicate,NewPredicate).
18
19 % randomly replaces ground integer, set or sequence ast nodes with a matching
20 % expression all over the predicate, ProB values get permutated
21
22 % two argument predicates
23 random_pred_mutation(b(Predicate,pred,Info),b(NewPredicate,pred,Info)) :-
24 Predicate =.. [Type,Expr1,Expr2] ,
25 random_mutation(Expr1,NewExpr1) ,
26 random_mutation(Expr2,NewExpr2) ,
27 % randomly swap predicates with a matching one
28 random(0,9,R) ,
29 (R > 4
30 -> swap_type(Type,MutatedType)
31 ; MutatedType = Type) ,
32 NewPredicate =.. [MutatedType,NewExpr1,NewExpr2].
33
34 % one argument predicates
35 random_pred_mutation(b(Predicate,pred,Info),b(NewPredicate,pred,Info)) :-
36 Predicate =.. [Type,Expr] ,
37 random_mutation(Expr,NewExpr) ,
38 NewPredicate =.. [Type,NewExpr].
39
40 random_pred_mutation(Value,Value).
41
42 % apply respective mutation
43 random_mutation(Expr,Mutation) :-
44 Expr = b(_,set(_),_) ,
45 random_set_expr_mutation(Expr,Mutation).
46 random_mutation(Expr,Mutation) :-
47 Expr = b(_,seq(_),_) ,
48 random_seq_expr_mutation(Expr,Mutation).
49 random_mutation(Expr,Mutation) :-
50 Expr = b(_,integer,_) ,
51 random_int_expr_mutation(Expr,Mutation).
52 random_mutation(Expr,Mutation) :-
53 random_pred_mutation(Expr,Mutation).
54
55 % concatenate a list of expressions or predicates by using one expression of argument Nodes
56 concatenate_ast(ListOfExpressions,Nodes,Expression) :-
57 random_permutation(ListOfExpressions,[H|Permutation]) ,
58 % use an accumulator
59 concatenate_ast(Permutation,H,Nodes,Expression).
60 concatenate_ast([],NewExpression,_,NewExpression).
61 concatenate_ast([Expression|T],Current,Nodes,NewExpression) :-
62 concatenate(Expression,Current,Nodes,NewCurrent) ,
63 % permutate rest of list
64 random_permutation(T,Permutation) ,
65 concatenate_ast(Permutation,NewCurrent,Nodes,NewExpression).
66
67 concatenate(Expression1,Expression2,Nodes,NewExpression) :-
68 random_member(SurroundingType,Nodes) ,
69 InnerType =.. [SurroundingType,Expression1,Expression2] ,
70 NewExpression = b(InnerType,integer,[]).
71
72 % change some types for mutation
73 swap_type(Type,NType) :-
74 ValidTypes = [less,less_equal,greater,greater_equal] ,
75 member(Type,ValidTypes) ,
76 % don't choose the same type for replacement
77 subtract(ValidTypes,Type,NewValidTypes) ,
78 random_member(NType,[equal,not_equal|NewValidTypes]).
79 swap_type(disjunct,conjunct).
80 swap_type(conjunct,disjunct).
81 swap_type(implication,equivalence).
82 swap_type(equivalence,implication).
83 swap_type(equal,not_equal).
84 swap_type(not_equal,equal).
85 swap_type(subset,subset_strict).
86 swap_type(subset_strict,subset).
87 swap_type(member,not_member).
88 swap_type(not_member,member).
89 swap_type(Type,Type).