| 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(random),[random_permutation/2,random_member/2,random/3]). | |
| 7 | ||
| 8 | % mutation of ProB ast set expressions | |
| 9 | generate(mutation(Expression:prob_ast_set_expr),NewExpression) :- | |
| 10 | \+is_list(Expression) , | |
| 11 | random_set_expr_mutation(Expression,NewExpression). | |
| 12 | % list of set expressions, random concatenation of expression then | |
| 13 | % mutation of consisting set expressions | |
| 14 | generate(mutation(Expressions:prob_ast_set_expr),NewExpression) :- | |
| 15 | maplist(random_set_expr_mutation,Expressions,Mutated) , | |
| 16 | concatenate_ast(Mutated,[union,intersection],NewExpression). | |
| 17 | ||
| 18 | % mutation of ProB value list sets | |
| 19 | generate(mutation(L:prob_value_set),Value) :- | |
| 20 | generate(mutation(L:list),Value). | |
| 21 | ||
| 22 | % mutation of ProB value avl sets | |
| 23 | generate(mutation(avl_set(Set):prob_value_set),avl_set(Value)) :- | |
| 24 | avl_to_list(Set,AvlList) , | |
| 25 | random_permutation(AvlList,Permutation) , | |
| 26 | % don't sort values during creation of avl | |
| 27 | ord_list_to_avl(Permutation,Value). | |
| 28 | % mutate several avl sets and return a single one | |
| 29 | generate(mutation(L:prob_value_set),avl_set(Value)) :- | |
| 30 | maplist(avl_to_list,L,ListOfLists) , | |
| 31 | flatten(ListOfLists,List) , | |
| 32 | random_permutation(List,Permutation) , | |
| 33 | ord_list_to_avl(Permutation,Value). | |
| 34 | ||
| 35 | % union, intersection, set_subtraction | |
| 36 | random_set_expr_mutation(b(Expression,set(SetType),Info),b(NewExpression,set(SetType),Info)) :- | |
| 37 | Expression =.. [Type,Expr1,Expr2] , | |
| 38 | member(Type,[union,intersection,set_subtraction]) , | |
| 39 | random(0,3,R) , | |
| 40 | random_set_expr_mutation_aux(R,Expr1,Expr2,NewExpr1,NewExpr2) , | |
| 41 | NewExpression =.. [Type,NewExpr1,NewExpr2]. | |
| 42 | ||
| 43 | % general_union, general_intersection | |
| 44 | random_set_expr_mutation(b(Expression,set(SetType),Info),b(NewExpression,set(SetType),Info)) :- | |
| 45 | Expression =.. [Type,Expr] , | |
| 46 | member(Type,[general_union,general_intersection]) , | |
| 47 | Expr = b(set_extension([Set]),set(set(SetType)),ArgInfo) , | |
| 48 | % just permutation | |
| 49 | permutate_set(Set,NewSet) , | |
| 50 | NewExpr = b(set_extension([NewSet]),set(set(SetType)),ArgInfo) , | |
| 51 | NewExpression =.. [Type,NewExpr]. | |
| 52 | ||
| 53 | % if set_extension or value set is given | |
| 54 | random_set_expr_mutation(Expression,NewExpression) :- | |
| 55 | mutate_set(Expression,NewExpression). | |
| 56 | ||
| 57 | % don't mutate empty set or interval | |
| 58 | random_set_expr_mutation(Expression,Expression). | |
| 59 | ||
| 60 | random_set_expr_mutation_aux(0,Expr1,Expr2,NewExpr1,Expr2) :- | |
| 61 | random_set_expr_mutation(Expr1,NewExpr1). | |
| 62 | random_set_expr_mutation_aux(1,Expr1,Expr2,Expr1,NewExpr2) :- | |
| 63 | random_set_expr_mutation(Expr2,NewExpr2). | |
| 64 | random_set_expr_mutation_aux(2,Expr1,Expr2,NewExpr1,NewExpr2) :- | |
| 65 | random_set_expr_mutation(Expr1,NewExpr1) , | |
| 66 | random_set_expr_mutation(Expr2,NewExpr2). | |
| 67 | ||
| 68 | % mutate set_extension nodes by replacing with matching set expressions like union or set_subtraction | |
| 69 | mutate_set(b(set_extension(Set),SetType,Info),Mutation) :- | |
| 70 | (random(0,2,0) | |
| 71 | -> random_union(Set,SubSetA,SubSetB) , | |
| 72 | Temp = b(union(b(set_extension(SubSetA),SetType,Info),b(set_extension(SubSetB),SetType,Info)),SetType,[]) | |
| 73 | ; random_subtraction(Set,SetA,SetB) , | |
| 74 | Temp = b(set_subtraction(b(set_extension(SetA),SetType,Info),b(set_extension(SetB),SetType,Info)),SetType,[])) , | |
| 75 | % random choice of further mutation | |
| 76 | random(0,10,R) , | |
| 77 | (R < 7 | |
| 78 | -> Mutation = Temp | |
| 79 | ; random_set_expr_mutation(Temp,Mutation)). | |
| 80 | mutate_set(b(value(Set),SetType,Info),b(value(NewSet),SetType,Info)) :- | |
| 81 | generate(mutation(Set:prob_value_set),NewSet). | |
| 82 | ||
| 83 | % just permutate given data, no generation | |
| 84 | permutate_set(b(set_extension(Set),SetType,Info),b(set_extension(NewSet),SetType,Info)) :- | |
| 85 | generate(mutation(Set:list),NewSet). | |
| 86 | permutate_set(b(value(Set),SetType,Info),b(value(NewSet),SetType,Info)) :- | |
| 87 | generate(mutation(Set:prob_value_set),NewSet). | |
| 88 | ||
| 89 | % split a list in two sublists randomly | |
| 90 | random_union([],[],[]). | |
| 91 | random_union(List,A,B) :- | |
| 92 | length(List,Length) , | |
| 93 | generate(integer([between(1,Length)]),LengthA) , | |
| 94 | LengthB is Length - LengthA , | |
| 95 | LengthA >= 0 , LengthB >= 0 , | |
| 96 | % set length of both sublists | |
| 97 | length(A,LengthA) , | |
| 98 | length(B,LengthB) , | |
| 99 | % use append to find solutions | |
| 100 | append(A,B,List). | |
| 101 | random_union(_,[],[]). | |
| 102 | ||
| 103 | % add random list B to first argument so that A - B = List | |
| 104 | % like replace [1,2] with [1,2,3] - [3] | |
| 105 | random_subtraction(List,A,B) :- | |
| 106 | List = [b(_,Type,_)|_] , | |
| 107 | NType =.. [Type,[]] , | |
| 108 | generate(prob_ast_set(NType,[extension]),b(set_extension(B),_,_)) , | |
| 109 | append(List,B,A). |