1 :- multifile generate/2.
2 :- multifile shrink/3.
3
4 :- use_module(library(random),[random/3]).
5
6 % list of options:
7 % size:Size to set the size of record, names:NameList to specify the used names in the record
8 % if both Options are given the length of NameList will determine the size of the record
9 %
10 % the optional declaration of a NameList is useful to be able to generate
11 % different records with the same field names, so the ProB Interpreter is able to
12 % compare two records with the chance of success (different names are also accepted, but those
13 % comparisons would probably never succeed with the addition of random selected names)
14
15 generate(prob_ast_record(Type),Record) :-
16 \+is_list(Type) ,
17 generate(prob_ast_record(Type,[]),Record).
18
19 % generate a list of records with the same field names but mixed values
20 generate(prob_ast_record(Type,Options),ListOfRecords) :-
21 member(list:Size,Options) ,
22 (member(names:NameList,Options)
23 -> true
24 ; (member(size:R,Options)
25 -> true
26 ; random(1,20,R)) ,
27 generate(list(atom([size:5,alph]),[size:R]),NameList)) ,
28 length(ListOfRecords,Size) ,
29 maplist(generate(prob_ast_record(Type,[names:NameList])),ListOfRecords).
30
31 % record
32 generate(prob_ast_record(Type,Options),b(rec(Record),record(FieldTypes),[])) :-
33 member(Type,[integer(_),string(_),boolean(_),any(_)]) ,
34 (member(size:Size,Options)
35 -> true
36 ; random(1,20,Size)) ,
37 length(NType,Size) ,
38 % any or given type
39 (Type = any(InOptions)
40 -> maplist(generate(ground_type(InOptions)),NType)
41 ; length(NType,Size) ,
42 maplist(equal(Type),NType)) ,
43 (member(names:NameList,Options)
44 -> length(NameList,NewSize) ,
45 length(Record,NewSize) ,
46 % size of name list is more substantial than given size
47 length(NNType,NewSize) ,
48 maplist(equal(Type),NNType) ,
49 maplist(prob_field(ast),NNType,NameList,Record)
50 ; % list of single type to use maplist
51 length(Record,Size) ,
52 maplist(prob_field(ast),NType,Record)) ,
53 maplist(field_value_to_type,Record,FieldTypes).
54
55 equal(A,A).
56
57 % shrink single record
58 shrink(Type,b(rec(Record),RecType,Info),b(rec(Shrunken),RecType,Info)) :-
59 Type =.. [prob_ast_record|_] ,
60 shrink(list(_),Record,Temp) ,
61 % don't shrink to an empty record
62 (Temp = [] -> Shrunken = Record , ! ; Shrunken = Temp).
63 % shrink list of records
64 shrink(Type,ListOfRecords,Shrunken) :-
65 Type =.. [prob_ast_record|_] ,
66 is_list(ListOfRecords) ,
67 maplist(shrink(prob_ast_record),ListOfRecords,Shrunken).
68
69 % generation of a field used in records
70 % not defined within generate/2 to be able to use maplist with list of names
71 % ProBType is either ast or value
72 prob_field(ProBType,Type,field(VarName,FieldValue)) :-
73 generate(atom([alph,size:5]),VarName) ,
74 gen_type(Type,ProBType,NType) ,
75 generate(NType,FieldValue).
76 prob_field(ProBType,Type,VarName,field(VarName,FieldValue)) :-
77 gen_type(Type,ProBType,NType) ,
78 generate(NType,FieldValue).
79
80 % abstract value to its type in a field
81 field_value_to_type(field(VarName,FieldValue),field(VarName,FieldType)) :-
82 FieldValue = b(_,FieldType,_).