1 | % Heinrich Heine Universitaet Duesseldorf | |
2 | % (c) 2018-2022 Lehrstuhl fuer Softwaretechnik und Programmiersprachen, | |
3 | % This software is licenced under EPL 1.0 (http://www.eclipse.org/org/documents/epl-v10.html) | |
4 | :- module(ground_truth, [get_empty_ground_truth/1, | |
5 | get_library_components_from_pred_or_expr/2, | |
6 | get_missing_components/1, | |
7 | contains_record_type/1, | |
8 | current_machine_uses_records/0, | |
9 | get_library_components_for_params_from_pred/3, | |
10 | get_ground_truth_from_operation_body/4, | |
11 | extend_ground_truth/4, | |
12 | get_library_components_from_op_ast/8]). | |
13 | ||
14 | :- use_module(library(avl)). | |
15 | :- use_module(library(sets)). | |
16 | :- use_module(library(lists)). | |
17 | :- use_module(probsrc(bmachine)). | |
18 | :- use_module(probsrc(bsyntaxtree)). | |
19 | :- use_module(probsrc(error_manager)). | |
20 | :- use_module(synthesis('deep_learning/b_machine_identifier_normalization')). | |
21 | ||
22 | :- dynamic missing_component/1,operation_parameter/1,explicit_collected_component/1. | |
23 | :- volatile missing_component/1,operation_parameter/1,explicit_collected_component/1. | |
24 | ||
25 | % NOTE:single ground truth nicht korrekt für regression (vor allem wenn multi-assignments), z.B.: a,b = a+1,b+1 braucht global nur 1 constant_integer, für single gt aber jeweils 1 constant_integer | |
26 | % single gt kombiniert zu bundled gibt dann 2 constant_integer was falsch ist | |
27 | ||
28 | % TODO: split skip component? | |
29 | ||
30 | % TODO: get_library_components_from_assignments/7 ??? | |
31 | % path="/home/joshua/STUPS/prob_examples/public_examples/B/Petri/AutoFlight_PT_03a.mch" machine="AutoFlight_PT_03a" operation="transition5668" | |
32 | ||
33 | %% contains_record_type(+Ast). | |
34 | % | |
35 | % True if the given typed ast contains at least one record type. | |
36 | contains_record_type(b(_,Type,_)) :- | |
37 | contains_record_type_aux(Type). | |
38 | ||
39 | contains_record_type_aux(field(_,_)) :- | |
40 | !. | |
41 | contains_record_type_aux(record(_)) :- | |
42 | !. | |
43 | contains_record_type_aux(Type) :- | |
44 | Type =.. [_|T], | |
45 | member(Arg, T), | |
46 | contains_record_type_aux(Arg). | |
47 | ||
48 | %% current_machine_uses_records. | |
49 | % | |
50 | % True if the current machine has a machine variable or constant of type record. | |
51 | current_machine_uses_records :- | |
52 | b_get_machine_variables(MachineVars), | |
53 | current_machine_uses_records_aux(MachineVars). | |
54 | current_machine_uses_records :- | |
55 | b_get_machine_constants(MachineConstants), | |
56 | current_machine_uses_records_aux(MachineConstants). | |
57 | ||
58 | current_machine_uses_records_aux(Vars) :- | |
59 | member(Var, Vars), | |
60 | contains_record_type(Var). | |
61 | ||
62 | %% get_missing_components(-MissingComponents) | |
63 | % | |
64 | get_missing_components(MissingComponents) :- | |
65 | findall(C, missing_component(C), MissingComponents). | |
66 | ||
67 | %% get_empty_ground_truth(-GroundTruth) | |
68 | % | |
69 | get_empty_ground_truth(GroundTruth) :- | |
70 | findall(CC, ( ground_truth_component(C), | |
71 | CC = C-0 | |
72 | ), Components), | |
73 | list_to_avl(Components, GroundTruth). | |
74 | ||
75 | %% get_empty_ground_truth(+MachineVars, -GroundTruth) | |
76 | % | |
77 | get_empty_ground_truth_for_vars(MachineVars, GroundTruth) :- | |
78 | findall((VarName,EmptyGt), ( member(b(identifier(VarName),_,_), MachineVars), | |
79 | get_empty_ground_truth(EmptyGt) | |
80 | ), GroundTruth). | |
81 | ||
82 | :- use_module(library(aggregate),[forall/2]). | |
83 | ||
84 | %% get_ground_truth_from_operation_body(+OpReturnVars, +OperationBody, +ParameterIds, -UsedComponents) | |
85 | % | |
86 | get_ground_truth_from_operation_body(OpReturnVars, OperationBody, ParameterIds, UsedComponents) :- | |
87 | b_get_machine_variables(MachineVars), | |
88 | append(MachineVars, ParameterIds, Vars), | |
89 | get_empty_ground_truth_for_vars([b(identifier(global_ground_truth_vars),_,_),b(identifier(global_ground_truth_params),_,_)|Vars], Acc), | |
90 | retractall(operation_parameter(_)), | |
91 | retractall(explicit_collected_component(_)), | |
92 | forall(member(b(identifier(Name),_,_), ParameterIds), | |
93 | ( \+ operation_parameter(Name), | |
94 | assertz(operation_parameter(Name)) | |
95 | )), | |
96 | get_library_components_from_op_ast_state(OpReturnVars, [], none, [OperationBody], _, Acc, TempUsedComponents, AssignedIds), | |
97 | !, | |
98 | % some Ids may appear in the precondition but are not assigned in the substitution, thus, missing a skip component | |
99 | find_identifier_uses(OperationBody, [], UsedIds), | |
100 | subtract(UsedIds, AssignedIds, NotAssignedIds), | |
101 | extend_ground_truth_for_vars([], NotAssignedIds, [skip], TempUsedComponents, UsedComponentsAvlList), | |
102 | ||
103 | ( Acc == UsedComponentsAvlList | |
104 | -> | |
105 | add_warning(get_ground_truth_from_operation_body, 'Empty ground truth of B components for operation/event:', [OperationBody]), | |
106 | fail | |
107 | ; post_process_operations_ground_truth(UsedComponentsAvlList, UsedComponents) | |
108 | ). | |
109 | ||
110 | post_process_operations_ground_truth([], []). | |
111 | post_process_operations_ground_truth([(VarName, GtAvl)|T], [(VarName, CleanGt)|NT]) :- | |
112 | avl_to_list(GtAvl, GtList), | |
113 | filter_used_components(GtList, [], CleanGt), | |
114 | post_process_operations_ground_truth(T, NT). | |
115 | ||
116 | wrap_list_if_flat(H, H) :- | |
117 | is_list(H), | |
118 | !. | |
119 | wrap_list_if_flat(H, [H]). | |
120 | ||
121 | split_conjunct_or_disjunct(conjunct(Lhs, Rhs), conjunct, Lhs, Rhs). | |
122 | split_conjunct_or_disjunct(disjunct(Lhs, Rhs), disjunct, Lhs, Rhs). | |
123 | ||
124 | get_parameter_ids_from_list([], []). | |
125 | get_parameter_ids_from_list([ID|T], [ID|NT]) :- | |
126 | operation_parameter(ID), | |
127 | !, | |
128 | get_parameter_ids_from_list(T, NT). | |
129 | get_parameter_ids_from_list([_|T], NT) :- | |
130 | get_parameter_ids_from_list(T, NT). | |
131 | ||
132 | % Only keep conjunct/2 and disjunct/2 if necessary for the parameters. | |
133 | get_library_components_for_params_from_pred(b(Node,_,_), Acc, UsedComponents) :- | |
134 | split_conjunct_or_disjunct(Node, Functor, Lhs, Rhs), | |
135 | !, | |
136 | find_identifier_uses(Lhs, [], UsedIdsLhs), | |
137 | find_identifier_uses(Rhs, [], UsedIdsRhs), | |
138 | get_parameter_ids_from_list(UsedIdsLhs, ParamIdsLhs), | |
139 | get_parameter_ids_from_list(UsedIdsRhs, ParamIdsRhs), | |
140 | ( ParamIdsLhs \== [] -> | |
141 | get_library_components_for_params_from_pred(Lhs, Acc, NewAcc1) | |
142 | ; NewAcc1 = Acc | |
143 | ), | |
144 | ( ParamIdsRhs \== [] -> | |
145 | get_library_components_for_params_from_pred(Rhs, NewAcc1, NewAcc2) | |
146 | ; NewAcc2 = NewAcc1 | |
147 | ), | |
148 | ( ( ParamIdsLhs \== [], | |
149 | ParamIdsRhs \== [] | |
150 | ) | |
151 | -> | |
152 | extend_ground_truth_for_vars([], [global_ground_truth_params], [Functor], NewAcc2, UsedComponents) | |
153 | ; UsedComponents = NewAcc2 | |
154 | ), | |
155 | !. | |
156 | get_library_components_for_params_from_pred(b(equal(b(identifier(Name),_,_),Rhs),_,_), Acc, UsedComponents) :- | |
157 | % like p = x + 1 and we only want to collect equal and add for p but not for x | |
158 | operation_parameter(Name), | |
159 | get_library_components_from_op_ast_state([], [equal], none, [Rhs], CarryComponentsAcc, Acc, _, _), | |
160 | !, | |
161 | extend_ground_truth_for_vars([], [Name], CarryComponentsAcc, Acc, UsedComponents). | |
162 | get_library_components_for_params_from_pred(b(Node,_,_), Acc, UsedComponents) :- | |
163 | Node =.. [Functor|Args], | |
164 | ground_truth_component(Functor), | |
165 | find_identifier_uses(b(Node,_,_), [], UsedIds), | |
166 | findall(Id, ( member(Id, UsedIds), | |
167 | operation_parameter(Id) | |
168 | ), ParamIds), | |
169 | ParamIds \== [], | |
170 | get_library_components_from_op_ast_state([], [], none, Args, CarryComponents, Acc, _, _), | |
171 | !, | |
172 | extend_ground_truth_for_vars([], [global_ground_truth_params], [Functor|CarryComponents], Acc, UsedComponents). | |
173 | get_library_components_for_params_from_pred(_, Acc, Acc). | |
174 | ||
175 | % Filter used components from avl pairs and convert to tuples. | |
176 | filter_used_components([], Acc, Acc). | |
177 | filter_used_components([Component-Amount|T], Acc, UsedComponentsList) :- | |
178 | Amount \== 0, | |
179 | !, | |
180 | filter_used_components(T, [(Component,Amount)|Acc], UsedComponentsList). | |
181 | filter_used_components([_|T], Acc, UsedComponentsList) :- | |
182 | filter_used_components(T, Acc, UsedComponentsList). | |
183 | ||
184 | %% get_library_components_from_pred_or_expr(+Ast, -UsedComponents). | |
185 | % | |
186 | % Returns the B components used in Ast as a list of tuples ComponentName-ComponentAmount. | |
187 | get_library_components_from_pred_or_expr(Ast, UsedComponentsList) :- | |
188 | % if no assignment is made in Ast, the CarryComponents are the UsedComponents | |
189 | get_empty_ground_truth(EmptyGt), | |
190 | get_library_components_from_op_ast([], [], none, Ast, CarryComponents, [], _, _), | |
191 | extend_ground_truth_for_vars([], [global], CarryComponents, [(global,EmptyGt)], UsedComponents), | |
192 | member((global,GroundTruth), UsedComponents), | |
193 | avl_to_list(GroundTruth, TempUsedComponentsList), | |
194 | filter_used_components(TempUsedComponentsList, [], UsedComponentsList). | |
195 | ||
196 | % CarryComponents used to collect components for single variables in a machine operation especially | |
197 | % when using nested operators like if-then-else. | |
198 | % Predicate fails if a component from skip_record_for_operator/1 is used. | |
199 | get_library_components_from_op_ast(ExcludeVars, CarryComponents, AssigningVar, In, NewCarryComponentsAcc, Acc, UsedComponents, AssignedIds) :- | |
200 | retractall(operation_parameter(_)), | |
201 | retractall(explicit_collected_component(_)), | |
202 | get_library_components_from_op_ast_state(ExcludeVars, CarryComponents, AssigningVar, In, NewCarryComponentsAcc, Acc, UsedComponents, AssignedIds). | |
203 | ||
204 | % Note: this predicate is not pure see operation_parameter/1 and explicit_collected_component/1. | |
205 | get_library_components_from_op_ast_state(ExcludeVars, CarryComponents, AssigningVar, In, NewCarryComponentsAcc, Acc, UsedComponents, AssignedIds) :- | |
206 | wrap_list_if_flat(In, NIn), | |
207 | get_library_components_from_op_ast_state_l(ExcludeVars, CarryComponents, AssigningVar, NIn, NewCarryComponentsAcc, Acc, UsedComponents, AssignedIds). | |
208 | ||
209 | get_library_components_from_op_ast_state_l(_, CarryComponents, _, [], CarryComponents, Acc, NewAcc, AssignedIds) :- | |
210 | !, | |
211 | NewAcc = Acc, | |
212 | AssignedIds = []. | |
213 | get_library_components_from_op_ast_state_l(ExcludeVars, CarryComponents, AssigningVar, [Ast|T], NewCarryComponentsAcc, Acc, UsedComponents, AssignedIds) :- | |
214 | Ast = b(rlevent(_Name,_Section,_Status,_Params,Guard,_Theorems,Actions,_VWitnesses,_PWitnesses,_Unmod,_AbstractEvents),_,_), | |
215 | !, | |
216 | get_library_components_for_params_from_pred(Guard, Acc, NewAcc1), | |
217 | get_library_components_from_op_ast_state(ExcludeVars, CarryComponents, AssigningVar, Actions, _, NewAcc1, NewAcc2, AssignedIds1), | |
218 | get_library_components_from_op_ast_state(ExcludeVars, CarryComponents, AssigningVar, T, NewCarryComponentsAcc, NewAcc2, UsedComponents, AssignedIds2), | |
219 | append(AssignedIds1, AssignedIds2, AssignedIds). | |
220 | get_library_components_from_op_ast_state_l(ExcludeVars, CarryComponents, AssigningVar, [b(Substitution,_,_)|T], NewCarryComponentsAcc, Acc, UsedComponents, AssignedIds) :- | |
221 | Substitution =.. [Functor,Assignments], | |
222 | ( Functor = parallel | |
223 | ; Functor = sequence | |
224 | ), | |
225 | !, | |
226 | get_library_components_from_op_ast_state(ExcludeVars, CarryComponents, AssigningVar, Assignments, _, Acc, NewAcc, AssignedIds1), | |
227 | get_library_components_from_op_ast_state(ExcludeVars, CarryComponents, AssigningVar, T, NewCarryComponentsAcc, NewAcc, UsedComponents, AssignedIds2), | |
228 | append(AssignedIds1, AssignedIds2, AssignedIds). | |
229 | get_library_components_from_op_ast_state_l(ExcludeVars, CarryComponents, AssigningVar, [b(Node,_,_)|T], NewCarryComponentsAcc, Acc, UsedComponents, AssignedIds) :- | |
230 | Node =.. [Functor,_Ids,Pred,Substitutions], | |
231 | ( Functor = let | |
232 | ; Functor = any | |
233 | ), | |
234 | !, | |
235 | get_library_components_for_params_from_pred(Pred, Acc, NewAcc1), | |
236 | get_library_components_from_op_ast_state(ExcludeVars, CarryComponents, AssigningVar, Substitutions, CarryComponentsAcc, NewAcc1, NewAcc2, AssignedIds1), | |
237 | get_library_components_from_op_ast_state(ExcludeVars, CarryComponentsAcc, AssigningVar, T, NewCarryComponentsAcc, NewAcc2, UsedComponents, AssignedIds2), | |
238 | append(AssignedIds1, AssignedIds2, AssignedIds). | |
239 | get_library_components_from_op_ast_state_l(ExcludeVars, CarryComponents, AssigningVar, [b(precondition(Pred,Substitution),_,_)|T], NewCarryComponentsAcc, Acc, UsedComponents, AssignedIds) :- | |
240 | !, | |
241 | get_library_components_for_params_from_pred(Pred, Acc, NewAcc1), | |
242 | get_library_components_from_op_ast_state(ExcludeVars, CarryComponents, AssigningVar, [Substitution], _, NewAcc1, NewAcc2, AssignedIds1), | |
243 | get_library_components_from_op_ast_state(ExcludeVars, CarryComponents, AssigningVar, T, NewCarryComponentsAcc, NewAcc2, UsedComponents, AssignedIds2), | |
244 | append(AssignedIds1, AssignedIds2, AssignedIds). | |
245 | get_library_components_from_op_ast_state_l(ExcludeVars, CarryComponents, AssigningVar, [b(select([Substitution1],Substitution),_,_)|T], NewCarryComponentsAcc, Acc, UsedComponents, AssignedIds) :- | |
246 | !, | |
247 | get_library_components_from_op_ast_state(ExcludeVars, CarryComponents, AssigningVar, [Substitution,Substitution1], _, Acc, NewAcc, AssignedIds1), | |
248 | get_library_components_from_op_ast_state(ExcludeVars, CarryComponents, AssigningVar, T, NewCarryComponentsAcc, NewAcc, UsedComponents, AssignedIds2), | |
249 | append(AssignedIds1, AssignedIds2, AssignedIds). | |
250 | get_library_components_from_op_ast_state_l(ExcludeVars, CarryComponents, AssigningVar, [b(select(Substitutions),_,_)|T], NewCarryComponentsAcc, Acc, UsedComponents, AssignedIds) :- | |
251 | !, | |
252 | get_library_components_from_op_ast_state(ExcludeVars, CarryComponents, AssigningVar, Substitutions, CarryComponentsAcc, Acc, NewAcc, AssignedIds1), | |
253 | get_library_components_from_op_ast_state(ExcludeVars, CarryComponentsAcc, AssigningVar, T, NewCarryComponentsAcc, NewAcc, UsedComponents, AssignedIds2), | |
254 | append(AssignedIds1, AssignedIds2, AssignedIds). | |
255 | get_library_components_from_op_ast_state_l(ExcludeVars, CarryComponents, AssigningVar, [b(select_when(Pred,Substitution),_,_)|T], NewCarryComponentsAcc, Acc, UsedComponents, AssignedIds) :- | |
256 | !, | |
257 | get_library_components_for_params_from_pred(Pred, Acc, NewAcc1), | |
258 | get_library_components_from_op_ast_state(ExcludeVars, CarryComponents, AssigningVar, [Substitution], CarryComponentsAcc, NewAcc1, NewAcc2, AssignedIds1), | |
259 | get_library_components_from_op_ast_state(ExcludeVars, CarryComponentsAcc, AssigningVar, T, NewCarryComponentsAcc, NewAcc2, UsedComponents, AssignedIds2), | |
260 | append(AssignedIds1, AssignedIds2, AssignedIds). | |
261 | get_library_components_from_op_ast_state_l(ExcludeVars, CarryComponents, AssigningVar, [b(if_then_else(Pred,If,Else),subst,_)|T], NewCarryComponentsAcc, Acc, UsedComponents, AssignedIds) :- | |
262 | !, | |
263 | get_library_components_from_op_ast_state(ExcludeVars, CarryComponents, AssigningVar, [Pred], CarryComponentsAccPred, Acc, _, AssignedIds1), | |
264 | get_library_components_from_op_ast_state(ExcludeVars, [if_then_else|CarryComponentsAccPred], AssigningVar, [If,Else], CarryComponentsAcc, Acc, NewAcc1, AssignedIds2), | |
265 | extend_ground_truth_for_vars(ExcludeVars, [global_ground_truth_vars], [if_then_else|CarryComponentsAccPred], NewAcc1, NewAcc2), | |
266 | get_library_components_from_op_ast_state(ExcludeVars, CarryComponentsAcc, AssigningVar, T, NewCarryComponentsAcc, NewAcc2, UsedComponents, AssignedIds3), | |
267 | append([AssignedIds1,AssignedIds2,AssignedIds3], AssignedIds). | |
268 | get_library_components_from_op_ast_state_l(ExcludeVars, CarryComponents, AssigningVar, [b(if_then_else(Pred,If,Else),_,_)|T], NewCarryComponentsAcc, Acc, UsedComponents, AssignedIds) :- | |
269 | !, | |
270 | % if_then_else expression | |
271 | get_library_components_from_op_ast_state(ExcludeVars, [if_then_else|CarryComponents], AssigningVar, [Pred,If,Else], CarryComponentsAcc, Acc, NewAcc, AssignedIds1), | |
272 | get_library_components_from_op_ast_state(ExcludeVars, CarryComponentsAcc, AssigningVar, T, NewCarryComponentsAcc, NewAcc, UsedComponents, AssignedIds2), | |
273 | append(AssignedIds1, AssignedIds2, AssignedIds). | |
274 | get_library_components_from_op_ast_state_l(ExcludeVars, CarryComponents, AssigningVar, [b(if(SubstitutionList),_,_)|T], NewCarryComponentsAcc, Acc, UsedComponents, AssignedIds) :- | |
275 | !, | |
276 | extend_ground_truth_for_vars(ExcludeVars, [global_ground_truth_vars], [if_then_else], Acc, NewAcc1), | |
277 | get_library_components_from_op_ast_state(ExcludeVars, [if_then_else|CarryComponents], AssigningVar, SubstitutionList, _, NewAcc1, NewAcc2, AssignedIds1), | |
278 | get_library_components_from_op_ast_state(ExcludeVars, CarryComponents, AssigningVar, T, NewCarryComponentsAcc, NewAcc2, UsedComponents, AssignedIds2), | |
279 | append(AssignedIds1, AssignedIds2, AssignedIds). | |
280 | get_library_components_from_op_ast_state_l(ExcludeVars, CarryComponents, AssigningVar, [b(if_elsif(Condition,Substitution),_,_)|T], NewCarryComponentsAcc, Acc, UsedComponents, AssignedIds) :- | |
281 | !, | |
282 | get_library_components_from_op_ast_state(ExcludeVars, [], AssigningVar, [Condition], CarryComponentsAccPred, Acc, _, AssignedIds1), | |
283 | extend_ground_truth_for_vars(ExcludeVars, [global_ground_truth_vars], [if_then_else|CarryComponentsAccPred], Acc, NewAcc1), | |
284 | get_library_components_from_op_ast_state(ExcludeVars, [if_then_else|CarryComponentsAccPred], AssigningVar, [Substitution], _, NewAcc1, NewAcc2, AssignedIds2), | |
285 | get_library_components_from_op_ast_state(ExcludeVars, CarryComponents, AssigningVar, T, NewCarryComponentsAcc, NewAcc2, UsedComponents, AssignedIds3), | |
286 | append([AssignedIds1,AssignedIds2,AssignedIds3], AssignedIds). | |
287 | get_library_components_from_op_ast_state_l(ExcludeVars, CarryComponents, AssigningVar, [b(assign(Ids,Assignments),_,_)|T], NewCarryComponentsAcc, Acc, UsedComponents, AssignedIds) :- | |
288 | !, | |
289 | get_library_components_from_assignments(ExcludeVars, CarryComponents, Ids, Assignments, Acc, NewAcc1, AssignedIds1), | |
290 | get_library_components_from_op_ast_state(ExcludeVars, CarryComponents, AssigningVar, T, NewCarryComponentsAcc, NewAcc1, UsedComponents, AssignedIds2), | |
291 | append(AssignedIds1, AssignedIds2, AssignedIds). | |
292 | get_library_components_from_op_ast_state_l(ExcludeVars, CarryComponents, AssigningVar, [b(identifier(_Name),_,_)|T], NewCarryComponentsAcc, Acc, UsedComponents, AssignedIds) :- | |
293 | !, | |
294 | get_library_components_from_op_ast_state(ExcludeVars, CarryComponents, AssigningVar, T, NewCarryComponentsAcc, Acc, UsedComponents, AssignedIds). | |
295 | get_library_components_from_op_ast_state_l(ExcludeVars, CarryComponents, AssigningVar, [b(skip,subst,_)|T], NewCarryComponentsAcc, Acc, UsedComponents, AssignedIds) :- | |
296 | !, | |
297 | b_get_machine_variables(MachineVars), | |
298 | findall(N, member(b(identifier(N),_,_), MachineVars), MachineVarNames), | |
299 | extend_ground_truth_for_vars(ExcludeVars, MachineVarNames, [skip|CarryComponents], Acc, NewAcc), | |
300 | get_library_components_from_op_ast_state(ExcludeVars, CarryComponents, AssigningVar, T, NewCarryComponentsAcc, NewAcc, UsedComponents, AssignedIds1), | |
301 | append(MachineVarNames, AssignedIds1, AssignedIds). | |
302 | get_library_components_from_op_ast_state_l(ExcludeVars, CarryComponents, none, [b(assign_single_id(b(identifier(Name),_,_),b(identifier(Name),_,_)),_,_)|T], NewCarryComponentsAcc, Acc, UsedComponents, [Name|AssignedIds]) :- | |
303 | !, | |
304 | extend_ground_truth_for_vars(ExcludeVars, [Name], [skip|CarryComponents], Acc, NewAcc), | |
305 | get_library_components_from_op_ast_state(ExcludeVars, CarryComponents, none, T, NewCarryComponentsAcc, NewAcc, UsedComponents, AssignedIds). | |
306 | get_library_components_from_op_ast_state_l(ExcludeVars, CarryComponents, none, [b(assign_single_id(b(identifier(Name),_,_),_),_,_)|T], NewCarryComponentsAcc, Acc, UsedComponents, [Name|AssignedIds]) :- | |
307 | % exclude assignments of operation return values | |
308 | member(b(identifier(Name),_,_), ExcludeVars), | |
309 | !, | |
310 | get_library_components_from_op_ast_state(ExcludeVars, CarryComponents, none, T, NewCarryComponentsAcc, Acc, UsedComponents, AssignedIds). | |
311 | get_library_components_from_op_ast_state_l(ExcludeVars, CarryComponents, none, [b(assign_single_id(b(identifier(Name),_,_),Arg),_,_)|T], NewCarryComponentsAcc, Acc, UsedComponents, [Name|AssignedIds]) :- | |
312 | !, | |
313 | get_library_components_from_op_ast_state(ExcludeVars, CarryComponents, none, [Arg], CarryComponentsAcc, Acc, NewAcc1, AssignedIds1), | |
314 | extend_ground_truth_for_vars(ExcludeVars, [Name], CarryComponentsAcc, NewAcc1, NewAcc2), | |
315 | get_library_components_from_op_ast_state(ExcludeVars, CarryComponents, none, T, NewCarryComponentsAcc, NewAcc2, UsedComponents, AssignedIds2), | |
316 | append(AssignedIds1, AssignedIds2, AssignedIds). | |
317 | get_library_components_from_op_ast_state_l(ExcludeVars, CarryComponents, none, [b(Node,_,_)|T], NewCarryComponentsAcc, Acc, UsedComponents, AssignedIds) :- | |
318 | % treat becomes_element_of and becomes_such like assignments when collecting components since the semantics do not matter here | |
319 | Node =.. [Functor,Ids,Arg], | |
320 | ( Functor == becomes_element_of | |
321 | ; Functor == becomes_such | |
322 | ), | |
323 | !, | |
324 | findall(Name, member(b(identifier(Name),_,_), Ids), IdNames), | |
325 | get_library_components_from_op_ast_state(ExcludeVars, CarryComponents, none, [Arg], CarryComponentsAcc, Acc, NewAcc1, AssignedIds1), | |
326 | extend_ground_truth_for_vars(ExcludeVars, IdNames, [Functor|CarryComponentsAcc], NewAcc1, NewAcc2), | |
327 | get_library_components_from_op_ast_state(ExcludeVars, CarryComponents, none, T, NewCarryComponentsAcc, NewAcc2, UsedComponents, AssignedIds2), | |
328 | append([IdNames, AssignedIds1, AssignedIds2], AssignedIds). | |
329 | get_library_components_from_op_ast_state_l(ExcludeVars, CarryComponents, AssigningVar, [Constant|T], NewCarryComponentsAcc, Acc, UsedComponents, AssignedIds) :- | |
330 | get_constant_component(Constant, ConstantComponent), | |
331 | !, | |
332 | % do not duplicate constant components for the same constant value | |
333 | ( explicit_component_not_collected_yet(Constant) -> | |
334 | CarryComponents2 = [ConstantComponent|CarryComponents] | |
335 | ; CarryComponents2 = CarryComponents | |
336 | ), | |
337 | get_library_components_from_op_ast_state(ExcludeVars, CarryComponents2, AssigningVar, T, NewCarryComponentsAcc, Acc, UsedComponents, AssignedIds). | |
338 | get_library_components_from_op_ast_state_l(ExcludeVars, CarryComponents, AssigningVar, [b(Node,_,_)|T], NewCarryComponentsAcc, Acc, UsedComponents, AssignedIds) :- | |
339 | Node =.. [Component|Args], | |
340 | \+ member(Component, [assign_single_id,assign,choice]), | |
341 | explicit_component_not_collected_yet(b(Node,_,_)), | |
342 | !, | |
343 | get_library_components_from_op_ast_state_l(ExcludeVars, [Component|CarryComponents], AssigningVar, Args, CarryComponentsAcc, Acc, NewAcc, AssignedIds), | |
344 | get_library_components_from_op_ast_state(ExcludeVars, CarryComponentsAcc, AssigningVar, T, NewCarryComponentsAcc, NewAcc, UsedComponents, AssignedIds). | |
345 | get_library_components_from_op_ast_state_l(ExcludeVars, CarryComponents, AssigningVar, [List|T], NewCarryComponentsAcc, Acc, UsedComponents, AssignedIds) :- | |
346 | is_list(List), | |
347 | !, | |
348 | get_library_components_from_op_ast_state(ExcludeVars, CarryComponents, AssigningVar, List, CarryComponentsAcc, Acc, NewAcc, AssignedIds1), | |
349 | get_library_components_from_op_ast_state(ExcludeVars, CarryComponentsAcc, AssigningVar, T, NewCarryComponentsAcc, NewAcc, UsedComponents, AssignedIds2), | |
350 | append(AssignedIds1, AssignedIds2, AssignedIds). | |
351 | get_library_components_from_op_ast_state_l(ExcludeVars, CarryComponents, AssigningVar, [b(Node,_,_)|T], NewCarryComponentsAcc, Acc, UsedComponents, AssignedIds) :- | |
352 | ( skip_record_for_operator(Node) -> | |
353 | !, | |
354 | fail | |
355 | ; true | |
356 | ), | |
357 | functor(Node, Functor, _), | |
358 | ( \+ explicit_component_not_collected_yet(b(Node,_,_)) -> | |
359 | true | |
360 | ; add_warning(get_library_components_from_op_ast, 'Warning: Skipped component with functor:', [Functor,Node]) | |
361 | ), | |
362 | get_library_components_from_op_ast_state(ExcludeVars, CarryComponents, AssigningVar, T, NewCarryComponentsAcc, Acc, UsedComponents, AssignedIds). | |
363 | ||
364 | skip_record_for_operator(assign_single_id(b(function(_,_),_,_),_)). | |
365 | skip_record_for_operator(choice(_)). | |
366 | ||
367 | ||
368 | % path="/home/joshua/STUPS/prob_examples/public_examples/B/Petri/AutoFlight_PT_03a.mch" machine="AutoFlight_PT_03a" operation="transition5668" | |
369 | get_library_components_from_assignments(_, _, [], [], Acc, Acc, []). | |
370 | get_library_components_from_assignments(ExcludeVars, CarryComponents, [Id|TId], [Assignment|TA], Acc, UsedComponents, [AssignedId|AssignedVars]) :- | |
371 | get_library_components_from_op_ast_state(ExcludeVars, CarryComponents, none, [b(assign_single_id(Id,Assignment),subst,[])], _, Acc, NewAcc1, AssignedIds), | |
372 | AssignedIds = [AssignedId], | |
373 | get_library_components_from_assignments(ExcludeVars, CarryComponents, TId, TA, NewAcc1, UsedComponents, AssignedVars). | |
374 | ||
375 | explicit_component_not_collected_yet(Ast) :- | |
376 | remove_all_infos(Ast, CleanAst), | |
377 | \+ explicit_collected_component(CleanAst), | |
378 | assertz(explicit_collected_component(CleanAst)). | |
379 | ||
380 | extend_ground_truth_for_vars(ExcludeVars, VarNames, Components, Acc, New) :- | |
381 | group_atom_list(Components, GroupedComponents), | |
382 | extend_ground_truth_for_vars_aux1(ExcludeVars, VarNames, GroupedComponents, Acc, New), | |
383 | !. | |
384 | ||
385 | extend_ground_truth_for_vars_aux1(_, [], _, Acc, Acc). | |
386 | extend_ground_truth_for_vars_aux1(ExcludeVars, [VarName|T], GroupedComponents, Acc, New) :- | |
387 | extend_ground_truth_for_vars_aux2(ExcludeVars, VarName, GroupedComponents, Acc, TempNewAcc), | |
388 | extend_ground_truth_for_vars_aux1(ExcludeVars, T, GroupedComponents, TempNewAcc, New). | |
389 | ||
390 | extend_ground_truth_for_vars_aux2(_, VarName, GroupedComponents, Acc, [(VarName,NewVarNameAcc)|TempAcc]) :- | |
391 | select((VarName,VarNameAcc), Acc, TempAcc), | |
392 | !, | |
393 | extend_ground_truth_for_vars_aux3(GroupedComponents, VarNameAcc, NewVarNameAcc). | |
394 | extend_ground_truth_for_vars_aux2(ExcludeVars, VarName, GroupedComponents, Acc, [(VarName,NewVarNameAcc)|Acc]) :- | |
395 | b_get_machine_variables(MachineVars), | |
396 | \+ member(b(identifier(VarName),_,_), MachineVars), | |
397 | \+ member(b(identifier(VarName),_,_), ExcludeVars), | |
398 | % parameter ids have been added to the accumulator beforehand | |
399 | % any missing id at this point that is no operation return variable has been introduced by a let or any | |
400 | % we collect the components used for those ids as well as parameters to insert them later on in case an id is used | |
401 | get_empty_ground_truth(EmptyGt), | |
402 | extend_ground_truth_for_vars_aux3(GroupedComponents, EmptyGt, NewVarNameAcc). | |
403 | extend_ground_truth_for_vars_aux2(_, _, _, Acc, Acc). | |
404 | ||
405 | extend_ground_truth_for_vars_aux3([], VarNameAcc, VarNameAcc). | |
406 | extend_ground_truth_for_vars_aux3([(Component,Amount)|T], VarNameAcc, NewVarNameAcc) :- | |
407 | extend_ground_truth(Component, Amount, VarNameAcc, TempVarNameAcc), | |
408 | extend_ground_truth_for_vars_aux3(T, TempVarNameAcc, NewVarNameAcc). | |
409 | ||
410 | %% extend_ground_truth(+Component, +Amount, +Old, -New). | |
411 | % | |
412 | extend_ground_truth(_, Amount, Acc, Acc) :- | |
413 | Amount =< 0, | |
414 | !. | |
415 | extend_ground_truth(Component, Amount, Old, New) :- | |
416 | extend_ground_truth(Component, Old, Acc), | |
417 | Amount1 is Amount-1, | |
418 | extend_ground_truth(Component, Amount1, Acc, New), | |
419 | !. | |
420 | ||
421 | extend_ground_truth(Component, Old, New) :- | |
422 | avl_member(Component, Old), | |
423 | !, | |
424 | avl_incr(Component, Old, 1, New). | |
425 | extend_ground_truth(Component, Old, Old) :- | |
426 | assertz(missing_component(Component)). | |
427 | ||
428 | % TODO: equal-integer? mehr komponenten? | |
429 | get_constant_component(b(integer_set('INT'),_,_), int_set). | |
430 | get_constant_component(b(integer_set('INTEGER'),_,_), integer_set). | |
431 | get_constant_component(b(integer_set('NAT'),_,_), nat_set). | |
432 | get_constant_component(b(integer_set('NAT1'),_,_), nat1_set). | |
433 | get_constant_component(b(integer_set('NATURAL'),_,_), natural_set). | |
434 | get_constant_component(b(integer_set('NATURAL1'),_,_), natural1_set). | |
435 | get_constant_component(b(bool_set,_,_), constant_set). | |
436 | get_constant_component(b(boolean_true,boolean,_), constant_boolean). | |
437 | get_constant_component(b(boolean_false,boolean,_), constant_boolean). | |
438 | get_constant_component(b(integer(_),integer,_), constant_integer). | |
439 | get_constant_component(b(string(_),string,_), constant_string). | |
440 | get_constant_component(b(couple(_,_),couple(_,_),_), constant_couple). | |
441 | get_constant_component(b(value(_),Type,_), ConstantComponent) :- | |
442 | functor(Type, TopLevelType, _), | |
443 | atom_concat(constant_, TopLevelType, ConstantComponent). | |
444 | get_constant_component(b(record_field(_,_),_,_), constant_recordfield). | |
445 | get_constant_component(b(empty_set,_,_), constant_set). | |
446 | get_constant_component(b(set_extension(_),_,_), constant_set). | |
447 | get_constant_component(b(rec(_),_,_), constant_record). | |
448 | get_constant_component(b(Node,_,_), constant_set) :- % was: constant_seq | |
449 | ( Node == empty_seq | |
450 | ; Node == empty_sequence | |
451 | ). | |
452 | get_constant_component(b(sequence_extension(_),_,_), constant_set). % was: constant_seq | |
453 | ||
454 | ground_truth_component(C) :- | |
455 | b_component(C). | |
456 | %ground_truth_component(constant_seq). | |
457 | ground_truth_component(constant_set). | |
458 | ground_truth_component(constant_couple). | |
459 | ground_truth_component(constant_boolean). | |
460 | ground_truth_component(constant_integer). | |
461 | ground_truth_component(constant_string). | |
462 | ground_truth_component(constant_recordfield). | |
463 | ground_truth_component(constant_record). | |
464 | ||
465 | group_atom_list([], []). | |
466 | group_atom_list([X], [(X,1)]). | |
467 | group_atom_list([X|T], [(X,N1)|Compressed]) :- | |
468 | findall(X, member(X, T), LX), | |
469 | length(LX, N), | |
470 | N1 is N+1, | |
471 | subtract(T, [X], NewT), | |
472 | group_atom_list(NewT, Compressed). |