1 :- multifile generate/2.
2
3 % shrinking of all mutations defined in mutation.pl
4
5 :- use_module(library(random),[random/3]).
6 :- use_module(library(lists),[is_list/1]).
7
8 % mutation of ProB ast sequence expressions
9 generate(mutation(Expression:prob_ast_seq_expr),NewExpression) :-
10 \+is_list(Expression) ,
11 random_seq_expr_mutation(Expression,NewExpression).
12 % list of set expressions, random concatenation of expression then
13 % mutation of consisting sequence expressions
14 generate(mutation(Expressions:prob_ast_seq_expr),NewExpression) :-
15 maplist(random_seq_expr_mutation,Expressions,Mutated) ,
16 concatenate_ast(Mutated,[concat],NewExpression).
17
18
19 % mutation of ProB value sequences
20 % value avl seq
21 generate(mutation(avl_set(Seq):prob_value_seq),avl_set(Value)) :-
22 avl_to_list(Seq,AVLList) ,
23 % remove indices to generate new ones after mutation
24 % to get well-definedness
25 findall(Key,member(Key-_,AVLList),Temp) ,
26 seq_to_list(Temp,SeqValues) ,
27 random_permutation(SeqValues,Permutation) ,
28 gen_indexed_couple_list(1,Permutation,CoupleList) ,
29 findall(Key-true,member(Key,CoupleList),ValueAVL) ,
30 list_to_avl(ValueAVL,Value).
31 generate(mutation([H|ListOfSeq]:prob_value_seq),avl_set(Value)) :-
32 H = avl_set(_) ,
33 findall(Tree,member(avl_set(Tree),[H|ListOfSeq]),Seq) ,
34 maplist(avl_to_list,Seq,Temp) ,
35 maplist(avl_list_to_list,Temp,Temp2) ,
36 maplist(seq_to_list,Temp2,List) ,
37 flatten(List,SeqValues) ,
38 random_permutation(SeqValues,Permutation) ,
39 gen_indexed_couple_list(1,Permutation,CoupleList) ,
40 findall(Key-true,member(Key,CoupleList),ValueAVL) ,
41 list_to_avl(ValueAVL,Value).
42
43 % value list seq
44 generate(mutation(Seq:prob_value_seq),Value) :-
45 flattened(Seq) ,
46 seq_to_list(Seq,SeqValues) ,
47 random_permutation(SeqValues,Permutation) ,
48 gen_indexed_couple_list(1,Permutation,Value).
49 generate(mutation(ListOfSeq:prob_value_seq),Value) :-
50 maplist(seq_to_list,ListOfSeq,Temp) ,
51 flatten(Temp,SeqValues) ,
52 random_permutation(SeqValues,Permutation) ,
53 gen_indexed_couple_list(1,Permutation,Value).
54
55 % front, tail, rev
56 random_seq_expr_mutation(b(Expr,SeqType,Info),b(NewExpr,SeqType,Info)) :-
57 Expr =.. [Type,Seq] ,
58 member(Type,[front,tail,rev]) ,
59 mutate_seq(Seq,NewSeq) ,
60 NewExpr =.. [Type,NewSeq].
61
62 % restrict_front, restrict_tail
63 random_seq_expr_mutation(b(Expr,SeqType,Info),b(NewExpr,SeqType,Info)) :-
64 Expr =.. [Type,Seq,Restriction] ,
65 member(Type,[restrict_front,restrict_tail]) ,
66 mutate_seq(Seq,NewSeq) ,
67 NewExpr =.. [Type,NewSeq,Restriction].
68
69 % concat
70 random_seq_expr_mutation(b(concat(Expr1,Expr2),SeqType,Info),b(concat(NewExpr1,NewExpr2),SeqType,Info)) :-
71 random_seq_expr_mutation(Expr1,NewExpr1) ,
72 random_seq_expr_mutation(Expr2,NewExpr2).
73
74 % insert_front
75 random_seq_expr_mutation(b(insert_front(Value,Expr),SeqType,Info),b(insert_front(Value,NewExpr),SeqType,Info)) :-
76 random_seq_expr_mutation(Expr,NewExpr).
77
78 % insert_tail
79 random_seq_expr_mutation(b(insert_tail(Expr,Value),SeqType,Info),b(insert_tail(NewExpr,Value),SeqType,Info)) :-
80 random_seq_expr_mutation(Expr,NewExpr).
81
82 % general_concat
83 random_seq_expr_mutation(b(general_concat(b(sequence_extension(InnerSeq),seq(SeqType),Info)),SeqType,OutterInfo),Mutation) :-
84 maplist(mutate_seq,InnerSeq,NewInnerSeq) ,
85 Mutation = b(general_concat(b(sequence_extension(NewInnerSeq),seq(SeqType),Info)),SeqType,OutterInfo).
86
87 % if sequence_extension or value sequence is given
88 random_seq_expr_mutation(Seq,NewSeq) :-
89 mutate_seq(Seq,NewSeq).
90
91 % don't mutate empty set
92 random_seq_expr_mutation(Expression,Expression).
93
94 % mutate sequence_extension nodes by replacing with matching sequence expressions
95 % like restrict_front, restrict_tail or concat
96 mutate_seq(b(sequence_extension(Seq),Type,Info),Mutation) :-
97 random(0,3,R) ,
98 ( R = 0
99 -> random_front_restriction(Seq,Temp,Restriction) ,
100 Temp = b(restrict_front(b(sequence_extension(Temp),Type,Info),b(integer(Restriction),integer,[])),Type,Info)
101 ; R = 1
102 -> random_tail_restriction(Seq,Temp,Restriction) ,
103 Temp = b(restrict_tail(b(sequence_extension(Temp),Type,Info),b(integer(Restriction),integer,[])),Type,Info)
104 ; random_union(Seq,SubSeqA,SubSeqB) ,
105 Temp = b(concat(b(sequence_extension(SubSeqA),Type,Info),b(sequence_extension(SubSeqB),Type,Info)),Type,[])) ,
106 % random choice of further mutation
107 random(0,10,R) ,
108 (R < 7
109 -> Mutation = Temp
110 ; random_set_expr_mutation(Temp,Mutation)).
111 mutate_seq(b(value(Seq),Type,Info),b(value(NewSeq),Type,Info)) :-
112 generate(mutation(Seq:prob_value_seq),NewSeq).
113
114 % generate random list, concatenate with given one and get restriction value
115 random_front_restriction(List,NewList,Restriction) :-
116 List = [b(_,Type,_)|_] ,
117 NType =.. [Type,[]] ,
118 generate(prob_ast_set(NType,[extension]),b(set_extension(Set),_,_)) ,
119 append(List,Set,NewList) ,
120 length(List,Restriction).
121 % tail restriction diverse to front restriction in interpretation
122 random_tail_restriction(List,NewList,Restriction) :-
123 List = [b(_,Type,_)|_] ,
124 NType =.. [Type,[]] ,
125 generate(prob_ast_set(NType,[extension]),b(set_extension(Set),_,_)) ,
126 append(Set,List,NewList) ,
127 length(Set,Restriction).