2:- discontiguous shrink/3. 3
14get_length(N,NA):-
15 atomic(N),
16 N \= [], !, 17 ( atom_chars(N,[-|A]) -> true ; atom_chars(N,A)), 18 length(A,NA).
19get_length(L,S):-
20 is_list(L),
21 ( L = [LIn], is_list(LIn) ->
22 get_length(LIn,S) ;
23 length(L,S)
24 ).
25
29my_compare(<,N0,N1):-
30 get_length(N0,NA0),
31 get_length(N1,NA1),
32 NA0 < NA1.
33my_compare(>,N0,N1):-
34 get_length(N0,NA0),
35 get_length(N1,NA1),
36 NA0 >= NA1. 37my_compare(=,_N0,_N1).
38
39
40simplify_element(V,V1):-
41 is_list(V),
42 maplist(simplify_element,V,V1).
43simplify_element(V,V1):-
44 float(V), 45 V1 is floor(V),
46 V1 is ceil(V).
47simplify_element(V,V).
48
53generate_shrinking_alternatives(Type,Value,ShrankList):-
54 findall(S,shrink(Type,Value,S),LS),
55 maplist(simplify_element,LS,LSimpl), !,
56 predsort(my_compare,LSimpl,ShrankList), !.
57
62shrink(Type,_,0):-
63 member(Type,[int,float,number]).
65shrink(Type,Value,ChangedSign):-
66 member(Type,[int,float,number]),
67 ChangedSign is -Value.
69shrink(Type,Value,Shrank):-
70 member(Type,[int,float,number]),
71 setting(depth,MaxAttempts),
72 setting(minVal,MinV),
73 setting(maxVal,MaxV),
74 ( Value > 0 ->
75 LB is MinV, UB = Value ;
76 LB is Value, UB is MaxV
77 ),
78 LStartingPoints = [left, right],
79 member(StartingPoint,LStartingPoints),
80 shrink_bisect_number(Type,MaxAttempts,StartingPoint,LB,UB,Shrank).
81shrink_bisect_number(Type,MaxAttempts,_,LB,UB,Shrank):-
82 member(Type,[int,float,number]),
83 MaxAttempts > 0,
84 LB < UB,
85 ( LB < 0 ->
86 Shrank is UB + LB ;
87 Shrank is UB - LB
88 ).
89shrink_bisect_number(Type,MaxAttempts,left,LB,UB,Shrank):-
90 member(Type,[int,float,number]),
91 MaxAttempts > 0,
92 LB < UB,
93 ( Type = int ->
94 LB1 is floor(LB/2) ;
95 LB1 is LB/2
96 ),
97 LB1 \= LB, 98 M1 is MaxAttempts - 1,
99 shrink_bisect_number(Type,M1,right,LB1,UB,Shrank).
100shrink_bisect_number(Type,MaxAttempts,right,LB,UB,Shrank):-
101 MaxAttempts > 0,
102 LB < UB,
103 ( Type = int ->
104 UB1 is floor(UB/2) ;
105 UB1 is UB/2
106 ),
107 UB1 \= UB, 108 M1 is MaxAttempts - 1,
109 shrink_bisect_number(Type,M1,left,LB,UB1,Shrank).
111
113sublist(List,Start,End,Sublist) :-
114 findall(El,(between(Start,End,Idx),nth1(Idx,List,El)),Sublist).
116shrink(Type,_,[]):-
117 ( Type = list ; Type = list(*,_) ).
119shrink(Type,List,Shrank):-
120 121 ( Type = list ; Type = list(*,_) ),
122 setting(depth,MaxAttempts),
123 LStartingPoints = [left,right],
124 member(StartingPoint,LStartingPoints),
125 length(List,LenList),
126 shrink_bisect_list(MaxAttempts,List,StartingPoint,1,LenList,Shrank).
127shrink_bisect_list(MaxAttempts,List,_,Start,End,Shrank):-
128 MaxAttempts > 0,
129 Start < End,
130 sublist(List,Start,End,Shrank).
132shrink_bisect_list(MaxAttempts,List,left,Start,End,Shrank):-
133 MaxAttempts > 0,
134 Start < End,
135 S1 is floor((End + Start)/2),
136 M1 is MaxAttempts - 1,
137 shrink_bisect_list(M1,List,right,S1,End,Shrank).
139shrink_bisect_list(MaxAttempts,List,right,Start,End,Shrank):-
140 MaxAttempts > 0,
141 Start < End,
142 E1 is ceil((End + Start)/2),
143 M1 is MaxAttempts - 1,
144 shrink_bisect_list(M1,List,left,Start,E1,Shrank).
145
147get_type(A,int):- integer(A).
148get_type(A,float):- float(A).
149shrink(list(N,_Types),List,Shrank):-
150 151 integer(N),
152 maplist(get_type,List,TypeIndex), 153 maplist(shrink,TypeIndex,List,Shrank).
154shrink(list(Types),List,Shrank):-
155 156 maplist(shrink,Types,List,Shrank).
158
160first_n_atom(Atom,N,OutAtom):-
161 atom_codes(Atom,LAtom),
162 length(L1,N),
163 append(L1,_,LAtom),
164 L1 \= [],
165 atom_codes(OutAtom,L1).
166shrink(atom,Atom,S):-
167 atom_codes(Atom,LAtom),
168 (length(LAtom,1) ->
169 S = Atom ;
170 shrink(list,LAtom,SList),
171 SList \= [],
172 atom_codes(S,SList)
173 ).
174shrink(atom(L,U),Atom,S):-
175 ( L = U ->
176 S = Atom ;
177 setting(depth,MaxAttempts),
178 shrink_atom_bisect(atom(L,U),MaxAttempts,Atom,S)
179 ).
180shrink_atom_bisect(atom(L,U),Depth,Atom,S):-
181 Depth > 0,
182 atom_codes(Atom,LAtom),
183 length(LAtom,N),
184 N >= L,
185 N =< U,
186 first_n_atom(Atom,L,S).
187shrink_atom_bisect(atom(L,U),Depth,Atom,S):-
188 Depth > 0,
189 L =< U,
190 L1 is floor((L+U)/2),
191 D1 is Depth - 1,
192 shrink_atom_bisect(atom(L1,U),D1,Atom,S).
194shrink(string,String,S):-
195 atom_string(Atom,String),
196 shrink(atom,Atom,SA),
197 atom_string(SA,S).
198shrink(string(L,U),String,S):-
199 atom_string(Atom,String),
200 shrink(atom(L,U),Atom,SA),
201 atom_string(SA,S).