| 1 | | % (c) 2009-2025 Lehrstuhl fuer Softwaretechnik und Programmiersprachen, |
| 2 | | % Heinrich Heine Universitaet Duesseldorf |
| 3 | | % This software is licenced under EPL 1.0 (http://www.eclipse.org/org/documents/epl-v10.html) |
| 4 | | |
| 5 | | :- module(eval_strings,[ |
| 6 | | add_last_expression_to_unit_tests/0, print_last_expression/0, indent_print_last_expression/0, |
| 7 | | unsat_core_last_expression/0, |
| 8 | | recheck_pp_of_last_expression/3, |
| 9 | | last_expression_type/1, last_expression/2, get_last_result_value/3, clear_last_expression/0, |
| 10 | | print_last_info/0, print_last_value/0, browse_repl_lets/0, |
| 11 | | toggle_eval_det/0, toggle_normalising/0, |
| 12 | | eval_string/2,eval_string/3,eval_string/4,eval_string_with_time_out/4, |
| 13 | | eval_codes/6, |
| 14 | | eval_expression_codes/7, |
| 15 | | eval_file/6, |
| 16 | | toggle_observe_evaluation/0, |
| 17 | | set_eval_dot_file/1, unset_eval_dot_file/0, |
| 18 | | turn_normalising_on/0, turn_normalising_off/0, |
| 19 | | get_error_positions/1]). |
| 20 | | |
| 21 | | :- use_module(library(lists)). |
| 22 | | :- use_module(library(codesio),[format_to_codes/3]). |
| 23 | | |
| 24 | | :- use_module(error_manager). |
| 25 | | :- use_module(tools). |
| 26 | | :- use_module(debug). |
| 27 | | :- use_module(external_functions,[observe_parameters/2]). |
| 28 | | :- use_module(kernel_objects,[max_cardinality/2]). |
| 29 | | %:- use_module(b_ast_cleanup,[get_sorted_ids/2,not_occurs_in_predicate/2]). % TO DO: move predicate calling this to another module |
| 30 | | :- use_module(preferences,[get_computed_preference/2, get_preference/2, |
| 31 | | temporary_set_preference/3, reset_temporary_preference/2]). |
| 32 | | |
| 33 | | :- use_module(typing_tools,[create_maximal_type_set/2]). |
| 34 | | |
| 35 | | :- use_module(module_information,[module_info/2]). |
| 36 | | :- module_info(group,repl). |
| 37 | | :- module_info(description,'Tools to evaluate B expressions and predicates passed as strings.'). |
| 38 | | |
| 39 | | :- use_module(bmachine,[b_get_machine_constants/1,b_get_machine_variables/1, |
| 40 | | b_parse_machine_expression_from_codes/6, |
| 41 | | b_parse_machine_predicate_from_codes_open/5, |
| 42 | | b_parse_machine_subsitutions_from_codes/6]). |
| 43 | | :- use_module(wdsrc(well_def_analyser),[analyse_wd_for_expr/4, annotate_wd/2]). |
| 44 | | :- use_module(smt_solvers_interface(solver_dispatcher),[smt_solver_version/2, smt_solver_header_version/2]). |
| 45 | | :- use_module(kernel_waitflags). |
| 46 | | :- use_module(b_enumerate,[b_tighter_enumerate_values_in_ctxt/3]). |
| 47 | | :- use_module(bsyntaxtree). |
| 48 | | :- use_module(eval_let_store,[stored_let_value/3, add_stored_let_value/3, |
| 49 | | retract_stored_let_value/3, reset_let_values/0, |
| 50 | | extend_state_with_stored_lets/2, get_stored_let_typing_scope/1]). |
| 51 | | :- use_module(logger,[writeln_log/1]). |
| 52 | | |
| 53 | | |
| 54 | | :- set_prolog_flag(double_quotes, codes). |
| 55 | | |
| 56 | | % GENERAL EVAL for Expressions & Predicates |
| 57 | | |
| 58 | | eval_string(String,StringResult) :- eval_string(String,StringResult,_EnumWarning,_). |
| 59 | | eval_string(String,StringResult,EnumWarning) :- eval_string(String,StringResult,EnumWarning,_). |
| 60 | | eval_string(String,StringResult,EnumWarning,LocalState) :- % String is an atom |
| 61 | | atom_codes(String,Codes), |
| 62 | | eval_codes(Codes,exists,StringResult,EnumWarning,LocalState,_). |
| 63 | | |
| 64 | | eval_string_with_time_out(String,StringResult,EnumWarning,LocalState) :- |
| 65 | | atom_codes(String,Codes), |
| 66 | | eval_codes_with_time_out(Codes,exists,StringResult,EnumWarning,LocalState,_). |
| 67 | | |
| 68 | | % evaluate a single formula from a file |
| 69 | | % Solver is either default, or one of the solver names recognised in the REPL (sat, sat-z3, cdclt, prob, z3,...) |
| 70 | | eval_file(Solver,Filename,OuterQuantifier,StringResult,EnumWarning,TypeInfo) :- |
| 71 | | format('Solving ~w with ~w~n',[Filename,Solver]), |
| 72 | | safe_read_string_from_file(Filename,utf8,Codes), |
| 73 | | (Solver=default -> FullCodes=Codes |
| 74 | | ; translate_solver_to_prefix(Solver,Prefix) -> append(Prefix,Codes,FullCodes) |
| 75 | | ; add_error(eval_file,'Unknown solver name: ',Solver), |
| 76 | | FullCodes=Codes |
| 77 | | ), |
| 78 | | eval_codes_with_time_out(FullCodes,OuterQuantifier,StringResult,EnumWarning,_,TypeInfo), |
| 79 | | debug_println(19,eval_file(Filename,StringResult,EnumWarning)). |
| 80 | | |
| 81 | | %:- use_module(library(timeout)). |
| 82 | | :- use_module(tools_meta,[safe_time_out/3]). |
| 83 | | eval_codes_with_time_out(Codes,OuterQuantifier,StringResult,EnumWarning,LocalState,TypeInfo) :- |
| 84 | | %format("Eval: ~s~n",[Codes]), |
| 85 | | get_computed_preference(debug_time_out,DTO), |
| 86 | | %print(debug_time_out(DTO)),nl, |
| 87 | | safe_time_out(eval_codes(Codes,OuterQuantifier,StringResult,EnumWarning,LocalState,TypeInfo),DTO,TimeOutRes), |
| 88 | | (TimeOutRes=time_out -> |
| 89 | | StringResult = '**** TIME-OUT ****', print(StringResult), print(' ('),print(DTO), print('ms)'),nl, |
| 90 | | EnumWarning = time_out |
| 91 | | ; true). |
| 92 | | |
| 93 | | :- use_module(tools_meta,[call_residue/2]). |
| 94 | | :- volatile current_codes/1. |
| 95 | | :- dynamic current_codes/1. |
| 96 | | set_current_codes(C) :- retractall(current_codes(_)), assertz(current_codes(C)). |
| 97 | | %eval_codes(C,_,Res,E,L) :- print(eval_codes(C)),nl,fail. |
| 98 | | eval_codes(E,Q,Res,EnumWarning,LS,TypeInfo) :- |
| 99 | | call_residue(eval_codes2(E,Q,Res,EnumWarning,LS,TypeInfo),Residue), |
| 100 | | (Residue = [] -> true ; |
| 101 | | eval_det -> print('Call residue in eval_codes: '),print_term_summary(Residue),nl |
| 102 | | ; add_internal_error('Call residue in eval_codes: ',Residue) %,tools_printing:print_goal(Residue) |
| 103 | | ). |
| 104 | | eval_codes2(E,Q,Res,EnumWarning,LS,TypeInfo) :- |
| 105 | | set_error_context(eval_codes), |
| 106 | | reset_repl_lets, % remove invalid lets if required |
| 107 | | catch( |
| 108 | | eval_codes_aux0(E,Q,Res,EnumWarning,LS,TypeInfo), |
| 109 | | enumeration_warning(Cause,ID,_,_,_), |
| 110 | | (get_time_out_message(Cause,ID,CauseStr), |
| 111 | | format_with_colour_nl(user_output,[red,bold],'VIRTUAL TIME-OUT forced by ~w',[CauseStr]), |
| 112 | | EnumWarning = true, |
| 113 | | Res = 'TIME-OUT' |
| 114 | | )), |
| 115 | | clear_error_context. |
| 116 | | |
| 117 | | get_time_out_message(kodkod_timeout,_ProblemId,Msg) :- !, Msg = 'KODKOD'. |
| 118 | | get_time_out_message(kodkod_error,_ProblemId,Msg) :- !, Msg = 'KODKOD ERROR'. |
| 119 | | get_time_out_message(translating_for_kodkod,_Ids,Msg) :- !, Msg = 'UNABLE TO TRANSLATE TO KODKOD'. |
| 120 | | get_time_out_message(_,_,'ENUMERATION WARNING'). |
| 121 | | |
| 122 | | :- use_module(library(between),[between/3]). |
| 123 | | |
| 124 | | eval_codes_aux0("$$",_,Res,false,[],print_last_expression) :- !, Res='', |
| 125 | | print_last_expression. |
| 126 | | eval_codes_aux0("$",_,Res,false,[],print_last_info) :- !, Res='', |
| 127 | | print_last_info. |
| 128 | | eval_codes_aux0(":col",_,Res,false,[],print_last_expression) :- !, Res='', |
| 129 | | toggle_colouring. |
| 130 | | eval_codes_aux0(":recheck",_,Res,EnumWarning,[],recheck_pp_of_last_expression) :- !, |
| 131 | | recheck_pp_of_last_expression(ascii,Res,EnumWarning). |
| 132 | | eval_codes_aux0(Codes,_,Res,false,[],set_eval_repeat) :- append("!r",Rest,Codes), |
| 133 | | number_codes(Nr,Rest), !, Res='', |
| 134 | | set_eval_repeat(Nr). |
| 135 | | eval_codes_aux0(Codes,OuterQuantifier,Res,EnumWarning,LocalState,TypeInfo) :- |
| 136 | | append(":repeat ",RestC,Codes),!, |
| 137 | | (eval_repeat(Nr) -> true ; Nr=100), N1 is Nr-1, |
| 138 | ? | (between(1,N1,Try), |
| 139 | | format('>>> (~w)~n',[Try]), |
| 140 | | (eval_codes_aux0(RestC,OuterQuantifier,Res,EnumWarning,LocalState,TypeInfo) -> true), |
| 141 | | reset_errors, |
| 142 | | fail |
| 143 | | ; |
| 144 | | format('>>> (~w)~n',[Nr]), |
| 145 | | eval_codes_aux0(RestC,OuterQuantifier,Res,EnumWarning,LocalState,TypeInfo) |
| 146 | | ). |
| 147 | | eval_codes_aux0(Codes,_OuterQuantifier,Res,false,LocalState,list) :- |
| 148 | | ( append(":list ",Rest,Codes), |
| 149 | | scan_identifier(Rest,IDCodes,Rest2), atom_codes(ID,IDCodes) |
| 150 | | ; |
| 151 | | Codes = ":list", ID=help, Rest2=[]), |
| 152 | | !, |
| 153 | | (just_whitespace(Rest2) -> true ; add_error(eval_strings,'Ignoring extra argument: ',Rest2)), |
| 154 | | list_information(ID,Res,LocalState). |
| 155 | | eval_codes_aux0(Codes,OuterQuantifier,Res,EnumWarning,LocalState,TypeInfo) :- |
| 156 | | match_command(":print", Codes,PredCodes), |
| 157 | | TypeInfo=predicate(_), |
| 158 | | !, EnumWarning=false,LocalState=[], |
| 159 | | repl_parse_predicate_allow_ws(PredCodes,OuterQuantifier,Typed,TypeInfo), |
| 160 | | nested_print_repl_expression(Typed), |
| 161 | | Res=''. |
| 162 | | eval_codes_aux0(Codes,OuterQuantifier,Res,EnumWarning,LocalState,TypeInfo) :- |
| 163 | | match_command(":sym", Codes,PredCodes), |
| 164 | | TypeInfo=predicate(_), |
| 165 | | !, EnumWarning=false,LocalState=[], |
| 166 | | repl_parse_predicate_allow_ws(PredCodes,OuterQuantifier,ExTyped,TypeInfo), |
| 167 | | (is_existential_quantifier(ExTyped,_,Typed) -> true ; Typed=ExTyped), |
| 168 | | format('Computing symmetry breaking predicate for: ',[]), |
| 169 | | translate:print_bexpr(Typed),nl, |
| 170 | | smt_symmetry_breaking:get_top_level_symmetry_breaking_predicates_decomposed(Typed,TS), |
| 171 | | format('Symmetry breaking: ',[]), translate:print_bexpr(TS),nl, |
| 172 | | Res=''. |
| 173 | | eval_codes_aux0(Codes,OuterQuantifier,Res,EnumWarning,LocalState,TypeInfo) :- |
| 174 | | match_command(":check-ast",Codes,PredCodes), |
| 175 | | TypeInfo=predicate(_), |
| 176 | | !, EnumWarning=false,LocalState=[], |
| 177 | | format('Checking generated AST (Abstract Syntax Tree)~n',[]), |
| 178 | | repl_parse_predicate_allow_ws(PredCodes,OuterQuantifier,Typed,TypeInfo), |
| 179 | | (bsyntaxtree:check_ast(Typed) -> Res='TRUE' ; Res='FALSE'). |
| 180 | | eval_codes_aux0(Codes,_OuterQuantifier,Res,EnumWarning,LocalState,TypeInfo) :- |
| 181 | | match_command(":components", Codes,PredCodes), |
| 182 | | TypeInfo=predicate(_), |
| 183 | | !, EnumWarning=false,LocalState=[], |
| 184 | | repl_parse_predicate_allow_ws(PredCodes,no_quantifier,Typed,TypeInfo), |
| 185 | | predicate_components(Typed,Components), |
| 186 | | maplist(print_component,Components), |
| 187 | | Res=''. |
| 188 | | eval_codes_aux0(Codes,OuterQuantifier,Res,EnumWarning,LocalState,TypeInfo) :- |
| 189 | | match_command(":compile",Codes,PredCodes), |
| 190 | | TypeInfo=predicate(_), |
| 191 | | !, EnumWarning=false,LocalState=[], |
| 192 | | (repl_parse_predicate_allow_ws(PredCodes,OuterQuantifier,Typed,TypeInfo) |
| 193 | | -> write('Compiling: '), translate:print_bexpr(Typed),nl, |
| 194 | | get_cur_state_for_repl(Typed,State), |
| 195 | | b_compiler:b_optimize(Typed,[],[],State,NewTyped,no_wf_available), |
| 196 | | nested_print_repl_expression(NewTyped), Res='' |
| 197 | | ; add_error(eval_strings,'Illegal predicate for compiling'), |
| 198 | | Res='ERROR'). |
| 199 | | eval_codes_aux0(":wd",_,Res,EnumWarning,LocalState,analyse_wd_for_machine) :- !, |
| 200 | | EnumWarning=false,LocalState=[], |
| 201 | | well_def_analyser:analyse_wd_for_machine(_,_,Res). |
| 202 | | eval_codes_aux0(":pinv",_,Res,EnumWarning,LocalState,analyse_wd_for_machine) :- !, |
| 203 | | EnumWarning=false,LocalState=[], |
| 204 | | start_timer(T1,W1), |
| 205 | | well_def_analyser:analyse_invariants_for_machine(UnchangedNr,ProvenNr,UnProvenNr,TotPOsNr,[]), |
| 206 | | stop_timer('% Time to run wd-prover on all invariant POs: ',T1,W1), |
| 207 | | (TotPOsNr>0 -> Perc is (UnchangedNr+ProvenNr)*100/ TotPOsNr ; Perc = 100.0), |
| 208 | | format('Proof summary for ~w POs (~2f % discharged): ~w unchanged, ~w proven, ~w unproven~n', |
| 209 | | [TotPOsNr,Perc,UnchangedNr,ProvenNr,UnProvenNr]), Res=ProvenNr. |
| 210 | | eval_codes_aux0(Codes,OuterQuantifier,Res,EnumWarning,LocalState,TypeInfo) :- |
| 211 | | append(":wd ",PredCodes,Codes), |
| 212 | | !, |
| 213 | | set_current_codes(PredCodes), |
| 214 | | (TypeInfo=predicate(_),repl_parse_predicate_allow_ws(PredCodes,OuterQuantifier,Typed,TypeInfo) |
| 215 | | -> EnumWarning=false,LocalState=[], |
| 216 | | analyse_wd_for_expr(Typed,_ResStr,Discharged,message), Res=Discharged |
| 217 | | ; eval_codes_error(Res,EnumWarning,LocalState,TypeInfo) |
| 218 | | ). |
| 219 | | eval_codes_aux0(Codes,OuterQuantifier,Res,EnumWarning,LocalState,TypeInfo) :- |
| 220 | | match_command(":wde",Codes,PredCodes), % perform WD analysis and solve transformed predicate |
| 221 | | TypeInfo=predicate(_), |
| 222 | | !, |
| 223 | | repl_parse_predicate_allow_ws(PredCodes,OuterQuantifier,Typed,TypeInfo), |
| 224 | | annotate_wd(Typed,NewTyped), |
| 225 | | eval_predicate_in_cur_state(NewTyped,Res,EnumWarning,LocalState). |
| 226 | | eval_codes_aux0(Codes,OuterQuantifier,Res,EnumWarning,LocalState,TypeInfo) :- |
| 227 | | append(":check ",Rest,Codes), |
| 228 | | TypeInfo=predicate(_), |
| 229 | | !, |
| 230 | | debug_println(20,check_recognised), |
| 231 | | (eval_codes_aux(Rest,OuterQuantifier,Res,EnumWarning,LocalState,TypeInfo) |
| 232 | | -> (Res== 'TRUE' -> true ; |
| 233 | | atom_codes(S,Rest), add_error(check,':check predicate not TRUE: ',S) |
| 234 | | ) |
| 235 | | ; atom_codes(S,Rest), add_error(check,':check illegal predicate: ',S) |
| 236 | | ). |
| 237 | | eval_codes_aux0(Codes,_OuterQuantifier,RRes,EnumWarning,LocalState,TypeInfo) :- |
| 238 | | append(":exec ",Rest,Codes), |
| 239 | | TypeInfo=subst, |
| 240 | | !, |
| 241 | | debug_println(4,'parsing substitution'), |
| 242 | | repl_parse_substitution(Rest,Statement), |
| 243 | | pp_eval_expr(Statement), |
| 244 | | enter_new_error_scope(ScopeID,eval_codes_aux0),clear_all_errors_in_error_scope(ScopeID), |
| 245 | | (tcltk_interface:tcltk_add_user_executed_statement(Statement,Updates,NewID) |
| 246 | | -> format('Successfully executed statement leading to state: ~w~n',[NewID]), |
| 247 | | Res = 'TRUE',LocalState=Updates |
| 248 | | ; translate:translate_substitution(Statement,Str), |
| 249 | | format_with_colour_nl(user_output,[red],'Could not execute statement: ~w',[Str]), |
| 250 | | Res = 'FALSE',LocalState=[] |
| 251 | | ), |
| 252 | | EnumWarning=false, |
| 253 | | print('Execution result: '),display_and_set_result(ScopeID,Res,RRes,EnumWarning), |
| 254 | | (LocalState=[] -> true |
| 255 | | ; display_solution('Updates:~n',unknown,LocalState)). |
| 256 | | eval_codes_aux0(Codes,OuterQuantifier,Res,EnumWarning,LocalState,TypeInfo) :- % let ID = EXPR construct |
| 257 | | (append("let ",Rest,Codes),DotForm=false ; append(":let ",Rest,Codes), DotForm=true), |
| 258 | ? | scan_identifier(Rest,IDCodes,Rest2), |
| 259 | | atom_codes(ID,IDCodes), |
| 260 | | (scan_to_equal(Rest2,Rest3) -> true |
| 261 | | ; DotForm=false -> debug_println(19,'Missing = sign for let-construction'), |
| 262 | | fail % let mod 2 = 0 is a valid predicate |
| 263 | | ; debug_println(19,'Inserting missing = for :let'), Rest3=Rest2 |
| 264 | | ), |
| 265 | | !, |
| 266 | | debug_println(20,let_recognised(ID)), |
| 267 | | eval_codes_aux(Rest3,OuterQuantifier,Res,EnumWarning,LocalState,TypeInfo), |
| 268 | | (store_let_id_last_value(ID) -> true ; |
| 269 | | format_with_colour_nl(user_error,[red],'### Could not store let: ~w',[ID])). |
| 270 | | eval_codes_aux0(Codes,_,Res,EnumWarning,LocalState,TypeInfo) :- % :s ID : store ID extracted from last predicate |
| 271 | | (append(":s ",Rest,Codes) ; append(":store ",Rest,Codes)), |
| 272 | | scan_identifier(Rest,IDCodes,Rest2), |
| 273 | | atom_codes(ID,IDCodes), |
| 274 | | Rest2=[], % TO DO: allow whitespace |
| 275 | | !, |
| 276 | | (get_last_predicate_value_for_id(ID,T,Val) |
| 277 | | -> store_let_id_last_value(ID), translate_bvalue_with_limit_and_col(Val,50,VS), |
| 278 | | format('Stored ~w = ~w~n',[ID,VS]), Res=Val, TypeInfo = T |
| 279 | | ; format_with_colour_nl(user_error,[red],'### Could not find value for ~w in last predicate',[ID]), |
| 280 | | Res=error, TypeInfo=error), |
| 281 | | EnumWarning=false, LocalState=[]. |
| 282 | | eval_codes_aux0(Codes,_,Res,EnumWarning,LocalState,TypeInfo) :- % :u ID : remove let for ID |
| 283 | | (append(":u ",Rest,Codes) ; append(":unlet ",Rest,Codes)), |
| 284 | | scan_identifier(Rest,IDCodes,Rest2), |
| 285 | | atom_codes(ID,IDCodes), |
| 286 | | Rest2=[], % TO DO: allow whitespace |
| 287 | | !, |
| 288 | | (retract_stored_let_value(ID,_,_) -> |
| 289 | | format('Undefined let ~w~n',[ID]), Res=ID, TypeInfo = unlet, |
| 290 | | reset_parse_cache % TO DO: maybe remove just all cached expressions using ID |
| 291 | | ; format_with_colour_nl(user_error,[red],'### Could not find let for ~w. Use :b to browse your lets.',[ID]), Res=error, TypeInfo=error), |
| 292 | | EnumWarning=false, LocalState=[]. |
| 293 | | eval_codes_aux0(":b",_,Res,EnumWarning,LocalState,browsing) :- |
| 294 | | !,EnumWarning=false, LocalState=[], |
| 295 | | get_repl_lets_info(Res), print(repl_lets(Res)),nl. |
| 296 | | eval_codes_aux0(Codes,_,Res,EnumWarning,LocalState,typing) :- |
| 297 | | (append(":t ",Expression,Codes) ; append(":type ",Expression,Codes)), |
| 298 | | % :t Expression Haskell like command |
| 299 | | !, EnumWarning=false, LocalState=[], |
| 300 | | repl_typing_scope(TypingScope), |
| 301 | | (b_parse_machine_expression_from_codes(Expression,TypingScope,_Typed,Type,true,Error) |
| 302 | | -> (Error=none |
| 303 | | -> %translate:pretty_type(Type,PrettyType), % will print seq(.) |
| 304 | | create_maximal_type_set(Type,MaxTS), translate_bexpression(MaxTS,PrettyType), |
| 305 | | (max_cardinality(Type,Card) -> true ; Card='??'), |
| 306 | | ajoin([PrettyType,' /* card=',Card,' */'],Res), |
| 307 | | print(Res),nl |
| 308 | | ; (Error=type_error -> get_type_error(Res) ; Res = 'SYNTAX ERROR'), |
| 309 | | print_red('Not a valid expression'),nl) |
| 310 | | ; print_red('Parsing failed'),nl, |
| 311 | | Res = 'SYNTAX ERROR'). |
| 312 | | % TO DO: add bind(VAR,EXPR_Val) for next eval |
| 313 | | eval_codes_aux0(Codes,_,Res,EnumWarning,LocalState,TypeInfo) :- |
| 314 | | append(":find-value ",Codes1,Codes), |
| 315 | | find_value_options(Options,Codes1,ExpressionCodes), |
| 316 | | EnumWarning=false, LocalState=[], |
| 317 | | repl_parse_expression(ExpressionCodes,TExpr,TypeInfo,Error), |
| 318 | | Error=none, |
| 319 | | eval_expression_direct(TExpr,GoalValue), |
| 320 | | get_texpr_type(TExpr,Type), |
| 321 | | (Options = [Opt1|_], GoalValue \= string(_) |
| 322 | | -> add_warning(find_value,':find-value option only useful when using string as target: ',Opt1) |
| 323 | | ; true), |
| 324 | | findall(list([ID,Kind,MatchMsg]), |
| 325 | | (tcltk_interface:find_value_in_cur_state(GoalValue,Type,Options,match(Kind,ID,Path)), |
| 326 | | format_to_codes('~w~n',[Path],MatchMsgC), |
| 327 | | format('* match inside ~w ~w @ path: ~w~n',[Kind,ID,Path]), |
| 328 | | atom_codes(MatchMsg,MatchMsgC)),Res). |
| 329 | | |
| 330 | | eval_codes_aux0(Codes,_OuterQuantifier,OuterRes,false,LocalState,TypeInfo) :- TypeInfo=predicate(_), |
| 331 | ? | available_krt_prover(_,Provers,CommandStr), |
| 332 | | match_command(CommandStr,Codes,PredCodes), % commands like :pp, :ml, :krt |
| 333 | | !, |
| 334 | | % we ignore OuterQuantifier for proof commands and use forall: |
| 335 | | temporary_set_preference(use_common_subexpression_elimination,false,CHG), |
| 336 | | call_cleanup(repl_parse_predicate_allow_ws(PredCodes,forall,ExTyped,TypeInfo), |
| 337 | | reset_temporary_preference(use_common_subexpression_elimination,CHG)), |
| 338 | | LocalState=[], |
| 339 | | prove_sequent_with_krt_provers(Provers,ExTyped,Res), |
| 340 | | format('Universally quantified predicate is ',[]), |
| 341 | | (Res=proved |
| 342 | | -> print_green('PROVED'), |
| 343 | | OuterRes='TRUE' % for -evalt |
| 344 | | ; print_red(Res), |
| 345 | | OuterRes = 'UNKNOWN' % for -evalu |
| 346 | | ), |
| 347 | | format(' with ~w~n',[Provers]). |
| 348 | | eval_codes_aux0(Codes,_OuterQuantifier,Res,EnumWarning,LocalState,TypeInfo) :- TypeInfo=predicate(_), |
| 349 | | append(":forall ",PredCodes,Codes), % like krt, ml, pp command, but using ProB |
| 350 | | !, |
| 351 | | eval_codes_aux(PredCodes,forall,Res,EnumWarning,LocalState,TypeInfo). |
| 352 | | eval_codes_aux0(Codes,OuterQuantifier,Res,false,LocalState,TypeInfo) :- TypeInfo=predicate(_), |
| 353 | ? | available_smt_solver(Solver,CommandStr), % :z3, :cvc4, ... |
| 354 | | append(CommandStr,PredCodes,Codes), |
| 355 | | !, |
| 356 | | solve_using_smt_solver(Solver,PredCodes,no_prolog,OuterQuantifier,Res,LocalState,TypeInfo). |
| 357 | | eval_codes_aux0(Codes,OuterQuantifier,Res,false,LocalState,TypeInfo) :- TypeInfo=predicate(_), |
| 358 | | append(":fuzz ",Codes2,Codes), % like krt, ml, pp command, but using ProB |
| 359 | | available_smt_solver(Solver,[_|CommandStr]), % :z3-double-check, :prob-chr-double-check, ... without : |
| 360 | | append(CommandStr,PredCodes,Codes2), |
| 361 | | % typical command :fuzz prob-chr-double-check @FUZZ or :fuzz prob-double-check @FUZZ-BF-WD |
| 362 | | !, |
| 363 | | format('Fuzzing solver ~w~n',[Solver]), |
| 364 | | bb_put(fuzz_counter_nr,0), |
| 365 | | (repeat, |
| 366 | | bb_get(fuzz_counter_nr,Nr), Nr1 is Nr+1, bb_put(fuzz_counter_nr,Nr1), |
| 367 | | format('Fuzzing attempt ~w~n',[Nr1]), |
| 368 | | solve_using_smt_solver(Solver,PredCodes,no_prolog,OuterQuantifier,Res,LocalState,TypeInfo), |
| 369 | | check_error_occured(double_check_smt_result,_) |
| 370 | | ). |
| 371 | | eval_codes_aux0(":z3-version",_,Res,false,LS,TypeInfo) :- LS=[], TypeInfo=string, |
| 372 | | smt_solver_version(z3,Version), |
| 373 | | smt_solver_header_version(z3,HVersion), |
| 374 | | !, |
| 375 | | format('Z3 version is ~w (ProB was compiled against ~w)~n',[Version,HVersion]), |
| 376 | | Res = Version. |
| 377 | | eval_codes_aux0(Codes,OuterQuantifier,Res,false,LocalState,TypeInfo) :- TypeInfo=predicate(_), |
| 378 | ? | available_smt_solver_for_file(Solver,FileCommandStr), % :z3-file, ... |
| 379 | | append(FileCommandStr,FileCodes,Codes), |
| 380 | | !, |
| 381 | | solve_using_smt_solver_from_file(Solver,FileCodes,OuterQuantifier,Res,LocalState,TypeInfo). |
| 382 | | eval_codes_aux0(Codes,OuterQuantifier,Res,EnumWarning,LocalState,TypeInfo) :- %TypeInfo=predicate(_), |
| 383 | | append(":kodkod ",PredCodes,Codes), !, |
| 384 | | temporary_set_preference(use_solver_on_load,kodkod,CHG), |
| 385 | | call_cleanup(eval_codes_aux(PredCodes,OuterQuantifier,Res,EnumWarning,LocalState,TypeInfo), |
| 386 | | reset_temporary_preference(use_solver_on_load,CHG)). |
| 387 | | eval_codes_aux0(Codes,OuterQuantifier,Res,EnumWarning,LocalState,TypeInfo) :- |
| 388 | | append(":chr ",PredCodes,Codes), !, |
| 389 | | temporary_set_preference(use_chr_solver,true,CHG), |
| 390 | | call_cleanup(eval_codes_aux(PredCodes,OuterQuantifier,Res,EnumWarning,LocalState,TypeInfo), |
| 391 | | reset_temporary_preference(use_chr_solver,CHG)). |
| 392 | | eval_codes_aux0(Codes,OuterQuantifier,Res,EnumWarning,LocalState,TypeInfo) :- |
| 393 | | append(":cse ",PredCodes,Codes), !, |
| 394 | | temporary_set_preference(use_common_subexpression_elimination,true,CHG), |
| 395 | | call_cleanup(eval_codes_aux(PredCodes,OuterQuantifier,Res,EnumWarning,LocalState,TypeInfo), |
| 396 | | reset_temporary_preference(use_common_subexpression_elimination,CHG)). |
| 397 | | eval_codes_aux0(Codes,_OuterQuantifier,Res,EnumWarning,LocalState,TypeInfo) :- |
| 398 | | get_minmax_command(Codes,OptMode,LambdaExprC), % :min or :max |
| 399 | | repl_parse_expression(LambdaExprC,LambdaExpr,TypeInfo,Error), |
| 400 | | Error=none, |
| 401 | | closures:is_lambda_comprehension_set(LambdaExpr,Parameters,TypedPred,OptExpr), |
| 402 | | format(' ~w lambda expression of type ~w~n',[OptMode,TypeInfo]), |
| 403 | | !, |
| 404 | | get_cur_state_for_repl(LambdaExpr,EState), |
| 405 | | optimizing_solve_predicate(OptMode,EState, Parameters,TypedPred,OptExpr,OptVal,LocalState), |
| 406 | | translate:translate_bvalue(OptVal,OS), |
| 407 | | format('OPTIMAL VALUE = ~w~nFOR SOLUTION:~n',[OS]), |
| 408 | | display_solution('',Parameters,LocalState), |
| 409 | | Res = OS,EnumWarning=false. |
| 410 | | eval_codes_aux0(Codes,OuterQuantifier,Res,EnumWarning,LocalState,TypeInfo) :- |
| 411 | | get_minmax_command(Codes,OptMode,PredCodes), |
| 412 | | !, |
| 413 | | set_eval_mode(optimizing(OptMode)), |
| 414 | | call_cleanup(eval_codes_aux(PredCodes,OuterQuantifier,Res,EnumWarning,LocalState,TypeInfo), |
| 415 | | unset_eval_mode). |
| 416 | | |
| 417 | | eval_codes_aux0(Codes,OuterQuantifier,Res,EnumWarning,LocalState,TypeInfo) :- |
| 418 | | eval_codes_aux(Codes,OuterQuantifier,Res,EnumWarning,LocalState,TypeInfo). |
| 419 | | |
| 420 | | eval_codes_aux(Expression,_,Res,EnumWarning,LocalState,TypeInfo) :- TypeInfo=expression(_), |
| 421 | | repl_parse_expression(Expression,Typed,Type,Error), |
| 422 | | (Error=none ; Error=type_error), |
| 423 | | !, |
| 424 | | eval_expression_codes2(Typed,Type,Error,Res,EnumWarning,LocalState,TypeInfo,[]). |
| 425 | | eval_codes_aux(Expression,OuterQuantifier,Res,EnumWarning,LocalState,TypeInfo) :- |
| 426 | | TypeInfo=predicate(_), |
| 427 | | repl_parse_predicate_for_solving(Expression,OuterQuantifier,Typed,TypeInfo), |
| 428 | | !, |
| 429 | | eval_predicate_in_cur_state(Typed,Res,EnumWarning,LocalState). |
| 430 | | eval_codes_aux(_E,_,Res,EnumWarning,LocalState,TypeInfo) :- eval_codes_error(Res,EnumWarning,LocalState,TypeInfo). |
| 431 | | |
| 432 | | % an error occured: provide user feedback |
| 433 | | eval_codes_error(Res,false,[],TypeInfo) :- |
| 434 | | %findall(S,check_error_occured(S,_),L), print(errs(L)),nl, |
| 435 | ? | (check_error_occured(type_expression_error,_) -> Res = 'TYPE ERROR', TI = error |
| 436 | | ; Res = 'SYNTAX ERROR', TI = syntax_error |
| 437 | | ), |
| 438 | | show_error_pos, |
| 439 | | ((nonvar(TypeInfo),TypeInfo=predicate(_)) -> print('Not a valid predicate'),nl |
| 440 | | ; (nonvar(TypeInfo),TypeInfo=expression(_)) -> print('Not a valid expression'),nl |
| 441 | | ; print('Not a valid expression or predicate'),nl |
| 442 | | ), |
| 443 | | TypeInfo=TI. |
| 444 | | |
| 445 | | % ------------------ |
| 446 | | |
| 447 | | % a separate predicate for evaluating expressions |
| 448 | | eval_expression_codes(Expression,Res,EnumWarning,LocalState,Typed,TypeInfo,Options) :- |
| 449 | | repl_parse_expression(Expression,Typed,Type,Error), |
| 450 | | (Error=none ; Error=type_error), |
| 451 | | eval_expression_codes2(Typed,Type,Error,Res,EnumWarning,LocalState,TypeInfo,Options). |
| 452 | | eval_expression_codes2(Typed,Type,Error,Res,EnumWarning,LocalState,TypeInfo,Options) :- |
| 453 | | (Error=type_error |
| 454 | | -> show_error_pos,print('TYPE ERROR'),nl, |
| 455 | | get_type_error(Res), EnumWarning=false, LocalState=[], TypeInfo=error |
| 456 | | ; pp_eval_expr(Typed), |
| 457 | | (Type=pred |
| 458 | | -> eval_predicate_in_cur_state(Typed,Res,EnumWarning,LocalState) % happens for DEFINITIONS ?? |
| 459 | | % TypeInfo unification will fail ??? TO DO : investigate !! |
| 460 | | ; eval_expression(Typed,Res,Options), |
| 461 | | EnumWarning=false,LocalState=[]), |
| 462 | | extract_type_information(Typed,TypeInfo) |
| 463 | | ). |
| 464 | | |
| 465 | | % optionally cache parsing results, avoid overhead of Java B parser call and socket communication |
| 466 | | % especially useful for latex_processor with while loops |
| 467 | | :- dynamic parse_expr_cache/5, parse_pred_cache/5. |
| 468 | | :- use_module(library(terms),[term_hash/2]). |
| 469 | | %:- use_module(covsrc(hit_profiler),[add_profile_hit/1]). |
| 470 | | % TO DO: try number_codes, TRUE, FALSE, simple identifier to avoid calling Java |
| 471 | | repl_parse_expression(Expression,Typed,Type,Error) :- |
| 472 | | get_preference(repl_cache_parsing,true), |
| 473 | | term_hash(Expression,H),!, |
| 474 | | (parse_expr_cache(H,Expression,CTyped,CType,CError) -> true |
| 475 | | ; parse_pred_cache(H,Expression,_,_,_) |
| 476 | | -> !, fail % we have already parsed it as a predicate; fail so that we call repl_parse_predicate later |
| 477 | | ; repl_parse_expression_direct(Expression,CTyped,CType,CError), %format('Cached: ~s~n',[Expression]), |
| 478 | | assertz(parse_expr_cache(H,Expression,CTyped,CType,CError)) |
| 479 | | ), |
| 480 | | Typed=CTyped, Type=CType, Error=CError. |
| 481 | | %hit_profiler:add_profile_hit(parse_expr_cache). |
| 482 | | repl_parse_expression(Expression,Typed,Type,Error) :- |
| 483 | | repl_parse_expression_direct(Expression,Typed,Type,Error). |
| 484 | | |
| 485 | | repl_parse_expression_direct(Expression,Typed,Type,Error) :- |
| 486 | | %hit_profiler:add_profile_hit(parse_expr), |
| 487 | | set_current_codes(Expression), |
| 488 | | debug_format(20,"parsing_as_expression: '~s'~n",[Expression]), |
| 489 | | %open('repl_parsing.txt',append,S),format(S,'~s~n',[Expression]),close(S), |
| 490 | | repl_typing_scope(TypingScope), |
| 491 | | b_parse_machine_expression_from_codes(Expression,TypingScope,Typed,Type,type_errors_only,Error), |
| 492 | | debug_println(20,parse_result(Error,Type)). %translate:print_bexpr(Typed),nl, |
| 493 | | |
| 494 | | |
| 495 | | :- use_module(bmachine,[b_get_properties_from_machine/1,b_get_invariant_from_machine/1]). |
| 496 | | repl_parse_predicate_allow_ws(WS,_OuterQuantifier,Typed,TypeInfo) :- |
| 497 | | is_whitspace(WS), !, % no argument provided; use last expr |
| 498 | | (last_expression(pred,Typed,_) |
| 499 | | -> extract_type_information(Typed,TypeInfo) |
| 500 | | ; last_expression(_,_,_) -> add_error(repl_parse_predicate,'Last REPL expression is not a predicate'),fail |
| 501 | | ; add_error(repl_parse_predicate,'Evaluate a predicate first or provide it as an argument'),fail |
| 502 | | ). |
| 503 | | repl_parse_predicate_allow_ws(PredCodes,OuterQuantifier,Typed,TypeInfo) :- |
| 504 | | repl_parse_predicate(PredCodes,OuterQuantifier,Typed,TypeInfo). |
| 505 | | |
| 506 | | repl_parse_predicate_for_solving(PredCodes,OuterQuantifier,Typed,TypeInfo) :- |
| 507 | | temporary_set_preference(allow_improving_wd_mode,true,Change), |
| 508 | | % allow some left propagations of failure/truth in ast_cleanup which would be done by the solver anyway: |
| 509 | | call_cleanup(repl_parse_predicate(PredCodes,OuterQuantifier,Typed,TypeInfo), |
| 510 | | reset_temporary_preference(allow_improving_wd_mode,Change)). |
| 511 | | |
| 512 | | :- use_module(b_operation_guards,[get_unsimplified_operation_guard/2]). |
| 513 | | repl_parse_predicate("@INVARIANT",_OuterQuantifier,Typed,TypeInfo) :- |
| 514 | | b_get_invariant_from_machine(Invariant),!, |
| 515 | | Typed=Invariant,extract_type_information(Typed,TypeInfo). |
| 516 | | repl_parse_predicate("@PROPERTIES",_OuterQuantifier,Typed,TypeInfo) :- |
| 517 | | b_get_properties_from_machine(Properties),!, |
| 518 | | Typed=Properties,extract_type_information(Typed,TypeInfo). |
| 519 | | %TODO: @ASSERTIONS for b_get_assertions_from_main_machine |
| 520 | | repl_parse_predicate(Codes,_OuterQuantifier,Typed,TypeInfo) :- |
| 521 | | append("@GUARD-",SOp,Codes), |
| 522 | | atom_codes(Operation,SOp), |
| 523 | | (get_unsimplified_operation_guard(Operation,Guard) -> true |
| 524 | | ; add_error(eval_strings,'Unknown operation: ',Operation), |
| 525 | | Guard = b(falsity,pred,[]) |
| 526 | | ), |
| 527 | | Typed=Guard,extract_type_information(Typed,TypeInfo). |
| 528 | | repl_parse_predicate(Codes,_OuterQuantifier,Typed,TypeInfo) :- |
| 529 | | append("@FUZZ",Qualifier,Codes), |
| 530 | | % can be useful, e.g., in !r10000 and :repeat :prove-double-check @FUZZ-BF-IMP |
| 531 | | !, |
| 532 | | parse_fuzz_qualifier(Qualifier,RequireWD,Fuzzer), |
| 533 | | generate_fuzz_pred(Typed,RequireWD,Fuzzer), |
| 534 | | write('@FUZZ = '),translate:print_bexpr_with_limit_and_typing(Typed,20000,all),nl, flush_output, |
| 535 | | (debug_mode(on) |
| 536 | | -> tools_printing:nested_write_term_to_codes(Typed,Cs), format('% Prolog term:~n~s~n',[Cs]) ; true), |
| 537 | | extract_type_information(Typed,TypeInfo). |
| 538 | | repl_parse_predicate(Codes,OuterQuantifier,Typed,TypeInfo) :- |
| 539 | | append("@RANDOMISE",Rest,Codes),!, |
| 540 | | % example use :prove-double-check @RANDOMISE x:@INT..@INT => x*@INT <= @INT |
| 541 | | randomiser(NewCodes,Rest,[]), |
| 542 | | format('Transformed input into ~s~n',[NewCodes]), |
| 543 | | repl_parse_predicate(NewCodes,OuterQuantifier,Typed,TypeInfo). |
| 544 | | repl_parse_predicate([First|PredCodes],OuterQuantifier,Typed,TypeInfo) :- |
| 545 | | (First = 35 ; First = 64), % # or @ or #file or @file |
| 546 | | append("file",[Code1|FileCodes],PredCodes), |
| 547 | | (Code1=32 -> true ; Code1=61), % space or equal = sign |
| 548 | | (FileCodes = [46,Code2|_] % 46 is the dot. |
| 549 | | -> Code2 \= 32, Code2 \= 40 % we do not have existential quantifer #file .(PRED) |
| 550 | | % TODO: check for other whitespace than 32 (40 is open parenthesis) |
| 551 | | ; true), |
| 552 | | !, |
| 553 | | atom_codes(Filename,FileCodes), |
| 554 | | format('Reading predicate from file: ~w~n',[Filename]), |
| 555 | | statistics(walltime,[T1,_]), |
| 556 | | safe_read_string_from_file(Filename,utf8,Codes), |
| 557 | | %format('Read:~n~s~n',[Codes]),nl, |
| 558 | | statistics(walltime,[T2,_]), Delta1 is T2-T1, |
| 559 | | (debug_mode(off) -> true ; length(Codes,NrC), format('Read ~w characters in ~w ms~n',[NrC,Delta1])), |
| 560 | | (repl_get_prolog_predicate(Codes,clean_up_pred,Typed,TypeInfo) |
| 561 | | -> true |
| 562 | | ; repl_parse_predicate_direct(Codes,OuterQuantifier,Typed,TypeInfo) |
| 563 | | ), |
| 564 | | statistics(walltime,[T3,_]), Delta2 is T3-T2, |
| 565 | | (debug_mode(off) -> true ; format('Parsed and typechecked predicate in ~w ms~n',[Delta2])). |
| 566 | | repl_parse_predicate(PredCodes,OuterQuantifier,Typed,TypeInfo) :- |
| 567 | | repl_parse_predicate2(PredCodes,OuterQuantifier,Typed,TypeInfo). |
| 568 | | |
| 569 | | repl_parse_predicate2(PredCodes,OuterQuantifier,Typed,TypeInfo) :- |
| 570 | | get_preference(repl_cache_parsing,true), |
| 571 | | term_hash(PredCodes,H),!, |
| 572 | | (parse_pred_cache(H,PredCodes,OuterQuantifier,CTyped,CTypeInfo) -> true |
| 573 | | ; repl_parse_predicate_direct(PredCodes,OuterQuantifier,CTyped,CTypeInfo), |
| 574 | | assertz(parse_pred_cache(H,PredCodes,OuterQuantifier,CTyped,CTypeInfo)) |
| 575 | | ), |
| 576 | | Typed=CTyped, TypeInfo=CTypeInfo. |
| 577 | | repl_parse_predicate2(PredCodes,OuterQuantifier,Typed,TypeInfo) :- |
| 578 | | repl_parse_predicate_direct(PredCodes,OuterQuantifier,Typed,TypeInfo). |
| 579 | | |
| 580 | | repl_parse_predicate_direct(PredCodes,OuterQuantifier,Typed,TypeInfo) :- |
| 581 | | repl_typing_scope(TypingScope), |
| 582 | | b_parse_machine_predicate_from_codes_open(OuterQuantifier,PredCodes, |
| 583 | | % will also mark outer variables so that they are not removed |
| 584 | | [],TypingScope,Typed),!, |
| 585 | | pp_eval_expr(Typed), |
| 586 | | extract_type_information(Typed,TypeInfo). |
| 587 | | |
| 588 | | |
| 589 | | :- use_module(probsrc(tools), [split_chars/3]). |
| 590 | | parse_fuzz_qualifier(Codes,RequireWD,Fuzzer) :- |
| 591 | | split_chars(Codes,"-",Options), |
| 592 | | (Options = [ [] | Opt2] -> true ; Opt2=Options), |
| 593 | | qualifiers2fuzzer(Opt2,RequireWD,Fuzzer). |
| 594 | | |
| 595 | | % parse qualifiers like @FUZZ-AB-EWD or @FUZZ-SAT .... |
| 596 | | % EWD suffix: ensure WD by construction |
| 597 | | % WD suffix: filter WD by checking and failing if not WD |
| 598 | | % no suffix: accept what has been generated by the fuzzer |
| 599 | | qualifiers2fuzzer(["CLASSIC"|T],RequireWD,classic) :- !, qualifiers2reqwd(T,RequireWD,_). |
| 600 | | qualifiers2fuzzer(["IMP"|T],ReqWD,banditfuzz(Opts,implication,EnsureWD)) :- !, |
| 601 | | get_opts(T,Opts,TT), qualifiers2reqwd(TT,ReqWD,EnsureWD). |
| 602 | | qualifiers2fuzzer([Opt|T],ReqWD,banditfuzz([BFOpt|Opts],TopLevelOperator,EnsureWD)) :- |
| 603 | | core_bf_opt(Opt,BFOpt,TopLevelOperator), !, |
| 604 | | get_opts(T,Opts,TT), qualifiers2reqwd(TT,ReqWD,EnsureWD). |
| 605 | | qualifiers2fuzzer(T,ReqWD,banditfuzz(Opts,implication,EnsureWD)) :- get_opts(T,Opts,TT), Opts \= [], !, |
| 606 | | qualifiers2reqwd(TT,ReqWD,EnsureWD). |
| 607 | | qualifiers2fuzzer(T,ReqWD,banditfuzz(EnsureWD)) :- !, qualifiers2reqwd(T,ReqWD,EnsureWD). |
| 608 | | |
| 609 | | core_bf_opt("AB",atelierb_safe,implication). |
| 610 | | core_bf_opt("ARITH",arithmetic_only,implication). |
| 611 | | core_bf_opt("CNF",cnf,conjunct). |
| 612 | | core_bf_opt("SAT",sat_only,implication). |
| 613 | | core_bf_opt("Z3",z3safe,implication). |
| 614 | | |
| 615 | | get_opts(["NOREAL"|T],[use_reals(false)|OT],Rest) :- !, get_opts(T,OT,Rest). |
| 616 | | get_opts(["NOSTRING"|T],[use_strings(false)|OT],Rest) :- !, get_opts(T,OT,Rest). |
| 617 | | get_opts(["SHALLOW"|T],[size(2)|OT],Rest) :- !, get_opts(T,OT,Rest). |
| 618 | | get_opts(["DEEP"|T],[size(5)|OT],Rest) :- !, get_opts(T,OT,Rest). |
| 619 | | get_opts([SIZEN|T],[size(Size)|OT],Rest) :- |
| 620 | | append("SIZE",Digits,SIZEN), get_nr(Digits,0,Size),!, % Note : with Size=1 fuzz_node fails |
| 621 | | get_opts(T,OT,Rest). |
| 622 | | get_opts(T,[],T). |
| 623 | | |
| 624 | | get_nr([],Acc,Acc). |
| 625 | | get_nr([N|T],Acc,Res) :- Size is N-0'0, Size =< 9, |
| 626 | | NewAcc is Acc*10+Size, |
| 627 | | get_nr(T,NewAcc,Res). |
| 628 | | |
| 629 | | qualifiers2reqwd([],RequireWD,EnsureWD) :- !, RequireWD=false,EnsureWD=no. |
| 630 | | qualifiers2reqwd(["WD"],RequireWD,EnsureWD) :- !, RequireWD=true,EnsureWD=no. |
| 631 | | qualifiers2reqwd(["EWD"],RequireWD,EnsureWD) :- !, RequireWD=false,EnsureWD=ensure_wd. |
| 632 | | qualifiers2reqwd([Rest|_],true,false) :- format('Unrecognised @FUZZ qualifier: ~s~n',[Rest]). |
| 633 | | |
| 634 | | |
| 635 | | % generate a fuzzed predicated |
| 636 | | generate_fuzz_pred(Typed,RequireWD,Fuzzer) :- |
| 637 | | (current_prolog_flag(system_type,development) -> true |
| 638 | | ; add_warning(eval_string,'@FUZZ only available when running probcli from source!'), |
| 639 | | fail), |
| 640 | | fuzz_predicate(Fuzzer,Pred), |
| 641 | | %nl,write(Pred),nl, |
| 642 | | clean_up_pred(Pred,[],Typed), |
| 643 | | (RequireWD=false -> true |
| 644 | | ; % write('CHECKING WD: '), translate:print_bexpr(Typed),nl, |
| 645 | | analyse_wd_for_expr(Typed,_ResStr,Discharged,silent) % use message to see output |
| 646 | | -> (Discharged='TRUE' -> true |
| 647 | | ; generate_fuzz_pred(Typed,RequireWD,Fuzzer) %try again |
| 648 | | ) |
| 649 | | ). |
| 650 | | |
| 651 | | :- use_module(bsyntaxtree, [find_typed_identifier_uses/2,create_exists/3]). |
| 652 | | fuzz_predicate(classic,Pred) :- |
| 653 | | use_module(extension('prolog_fuzzer/fuzzing')), |
| 654 | | (generate(prob_ast_pred([]), Pred) -> true |
| 655 | | ; generate(prob_ast_pred([]), Pred) -> true % generation sometimes fails; try again |
| 656 | | ; Pred = b(truth,pred,[]) |
| 657 | | ). |
| 658 | | fuzz_predicate(banditfuzz(EnsureWD),RPred) :- |
| 659 | | use_module(extension('banditfuzz/fuzzer'),[qfuzz/1]), |
| 660 | | use_module(extension('banditfuzz/welldef'),[ensure_wd/2]), |
| 661 | | (fuzzer:qfuzz(Pred) -> true |
| 662 | | ; write(retry),nl,fuzzer:qfuzz(Pred) -> true), |
| 663 | | (find_typed_identifier_uses(Pred,Ids) -> true), |
| 664 | | create_exists(Ids,Pred,QPred), |
| 665 | | (EnsureWD=ensure_wd, % EnsureWD by adding WD POs |
| 666 | | clean_up_pred(QPred,[],Pred2),ensure_wd(Pred2,RPred) |
| 667 | | -> true |
| 668 | | ; RPred=QPred). |
| 669 | | fuzz_predicate(banditfuzz(FOpts,TLOperator,EnsureWD),RPred) :- % fuzz with a particular top-level operator as target |
| 670 | | use_module(extension('banditfuzz/bf_env'),[env/2]), |
| 671 | | use_module(extension('banditfuzz/fuzzer'),[fuzz/3]), |
| 672 | | use_module(extension('banditfuzz/welldef'),[ensure_wd/2]), |
| 673 | | (bf_env:env(FOpts,Env),fuzzer:fuzz_node(TLOperator, Env, _, Pred) -> true |
| 674 | | ; add_warning(banditfuzz,'Fuzzing failed with options: ',FOpts), fail), |
| 675 | | (EnsureWD=ensure_wd,clean_up_pred(Pred,[],Pred2),ensure_wd(Pred2,RPred) -> true ; RPred=Pred). |
| 676 | | |
| 677 | | % ----------------- |
| 678 | | |
| 679 | | :- use_module(library(random),[random/3, random/1]). |
| 680 | ? | randomiser(Res) --> "@",random_int(Low,Up),!, |
| 681 | | {random(Low, Up, R), |
| 682 | | number_codes(R,Codes), |
| 683 | | append(Codes,T,Res)}, |
| 684 | | randomiser(T). |
| 685 | | randomiser([H|T]) --> [H],!, randomiser(T). |
| 686 | | randomiser([]) --> "". |
| 687 | | |
| 688 | | random_int(-9223372036854775809,9223372036854775808) --> "INTEGER". |
| 689 | | random_int(-1024,1024) --> "INT". |
| 690 | | random_int(1,1024) --> "NAT1". |
| 691 | | random_int(0,1024) --> "NAT". |
| 692 | | |
| 693 | | |
| 694 | | % ------------------ |
| 695 | | |
| 696 | | is_whitspace(Codes) :- is_whitspace(Codes,[]). |
| 697 | | is_whitspace --> " ",is_whitspace. |
| 698 | | is_whitspace --> "". |
| 699 | | |
| 700 | | match_command(Command,Codes,Arguments) :- |
| 701 | | append(Command,Args,Codes), % command matched |
| 702 | | (Args = [32|Rest] -> Arguments = Rest |
| 703 | | ; Args=[] -> Arguments = []). % no whitespace after; also allow as command without args |
| 704 | | |
| 705 | | repl_parse_substitution(Codes,Typed) :- |
| 706 | | repl_typing_scope(TypingScope), |
| 707 | | delete(TypingScope,variables,IntScope), % remove variables; otherwise we get clash warnings |
| 708 | | delete(IntScope,variables_and_additional_defs,SubstScope), % ditto; but makes additional defs unavailable |
| 709 | | % we could also always allow calling operations in expressions? |
| 710 | | b_parse_machine_subsitutions_from_codes(Codes,[operation_bodies|SubstScope], |
| 711 | | Typed,_Type,true,Error), |
| 712 | | (Error=none -> true ; add_error(eval_strings,'Error occured while parsing substitution: ',Error),fail). |
| 713 | | |
| 714 | | |
| 715 | | % repeat a pretty-printed version of the expression/predicate that is evaluated |
| 716 | | pp_eval_expr(Typed) :- |
| 717 | | % nl,nl,print('SOLVING:'),nl,nested_print_bexpr(Typed),nl,nl, |
| 718 | | % get_texpr_type(Typed,Type), |
| 719 | | (preferences:get_preference(repl_unicode,true) -> |
| 720 | | translate_subst_or_bexpr_in_mode(unicode,Typed,UnicodeString), |
| 721 | | format(' ~w ~w~n',['\x21DD\',UnicodeString]) |
| 722 | | ; true). |
| 723 | | |
| 724 | | extract_type_information(b(exists(Parameters,_Typed),pred,_),predicate(exists(Parameters))) :- !. |
| 725 | | extract_type_information(b(forall(Parameters,_LHS,_RHS),pred,_),predicate(forall(Parameters))) :- !. |
| 726 | | extract_type_information(b(_,pred,_),predicate(no_outer_quantifier)) :- !. |
| 727 | | extract_type_information(b(_,T,_),expression(T)). |
| 728 | | |
| 729 | | %:- use_module(library(timeout)). |
| 730 | | %:- use_module(library(file_systems)). |
| 731 | | |
| 732 | | % |
| 733 | | % |
| 734 | | % eval_rule_file removed; now use: probcli -eval_rule_file /Users/leuschel/svn_root/NewProBPrivate/examples/B/Siemens/RuleValidation/Deploy/AssociativityXY_3_type.v /Users/leuschel/svn_root/NewProBPrivate/examples/B/Siemens/RuleValidation/MainRuleBaseFile.mch |
| 735 | | |
| 736 | | % performance benchmark: |
| 737 | | % time(eval_strings:test_parser('examples/Rules/sample.rule')). |
| 738 | | % time(eval_strings:test_parser('examples/Rules/sample2.rule')). |
| 739 | | % time(eval_strings:test_parser('examples/Rules/sudoku.rule')). |
| 740 | | :- public test_parser/1. |
| 741 | | test_parser(File) :- print(processing_rule_file(File)),nl, |
| 742 | | safe_read_string_from_file(File,utf8,Codes),print(parsing),nl, |
| 743 | | repl_typing_scope(TypingScope), |
| 744 | | b_parse_machine_predicate_from_codes_open(exists,Codes,[],TypingScope, |
| 745 | | _Typed), |
| 746 | | print(done),nl. |
| 747 | | |
| 748 | | |
| 749 | | % ---------- |
| 750 | | % EXPRESSIONS |
| 751 | | % ---------- |
| 752 | | |
| 753 | | :- use_module(state_space,[current_state_id/1]). |
| 754 | | :- use_module(store). |
| 755 | | :- use_module(translate). |
| 756 | | :- use_module(b_interpreter). |
| 757 | | |
| 758 | | :- meta_predicate probcli_clpfd_overflow_mnf_call1(0). |
| 759 | | :- meta_predicate probcli_clpfd_overflow_call1(0). |
| 760 | | |
| 761 | | :- dynamic last_expansion_time/1. |
| 762 | | |
| 763 | | :- use_module(eval_let_store,[extend_state_with_probids_and_lets/2]). |
| 764 | | :- use_module(specfile, [get_current_state_for_b_formula/2]). |
| 765 | | % get state for REPL as required by the provided typed expression/predicate |
| 766 | | get_cur_state_for_repl(Typed,State) :- |
| 767 | | retractall(last_expansion_time(_)), |
| 768 | | statistics(walltime,[T1,_]), |
| 769 | | get_current_state_for_b_formula(Typed,State1), |
| 770 | | extend_state_with_probids_and_lets(State1,State), |
| 771 | | statistics(walltime,[T2,_]), Delta is T2-T1, |
| 772 | | assertz(last_expansion_time(Delta)). |
| 773 | | |
| 774 | | |
| 775 | | |
| 776 | | :- use_module(kodkodsrc(kodkod), [current_solver_is_not_incremental/0]). |
| 777 | | replace_expression_by_kodkod_if_enabled(Typed,NewExpression) :- |
| 778 | | (replace_expression_by_kodkod_if_enabled_aux(Typed,NewExpression) -> true |
| 779 | | ; NewExpression=Typed). |
| 780 | | replace_expression_by_kodkod_if_enabled_aux(Typed,NewExpression) :- |
| 781 | | % do :kodkod replacment inside set comprehensions |
| 782 | | get_texpr_expr(Typed,comprehension_set(Ids,Pred)), |
| 783 | | get_preference(use_solver_on_load,kodkod), |
| 784 | | \+ current_solver_is_not_incremental, % otherwise we cannot get all solutions |
| 785 | | replace_kodkod_if_enabled(Ids,Pred,NewPred), % TO DO: we could pass a parameter that says we want all solutions here |
| 786 | | get_preference(kodkod_symmetry_level,Symm), |
| 787 | | (Symm > 0 , Pred \= NewPred |
| 788 | | -> get_texpr_ids(Ids,I), |
| 789 | | add_warning(kodkod,'KODKOD_SYMMETRY > 0, not all solutions to set comprehension may be computed: ',I,Typed) |
| 790 | | % it seems too late now to set symmetry to 0; problem already loaded ?!? |
| 791 | | ; true), |
| 792 | | get_texpr_info(Typed,Info),get_texpr_type(Typed,Type), |
| 793 | | create_texpr(comprehension_set(Ids,NewPred),Type,Info,NewExpression). |
| 794 | | |
| 795 | | |
| 796 | | eval_expression_direct(Typed,Value) :- |
| 797 | | get_cur_state_for_repl(Typed,EState), |
| 798 | | eval_expression_direct(Typed,EState,Value). |
| 799 | | eval_expression_direct(Typed,EState,Value) :- |
| 800 | | probcli_clpfd_overflow_mnf_call1(b_interpreter:b_compute_expression_nowf(Typed,[],EState,Value,'none',0)). |
| 801 | | |
| 802 | | eval_expression(Typed,RRes,Options) :- eval_expression(Typed,RRes,_PrologTerm,Options). |
| 803 | | |
| 804 | | % EnumWarnings are no longer returned but thrown if problematic |
| 805 | | eval_expression(Typed,RRes,NValue,Options) :- %% print('Start Eval Expression: '),nl,flush_output, |
| 806 | | enter_new_error_scope(ScopeID,eval_expression), |
| 807 | | clear_all_errors_in_error_scope(ScopeID), |
| 808 | | replace_expression_by_kodkod_if_enabled(Typed,Typed2), |
| 809 | | set_last_expression(expr,Typed2,exception), |
| 810 | | debug_println(5,'Start Eval Expression'), |
| 811 | | %profile_reset, set_prolog_flag(profiling,on), % comment in to profile individual expression evaluations |
| 812 | | (eval_expression_direct(Typed2,Value) |
| 813 | | -> true |
| 814 | | ; set_last_expression(expr,Typed2,error),fail % probably wd-error |
| 815 | | ), |
| 816 | | !, |
| 817 | | %set_prolog_flag(profiling,off), print_profile, % comment in to profile individual expression evaluations |
| 818 | | debug_println(5,'Normalising Value'), |
| 819 | | normalise_eval_value(Value,NValue), |
| 820 | | set_last_expression(expr,Typed2,NValue), |
| 821 | | (member(silent_no_string_result,Options) -> RRes = '?' |
| 822 | | ; |
| 823 | | debug_println(5,'Translating Value'), |
| 824 | | translate_bvalue_with_col(NValue,Typed2,Result), |
| 825 | | %get_only_critical_enum_warning(EnumWarning), |
| 826 | | start_terminal_colour([dark_gray],user_output), |
| 827 | | format(user_output,'Expression Value = ~n',[]), % TO DO: make output optional, e.g., for json trace replay |
| 828 | | reset_terminal_colour(user_output), |
| 829 | | display_and_set_result(ScopeID,Result,RRes,false), |
| 830 | | display_dot_expr_result(Typed2,NValue) % TO DO: if we have a let with ID: use ID rather than result |
| 831 | | ). |
| 832 | | eval_expression(_,Cause,error,_) :- |
| 833 | | get_fail_error_cause(Cause), % TO DO: refactor and use abort_error_occured_in_error_scope,... |
| 834 | | exit_error_scope(_ScopeID,_,eval_expression). |
| 835 | | |
| 836 | | |
| 837 | | :- dynamic normalising_off/0. |
| 838 | | toggle_normalising :- print('% Normalising Result Values: '), |
| 839 | | (retract(normalising_off) -> print('ON') |
| 840 | | ; assertz(normalising_off),print('OFF')),nl. |
| 841 | | turn_normalising_off :- (normalising_off -> true ; assertz(normalising_off)). |
| 842 | | turn_normalising_on :- retractall(normalising_off). |
| 843 | | |
| 844 | | normalise_eval_value(Value,NValue) :- normalising_off,!, |
| 845 | | start_norm_timer(NT,NWT), |
| 846 | | NValue=Value, stop_norm_timer(NT,NWT). |
| 847 | | normalise_eval_value(Value,NValue) :- |
| 848 | | %EXPAND=limit(100000), % expand up until 100,000 elements; don't expand SYMBOLIC |
| 849 | | EXPAND=force, % don't expand definitely infinite sets + sets known larger than 20,000 |
| 850 | | % but sets marked with prob_annotation('SYMBOLIC') may be expanded! |
| 851 | | debug_println(20,normalising(Value)), |
| 852 | | start_norm_timer(NT,NWT), |
| 853 | | ( store:normalise_value_for_var(eval_strings,EXPAND,Value,NValue), |
| 854 | | stop_norm_timer(NT,NWT) |
| 855 | | -> true |
| 856 | | ; stop_norm_timer(NT,NWT), |
| 857 | | print_red('Could not normalise value:'),nl, |
| 858 | | NValue=Value |
| 859 | | ). |
| 860 | | |
| 861 | | get_fail_error_cause(Cause) :- |
| 862 | | logged_error(identifier_not_found,_B,_C,_D), % print(logged_error(identifier_not_found,B,_C,_D)), |
| 863 | | %atom_codes(B,Codes), append("Cannot find identifier",_,Codes), |
| 864 | | !, |
| 865 | | Cause = 'IDENTIFIER(S) NOT YET INITIALISED; INITIALISE MACHINE FIRST'. |
| 866 | | get_fail_error_cause('NOT-WELL-DEFINED'). |
| 867 | | |
| 868 | | get_type_error(Cause) :- logged_error(A,B,_C,_D), % print(logged_error(A,B,C,D)), |
| 869 | | A=type_expression_error, |
| 870 | | atom_codes(B,Codes), |
| 871 | | append("Unknown identifier",_,Codes),!, |
| 872 | | Cause = 'UNKNOWN IDENTIFIER(S)'. |
| 873 | | get_type_error('TYPE ERROR'). |
| 874 | | |
| 875 | | |
| 876 | | % ----------------- |
| 877 | | |
| 878 | | |
| 879 | | |
| 880 | | % options in REPL for :find-value |
| 881 | | find_value_options([prefix]) --> "prefix ". |
| 882 | | find_value_options([suffix]) --> "suffix ". |
| 883 | | find_value_options([exact]) --> "exact ". |
| 884 | | find_value_options([fuzzy]) --> "fuzzy ". |
| 885 | | find_value_options([infix]) --> "infix ". |
| 886 | | find_value_options([]) --> "". |
| 887 | | |
| 888 | | |
| 889 | | % ---------- |
| 890 | | % PREDICATES |
| 891 | | % ---------- |
| 892 | | |
| 893 | | |
| 894 | | :- volatile eval_repeat/1. |
| 895 | | :- dynamic eval_repeat/1. |
| 896 | | |
| 897 | | set_eval_repeat(X) :- format('Finding ~w first solutions for predicates~n',[X]), |
| 898 | | retractall(eval_repeat(_)),assertz(eval_repeat(X)). |
| 899 | | |
| 900 | | :- use_module(succeed_max,[succeed_max_call_id/3]). %succeed_max_call_id('$setup_constants',member(_,_),1) |
| 901 | | test_bool_exists(EState, Parameters,Typed,LocalState,WF) :- eval_repeat(Nr), |
| 902 | | format_with_colour_nl(user_output,[dark_gray],'** Finding first ~w solutions',[Nr]), |
| 903 | | call_residue(succeed_max_call_id(test_bool_exists, |
| 904 | | eval_strings:test_bool_exists2(EState, Parameters,Typed,LocalState,WF),Nr),Residue), |
| 905 | | display_solution('Solution:~n',Parameters,LocalState), |
| 906 | | (Residue = [] -> true ; print_red('RESIDUE = '), print_red(Residue),nl), |
| 907 | | fail. |
| 908 | | test_bool_exists(EState, Parameters,Typed,LocalState,WF) :- |
| 909 | ? | test_bool_exists2(EState, Parameters,Typed,LocalState,WF). |
| 910 | | |
| 911 | | :- use_module(extrasrc(optimizing_solver),[optimizing_solve_predicate/5,optimizing_solve_predicate/7]). |
| 912 | | get_minmax_command(Codes,maximizing,PredCodes) :- append(":max ",PredCodes,Codes). |
| 913 | | get_minmax_command(Codes,minimizing,PredCodes) :- append(":min ",PredCodes,Codes). |
| 914 | | test_bool_exists2(EState, Parameters,Typed,LocalState,_WF) :- eval_mode(optimizing(OptMode)), !, |
| 915 | | optimizing_solve_predicate(OptMode,EState, Parameters,Typed,LocalState). |
| 916 | | test_bool_exists2(EState, Parameters,Typed,LocalState,WF) :- \+ eval_det, !, |
| 917 | | % evaluate component wise |
| 918 | | %init_wait_flags(WF,[expansion_context(test_bool_exists2,Parameters)]), |
| 919 | | init_quantifier_wait_flag(no_wf_available,exists,Parameters,FreshOutputVars,unknown,WF), |
| 920 | ? | b_interpreter:set_up_typed_localstate(Parameters,FreshOutputVars,TypedVals,[],LocalState,positive), |
| 921 | | append(LocalState,EState,State), |
| 922 | | b_interpreter_components:reset_unsat_component_info, |
| 923 | | % NOTE: WF not passed to b_interpreter_components ! |
| 924 | ? | b_interpreter_components:b_trace_test_components_wf(Typed,State,TypedVals,WF), |
| 925 | | \+ b_interpreter_components:unsat_component_exists. |
| 926 | | test_bool_exists2(EState, Parameters,Typed,LocalState,WF) :- |
| 927 | | %init_wait_flags(WF,[expansion_context(test_bool_exists2,Parameters)]), |
| 928 | | init_quantifier_wait_flag(no_wf_available,exists,Parameters,FreshOutputVars,unknown,WF), |
| 929 | ? | b_interpreter:set_up_typed_localstate(Parameters,FreshOutputVars,TypedVals,[],LocalState,positive), |
| 930 | | b_tighter_enumerate_values_in_ctxt(TypedVals,Typed,WF), |
| 931 | | b_interpreter:b_test_boolean_expression(Typed,LocalState,EState,WF). |
| 932 | | |
| 933 | | |
| 934 | | :- use_module(eventhandling,[announce_event/1]). |
| 935 | | %:- use_module(bmachine, [determine_type_of_formula/2]). |
| 936 | | |
| 937 | | eval_predicate_in_cur_state(ExTyped,RRes,EnumWarning,LocalState) :- |
| 938 | | get_cur_state_for_repl(ExTyped,State),!, |
| 939 | | announce_event(start_solving), |
| 940 | | eval_predicate(State,ExTyped,RRes,EnumWarning,LocalState), |
| 941 | | announce_event(end_solving). |
| 942 | | eval_predicate_in_cur_state(_ExTyped,RRes,EnumWarning,LocalState) :- |
| 943 | | format_with_colour_nl(user_output,[red,bold],'UNKNOWN',[]), |
| 944 | | RRes = 'UNKNOWN', EnumWarning=false, LocalState=[]. |
| 945 | | |
| 946 | | :- use_module(probsrc(solver_interface),[apply_kodkod_or_other_optimisations/3]). |
| 947 | | replace_kodkod_if_enabled(Parameters,Typed,NewPredicate) :- |
| 948 | | b_get_machine_constants(Constants), |
| 949 | | b_get_machine_variables(Variables), |
| 950 | | get_repl_lets_tids(LetIds), |
| 951 | | append([Parameters,Variables,Constants,LetIds],Identifiers), |
| 952 | | apply_kodkod_or_other_optimisations(Identifiers,Typed,NewPredicate). |
| 953 | | |
| 954 | | eval_predicate(State,Typed,RRes,EnumWarning,LocalState) :- |
| 955 | | %b_ast_cleanup:predicate_level_optimizations(Typed,Typed2), |
| 956 | | % detect set partitions, ... no longer necessary ! as already called in b_ast_cleanup now |
| 957 | | eval_predicate_aux(State,Typed,RRes,EnumWarning,LocalState). |
| 958 | | eval_predicate_aux(State,ExTyped,RRes,EnumWarning,LocalState) :- |
| 959 | | %ExTyped=b(exists(Parameters,Typed),pred,_I), |
| 960 | | is_existential_quantifier(ExTyped,Parameters,Typed), |
| 961 | | !, |
| 962 | | %print('Existentially Quantified Predicate is '),flush_output, |
| 963 | | replace_kodkod_if_enabled(Parameters,Typed,NTyped), |
| 964 | | enter_new_error_scope(ScopeID,eval_predicate_exists), clear_all_errors_in_error_scope(ScopeID), |
| 965 | | set_last_expression(pred,ExTyped,exception), % in case an exception occurs |
| 966 | | (observe_parameters(true) -> observe_parameters(Parameters,LocalState) ; true), |
| 967 | | (probcli_clpfd_overflow_call1((test_bool_exists(State, Parameters,NTyped,LocalState,WF), |
| 968 | | eval_ground_wf(WF))) |
| 969 | | -> get_only_critical_enum_warning(EnumWarning), |
| 970 | | (eval_det -> Res = 'POSSIBLY TRUE' ; Res = 'TRUE'), |
| 971 | | set_last_expression(pred,ExTyped,pred_true) |
| 972 | | ; get_enum_warning(EnumWarning), |
| 973 | | % The result has to be ground for the eclipse interface to work as intended. |
| 974 | | % Hence, we need to bind the LocalState (?) |
| 975 | | LocalState = [], |
| 976 | | Res = 'FALSE', set_last_expression(pred,ExTyped,pred_false)), |
| 977 | | (eval_det, debug_level_active_for(20) -> portray_waitflags_and_frozen_state_info(WF,(LocalState,State)) ; true), |
| 978 | | print('Existentially Quantified Predicate over '), print_parameters(Parameters), |
| 979 | | print(' is '),display_and_set_result(ScopeID,Res,RRes,EnumWarning), |
| 980 | | (Res='FALSE' -> true |
| 981 | | ; display_solution('Solution:~n',Parameters,LocalState) |
| 982 | | ). |
| 983 | | eval_predicate_aux(State, ExTyped,RRes,EnumWarning,LocalState) :- |
| 984 | | ExTyped=b(forall(Parameters,TypedLHS,TypedRHS),pred,_I),!, |
| 985 | | %print('Universally Quantified Predicate is '),flush_output, |
| 986 | | enter_new_error_scope(ScopeID,eval_predicate_forall), clear_all_errors_in_error_scope(ScopeID), |
| 987 | | safe_create_texpr(negation(TypedRHS),pred,[try_smt],NegRHS), |
| 988 | | conjunct_predicates([TypedLHS,NegRHS],Conjunction), % LHS & not(RHS) |
| 989 | | replace_kodkod_if_enabled(Parameters,Conjunction,NConjunction), |
| 990 | | %translate:print_bexpr(Conjunction), |
| 991 | | set_last_expression(pred,ExTyped,exception), % in case an exception occurs |
| 992 | | (probcli_clpfd_overflow_call1((test_bool_exists(State, Parameters,NConjunction,LocalState,WF), |
| 993 | | eval_ground_wf(WF))) |
| 994 | | -> get_only_critical_enum_warning(EnumWarning), |
| 995 | | (eval_det -> Res = 'POSSIBLY TRUE' ; Res = 'FALSE'), |
| 996 | | set_last_expression(pred,ExTyped,pred_false) |
| 997 | | ; get_enum_warning(EnumWarning), |
| 998 | | % The result has to be ground for the eclipse interface to work as intended. |
| 999 | | % Hence, we need to bind the LocalState (?) |
| 1000 | | LocalState = [], |
| 1001 | | Res = 'TRUE', set_last_expression(pred,ExTyped,pred_true)), |
| 1002 | | print('Universally Quantified Predicate over '), print_parameters(Parameters), |
| 1003 | | print(' is '),display_and_set_result(ScopeID,Res,RRes,EnumWarning), |
| 1004 | | (Res='TRUE' -> true |
| 1005 | | ; display_solution('Counter example:~n',Parameters,LocalState) |
| 1006 | | ). |
| 1007 | | eval_predicate_aux(State, Typed,RRes,EnumWarning,[]) :- |
| 1008 | | enter_new_error_scope(ScopeID,eval_predicate), clear_all_errors_in_error_scope(ScopeID), |
| 1009 | | debug_println(20,test_boolean_expression(Typed)), |
| 1010 | | replace_kodkod_if_enabled([],Typed,NTyped), |
| 1011 | | set_last_expression(pred,NTyped,exception), % in case an exception occurs |
| 1012 | | % TO DO: the next does not decompose into components !?; either call solve_predicate if State=[] or call b_trace_test_components inside b_test_boolean_expression_cs |
| 1013 | | (probcli_clpfd_overflow_call1(b_interpreter:b_test_boolean_expression_cs(NTyped,[],State,'none',0)) |
| 1014 | | -> Res='TRUE',set_last_expression(pred,Typed,pred_true), |
| 1015 | | get_only_critical_enum_warning(EnumWarning) |
| 1016 | | ; Res='FALSE',set_last_expression(pred,Typed,pred_false), |
| 1017 | | get_enum_warning(EnumWarning) |
| 1018 | | ), |
| 1019 | | print('Predicate is '),display_and_set_result(ScopeID,Res,RRes,EnumWarning). |
| 1020 | | |
| 1021 | | get_enum_warning(EnumWarning) :- |
| 1022 | | (event_occurred_in_error_scope(enumeration_warning(_,_,_,_,_Critical)) |
| 1023 | | -> EnumWarning=true %,print(' ** ENUM WARNING ** ') |
| 1024 | | ; EnumWarning=false). |
| 1025 | | get_only_critical_enum_warning(EnumWarning) :- EnumWarning=false. |
| 1026 | | % we no longer distinguish between critical & non-critical; also assuming_finite_closure now fails (renamed to checking_finite_closure) |
| 1027 | | % Enumeration warning means that not all cases have been looked at, but if a result is true then it is guaranteed to be true |
| 1028 | | |
| 1029 | | |
| 1030 | | display_and_set_result(ScopeID,Res,RRes,EnumWarning) :- |
| 1031 | | %error_manager:print_error_scopes, |
| 1032 | | findall(TE,(specific_event_occurred_at_level(ScopeID,E),translate_error_event(E,TE)), Errors), |
| 1033 | | (abort_error_occured_in_error_scope -> WDError=true ; WDError=false), |
| 1034 | | (specific_event_occurred_at_level(ScopeID,identifier_not_found) -> IdNotFound=true ; IdNotFound=false), |
| 1035 | | exit_error_scope(ScopeID,ErrOcc,display_and_set_result), |
| 1036 | | ErrOcc=true, % TO DO: check which kind of error occured: could be CLPFD overflow |
| 1037 | | !, |
| 1038 | | show_error_pos, |
| 1039 | | (WDError=true |
| 1040 | | -> format_with_colour(user_output,[red,bold],'NOT-WELL-DEFINED (~w)',[Res]), |
| 1041 | | RRes = 'NOT-WELL-DEFINED' |
| 1042 | | ; IdNotFound=true -> % should no longer happen; we check requirements first |
| 1043 | | format_with_colour(user_output,[red,bold],'IDENTIFIER-NOT-FOUND-ERROR ~w',[Errors]), |
| 1044 | | RRes = 'IDENTIFIER(S) NOT YET INITIALISED; INITIALISE MACHINE FIRST' |
| 1045 | | ; format_with_colour(user_output,[red,bold],'UNKNOWN ~w',[Errors]), |
| 1046 | | RRes = 'UNKNOWN' |
| 1047 | | ), |
| 1048 | | print_enum_warning(EnumWarning), nl. |
| 1049 | | display_and_set_result(_,Res,RRes,EnumWarning) :- |
| 1050 | | print_result(Res,EnumWarning), nl, |
| 1051 | | (EnumWarning=false -> RRes=Res |
| 1052 | | % ; Res = 'TRUE' -> RRes=Res % enumeration warning does not matter when solution found, |
| 1053 | | % unless this is a universally quantified formula! |
| 1054 | | % inner enum warnings are not propagated to EnumWarning anymore; so we remove this case above |
| 1055 | | ; RRes= 'UNKNOWN'). |
| 1056 | | |
| 1057 | | print_result('FALSE',false) :- !, |
| 1058 | | start_terminal_colour(light_red,user_output), |
| 1059 | | write('FALSE'),reset_terminal_colour(user_output). |
| 1060 | | print_result('TRUE',false) :- !, |
| 1061 | | start_terminal_colour(green,user_output), |
| 1062 | | write('TRUE'),reset_terminal_colour(user_output). |
| 1063 | | print_result(Res,false) :- !, write(Res). |
| 1064 | | print_result(Res,_) :- |
| 1065 | | (debug_mode(on) |
| 1066 | | -> format_with_colour(user_output,[red,bold],'UNKNOWN [~w with ** ENUMERATION WARNING **]',[Res]) |
| 1067 | | ; format_with_colour(user_output,[red,bold],'UNKNOWN',[]) |
| 1068 | | ). |
| 1069 | | |
| 1070 | | |
| 1071 | | :- use_module(tools_printing,[print_red/1,print_green/1,format_with_colour/4, format_with_colour_nl/4]). |
| 1072 | | print_enum_warning(false) :- !. |
| 1073 | | print_enum_warning(_) :- print_red(' [** ENUMERATION WARNING **]'). |
| 1074 | | |
| 1075 | | :- use_module(dotsrc(state_as_dot_graph),[print_cstate_graph/2]). |
| 1076 | | display_sol_required :- silent_mode(off),!. |
| 1077 | | display_sol_required :- eval_dot_file(_),!. |
| 1078 | | %display_sol_required :- format(user_output,'Not showing solution~n',[]),trace,fail. |
| 1079 | | |
| 1080 | | display_solution(HeaderStr,Parameters,LocalState) :- |
| 1081 | | set_last_solution(Parameters,LocalState), |
| 1082 | | (display_sol_required |
| 1083 | | -> format(HeaderStr,[]), |
| 1084 | | display_solution_aux(Parameters,LocalState) |
| 1085 | | ; true). |
| 1086 | | display_solution_aux(Parameters,LocalState) :- |
| 1087 | | (eval_det |
| 1088 | | -> % copy_term(LocalState,CLS), % avoid triggering co-routines via numbervars |
| 1089 | | % tools_meta:safe_numbervars(CLS,0,_), |
| 1090 | | print_visible_solution_with_type(Parameters,LocalState) |
| 1091 | | ; debug_println(19,normalising_solution(LocalState)), |
| 1092 | | normalise_solution(LocalState,NState) |
| 1093 | | -> %translate:print_bstate(NState) |
| 1094 | | print_visible_solution_with_type(Parameters,NState), |
| 1095 | | %visualize_graph:tcltk_print_state_as_graph_for_dot(NState,'~/Desktop/out.dot') |
| 1096 | | display_dot_solution(NState) |
| 1097 | | ; print_red('Could not normalise value(s):'),nl, |
| 1098 | | translate:print_bstate(LocalState) |
| 1099 | | ),nl. |
| 1100 | | |
| 1101 | | normalise_solution(LocalState,NormState) :- normalising_off,!, NormState=LocalState. |
| 1102 | | normalise_solution(LocalState,NormState) :- |
| 1103 | | start_norm_timer(NT,NWT), |
| 1104 | | (normalise_store(LocalState,NormState) -> stop_norm_timer(NT,NWT) ; stop_norm_timer(NT,NWT),fail). |
| 1105 | | |
| 1106 | | display_dot_expr_result(Expr,Value) :- |
| 1107 | | (eval_dot_file(File) |
| 1108 | | -> get_dot_expr_state(Expr,Value,NState,[]), |
| 1109 | | debug_println(9,writing_dot_file(File)), |
| 1110 | | print_cstate_graph(NState,File) |
| 1111 | | ; true). |
| 1112 | | |
| 1113 | | % try and decompose an expression value into subvalues for better dot rendering |
| 1114 | | get_dot_expr_state(b(couple(A,B),_,_),(VA,VB)) --> !, |
| 1115 | | get_dot_expr_state(A,VA), |
| 1116 | | get_dot_expr_state(B,VB). |
| 1117 | | get_dot_expr_state(b(identifier(ID),_,_),Val) --> !, [bind(ID,Val)]. |
| 1118 | | get_dot_expr_state(_,Val) --> [bind(result,Val)]. |
| 1119 | | |
| 1120 | | % display_dot_solution([bind(result,NValue)]). |
| 1121 | | display_dot_solution(NState) :- |
| 1122 | | (eval_dot_file(File) |
| 1123 | | -> debug_println(9,writing_dot_file(File)), |
| 1124 | | print_cstate_graph(NState,File) ; true). |
| 1125 | | |
| 1126 | | :- dynamic last_solution/2. |
| 1127 | | set_last_solution(Parameters,LocalState) :- |
| 1128 | | retractall(last_solution(_,_)), |
| 1129 | | assertz(last_solution(Parameters,LocalState)). |
| 1130 | | |
| 1131 | | % small utility to extract last result; if we had a predicate with just one existential variable extract its value: |
| 1132 | | get_last_result_value(Parameter,Type,Value) :- |
| 1133 | ? | get_last_predicate_value_for_typed_id(Parameter,[],T,V), % only allow single parameter; otherwise confusion may exist |
| 1134 | | !,Value=V, Type=T. |
| 1135 | | get_last_result_value(Expr,Type,Value) :- get_last_expr_type_and_value(Expr,Type,Value). |
| 1136 | | |
| 1137 | | convert_result(T,V,Type,Value) :- |
| 1138 | | (convert_aux(T,V,Type,Value) -> true ; Type=T,Value=V). |
| 1139 | | convert_aux(pred,pred_true,boolean,pred_true). |
| 1140 | | convert_aux(pred,pred_false,boolean,pred_false). |
| 1141 | | |
| 1142 | | % try and extract a value for a give parameter from last solution for a predicate |
| 1143 | | get_last_predicate_value_for_id(ID,Type,Val) :- |
| 1144 | | get_texpr_id(Parameter,ID),get_last_predicate_value_for_typed_id(Parameter,_,Type,Val). |
| 1145 | | get_last_predicate_value_for_typed_id(Parameter,Rest,Type,Value) :- |
| 1146 | | last_expression(pred,_,pred_true), % we solved a predicate, look in solution environment |
| 1147 | | last_solution(Parameters,LocalState), |
| 1148 | ? | select(Parameter,Parameters,Rest), |
| 1149 | | get_texpr_id(Parameter,ParameterID), |
| 1150 | | get_texpr_type(Parameter,Type), |
| 1151 | | member(bind(ParameterID,Value),LocalState). |
| 1152 | | |
| 1153 | | :- volatile eval_dot_file/1, observe_parameters/1. |
| 1154 | | :- dynamic eval_dot_file/1, observe_parameters/1. |
| 1155 | | observe_parameters(false). |
| 1156 | | |
| 1157 | | toggle_observe_evaluation :- |
| 1158 | | (observe_parameters(false) |
| 1159 | | -> print('Observing parameters'),nl, |
| 1160 | | set_observe_evaluation(true) |
| 1161 | | ; print('Observing OFF'),nl, |
| 1162 | | set_observe_evaluation(false)). |
| 1163 | | set_observe_evaluation(T) :- retractall(observe_parameters(_)), assertz(observe_parameters(T)). |
| 1164 | | set_eval_dot_file(F) :- unset_eval_dot_file, |
| 1165 | | debug_println(5,setting_eval_dot_file(F)), |
| 1166 | | assertz(eval_dot_file(F)). |
| 1167 | | unset_eval_dot_file :- retractall(eval_dot_file(_)). |
| 1168 | | |
| 1169 | | % ---------------- |
| 1170 | | |
| 1171 | | % print solution using type information of non-generated ids (unless in debug mode) |
| 1172 | | print_visible_solution_with_type(Ids,Bindings) :- Ids = [_|_], |
| 1173 | | debug_mode(off), |
| 1174 | | exclude(generated_id,Ids,VisibleIds),!, |
| 1175 | | print_solution_with_type2(VisibleIds,Bindings). |
| 1176 | | print_visible_solution_with_type(Ids,Bindings) :- print_solution_with_type1(Ids,Bindings). |
| 1177 | | |
| 1178 | | generated_id(b(_,_,I)) :- member(generated,I). |
| 1179 | | |
| 1180 | | % print solution using type information |
| 1181 | | print_solution_with_type1([],Bindings) :- !,print_solution_with_type2(unknown,Bindings). |
| 1182 | | print_solution_with_type1(T,Bindings) :- print_solution_with_type2(T,Bindings). |
| 1183 | | |
| 1184 | | print_solution_with_type2([],_) :- !. % can be non-empty due to generated ids being removed |
| 1185 | | print_solution_with_type2([Identifier|TT],Bindings) :- |
| 1186 | | def_get_texpr_id(Identifier,Varname), |
| 1187 | ? | select(bind(Varname,Value), Bindings, VT), |
| 1188 | | !, |
| 1189 | | translate_bvalue_with_col(Value,Identifier,Result), |
| 1190 | | print_binding(Varname,Result), |
| 1191 | | (TT=[] -> nl ; print(' &'),nl,print_solution_with_type2(TT,VT)). |
| 1192 | | print_solution_with_type2(unknown,[bind(Varname,Value)|VT]) :- !, |
| 1193 | | (debug_mode(on) -> Lim=500 ; Lim=200), |
| 1194 | | translate_bvalue_with_limit_and_col(Value,Lim,Result), |
| 1195 | | print_binding(Varname,Result), |
| 1196 | | (VT=[] -> nl ; print(' &'),nl,print_solution_with_type2(unknown,VT)). |
| 1197 | | print_solution_with_type2(unknown,[]) :- !. |
| 1198 | | print_solution_with_type2([Identifier|TT],Bindings) :- |
| 1199 | | def_get_texpr_id(Identifier,Varname), !, |
| 1200 | | % possibly ast_cleanup has removed all predicates involving Identifier, appears in test 2168 for level 1 |
| 1201 | | % add_internal_error('No binding for variable: ', print_solution_with_type2(Varname,Bindings)), |
| 1202 | | get_texpr_type(Identifier,Type), |
| 1203 | | print_no_binding(Varname,Type), |
| 1204 | | (TT=[] -> nl ; print(' &'),nl,print_solution_with_type2(TT,Bindings)). |
| 1205 | | print_solution_with_type2(P,State) :- |
| 1206 | | add_internal_error('Illegal call: ', print_solution_with_type2(P,State)). |
| 1207 | | |
| 1208 | | print_binding(Varname,Result) :- |
| 1209 | | format(' ~w = ~w',[Varname,Result]). |
| 1210 | | print_no_binding(Varname,Type) :- |
| 1211 | | pretty_type(Type,PrettyType), |
| 1212 | | format(' ~w : ~w',[Varname,PrettyType]). |
| 1213 | | |
| 1214 | | % translate a value with optional colouring |
| 1215 | | :- dynamic colour_values/1. |
| 1216 | | colour_values(false). |
| 1217 | | toggle_colouring :- retract(colour_values(V)), |
| 1218 | | (V=false -> V2=true ; V2=false), |
| 1219 | | assertz(colour_values(V2)), |
| 1220 | | format('Colouring of values is now ~w~n',[V2]). |
| 1221 | | translate_bvalue_with_col(Value,Identifier,Result) :- colour_values(false),!, |
| 1222 | | translate_bvalue_for_expression(Value,Identifier,Result). |
| 1223 | | translate_bvalue_with_col(Value,Identifier,Result) :- |
| 1224 | | temporary_set_preference(pp_with_terminal_colour,true,C), |
| 1225 | | call_cleanup(translate_bvalue_for_expression(Value,Identifier,Result), |
| 1226 | | reset_temporary_preference(pp_with_terminal_colour,C)). |
| 1227 | | |
| 1228 | | translate_bvalue_with_limit_and_col(Value,Limit,Result) :- colour_values(false),!, |
| 1229 | | translate_bvalue_with_limit(Value,Limit,Result). |
| 1230 | | translate_bvalue_with_limit_and_col(Value,Limit,Result) :- |
| 1231 | | temporary_set_preference(pp_with_terminal_colour,true,C), |
| 1232 | | call_cleanup(translate_bvalue_with_limit(Value,Limit,Result), |
| 1233 | | reset_temporary_preference(pp_with_terminal_colour,C)). |
| 1234 | | |
| 1235 | | % ------------------ |
| 1236 | | |
| 1237 | | % translate a solver name to the prefix to be used on the REPL: |
| 1238 | | translate_solver_to_prefix(Solver,Prefix) :- available_smt_solver(Solver,Prefix). |
| 1239 | | translate_solver_to_prefix('sat',":sat "). % entry for eval_file |
| 1240 | | translate_solver_to_prefix(prob,":prob "). % for eval_file |
| 1241 | | translate_solver_to_prefix('prob-chr',":prob "). % for eval_file |
| 1242 | | translate_solver_to_prefix('sat-z3',":sat-z3 "). % entry for eval_file |
| 1243 | | translate_solver_to_prefix(kodkod,":kodkod "). % entry for eval_file |
| 1244 | | |
| 1245 | | available_smt_solver(cvc4,":cvc "). |
| 1246 | | available_smt_solver(cvc4,":cvc4 "). |
| 1247 | | available_smt_solver(nostate(cvc4),":cvc4-free "). |
| 1248 | | available_smt_solver(z3,":z3 "). |
| 1249 | | available_smt_solver(z3sat,":z3-sat "). |
| 1250 | | available_smt_solver(z3axm,":z3-axm "). |
| 1251 | | available_smt_solver(z3cns,":z3-cns "). |
| 1252 | | available_smt_solver(nostate(z3),":z3-free "). |
| 1253 | | available_smt_solver(nostate(z3sat),":z3-sat-free "). |
| 1254 | | available_smt_solver(nostate(z3axm),":z3-axm-free "). |
| 1255 | | available_smt_solver(nostate(z3cns),":z3-cns-free "). |
| 1256 | | available_smt_solver(double_check(z3),":z3-double-check "). |
| 1257 | | available_smt_solver(double_check(nostate(z3)),":z3-free-double-check "). |
| 1258 | | available_smt_solver(cdcl_sat,":cdcl-sat "). |
| 1259 | | available_smt_solver(nostate(cdcl_sat),":cdcl-sat-free "). |
| 1260 | | available_smt_solver(cdclt,":cdclt "). |
| 1261 | | available_smt_solver(nostate(cdclt),":cdclt-free "). |
| 1262 | | available_smt_solver(double_check(cdclt),":cdclt-double-check "). |
| 1263 | | available_smt_solver(double_check(nostate(cdclt)),":cdclt-free-double-check "). |
| 1264 | | available_smt_solver(idl,":idl "). |
| 1265 | | available_smt_solver(setlog,":slog "). |
| 1266 | | available_smt_solver(double_check(setlog),":slog-double-check "). |
| 1267 | | available_smt_solver(clingo,":clingo "). |
| 1268 | | available_smt_solver(double_check(clingo),":clingo-double-check "). |
| 1269 | | available_smt_solver(prob(default),":prob "). % solve with SMT |
| 1270 | | available_smt_solver(prob(strong),":prob-chr "). |
| 1271 | | available_smt_solver(prob(no_opts),":prob-no-opts "). |
| 1272 | | available_smt_solver(double_check(prob(strong)),":prob-chr-double-check "). |
| 1273 | | available_smt_solver(double_check(prob(no_opts)),":prob-double-check "). |
| 1274 | | available_smt_solver(prob(eval),":eval "). % solve without SMT option; like default REPL eval |
| 1275 | | available_smt_solver('prob-unsat-core',":core "). |
| 1276 | | available_smt_solver('prob-unsat-core-no-chr',":ccore "). |
| 1277 | | available_smt_solver('prob-unsat-cores',":cores "). |
| 1278 | | available_smt_solver('prob-fast-unsat-core',":fcore "). |
| 1279 | | available_smt_solver('prob-fast-unsat-core',":fast-core "). |
| 1280 | | available_smt_solver('prob-min-core',":mcore "). |
| 1281 | | available_smt_solver('prob-min-core',":min-core "). |
| 1282 | | available_smt_solver('smt-unsat-core'(z3),":z3-core "). |
| 1283 | | available_smt_solver('smt-quick-bup-unsat-core'(z3),":z3-qcore "). |
| 1284 | | available_smt_solver('smt-quick-bup-unsat-core'(z3cns),":z3-cns-qcore "). |
| 1285 | | available_smt_solver('smt-quick-bup-unsat-core'(z3axm),":z3-axm-qcore "). % z3axm best for bup-unsat core? |
| 1286 | | available_smt_solver('smt-unsat-core'(z3cns),":z3-cns-core "). |
| 1287 | | available_smt_solver('smt-unsat-core'(z3axm),":z3-axm-core "). |
| 1288 | | available_smt_solver('cdclt-unsat-core',":cdclt-core "). |
| 1289 | | available_smt_solver('satsolver'(glucose,with_state),":sat "). |
| 1290 | | available_smt_solver('satsolver'(glucose,nostate),":sat-free "). |
| 1291 | | available_smt_solver('satsolver'(z3,with_state),":sat-z3 "). |
| 1292 | | available_smt_solver('satsolver'(z3,nostate),":sat-z3-free "). |
| 1293 | | available_smt_solver(double_check('satsolver'(glucose,with_state)),":sat-double-check "). |
| 1294 | | available_smt_solver(double_check('satsolver'(z3,with_state)),":sat-z3-double-check "). |
| 1295 | | |
| 1296 | | |
| 1297 | | available_smt_solver_for_file(cdclt,":cdclt-file "). |
| 1298 | | available_smt_solver_for_file(nostate(cdclt),":cdclt-free-file "). |
| 1299 | | available_smt_solver_for_file(idl,":idl-file "). |
| 1300 | | available_smt_solver_for_file(z3,":z3-file "). |
| 1301 | | available_smt_solver_for_file(z3sat,":z3-sat-file "). |
| 1302 | | available_smt_solver_for_file(z3axm,":z3-axm-file "). |
| 1303 | | available_smt_solver_for_file(z3cns,":z3-cns-file "). |
| 1304 | | available_smt_solver_for_file(nostate(z3),":z3-free-file "). |
| 1305 | | available_smt_solver_for_file('smt-unsat-core'(z3),":z3-core-file "). |
| 1306 | | available_smt_solver_for_file(cvc4,":cvc4-file "). |
| 1307 | | available_smt_solver_for_file(nostate(cvc4),":cvc4-free-file "). |
| 1308 | | available_smt_solver_for_file(prob(default),":prob-file "). |
| 1309 | | available_smt_solver_for_file(prob(strong),":prob-chr-file "). |
| 1310 | | available_smt_solver_for_file('prob-unsat-core',":prob-core-file "). |
| 1311 | | |
| 1312 | | :- use_module(extrasrc(atelierb_provers_interface),[prove_sequent_with_provers/3]). |
| 1313 | | available_krt_prover(krt,[ml,pp],":krt"). |
| 1314 | | available_krt_prover(ml,[ml],":ml"). |
| 1315 | | available_krt_prover(mldc, krt_double_check([ml],[prob(strong)]),":ml-double-check"). |
| 1316 | | available_krt_prover(mldcz3,krt_double_check([ml],[prob(strong),z3]),":ml-double-check-z3"). |
| 1317 | | available_krt_prover(pp,[pp],":pp"). |
| 1318 | | available_krt_prover(ppdc, krt_double_check([pp],[prob(strong)]),":pp-double-check"). |
| 1319 | | available_krt_prover(ppdcz3,krt_double_check([pp],[prob(strong),z3]),":pp-double-check-z3"). |
| 1320 | | available_krt_prover(probwd,['prob-wd-prover'(no_double_check)],":prove"). % not a krt prover |
| 1321 | | available_krt_prover(probwddc1,['prob-wd-prover'([prob(strong)])],":prove-double-check"). |
| 1322 | | available_krt_prover(probwddc2,['prob-wd-prover'([prob(strong),z3])],":prove-double-check-z3"). |
| 1323 | | available_krt_prover(probwddc2,['wd-krt-prover'([ml],[prob(strong)])],":prove-bench"). |
| 1324 | | |
| 1325 | | prove_sequent_with_krt_provers(['prob-wd-prover'(DC)],Typed,Result) :- !, |
| 1326 | | debug_format(19,'Calling ProB WD Prover~n',[]), |
| 1327 | | (prove_sequent(Typed) |
| 1328 | | -> Result = 'proved', |
| 1329 | | (DC = no_double_check -> true ; double_check_proven_sequent(DC,Typed,_)) |
| 1330 | | ; Result = 'unproved' |
| 1331 | | ). |
| 1332 | | prove_sequent_with_krt_provers(['wd-krt-prover'(Provers,DC)],Typed,Result) :- !, |
| 1333 | | bb_inc(prove_bench_counter,BCNr), |
| 1334 | | debug_format(19,'Calling ProB WD Prover (~w)~n',[BCNr]), |
| 1335 | | writeln_log(proving_with_wd_and_krt(BCNr,Typed)), |
| 1336 | | (prove_sequent(Typed) |
| 1337 | | -> Result = 'proved', WDResult=Result, bb_inc(prove_bench_wd_proved,_), |
| 1338 | | prove_sequent_with_provers(Provers,Typed,KRTResult), |
| 1339 | | (KRTResult='proved' |
| 1340 | | -> format_with_colour_nl(user_output,[green],'Proven by WD & ~w',[Provers]), |
| 1341 | | bb_inc(prove_bench_krt_proved,_) |
| 1342 | | ; format_with_colour_nl(user_output,[blue],'Proven by WD but *not* by ~w',[Provers]) |
| 1343 | | ), % TODO: count number of proven/unproven by each prover |
| 1344 | | (DC = no_double_check -> DCResult=DC ; double_check_proven_sequent(DC,Typed,DCResult)) |
| 1345 | | ; WDResult='unproven', Result=KRTResult, |
| 1346 | | debug_format(19,'Proving with Atelier-B provers ~w (~w)~n',[Provers,BCNr]), |
| 1347 | | prove_sequent_with_provers(Provers,Typed,KRTResult), |
| 1348 | | (Result='proved' |
| 1349 | | -> format_with_colour_nl(user_output,[orange],'Proven by ~w but *not* by WD',[Provers]), |
| 1350 | | bb_inc(prove_bench_krt_proved,_) |
| 1351 | | ; format_with_colour_nl(user_output,[grey],'Unproven by WD and ~w',[Provers]) |
| 1352 | | ), |
| 1353 | | (DC = no_double_check -> DCResult=DC |
| 1354 | | ; Result='proved' -> double_check_proven_sequent(DC,Typed,DCResult) |
| 1355 | | ; DCResult = not_required) |
| 1356 | | ), writeln_log(prove_status(BCNr,WDResult,KRTResult,DCResult)), |
| 1357 | | portray_prove_bench_stats. |
| 1358 | | prove_sequent_with_krt_provers(krt_double_check(Provers,DC),ExTyped,Res) :- !, |
| 1359 | | debug_format(19,'Proving with Atelier-B provers ~w~n',[Provers]), |
| 1360 | | prove_sequent_with_provers(Provers,ExTyped,Res), |
| 1361 | | (Res='proved' -> double_check_proven_sequent(DC,ExTyped,_) ; true). |
| 1362 | | prove_sequent_with_krt_provers(Provers,ExTyped,Res) :- |
| 1363 | | debug_format(19,'Proving with Atelier-B provers ~w~n',[Provers]), |
| 1364 | | prove_sequent_with_provers(Provers,ExTyped,Res). |
| 1365 | | |
| 1366 | | portray_prove_bench_stats :- bb_sget(prove_bench_counter,Tot), |
| 1367 | | bb_sget(prove_bench_krt_proved,KRT), |
| 1368 | | bb_sget(prove_bench_wd_proved,WD), |
| 1369 | | format(':prove-bench statistics: total: ~w KRT:~w WD-Prover:~w~n',[Tot,KRT,WD]). |
| 1370 | | |
| 1371 | | bb_inc(Counter,OldNr) :- bb_get(Counter,OldNr), !, N1 is OldNr+1, bb_put(Counter,N1). |
| 1372 | | bb_inc(Counter,1) :- bb_put(Counter,2). |
| 1373 | | bb_sget(Counter,Nr) :- (bb_get(Counter,R) -> Nr=R ; Nr=0). |
| 1374 | | |
| 1375 | | double_check_proven_sequent(DCProvers,Typed,counter_example_found) :- |
| 1376 | | create_negation(Typed,NegTyped), |
| 1377 | | member(Solver,DCProvers), |
| 1378 | | %member(Solver,[prob(strong),z3]), |
| 1379 | | (debug_mode(off) -> true |
| 1380 | | ; format_with_colour_nl(user_output,[dark_gray],'Double checking proof using ~w',[Solver])), |
| 1381 | | statistics(walltime,[W1,_]), |
| 1382 | | %solve_typed_pred_using_smt_solver(Solver,NegTyped,Res,_), |
| 1383 | | temporary_set_preference(strict_raise_enum_warnings,false,Chng), |
| 1384 | | (solve_using_smt_solver_aux(Solver,[],NegTyped,_,Res) -> true), |
| 1385 | | reset_temporary_preference(strict_raise_enum_warnings,Chng), |
| 1386 | | statistics(walltime,[W2,_]), W is W2-W1, |
| 1387 | | (Res=solution(_) -> Col=[red,bold] ; Col = [dark_gray]), |
| 1388 | | format_with_colour_nl(user_output,Col,'Double checking proven sequent with ~w after ~w ms: ~w',[Solver,W,Res]), |
| 1389 | | (Res=solution(_) ; Res='TRUE'), |
| 1390 | | !, |
| 1391 | | add_error(double_check_proven_sequent,'Counter example for proven sequent found:',Typed,Typed). |
| 1392 | | %nl,print_quoted(Typed),nl,nl,trace, prove_sequent(Typed). |
| 1393 | | double_check_proven_sequent(_,_,ok). |
| 1394 | | |
| 1395 | | |
| 1396 | | |
| 1397 | | |
| 1398 | | :- use_module(probsrc(tools), [start_ms_timer/1,stop_ms_timer_with_debug_msg/2]). |
| 1399 | | solve_using_smt_solver_from_file(Solver,FileCodes,OuterQuantifier,Res,LocalState,TypeInfo) :- |
| 1400 | | atom_codes(File,FileCodes), |
| 1401 | | format_with_colour_nl(user_output,[dark_gray],'Reading B predicate for ~w from file ~w',[Solver,File]), |
| 1402 | | start_ms_timer(T0), |
| 1403 | | safe_read_string_from_file(File,utf8,PredCodes), |
| 1404 | | stop_ms_timer_with_debug_msg(T0,reading_file(File)), |
| 1405 | | debug_format(19,'Predicate read from file:~n~s~n',[PredCodes]), |
| 1406 | | solve_using_smt_solver(Solver,PredCodes,try_prolog,OuterQuantifier,Res,LocalState,TypeInfo). |
| 1407 | | |
| 1408 | | :- use_module(state_space,[current_state_id/1]). |
| 1409 | | :- use_module(smt_solvers_interface(smt_solvers_interface),[smt_solve_predicate_in_state/5, |
| 1410 | | smt_solve_predicate/4]). |
| 1411 | | solve_using_smt_solver(Solver,PredCodes,TryProlog,OuterQuantifier,Res,LocalState,TypeInfo) :- |
| 1412 | | (TryProlog=try_prolog, |
| 1413 | | repl_get_prolog_predicate(PredCodes,clean_up_pred,ExTyped,TypeInfo) -> true |
| 1414 | | ; repl_parse_predicate_for_solving(PredCodes,OuterQuantifier,ExTyped,TypeInfo) % TO DO: make lets,... available |
| 1415 | | ), |
| 1416 | | solve_typed_pred_using_smt_solver(Solver,ExTyped,Res,LocalState). |
| 1417 | | |
| 1418 | | solve_typed_pred_using_smt_solver(Solver,ExTyped,Res,LocalState) :- |
| 1419 | | set_last_expression(pred,ExTyped,exception), % in case an exception occurs |
| 1420 | | start_ms_timer(T0), |
| 1421 | | (is_existential_quantifier(ExTyped,Parameters,Typed) |
| 1422 | | -> get_clashing_identifiers(Parameters,ClashParas), |
| 1423 | | % we cannot peel off quantified variables which clash with current state variables, constants, ... |
| 1424 | | create_exists_opt_liftable(ClashParas,Typed,NewTyped), |
| 1425 | | % we could also remove the ClashParas from the state passed to the smt solver |
| 1426 | | (debug_mode(on), ClashParas=[_|_] |
| 1427 | | -> get_texpr_ids(ClashParas,CP), |
| 1428 | | add_message(eval_strings,'Existentially quantified variables have global definition: ',CP) |
| 1429 | | ; true |
| 1430 | | ) |
| 1431 | | ; Parameters=[],ExTyped = NewTyped), |
| 1432 | | stop_ms_timer_with_debug_msg(T0,existential_quantifier_lifting(Solver)), |
| 1433 | | start_timer(T1,WT1), |
| 1434 | ? | (call_residue(solve_using_smt_solver_aux0(Solver,Parameters,NewTyped,LocalState,Result),Residue) |
| 1435 | | -> ajoin(['% Solve using solver ',Solver,':'],Msg), |
| 1436 | | stop_timer(Msg,T1,WT1), |
| 1437 | | %print(smt_result(Solver,Result)),nl, |
| 1438 | | print('PREDICATE is '),display_smt_result(Result,Parameters,ExTyped,Res), |
| 1439 | | check_residue(Residue) |
| 1440 | | ; stop_timer('% Solve using SMT solver FAILED',T1,WT1), Res = 'FAILED', |
| 1441 | | set_last_expression(pred,ExTyped,failed), |
| 1442 | | LocalState=[]). |
| 1443 | | |
| 1444 | | %:- use_module(tools_fastread,[read_term_from_string/2]). |
| 1445 | | :- use_module(library(codesio),[read_from_codes/2]). |
| 1446 | | %:- use_module(bsyntaxtree,[repair_used_ids/3]). |
| 1447 | | :- use_module(b_ast_cleanup,[clean_up_pred/3]). |
| 1448 | | % detect if we have a Prolog AST terminated by a dot and read it in: |
| 1449 | | repl_get_prolog_predicate(PredPrologASTCodes,Cleanup,CTyped,TypeInfo) :- |
| 1450 | | append("b(",_,PredPrologASTCodes), |
| 1451 | | reverse(PredPrologASTCodes,RC), |
| 1452 | | skip_ws(RC,RC2), |
| 1453 | | (RC2 = [0'., 0')|_] -> true % we end in ")." |
| 1454 | | ; append("/*",_,RC2) |
| 1455 | | -> add_message(eval_strings,'Predicate could be a Prolog AST term; remove final comment'), |
| 1456 | | fail % we end in a Prolog comment, but it could also be a B comment |
| 1457 | | ; add_debug_message(eval_strings,'Predicate could be a Prolog AST term; add final dot'), |
| 1458 | | fail |
| 1459 | | ), |
| 1460 | | add_message(eval_strings,'Predicate seems to be in Prolog AST format, trying to read it'), |
| 1461 | | read_from_codes(PredPrologASTCodes,Typed), |
| 1462 | | repair_used_ids(repl_get_prolog_predicate,Typed,RTyped), |
| 1463 | | bsyntaxtree:check_ast(RTyped), |
| 1464 | | (Cleanup = clean_up_pred, |
| 1465 | | clean_up_pred(RTyped,[],CTyped) -> true |
| 1466 | | ; CTyped=RTyped), |
| 1467 | | extract_type_information(CTyped,TypeInfo), |
| 1468 | | add_message(eval_strings,'Successfully read Prolog AST format:'), |
| 1469 | | nested_print_repl_expression(CTyped). |
| 1470 | | |
| 1471 | | skip_ws([32|T],R) :- !, skip_ws(T,R). |
| 1472 | | skip_ws([10|T],R) :- !, skip_ws(T,R). |
| 1473 | | skip_ws([13|T],R) :- !, skip_ws(T,R). |
| 1474 | | skip_ws([9|T],R) :- !, skip_ws(T,R). |
| 1475 | | skip_ws(R,R). |
| 1476 | | |
| 1477 | | :- use_module(bsyntaxtree,[get_global_identifiers/1]). |
| 1478 | | :- use_module(library(ordsets),[ord_member/2]). |
| 1479 | | clash(SIds,TID) :- def_get_texpr_id(TID,ID), ord_member(ID,SIds). |
| 1480 | | get_clashing_identifiers(Parameters,ClashParas) :- |
| 1481 | | get_repl_ids(TIds), |
| 1482 | | get_texpr_ids(TIds,Ids), get_global_identifiers(Csts), |
| 1483 | | append(Csts,Ids,AllIds), |
| 1484 | | sort(AllIds,SIds), |
| 1485 | | include(clash(SIds),Parameters,ClashParas). |
| 1486 | | |
| 1487 | | get_repl_ids(Identifiers) :- |
| 1488 | | b_get_machine_constants(Constants), |
| 1489 | | b_get_machine_variables(Variables), |
| 1490 | | get_repl_lets_tids(LetIds), |
| 1491 | | % TO DO: add enumerated set global constants |
| 1492 | | append([Variables,Constants,LetIds],Identifiers). |
| 1493 | | |
| 1494 | | :- use_module(probsrc(solver_interface), [solve_predicate/3, solve_predicate/5]). |
| 1495 | | :- use_module(wdsrc(well_def_analyser),[prove_sequent/1]). |
| 1496 | | :- use_module(library(terms),[term_size/2]). |
| 1497 | | |
| 1498 | | solve_with_cdclt_in_state(_Paras,Typed,LocalState,SolvedPred,Result) :- !, |
| 1499 | | get_current_state_full_store(Typed, FullStore), |
| 1500 | | LocalState=[], |
| 1501 | | cdclt_solve_predicate_in_state(Typed,FullStore,SolvedPred,Result). |
| 1502 | | |
| 1503 | | solve_with_cdclt_no_state(Paras,Typed,LocalState,SolvedPred,Result) :- !, |
| 1504 | | solver_clash_feedback(cdclt,Paras,Typed), |
| 1505 | | LocalState=[], |
| 1506 | | cdclt_solve_predicate(Typed,SolvedPred,Result). |
| 1507 | | |
| 1508 | | solve_with_cdcl_sat_in_state(_Paras,Typed,LocalState,Result) :- !, |
| 1509 | | get_current_state_full_store(Typed, FullStore), |
| 1510 | | LocalState=[], |
| 1511 | | cdcl_sat_solve_predicate_in_state(Typed,FullStore,Result). |
| 1512 | | |
| 1513 | | solve_with_cdcl_sat_no_state(Paras,Typed,LocalState,Result) :- !, |
| 1514 | | solver_clash_feedback(cdclt,Paras,Typed), |
| 1515 | | LocalState=[], |
| 1516 | | cdcl_sat_solve_predicate(Typed,Result). |
| 1517 | | |
| 1518 | | solve_using_smt_solver_aux0(Solver,Parameters,NewTyped,LocalState,Result) :- eval_repeat(Nr), |
| 1519 | | format('Trying to find ~w solutions using ~w:~n',[Nr,Solver]), |
| 1520 | | succeed_max_call_id(solve_using_smt_solver_aux, |
| 1521 | | solve_using_smt_solver_aux(Solver,Parameters,NewTyped,LocalState,Result), |
| 1522 | | Nr), |
| 1523 | | print('PREDICATE is '),display_smt_result(Result,Parameters,NewTyped,_), |
| 1524 | | fail. |
| 1525 | | solve_using_smt_solver_aux0(Solver,Parameters,NewTyped,LocalState,Result) :- |
| 1526 | ? | solve_using_smt_solver_aux(Solver,Parameters,NewTyped,LocalState,Result). |
| 1527 | | |
| 1528 | | :- use_module(cdclt_solver('cdclt_solver')). |
| 1529 | | :- use_module(cdclt_solver('difference_logic/difference_logic_solver'), [solve_idl_conj/2]). |
| 1530 | | :- use_module(extrasrc(b2setlog), [solve_pred_with_setlog/3]). |
| 1531 | | :- use_module(extension('b2asp/b2asp.pl'),[solve_pred_with_clingo/5]). |
| 1532 | | %solve_using_smt_solver_aux(Solver,_Paras,Typed,_,_) :- |
| 1533 | | % format('Solving with ~w:~n',[Solver]), translate:print_bexpr(Typed),nl,fail. |
| 1534 | | solve_using_smt_solver_aux(nostate(cdcl_sat),Paras,Typed,LocalState,Result) :- !, |
| 1535 | | solve_with_cdcl_sat_no_state(Paras,Typed,LocalState,Result). |
| 1536 | | solve_using_smt_solver_aux(cdcl_sat,Paras,Typed,LocalState,Result) :- !, |
| 1537 | | solve_with_cdcl_sat_in_state(Paras,Typed,LocalState,Result). |
| 1538 | | solve_using_smt_solver_aux(nostate(cdclt),Paras,Typed,LocalState,Result) :- !, |
| 1539 | | solve_with_cdclt_no_state(Paras,Typed,LocalState,_SolvedPred,Result). |
| 1540 | | solve_using_smt_solver_aux(cdclt,Paras,Typed,LocalState,Result) :- !, |
| 1541 | | solve_with_cdclt_in_state(Paras,Typed,LocalState,_SolvedPred,Result). |
| 1542 | | solve_using_smt_solver_aux(idl,_,Typed,LocalState,Result) :- !, |
| 1543 | | LocalState=[], |
| 1544 | | solve_idl_conj(Typed,Result). |
| 1545 | | solve_using_smt_solver_aux(setlog,_,Typed,LocalState,Result) :- !, |
| 1546 | | solve_pred_with_setlog(Typed,LocalState,Result). |
| 1547 | | solve_using_smt_solver_aux(clingo,_,Typed,LocalState,Result) :- !, |
| 1548 | | solve_pred_with_clingo(Typed,1,LocalState,Result,_Exhaustive). |
| 1549 | | solve_using_smt_solver_aux(double_check(nostate(cdclt)),Paras,Typed,LocalState,Result) :- !, |
| 1550 | | solve_with_cdclt_no_state(Paras, Typed, LocalState, SolvedPred, Result), |
| 1551 | | % cdclt possibly adds wd conditions; SolvedPred is always well-defined which is not guaranteed for the input |
| 1552 | | double_check_smt_result(nostate(cdclt),Paras,SolvedPred,LocalState,Result). |
| 1553 | | solve_using_smt_solver_aux(double_check(cdclt),Paras,Typed,LocalState,Result) :- !, |
| 1554 | | start_ms_timer(T0), |
| 1555 | | solve_with_cdclt_in_state(Paras, Typed, LocalState, SolvedPred, Result), |
| 1556 | | stop_ms_timer_with_debug_msg(T0,cdclt),start_ms_timer(T1), |
| 1557 | | double_check_smt_result(cdclt,Paras,SolvedPred,LocalState,Result), |
| 1558 | | stop_ms_timer_with_debug_msg(T1,double_check). |
| 1559 | | solve_using_smt_solver_aux(double_check(Solver),Paras,Typed,LocalState,Result) :- !, |
| 1560 | ? | solve_using_smt_solver_aux(Solver,Paras,Typed,LocalState,Result), |
| 1561 | | double_check_smt_result(Solver,Paras,Typed,LocalState,Result). |
| 1562 | | solve_using_smt_solver_aux(prob(POpts),Paras,Typed,LocalState,Result) :- !, |
| 1563 | | solver_clash_feedback(prob,Paras,Typed), |
| 1564 | | start_ms_timer(T0), |
| 1565 | | (POpts=default -> Opts = [use_smt_mode/true,use_clpfd_solver/true] |
| 1566 | | ; POpts=eval -> Opts = [use_smt_mode/false,use_clpfd_solver/true] |
| 1567 | | ; POpts=no_opts -> Opts = [use_smt_mode/false,use_clpfd_solver/true,optimize_ast/false] |
| 1568 | | ; POpts=strong -> Opts=[use_smt_mode/true,use_clpfd_solver/true,use_chr_solver/true,solver_strength/200] |
| 1569 | | ; Opts=POpts), %other options could be allow_improving_wd_mode, clean_up_pred, smt_supported_interpreter, ... |
| 1570 | | solve_predicate(Typed,LocalState,1,Opts,Result), |
| 1571 | | stop_ms_timer_with_debug_msg(T0,solve_predicate). |
| 1572 | | solve_using_smt_solver_aux('prob-unsat-core',_,Typed,LocalState,Result) :- !, LocalState=[], |
| 1573 | | % TODO: provide unsat core in state |
| 1574 | ? | unsat_core_predicate(Typed,1500,[auto_time_out_factor(180), |
| 1575 | | min_time_out(20),use_chr_solver/true],_Core,_,Result). |
| 1576 | | solve_using_smt_solver_aux('prob-unsat-core-no-chr',_,Typed,LocalState,Result) :- !, LocalState=[], |
| 1577 | | % TODO: provide unsat core in state |
| 1578 | | unsat_core_predicate(Typed,1500,[auto_time_out_factor(180), |
| 1579 | | min_time_out(20),use_chr_solver/false],_Core,_,Result). |
| 1580 | | solve_using_smt_solver_aux('prob-fast-unsat-core',_,Typed,LocalState,Result) :- !, LocalState=[], |
| 1581 | | unsat_core_predicate(Typed,20,[inspect_nested_conjuncts(false),use_chr_solver/true],_Core,_,Result). |
| 1582 | | solve_using_smt_solver_aux('smt-unsat-core'(Solver),_,Typed,LocalState,Result) :- !, LocalState=[], |
| 1583 | | unsat_core_predicate(Typed,1500,[auto_time_out_factor(180), use_smt_solver(Solver), use_chr_solver/true, |
| 1584 | | unsat_core_target(contradiction_found)],_Core,_,Result). |
| 1585 | | solve_using_smt_solver_aux('smt-quick-bup-unsat-core'(Solver),_,Typed,LocalState,Result) :- !, LocalState=[], |
| 1586 | | quick_bup_unsat_core_predicate(Typed,[use_smt_solver(Solver), use_chr_solver/true, |
| 1587 | | try_prob_solver_first(fixed_time_out(5))],Result). |
| 1588 | | solve_using_smt_solver_aux('cdclt-unsat-core',_,Typed,LocalState,Result) :- !, LocalState=[], |
| 1589 | | unsat_core_predicate(Typed,1500,[auto_time_out_factor(180), use_chr_solver/true, |
| 1590 | | min_time_out(20), use_cdclt_solver],_Core,_,Result). |
| 1591 | | solve_using_smt_solver_aux('prob-unsat-cores',_,Typed,LocalState,Result) :- !, LocalState=[], |
| 1592 | | findall(Len-R,unsat_core_predicate(Typed,1000,[use_chr_solver/true],_Core,Len,R),All), |
| 1593 | | length(All,Len), |
| 1594 | | min_member(MinL-Result,All), |
| 1595 | | format('~nFound ~w unsat cores, minimum number of conjuncts ~w~n',[Len,MinL]). |
| 1596 | | solve_using_smt_solver_aux('satsolver'(SOLVER,STATE),_,Typed,_LocalState,Result) :- !, % :sat |
| 1597 | | (STATE = nostate |
| 1598 | | -> b2sat:solve_predicate_with_satsolver_free(Typed,[],Result,[use_satsolver(SOLVER)]) |
| 1599 | | ; get_cur_state_for_repl(Typed,CState), |
| 1600 | ? | b2sat:solve_predicate_with_satsolver_in_state(Typed,CState,Result,[use_satsolver(SOLVER)]) |
| 1601 | | ). |
| 1602 | | solve_using_smt_solver_aux('prob-min-core',_,Typed,LocalState,Result) :- !, LocalState=[], |
| 1603 | | findall(core(Len,Sz,Core,R), |
| 1604 | | (unsat_core_predicate(Typed,1000,[use_chr_solver/true, |
| 1605 | | branch_and_bound,auto_time_out_factor(160),no_print],Core,Len,R), |
| 1606 | | term_size(Core,Sz)), |
| 1607 | | All), |
| 1608 | | length(All,Len), |
| 1609 | | min_member(core(MinL,_,MinCore,Result),All), |
| 1610 | | format(user_output,'~nFound ~w unsat cores~n% MINIMAL UNSAT CORE (~w conjuncts):~n',[Len,MinL]), |
| 1611 | | translate:nested_print_bexpr_as_classicalb(MinCore), |
| 1612 | | format(user_output,'% END OF MIN UNSAT CORE (~w conjuncts)~n',[MinL]). |
| 1613 | | solve_using_smt_solver_aux(Solver,Parameters,Typed,LocalState,Result) :- |
| 1614 | | (solver_call_should_ignore_state(Solver,Solver2) |
| 1615 | | -> solver_clash_feedback(Solver2,Parameters,Typed), |
| 1616 | | smt_solve_predicate(Solver2,Typed,LocalState,Result) |
| 1617 | | ; current_state_id(SID), SID \= root |
| 1618 | | -> smt_solve_predicate_in_state(SID,Solver,Typed,LocalState,Result) |
| 1619 | | ; smt_solve_predicate(Solver,Typed,LocalState,Result) |
| 1620 | | ). |
| 1621 | | |
| 1622 | | %is_already_declared_in_state(State,TID) :- def_get_texpr_id(TID,ID), member(bind(ID,_),State). |
| 1623 | | |
| 1624 | | solver_call_should_ignore_state(nostate(Solver),Solver). |
| 1625 | | solver_call_should_ignore_state('satsolver'(_,nostate),'satsolver'). |
| 1626 | | |
| 1627 | | % ------------- |
| 1628 | | % provide feedback when solver ignores variables/constants in current state |
| 1629 | | |
| 1630 | | solver_clash_feedback(Solver,Parameters,Typed) :- |
| 1631 | | current_state_id(SID), |
| 1632 | | potential_clash_in_state(Parameters,Typed,SID,Clashes), |
| 1633 | | Clashes \= [], |
| 1634 | | !, |
| 1635 | | (silent_mode(on) -> true |
| 1636 | | ; format_with_colour_nl(user_output,[dark_gray], |
| 1637 | | 'Calling solver ~w, ignoring values ~w in state ~w',[Solver,Clashes,SID])). |
| 1638 | | solver_clash_feedback(Solver,_,_) :- |
| 1639 | | debug_format(19,'Calling ~w solver via solve_predicate~n',[Solver]). |
| 1640 | | |
| 1641 | | potential_clash_in_state(_,_,root,IDs) :- !, IDs=[]. |
| 1642 | | potential_clash_in_state(Parameters,Typed,_StateID,IDs) :- |
| 1643 | | get_texpr_ids(Parameters,ParaIDs), |
| 1644 | | find_identifier_uses_top_level(Typed,UsedIds), |
| 1645 | | findall(ID,(member(ID,UsedIds), is_var_or_const(_,ID), nonmember(ID,ParaIDs)),IDs). |
| 1646 | | |
| 1647 | | is_var_or_const(constant,ID) :- bmachine:b_is_constant(ID). |
| 1648 | | is_var_or_const(variable,ID) :- bmachine:b_is_variable(ID). |
| 1649 | | |
| 1650 | | % ----------- |
| 1651 | | |
| 1652 | | :- use_module(probsrc(specfile),[get_state_for_b_formula/3]). |
| 1653 | | %:- use_module(probsrc(bsyntaxtree),[find_identifier_uses_top_level/2]). |
| 1654 | | |
| 1655 | | get_current_state_full_store(Typed, FullStore) :- |
| 1656 | | ( current_state_id(StateID) |
| 1657 | | -> get_state_for_b_formula(StateID, Typed, StateBindings) |
| 1658 | | ; StateBindings = [] |
| 1659 | | ), |
| 1660 | | find_identifier_uses_top_level(Typed, UsedIds), % do not include global sets |
| 1661 | | % add unbound variables for all used identifiers |
| 1662 | | findall(bind(Id,_), (member(Id, UsedIds), \+ member(bind(Id,_), StateBindings)), Bindings), |
| 1663 | | append(Bindings, StateBindings, FullStore). |
| 1664 | | |
| 1665 | | double_check_smt_result(Solver,_Parameters,Typed,_LocalState,solution(Bindings)) :- !, |
| 1666 | | maplist(get_bind,Bindings,State), |
| 1667 | | ( solver_call_should_ignore_state(Solver, Solver2) |
| 1668 | | -> find_identifier_uses_top_level(Typed, UsedIds), |
| 1669 | | findall(bind(IdName,_), (member(IdName,UsedIds), \+ member(bind(IdName,_),State)), FreeBindings), |
| 1670 | | append(State, FreeBindings, FullStore) |
| 1671 | | ; Solver2 = Solver, |
| 1672 | | get_current_state_full_store(Typed, TFullStore), |
| 1673 | | findall(bind(IdName,_), (member(bind(IdName,_),TFullStore), \+ member(bind(IdName,_),State)), TFullStore2), |
| 1674 | | append(State, TFullStore2, FullStore) |
| 1675 | | ), |
| 1676 | | debug_format(19,'Double-checking ~w with ProB solver using solve_predicate~n',[Solver]), |
| 1677 | | %print(bindings(Bindings)),nl, |
| 1678 | | (solve_predicate(Typed,FullStore,DCResult), %print(DCResult),nl, |
| 1679 | | check_dc_sol(DCResult,Solver2,solution(_)) -> true |
| 1680 | | ; add_error(double_check_smt_result,'Double checking NOT successful, solution not confirmed: ',Typed,Typed)). |
| 1681 | | double_check_smt_result(Solver,_Parameters, Typed, _LocalState, Res) :- |
| 1682 | | ( solver_call_should_ignore_state(Solver, Solver2) |
| 1683 | | -> % FullStore is var |
| 1684 | | debug_format(19,'Double checking result of ~w with ProB solver (ignoring current state)~n',[Solver2]) |
| 1685 | | ; get_current_state_full_store(Typed, FullStore), |
| 1686 | | Solver2 = Solver, |
| 1687 | | debug_format(19,'Double checking result with of ~w ProB solver (in current state)~n',[Solver2]) |
| 1688 | | ), |
| 1689 | | ( solve_predicate(Typed, FullStore, TDCResult) |
| 1690 | | -> DCResult = TDCResult |
| 1691 | | ; % solve_predicate did fail if contradiction with current state |
| 1692 | | % should no longer happen |
| 1693 | | add_warning(double_check_smt_result,'solve_predicate failed: ',Typed, Typed), |
| 1694 | | DCResult = contradiction_found |
| 1695 | | ), |
| 1696 | | ( check_dc_sol(DCResult, Solver2, Res) |
| 1697 | | -> true |
| 1698 | | ; add_error(double_check_smt_result,'Double checking NOT successful', Typed, Typed) |
| 1699 | | ). |
| 1700 | | |
| 1701 | | get_bind(binding(Var,Val,_PP),bind(Var,Val)). |
| 1702 | | get_bind(bind(Var,Val),bind(Var,Val)). |
| 1703 | | |
| 1704 | | check_dc_sol(X,_,X) :- !, print_green('double check ok'),nl. |
| 1705 | | check_dc_sol(no_solution_found(R1),_,no_solution_found(R2)) :- |
| 1706 | | functor(R1,F,N), functor(R2,F,N), !, |
| 1707 | | print_green('double check ok (small difference in reason for not finding solution)'),nl. |
| 1708 | | check_dc_sol(no_solution_found(unfixed_deferred_sets),_,contradiction_found) :- |
| 1709 | | % Z3, CDCL(T) do not check for unfixed_deferred sets; see test 2060 |
| 1710 | | !, print_green('double check of contradiction_found ok'),nl. |
| 1711 | | check_dc_sol(time_out,Solver,E) :- !, X=time_out, |
| 1712 | | format_with_colour_nl(user_error,[orange,bold], |
| 1713 | | 'double check not completed, ProB reported: ~w,~n ~w reported: ~w',[X,Solver,E]), |
| 1714 | | fail. % change to fail to report error, true to accept as ok |
| 1715 | | check_dc_sol(X,Solver,E) :- |
| 1716 | | format_with_colour_nl(user_error,[red,bold], |
| 1717 | | 'double check unexpected result, ProB reported: ~w,~n ~w reported: ~w',[X,Solver,E]), |
| 1718 | | fail. |
| 1719 | | |
| 1720 | | display_smt_result(solution(Bindings),Parameters,ExTyped,Res) :- !, |
| 1721 | | set_last_expression(pred,ExTyped,pred_true), |
| 1722 | | print_green('TRUE'),nl, |
| 1723 | | ( Bindings=[] |
| 1724 | | -> set_last_solution(Parameters,[]) |
| 1725 | | ; silent_mode(off), write('Solution: '),nl,Bindings=[bind(_,_)|_] |
| 1726 | | -> print_visible_solution_with_type(Parameters, Bindings), |
| 1727 | | set_last_solution(Parameters,Bindings) |
| 1728 | | ; Bindings = [bind(_,_)|_] -> set_last_solution(Parameters,Bindings) |
| 1729 | | ; findall(bind(ID,Val),member(binding(ID,Val,_),Bindings),LocalState), |
| 1730 | | set_last_solution(Parameters,LocalState), |
| 1731 | | findall(1,(member(binding(ID2,_,S2),Bindings),print_binding(ID2,S2),nl),_) |
| 1732 | | ), Res = 'TRUE'. |
| 1733 | | display_smt_result(contradiction_found,_,ExTyped,Res) :- !, |
| 1734 | | format_with_colour(user_output,[light_red],'FALSE',[]),nl, |
| 1735 | | set_last_expression(pred,ExTyped,pred_false), |
| 1736 | | Res = 'FALSE'. |
| 1737 | | display_smt_result(contradiction_found(UnsatCore),_,ExTyped,Res) :- !, |
| 1738 | | display_smt_result(contradiction_found,_,ExTyped,'FALSE'), |
| 1739 | | translate_bexpression(UnsatCore, PrettyUnsatCore), |
| 1740 | | format_with_colour_nl(user_output,[dark_gray],'Unsat Core: ~w',[PrettyUnsatCore]), |
| 1741 | | Res = 'FALSE'. |
| 1742 | | display_smt_result(no_solution_found(no_idl_constraint),_,_,'UNKNOWN') :- !, |
| 1743 | | print_red('UNKNOWN: '),nl, |
| 1744 | | format_with_colour_nl(user_output,[light_red],'Constraint can not be transformed to integer difference logic.',[]). |
| 1745 | | display_smt_result(no_solution_found(cvc4_unknown),_,ExTyped,'UNKNOWN') :- !, |
| 1746 | | print_red('UNKNOWN'),nl, |
| 1747 | | set_last_expression(pred,ExTyped,unknown). |
| 1748 | | display_smt_result(no_solution_found(Reason),_,ExTyped,'UNKNOWN') :- !, |
| 1749 | | print_red('UNKNOWN: '),print(Reason),nl, |
| 1750 | | set_last_expression(pred,ExTyped,unknown). |
| 1751 | | display_smt_result(error,_,ExTyped,'UNKNOWN') :- !, |
| 1752 | | print_red('UNKNOWN: '),print('(due to error, possibly well-definedness error)'),nl, |
| 1753 | | set_last_expression(pred,ExTyped,unknown). |
| 1754 | | display_smt_result(Other,_,ExTyped,'UNKNOWN') :- !, |
| 1755 | | print_red('*** UNKNOWN SMT RESULT ***: '),print(Other),nl, |
| 1756 | | set_last_expression(pred,ExTyped,unknown). |
| 1757 | | |
| 1758 | | |
| 1759 | | %:- use_module(bsyntaxtree,[def_get_texpr_id/2]). |
| 1760 | | print_parameters([]). |
| 1761 | | print_parameters([TID]) :- !, print_id(TID). |
| 1762 | | print_parameters([TID|T]) :- print_id(TID), print(','), print_parameters(T). |
| 1763 | | print_id(TID) :- def_get_texpr_id(TID,ID), print(ID). |
| 1764 | | |
| 1765 | | |
| 1766 | | |
| 1767 | | %indent(X) :- X<1,!. |
| 1768 | | %indent(X) :- print('+ '), X1 is X-1, indent(X1). |
| 1769 | | |
| 1770 | | % TOOLS |
| 1771 | | % ----- |
| 1772 | | |
| 1773 | | |
| 1774 | | % detecting existential quantifiers: so that the REPL can print the solutions for them |
| 1775 | | % an example is the following test: |
| 1776 | | % probcli -eval "#active,ready,waiting,rr.(active : POW(PID) & ready : POW(PID) & waiting : POW(PID) & active <: PID & ready <: PID & waiting <: PID & (ready /\ waiting = {}) & (active /\ (ready \/ waiting)) = {} & card(active) <= 1 & rr : waiting & active = {})" ../prob_examples/public_examples/B/Benchmarks/scheduler.mch |
| 1777 | | % alternative would be to avoid optimizer to run at top-level |
| 1778 | | is_existential_quantifier(TE,Par,Body) :- is_existential_quantifier(TE,recur,Par,Body). |
| 1779 | | is_existential_quantifier(b(EXISTS,pred,_),Recur,FullParameters,FullTypedBody) :- |
| 1780 | | is_existential_aux(EXISTS,Parameters,TypedBody), |
| 1781 | | !, |
| 1782 | | (Recur=recur, |
| 1783 | | is_existential_quantifier(TypedBody,Recur,InnerPar,InnerBody) % recursively look inside |
| 1784 | | -> append(Parameters,InnerPar,FullParameters), |
| 1785 | | FullTypedBody = InnerBody |
| 1786 | | ; FullTypedBody = TypedBody, FullParameters=Parameters). |
| 1787 | | is_existential_aux(Var,_,_) :- var(Var),!, add_internal_error('Illegal call:',is_existential_aux(Var,_,_)),fail. |
| 1788 | | is_existential_aux(exists(Parameters,TypedBody),Parameters,TypedBody). |
| 1789 | | is_existential_aux(let_predicate(Parameters,AssignmentExprs,Pred),Parameters,TypedBody) :- |
| 1790 | | generate_let_equality_pred(Parameters,AssignmentExprs,EqPreds), |
| 1791 | | append(EqPreds,[Pred],AllPreds), |
| 1792 | | conjunct_predicates(AllPreds,TypedBody). |
| 1793 | | is_existential_aux(conjunct(A,B),Parameters,TypedBody) :- |
| 1794 | | is_existential_quantifier(A,no_recur,Parameters,TAA), |
| 1795 | | !, % then do not look if B is existential quantifier below |
| 1796 | | b_ast_cleanup:get_sorted_ids(Parameters,SIds), |
| 1797 | | b_ast_cleanup:not_occurs_in_predicate(SIds,B), |
| 1798 | | \+ is_existential_quantifier(B,no_recur,_,_), |
| 1799 | | conjunct_predicates([TAA,B],TypedBody),!. |
| 1800 | | is_existential_aux(conjunct(A,B),Parameters,TypedBody) :- |
| 1801 | | is_existential_quantifier(B,no_recur,Parameters,TBB), |
| 1802 | | !, |
| 1803 | | b_ast_cleanup:get_sorted_ids(Parameters,SIds), |
| 1804 | | b_ast_cleanup:not_occurs_in_predicate(SIds,A), |
| 1805 | | conjunct_predicates([A,TBB],TypedBody). |
| 1806 | | % TO DO: treat lazy_let_pred |
| 1807 | | |
| 1808 | | generate_let_equality_pred([],[],[]). |
| 1809 | | generate_let_equality_pred([ID|T],[Exp|TE],[EqPred|TR]) :- |
| 1810 | | EqPred = b(equal(ID,Exp),pred,[]), % TO DO: update WD info |
| 1811 | | generate_let_equality_pred(T,TE,TR). |
| 1812 | | |
| 1813 | | |
| 1814 | | |
| 1815 | | :- use_module(clpfd_interface,[clpfd_overflow_error_message/0]). |
| 1816 | | |
| 1817 | | |
| 1818 | | :- use_module(tools_meta,[call_residue/2]). |
| 1819 | | :- use_module(clpfd_interface,[catch_clpfd_overflow_call2/2]). |
| 1820 | | probcli_clpfd_overflow_mnf_call1(Call) :- |
| 1821 | | call_residue(probcli_clpfd_overflow_mnf_call2(Call),Residue), |
| 1822 | | check_residue(Residue). |
| 1823 | | probcli_clpfd_overflow_mnf_call2(Call) :- start_timer(T1,WT1), |
| 1824 | | catch_clpfd_overflow_call2( |
| 1825 | | (Call->stop_timer(T1,WT1) |
| 1826 | | ; stop_timer('% ProB evaluation: ',T1,WT1),show_error_pos, |
| 1827 | | print_red('Expression not well-defined !'),nl, |
| 1828 | | fail), |
| 1829 | | ( stop_timer('% ProB evaluation: ',T1,WT1),clpfd_overflow_error_message, fail)). |
| 1830 | | |
| 1831 | | |
| 1832 | | |
| 1833 | | probcli_clpfd_overflow_call1(Call) :- |
| 1834 | | call_residue(probcli_clpfd_overflow_call2(Call),Residue), |
| 1835 | | check_residue(Residue). |
| 1836 | | probcli_clpfd_overflow_call2(Call) :- start_timer(T1,WT1), |
| 1837 | | catch_clpfd_overflow_call2( |
| 1838 | | (Call -> stop_timer(T1,WT1) ; stop_timer(T1,WT1),fail), |
| 1839 | | ( stop_timer(T1,WT1),clpfd_interface:clpfd_overflow_error_message, fail)). |
| 1840 | | |
| 1841 | | check_residue([]) :- !. |
| 1842 | | check_residue(Residue) :- |
| 1843 | | add_internal_error('Call residue: ',Residue), |
| 1844 | | portray_residue(Residue). % or tools_printing:print_goal(Residue) |
| 1845 | | portray_residue(L) :- gen_clause(L,C), portray_clause((residue :- C)). |
| 1846 | | gen_clause([],true). |
| 1847 | | gen_clause([X],X) :- !. |
| 1848 | | gen_clause([H|T],(H,R)) :- gen_clause(T,R). |
| 1849 | | |
| 1850 | | :- volatile last_eval_time/2. |
| 1851 | | :- dynamic last_eval_time/2. |
| 1852 | | start_timer(T1,WT1) :- retractall(last_eval_time(_,_)), retractall(last_norm_time(_,_)), |
| 1853 | | statistics(runtime,[T1,_]), |
| 1854 | | statistics(walltime,[WT1,_]). |
| 1855 | | stop_timer(T1,WT1) :- |
| 1856 | | statistics(runtime,[T2,_]), TotTime is T2-T1, |
| 1857 | | statistics(walltime,[WT2,_]), WTotTime is WT2-WT1, |
| 1858 | | retractall(last_eval_time(_,_)), |
| 1859 | | %debug_println(20,stopped_timer(TotTime,T2,T1)), |
| 1860 | | (debug_mode(off) -> true |
| 1861 | | ; format_with_colour_nl(user_output,[dark_gray],'stopped timer ~w ms (~w ms walltime).',[TotTime,WTotTime])), |
| 1862 | | assertz(last_eval_time(TotTime,WTotTime)). |
| 1863 | | stop_timer(Msg,T1,WT1) :- |
| 1864 | | statistics(runtime,[T2,_]), TotTime is T2-T1, |
| 1865 | | statistics(walltime,[WT2,_]), WTotTime is WT2-WT1, |
| 1866 | | format_with_colour_nl(user_output,[dark_gray],'~w ~w ms (~w ms walltime).',[Msg,TotTime,WTotTime]), |
| 1867 | | assertz(last_eval_time(TotTime,WTotTime)). |
| 1868 | | |
| 1869 | | :- volatile last_norm_time/2. |
| 1870 | | :- dynamic last_norm_time/2. |
| 1871 | | start_norm_timer(T1,WT1) :- retractall(last_norm_time(_,_)), |
| 1872 | | statistics(runtime,[T1,_]), |
| 1873 | | statistics(walltime,[WT1,_]). |
| 1874 | | stop_norm_timer(T1,WT1) :- |
| 1875 | | statistics(runtime,[T2,_]), TotTime is T2-T1, |
| 1876 | | statistics(walltime,[WT2,_]), WTotTime is WT2-WT1, |
| 1877 | | retractall(last_norm_time(_,_)), |
| 1878 | | debug_println(20,stopped_norm_timer(TotTime,T2,T1)), |
| 1879 | | assertz(last_norm_time(TotTime,WTotTime)). |
| 1880 | | |
| 1881 | | |
| 1882 | | :- volatile eval_mode/1. |
| 1883 | | :- dynamic eval_mode/1. |
| 1884 | | eval_det :- eval_mode(eval_det). |
| 1885 | | |
| 1886 | | toggle_eval_det :- retract(eval_mode(_)),!, |
| 1887 | | format('% Going back to ordinary enumeration~n',[]). |
| 1888 | | toggle_eval_det :- set_eval_det, |
| 1889 | | format('% Going to deterministic mode (for existentially quantified formulas)~n',[]). |
| 1890 | | |
| 1891 | | set_eval_det :- set_eval_mode(eval_det). |
| 1892 | | set_eval_mode(M) :- retractall(eval_mode(_)), assertz(eval_mode(M)). |
| 1893 | | unset_eval_mode :- retractall(eval_mode(_)). |
| 1894 | | |
| 1895 | | eval_ground_wf(WF) :- (eval_det -> ground_det_wait_flag(WF) ; ground_wait_flags(WF)). |
| 1896 | | |
| 1897 | | |
| 1898 | | |
| 1899 | | |
| 1900 | | |
| 1901 | | show_error_pos :- |
| 1902 | | %File = null, % console text typed by user |
| 1903 | | findall(error_pos(Line,Col,EndLine,EndCol), |
| 1904 | | (check_error_span_file_linecol(_Src,File,Line,Col,EndLine,EndCol), file_unknown(File)), |
| 1905 | | Errs), |
| 1906 | | !, |
| 1907 | | remove_dups(Errs,Errs2), |
| 1908 | | LastLine is -100, show_error_pos(Errs2,LastLine). |
| 1909 | | |
| 1910 | | file_unknown(null). |
| 1911 | | file_unknown(unknown(_)). |
| 1912 | | file_unknown(unknown). |
| 1913 | | |
| 1914 | | :- use_module(tools_printing,[start_terminal_colour/2, reset_terminal_colour/1]). |
| 1915 | | show_line(Line,FromCol,ToCol) :- % highlight if possible FromCol ToCol, Columns start at 0, ToCol is not included ?! |
| 1916 | | % TO DO: handle multiple errors on line |
| 1917 | | (current_codes(E),get_line(E,Line,ErrLine) |
| 1918 | | -> append(ErrLine,[32],Errline2), % add one whitespace at end |
| 1919 | | prefix_length(Errline2,Prefix,FromCol), |
| 1920 | | format(user_output,'~n### ~s',[Prefix]), |
| 1921 | | Len is ToCol - FromCol, |
| 1922 | | sublist(Errline2,ErrStr,FromCol,Len,_), |
| 1923 | | % start_terminal_colour([red_background,white,bold],user_output), |
| 1924 | | start_terminal_colour([red,underline,bold],user_output), |
| 1925 | | format(user_output,'~s',[ErrStr]), % Print Error Part in RED |
| 1926 | | reset_terminal_colour(user_output), |
| 1927 | ? | sublist(Errline2,Suffix,ToCol,_,0), |
| 1928 | | format(user_output,'~s~n',[Suffix]) |
| 1929 | | ; true). |
| 1930 | | show_line(Line) :- |
| 1931 | | (current_codes(E),get_line(E,Line,ErrLine) |
| 1932 | | -> format('~n### ~s~n',[ErrLine]) |
| 1933 | | ; true). |
| 1934 | | show_error_pos([],_). |
| 1935 | | show_error_pos([error_pos(Line,Col,EL,EC)|T],LastLine) :- % print(pos(Line,Col,EL,EC)),nl, |
| 1936 | | % first display source code of line with error: |
| 1937 | ? | (LastLine==Line -> true ; EL==Line,show_line(Line,Col,EC) -> true ; show_line(Line)), |
| 1938 | | print('### '), indent_ws(Col), |
| 1939 | | (EL=Line,EC>Col -> Len is EC-Col ; Len=1), |
| 1940 | | underline(Len),nl, |
| 1941 | | (Line>1 -> print('### Line: '), print(Line), |
| 1942 | | print(' Column: '), print(Col),nl |
| 1943 | | ; true), |
| 1944 | | show_error_pos(T,Line). |
| 1945 | | |
| 1946 | | indent_ws(X) :- X<1,!. |
| 1947 | | indent_ws(X) :- print(' '), X1 is X-1, indent_ws(X1). |
| 1948 | | underline(0) :- !. |
| 1949 | | underline(N) :- N>0, print('^'), N1 is N-1, underline(N1). |
| 1950 | | |
| 1951 | | get_line(_,Nr,R) :- Nr<1,!,R=[]. |
| 1952 | | get_line([],_,R) :- !, R=[]. |
| 1953 | | get_line(Codes,Nr,Res) :- is_newline(Codes,T),!, N1 is Nr-1, get_line(T,N1,Res). |
| 1954 | | get_line([H|T],1,Res) :- !, Res=[H|RT], get_line(T,1,RT). |
| 1955 | | get_line([_H|T],Nr,Res) :- get_line(T,Nr,Res). |
| 1956 | | |
| 1957 | | is_newline([10,13|T],T). |
| 1958 | | is_newline([10|T],T). |
| 1959 | | is_newline([13|T],T). |
| 1960 | | |
| 1961 | | %%%%% to show error position in Tcl/Tk console %%%%% |
| 1962 | | get_error_positions(EPos) :- |
| 1963 | | findall(error_pos(Line,Col,EndLine,EndCol),check_error_span_file_linecol(_Src,_File,Line,Col,EndLine,EndCol),Errs),!, |
| 1964 | | get_error_position_string_l(Errs,EPos). |
| 1965 | | |
| 1966 | | get_error_position_string_l(List,EPos) :- |
| 1967 | | maplist(get_error_position,List,StringList), |
| 1968 | | haskell_csp:convert_string_list_to_string(StringList,EPos). |
| 1969 | | |
| 1970 | | get_error_position(error_pos(Line,Col,EL,EC),String) :- |
| 1971 | | ((current_codes(E),get_line(E,Line,ErrLine)) |
| 1972 | | -> atom_codes(N,ErrLine), |
| 1973 | | atom_concat('### ',N, FirstLineAtom), |
| 1974 | | atom_concat(FirstLineAtom,';',FirstLineAtom1) |
| 1975 | | ; FirstLineAtom1 = '### ;'), |
| 1976 | | get_ident_ws(Col,'',WS), |
| 1977 | | (EL=Line,EC>Col -> Len is EC-Col ; Len=1), |
| 1978 | | get_underlines(Len,'',Underlines), |
| 1979 | | atom_concat('### ',WS,SecondLineAtom), |
| 1980 | | atom_concat(SecondLineAtom,Underlines,SecondLineAtom1), |
| 1981 | | atom_concat(SecondLineAtom1,';',SecondLineAtom2), |
| 1982 | | atom_concat(FirstLineAtom1,SecondLineAtom2,String). |
| 1983 | | |
| 1984 | | get_ident_ws(X,WS,WS) :- |
| 1985 | | X<1,!. |
| 1986 | | get_ident_ws(X,WS,Res) :- |
| 1987 | | atom_concat(WS,' ',WS1), |
| 1988 | | X1 is X-1, |
| 1989 | | get_ident_ws(X1,WS1,Res). |
| 1990 | | |
| 1991 | | get_underlines(0,U,U) :- !. |
| 1992 | | get_underlines(X,U,Res) :- |
| 1993 | | X>0, |
| 1994 | | atom_concat(U,'^',U1), |
| 1995 | | X1 is X-1, |
| 1996 | | get_underlines(X1,U1,Res). |
| 1997 | | |
| 1998 | | :- volatile last_expression/2, last_expression_value/1. |
| 1999 | | :- dynamic last_expression/2, last_expression_value/1. |
| 2000 | | last_expression(Type,Expr,Value) :- |
| 2001 | | last_expression(Type,Expr), last_expression_value(Value). |
| 2002 | | set_last_expression(Type,Expr,Value) :- |
| 2003 | | clear_last_expression, %print(assert),debug:nl_time, |
| 2004 | | assertz(last_expression(Type,Expr)), |
| 2005 | | % can be expensive; we could pack the value: mypack(Value,PackedValue),debug:nl_time, |
| 2006 | | PackedValue=Value, |
| 2007 | | assertz(last_expression_value(PackedValue)). % print(done),debug:nl_time. |
| 2008 | | |
| 2009 | | %mypack(Atom,PVal) :- atom(Atom),!,PVal=Atom. |
| 2010 | | %mypack(Val,PVal) :- state_packing:pack_value(Val,PVal). |
| 2011 | | |
| 2012 | | last_expression_type(Type) :- last_expression(Type,_). |
| 2013 | | |
| 2014 | | clear_last_expression :- |
| 2015 | | retractall(last_expression(_,_)), retractall(last_expression_value(_)). |
| 2016 | | |
| 2017 | | %:- use_module(bsyntaxtree,[get_texpr_type/2]). |
| 2018 | | |
| 2019 | | %print_last_info :- stream_property(A,mode(M)), write(open_stream(A,M)),nl,fail. |
| 2020 | | print_last_info :- \+ last_expression(_,_Expr),!, |
| 2021 | | print_red('Please evaluate an expression or predicate first.'),nl. |
| 2022 | | print_last_info :- last_expression(Type,Expr), |
| 2023 | | % for insertion into unit tests |
| 2024 | | print('% Type: '), print_quoted(Type), |
| 2025 | | (Type=expr,get_texpr_type(Expr,ET),pretty_type(ET,PrettyType) |
| 2026 | | -> print(' : '), print(PrettyType), |
| 2027 | | print(' [Card='), |
| 2028 | | (max_cardinality(ET,Card) -> print(Card) ; print('??')), print(']') |
| 2029 | | ; true),nl, |
| 2030 | | |
| 2031 | | print('% Eval Time: '), |
| 2032 | | (last_eval_time(Time,WTime) |
| 2033 | | -> format('~w ms (~w ms walltime)',[Time,WTime]), |
| 2034 | | (last_norm_time(NTime,NWTime) |
| 2035 | | -> format(' + Normalisation: ~w ms (~w ms walltime)',[NTime,NWTime]) |
| 2036 | | ; true), |
| 2037 | | (last_expansion_time(EWT) -> format(' + State expansion: ~w ms walltime',[EWT]) ; true) |
| 2038 | | ; print_red('*UNKNOWN*') |
| 2039 | | ),nl. |
| 2040 | | |
| 2041 | | |
| 2042 | | print_last_value :- \+ last_expression(_,_Expr),!, |
| 2043 | | print_red('Please evaluate an expression or predicate first.'),nl. |
| 2044 | | print_last_value :- last_expression_value(Value), |
| 2045 | | print('Last Expression Value = '),nl, |
| 2046 | | translate:print_bvalue(Value),nl. |
| 2047 | | |
| 2048 | | print_last_expression :- \+ last_expression(_,_Expr),!, |
| 2049 | | print_red('Please evaluate an expression or predicate first.'),nl. |
| 2050 | | print_last_expression :- last_expression(_Type,Expr,Value), |
| 2051 | | print_last_info, |
| 2052 | | print('% '), translate:print_bexpr(Expr),nl, |
| 2053 | | (Value = false -> print_quoted(must_fail_det(1,"",Expr)),print('.'),nl |
| 2054 | | ; print_quoted(Expr),nl, |
| 2055 | | print('% = '),print_quoted(Value),nl). |
| 2056 | | |
| 2057 | | indent_print_last_expression :- \+ last_expression(_,_Expr),!, |
| 2058 | | print_red('Please evaluate an expression or predicate first.'),nl. |
| 2059 | | indent_print_last_expression :- last_expression(_Type,Expr), |
| 2060 | | nested_print_bexpr(Expr). |
| 2061 | | |
| 2062 | | nested_print_repl_expression(Typed) :- |
| 2063 | | set_unicode_mode, temporary_set_preference(pp_with_terminal_colour,true,C), |
| 2064 | | call_cleanup((nested_print_bexpr(Typed),nl), |
| 2065 | | (unset_unicode_mode, reset_temporary_preference(pp_with_terminal_colour,C))). |
| 2066 | | print_component(component(Pred,Ids)) :- format('Component over ~w :~n',[Ids]), translate:print_bexpr(Pred),nl. |
| 2067 | | |
| 2068 | | :- use_module(extrasrc(unsat_cores),[unsat_core_wth_auto_time_limit/5, quick_bup_core/4]). |
| 2069 | | unsat_core_last_expression :- \+ last_expression(pred,_Expr),!, |
| 2070 | | print_red('Please evaluate a predicate first.'),nl. |
| 2071 | | unsat_core_last_expression :- \+ last_expression(pred,_Expr,pred_false),!, |
| 2072 | | print('The UNSAT CORE can only be computed for false predicates.'),nl. |
| 2073 | | unsat_core_last_expression :- last_expression(pred,Expr), |
| 2074 | | last_eval_time(_Time,WTime), |
| 2075 | | unsat_core_predicate(Expr,WTime,[use_chr_solver/true],_,_,_). % we could use without auto |
| 2076 | | |
| 2077 | | unsat_core_predicate(Pred,MaxTimeOut,Options,Core,Len,Result) :- |
| 2078 | | start_timer(T1,W1), |
| 2079 | | print('% COMPUTING UNSAT CORE: '), translate:print_bexpr(Pred),nl, |
| 2080 | | % maybe strip top-level existential quantifier |
| 2081 | ? | unsat_core_wth_auto_time_limit(Pred,MaxTimeOut,Options,Result,Core), |
| 2082 | | nl,stop_timer('% Time to compute core: ',T1,W1), |
| 2083 | | print_unsat_core(Pred,Core,Options,Result,Len). |
| 2084 | | |
| 2085 | | |
| 2086 | | quick_bup_unsat_core_predicate(Pred,Options,Result) :- |
| 2087 | | start_timer(T1,W1), |
| 2088 | | print('% Trying to compute UNSAT CORE in bottom-up fashion: '), translate:print_bexpr(Pred),nl, |
| 2089 | | quick_bup_core(Pred,Options,Core,Result),!, |
| 2090 | | nl,stop_timer('% Time to compute core: ',T1,W1), |
| 2091 | | print_unsat_core(Pred,Core,Options,Result,_). |
| 2092 | | quick_bup_unsat_core_predicate(_,_,'UNKNOWN') :- |
| 2093 | | print('% No unsat core found in bottom-up fashion. Use regular unsat core instead.'),nl. |
| 2094 | | |
| 2095 | | |
| 2096 | | print_unsat_core(Pred,Core,Options,Result,Len) :- |
| 2097 | | size_of_conjunction(Pred,OrigSize), |
| 2098 | | length(Core,Len), |
| 2099 | | (member(no_print,Options) -> true |
| 2100 | | ; format('% UNSAT CORE (~w conjuncts out of ~w): ~w~n',[Len,OrigSize,Result]), |
| 2101 | | translate:nested_print_bexpr_as_classicalb(Core), |
| 2102 | | format('% END OF UNSAT CORE (~w conjuncts)~n',[Len]) |
| 2103 | | ). |
| 2104 | | |
| 2105 | | % test that we obtain same value with pretty-printed version of last expression: |
| 2106 | | recheck_pp_of_last_expression(_,_,_) :- \+ last_expression(_,_Expr),!, |
| 2107 | | print_red('Please evaluate an expression or predicate first.'),nl. |
| 2108 | | recheck_pp_of_last_expression(Mode,NewResult,EnumWarning) :- last_expression(_Type,Expr,Value), |
| 2109 | | translate_subst_or_bexpr_in_mode(Mode,Expr,Str), % Mode=unicode or ascii |
| 2110 | | translate_bvalue(Value,ExpectedRes), |
| 2111 | | format('Rechecking pretty-printed version of last formula (expecting ~w): ~w~n',[ExpectedRes,Str]), |
| 2112 | | (eval_string(Str,NewResult,EnumWarning) |
| 2113 | | -> (NewResult = ExpectedRes -> print_green('OK'),nl |
| 2114 | | ; add_error(recheck_pp_of_last_expression,'Unexpected result: ',NewResult), |
| 2115 | | last_expression(_Type2,Expr2), |
| 2116 | | translate_subst_or_bexpr_in_mode(Mode,Expr2,Str2), |
| 2117 | | format(' Re-Pretty-printed version of re-checked formula: ~w~n',[Str2])) |
| 2118 | | ; add_error(recheck_pp_of_last_expression,'Evaluation failed:',Str), |
| 2119 | | NewResult='FAIL', EnumWarning=false |
| 2120 | | ). |
| 2121 | | |
| 2122 | | :- use_module(library(system)). |
| 2123 | | add_last_expression_to_unit_tests :- \+ last_expression(_,_Expr),!, |
| 2124 | | print_red('Please evaluate an expression or predicate first.'),nl. |
| 2125 | | add_last_expression_to_unit_tests :- last_expression(Type,Expr,Value), |
| 2126 | | open_unit_test_file(S), !, write(S,' & '), nl(S), write(S,' ( '), |
| 2127 | | (print_unit_test_assertion(Type,Expr,Value,S) -> true ; print('PRINTING FAILED'),nl), |
| 2128 | | write(S,' ) '), datime(datime(Yr,Mon,Day,Hr,Min,_Sec)), |
| 2129 | | format(S,'/* ~w/~w/~w ~w:~w */',[Day,Mon,Yr,Hr,Min]), |
| 2130 | | nl(S), close(S). |
| 2131 | | add_last_expression_to_unit_tests :- print('Could not save expression to unit test file ($PROB_EX_DIR/B/Laws/REPL_UNIT_TESTS.def).'),nl. |
| 2132 | | |
| 2133 | | open_unit_test_file(S) :- |
| 2134 | | environ('PROB_EX_DIR',Dir), |
| 2135 | | atom_concat(Dir,'/B/Laws/REPL_UNIT_TESTS.def',REPLFILE), |
| 2136 | | print(opening(REPLFILE)),nl, |
| 2137 | | my_open(REPLFILE,append,S). |
| 2138 | | |
| 2139 | | |
| 2140 | | my_open(File,Mode,S) :- |
| 2141 | | catch(open(File,Mode,S), |
| 2142 | | error(existence_error(_,_),E), |
| 2143 | | add_error_fail(my_open,'File does not exist: ',File:E)). |
| 2144 | | |
| 2145 | | %:- use_module(bsyntaxtree,[create_texpr/4, safe_create_texpr/4]). |
| 2146 | | print_unit_test_assertion(pred,Typed,true,S) :- |
| 2147 | | print_bexpr_stream(S,Typed). |
| 2148 | | print_unit_test_assertion(pred,Typed,false,S) :- |
| 2149 | | safe_create_texpr(negation(Typed),pred,[],Neg), |
| 2150 | | print_bexpr_stream(S,Neg). |
| 2151 | | print_unit_test_assertion(expr,Typed,Val,S) :- |
| 2152 | | print_bexpr_stream(S,Typed), write(S,' = '), print_bvalue_stream(S,Val). |
| 2153 | | |
| 2154 | | |
| 2155 | | :- use_module(tools_printing,[print_term_summary/1]). |
| 2156 | | portray_waitflags_and_frozen_state_info(WF,StateTerm) :- |
| 2157 | | portray_waitflags(WF), |
| 2158 | | print_term_summary(frozen_info_for_state(StateTerm)), |
| 2159 | | term_variables(StateTerm,Vars), |
| 2160 | | translate:l_print_frozen_info(Vars). |
| 2161 | | |
| 2162 | | %% Utilities for defining values inside the REPL using let : |
| 2163 | | % ---------------------- |
| 2164 | | % scanning code utilities to recognize let construct |
| 2165 | | scan_identifier([32|T],ID,Rest) :- scan_identifier(T,ID,Rest). |
| 2166 | ? | scan_identifier([H|T],[H|TID],Rest) :- letter(H), |
| 2167 | ? | scan_identifier2(T,TID,Rest). |
| 2168 | | scan_identifier2([],[],[]). |
| 2169 | | scan_identifier2([32|T],[],T). |
| 2170 | | scan_identifier2([61|T],[],[61|T]). |
| 2171 | ? | scan_identifier2([H|T],[H|TID],Rest) :- ( letter(H) ; H = 95 ; H=45 ; digit(H)), |
| 2172 | ? | scan_identifier2(T,TID,Rest). |
| 2173 | | letter(X) :- (X >= 97, X =< 122) ; (X >= 65, X=< 90). % underscore = 95, minus = 45 |
| 2174 | | digit(X) :- X >= 48, X =< 57. |
| 2175 | | |
| 2176 | | scan_to_equal([32|T],Rest) :- scan_to_equal(T,Rest). |
| 2177 | | scan_to_equal([61|T],T). % "=" = [61] |
| 2178 | | |
| 2179 | | just_whitespace([32|T]) :- just_whitespace(T). |
| 2180 | | just_whitespace([]). |
| 2181 | | |
| 2182 | | store_let_id_last_value(ID) :- |
| 2183 | | retract_stored_let_value(ID,LastType,_), |
| 2184 | | !, |
| 2185 | | get_last_value(ID,Type,Value), %print(updating(ID)),nl, |
| 2186 | | add_stored_let_value(ID,Type,Value), |
| 2187 | | (LastType=Type -> true |
| 2188 | | ; reset_parse_cache). % type has changed |
| 2189 | | store_let_id_last_value(ID) :- |
| 2190 | | get_cur_state_for_repl(b(truth,pred,[]),State), member(bind(ID,_),State),!, |
| 2191 | | add_error(store_let_id_last_value,'Cannot redefine existing identifier using let: ',ID). |
| 2192 | | store_let_id_last_value(ID) :- |
| 2193 | | get_last_value(ID,Type,Value), |
| 2194 | | add_stored_let_value(ID,Type,Value), |
| 2195 | | reset_parse_cache. |
| 2196 | | |
| 2197 | | % construct the scope that the typechecker will use |
| 2198 | | repl_typing_scope([IdScope,prob_ids(visible),S|L]) :- % promoted if we allow operation_call_in_expr |
| 2199 | | get_stored_let_typing_scope(IdScope), % identifier(Ids) |
| 2200 | | !, |
| 2201 | | get_main_repl_scope(S),external_libraries(L). |
| 2202 | | repl_typing_scope([prob_ids(visible),S|L]) :- get_main_repl_scope(S),external_libraries(L). |
| 2203 | | |
| 2204 | | external_libraries([external_library(all_available_libraries)]). |
| 2205 | | |
| 2206 | | get_main_repl_scope(assertions_scope_and_additional_defs) :- |
| 2207 | | get_preference(allow_operation_calls_in_expr,true),!. |
| 2208 | | get_main_repl_scope(variables_and_additional_defs). |
| 2209 | | |
| 2210 | | get_last_value(ID,Type,Value) :- % first try and see if we had a predicate with identifier ID |
| 2211 | | get_last_predicate_value_for_id(ID,T,V), |
| 2212 | | !, |
| 2213 | | Type=T, Value=V. |
| 2214 | | get_last_value(_ID,Type,Value) :- get_last_expr_type_and_value(_,Type,Value). |
| 2215 | | |
| 2216 | | get_last_expr_type_and_value(Expr,Type,Value) :- |
| 2217 | | last_expression(_,Expr,V), |
| 2218 | | get_texpr_type(Expr,T), |
| 2219 | | convert_result(T,V,Type,Value). |
| 2220 | | |
| 2221 | | % display information about stored lets |
| 2222 | | browse_repl_lets :- \+ \+ stored_let_value(_,_,_), |
| 2223 | | print('Available let definitions:'),nl, |
| 2224 | | stored_let_value(ID,_,Value), |
| 2225 | | translate_bvalue_with_limit_and_col(Value,50,VS), |
| 2226 | | format(' ~w = ~w~n',[ID,VS]), |
| 2227 | | fail. |
| 2228 | | browse_repl_lets. |
| 2229 | | |
| 2230 | | get_repl_lets_info(Lets) :- |
| 2231 | | findall(S, (stored_let_value(ID,_,Value), |
| 2232 | | translate_bvalue_with_limit_and_col(Value,50,VS), |
| 2233 | | ajoin([ID,' = ',VS,'\n'],S)), |
| 2234 | | Lets). |
| 2235 | | |
| 2236 | | get_repl_lets_tids(List) :- |
| 2237 | | findall(b(identifier(ID),Type,[repl_let]), stored_let_value(ID,Type,_),List). |
| 2238 | | |
| 2239 | | |
| 2240 | | list_information(INFO,Res,[INFO/BList]) :- !, |
| 2241 | | external_functions:'PROJECT_INFO'(string(INFO),BList,unknown,no_wf_available), |
| 2242 | | !, |
| 2243 | | translate_bvalue_with_limit_and_col(BList,5000,Res), |
| 2244 | | format('~w~n',[Res]). |
| 2245 | | list_information(Arg,Res,[]) :- add_error(eval_strings,'Unknown argument for :list: ',Arg), |
| 2246 | | Res='ERROR'. |
| 2247 | | |
| 2248 | | |
| 2249 | | :- use_module(eventhandling,[register_event_listener/3]). |
| 2250 | | :- register_event_listener(clear_specification,reset_eval_strings, |
| 2251 | | 'Reset REPL (lets, caches, ...)'). |
| 2252 | | |
| 2253 | | reset_eval_strings :- clear_last_expression, |
| 2254 | | retractall(last_solution(_,_)), |
| 2255 | | reset_parse_cache, |
| 2256 | | set_observe_evaluation(false), |
| 2257 | | retractall(eval_dot_file(_)), |
| 2258 | | retractall(stored_let_value(_,_,_)), |
| 2259 | | retractall(eval_repeat(_)), |
| 2260 | | unset_eval_mode, |
| 2261 | | (reset_required -> true ; assertz(reset_required)). % before next evaluation we need to remove invalid lets |
| 2262 | | |
| 2263 | | reset_parse_cache :- |
| 2264 | | retractall(parse_expr_cache(_,_,_,_,_)), |
| 2265 | | retractall(parse_pred_cache(_,_,_,_,_)). |
| 2266 | | |
| 2267 | | :- dynamic reset_required/0. |
| 2268 | | |
| 2269 | | reset_repl_lets :- retract(reset_required),!, |
| 2270 | | reset_let_values. |
| 2271 | | reset_repl_lets. |
| 2272 | | |
| 2273 | | |
| 2274 | | %% ------------------------------------ |
| 2275 | | %% DETERMINISTIC PROPAGATION UNIT TESTS |
| 2276 | | %% ------------------------------------ |
| 2277 | | |
| 2278 | | |
| 2279 | | % check that certain predicates are determined to be failing without enumeration |
| 2280 | | % to do: also add positive tests: certain predicates succeed with instantiating all variables |
| 2281 | | % eval_strings:must_fail_tests. |
| 2282 | | |
| 2283 | | must_fail_tests :- set_eval_det, |
| 2284 | ? | must_fail_det(Nr,Str,ExTyped), |
| 2285 | | check_failed(Nr,ExTyped), |
| 2286 | | Str \= [], |
| 2287 | | % print('PARSING: '),nl,name(SS,Str), print(SS),nl, |
| 2288 | | repl_typing_scope(TypingScope), |
| 2289 | | ( b_parse_machine_predicate_from_codes_open(exists,Str,[],TypingScope,NewTyped) -> |
| 2290 | | check_same_ast(Nr,NewTyped,ExTyped) |
| 2291 | | ; |
| 2292 | | print('*** Could not parse: '), print(Nr), nl |
| 2293 | | %add_error(must_fail_tests,'Could not parse saved string: ',Nr) |
| 2294 | | ), |
| 2295 | | fail. |
| 2296 | | must_fail_tests :- preferences:preference(use_clpfd_solver,true), |
| 2297 | ? | must_fail_clpfd_det(Nr,ExTyped), |
| 2298 | | test_enabled(Nr), |
| 2299 | | check_failed(Nr,ExTyped),fail. |
| 2300 | | must_fail_tests :- unset_eval_mode. |
| 2301 | | |
| 2302 | | check_failed(Nr,ExTyped) :- |
| 2303 | | nl,print(Nr), print(' >>> '), translate:print_bexpr(ExTyped),nl, |
| 2304 | | (eval_predicate_in_cur_state(ExTyped,Res,_,_) |
| 2305 | | -> (Res='FALSE' -> true ; |
| 2306 | | add_error(must_fail_tests,'Test has not failed deterministically: ',Nr)) |
| 2307 | | ; add_error(must_fail_tests,'eval_predicate failed: ',Nr) |
| 2308 | | ). |
| 2309 | | |
| 2310 | | :- use_module(self_check). |
| 2311 | | |
| 2312 | | :- assert_must_succeed(must_fail_tests). |
| 2313 | | |
| 2314 | | check_same_ast(Nr,A_New,B_Old) :- % check equivalent to stored AST B, apart from pos |
| 2315 | | (compare(A_New,B_Old) -> true |
| 2316 | | ; add_error(check_same_ast,'AST not identical: ',Nr), |
| 2317 | | print('New AST:'),nl,print(A_New),nl, |
| 2318 | | print('Stored AST :'),nl,print(B_Old),nl, |
| 2319 | | tools_printing:trace_unify(A_New,B_Old) |
| 2320 | | ). |
| 2321 | | |
| 2322 | | compare(A,B) :- atomic(A),!,B=A. |
| 2323 | | compare(b(A,TA,IA),b(B,TB,IB)) :- !, |
| 2324 | | TA=TB, |
| 2325 | | exclude(remove_this,IA,IA1), sort(IA1,SIA1), |
| 2326 | | exclude(remove_this,IB,IB1), sort(IB1,SIB1), |
| 2327 | | compare_infos(SIA1,SIB1), |
| 2328 | | compare(A,B). |
| 2329 | | compare(A,B) :- A=..[F|As], B=..[F|Bs], |
| 2330 | | maplist(compare,As,Bs). |
| 2331 | | |
| 2332 | | compare_infos([],[]). |
| 2333 | | compare_infos([H|TA],[H|TB]) :- !, compare_infos(TA,TB). |
| 2334 | | compare_infos([used_ids(_)|TA],TB) :- TB \= [used_ids(_)|_], % skip additional new used_ids field |
| 2335 | | compare_infos(TA,TB). |
| 2336 | | |
| 2337 | | remove_this(removed_typing). % new info field |
| 2338 | | remove_this(nodeid(_)). % new AST sometimes has more nodeids than old stored ones |
| 2339 | | remove_this(prob_annotation('DO_NOT_ENUMERATE'('$$NONE$$'))). % this field now shows when enumeration order analysis was run and nothing found |
| 2340 | | |
| 2341 | | :- load_files(library(system), [when(compile_time), imports([environ/2])]). |
| 2342 | | :- if(environ(prob_release,true)). |
| 2343 | | must_fail_det(_Nr,_Str,_ExTyped) :- fail. |
| 2344 | | must_fail_clpfd_det(_Nr,_ExTyped) :- fail. |
| 2345 | | :- else. |
| 2346 | | % |
| 2347 | | must_fail_det(1,"#(x,y,z).(x:BOOL & x=z & z=y & x /= y)", |
| 2348 | | %b(exists([b(identifier(x),boolean,[do_not_optimize_away,nodeid(pos(nan,1,1,3,1,3)),introduced_by(exists)]),b(identifier(y),boolean,[do_not_optimize_away,nodeid(pos(nan,1,1,5,1,5)),introduced_by(exists)]),b(identifier(z),boolean,[do_not_optimize_away,nodeid(pos(nan,1,1,7,1,7)),introduced_by(exists)])],b(conjunct(b(conjunct(b(equal(b(identifier(x),boolean,[nodeid(pos(nan,1,1,20,1,20)),introduced_by(exists)]),b(identifier(z),boolean,[nodeid(pos(nan,1,1,22,1,22)),introduced_by(exists)])),pred,[nodeid(pos(nan,1,1,20,1,22))]),b(equal(b(identifier(z),boolean,[nodeid(pos(nan,1,1,26,1,26)),introduced_by(exists)]),b(identifier(y),boolean,[nodeid(pos(nan,1,1,28,1,28)),introduced_by(exists)])),pred,[nodeid(pos(nan,1,1,26,1,28))])),pred,[nodeid(pos(nan,1,1,11,1,28))]),b(not_equal(b(identifier(x),boolean,[nodeid(pos(nan,1,1,32,1,32)),introduced_by(exists)]),b(identifier(y),boolean,[nodeid(pos(nan,1,1,37,1,37)),introduced_by(exists)])),pred,[nodeid(pos(nan,1,1,32,1,37))])),pred,[nodeid(pos(nan,1,1,11,1,37))])),pred,[used_ids([]),nodeid(pos(nan,1,1,1,1,38))])). |
| 2349 | | b(exists([b(identifier(x),boolean,[do_not_optimize_away,nodeid(pos(3,-1,1,3,1,3)),introduced_by(exists)]),b(identifier(y),boolean,[do_not_optimize_away,nodeid(pos(4,-1,1,5,1,5)),introduced_by(exists)]),b(identifier(z),boolean,[do_not_optimize_away,nodeid(pos(5,-1,1,7,1,7)),introduced_by(exists)])],b(conjunct(b(conjunct(b(conjunct(b(equal(b(identifier(x),boolean,[nodeid(pos(13,-1,1,20,1,20)),introduced_by(exists)]),b(identifier(z),boolean,[nodeid(pos(14,-1,1,22,1,22)),introduced_by(exists)])),pred,[nodeid(pos(12,-1,1,20,1,22))]),b(equal(b(identifier(z),boolean,[nodeid(pos(16,-1,1,26,1,26)),introduced_by(exists)]),b(identifier(y),boolean,[nodeid(pos(17,-1,1,28,1,28)),introduced_by(exists)])),pred,[nodeid(pos(15,-1,1,26,1,28))])),pred,[nodeid(pos(7,-1,1,11,1,28))]),b(not_equal(b(identifier(x),boolean,[nodeid(pos(19,-1,1,32,1,32)),introduced_by(exists)]),b(identifier(y),boolean,[nodeid(pos(20,-1,1,37,1,37)),introduced_by(exists)])),pred,[nodeid(pos(18,-1,1,32,1,37))])),pred,[nodeid(pos(6,-1,1,11,1,37))]),b(external_pred_call('LEQ_SYM',[b(identifier(x),boolean,[do_not_optimize_away,nodeid(pos(3,-1,1,3,1,3)),introduced_by(exists)]),b(identifier(y),boolean,[do_not_optimize_away,nodeid(pos(4,-1,1,5,1,5)),introduced_by(exists)])]),pred,[do_not_optimize_away,nodeid(pos(3,-1,1,3,1,3)),introduced_by(exists)])),pred,[])),pred,[used_ids([]),prob_symmetry(x,y),nodeid(pos(2,-1,1,1,1,38))])). % with symmetry breaking |
| 2350 | | |
| 2351 | | |
| 2352 | | % |
| 2353 | | must_fail_det(2,"#x.(x:BOOL & (x=FALSE <=> x=TRUE))", b(exists([b(identifier(x),boolean,[do_not_optimize_away,nodeid(pos(nan,1,1,2,1,2)),introduced_by(exists)])],b(equivalence(b(equal(b(identifier(x),boolean,[nodeid(pos(nan,1,1,15,1,15)),introduced_by(exists)]),b(boolean_false,boolean,[nodeid(pos(nan,1,1,17,1,17))])),pred,[nodeid(pos(nan,1,1,15,1,17))]),b(equal(b(identifier(x),boolean,[nodeid(pos(nan,1,1,27,1,27)),introduced_by(exists)]),b(boolean_true,boolean,[nodeid(pos(nan,1,1,29,1,29))])),pred,[nodeid(pos(nan,1,1,27,1,29))])),pred,[nodeid(pos(nan,1,1,15,1,29))])),pred,[used_ids([]),nodeid(pos(nan,1,1,1,1,34))])). |
| 2354 | | |
| 2355 | | % |
| 2356 | | must_fail_det(3,"#(b,c).(b:BOOL & b=c & b/=c)", |
| 2357 | | b(exists([b(identifier(b),boolean,[do_not_optimize_away,nodeid(pos(nan,1,1,3,1,3)),introduced_by(exists)]),b(identifier(c),boolean,[do_not_optimize_away,nodeid(pos(nan,1,1,5,1,5)),introduced_by(exists)])],b(conjunct(b(equal(b(identifier(b),boolean,[nodeid(pos(nan,1,1,18,1,18)),introduced_by(exists)]),b(identifier(c),boolean,[nodeid(pos(nan,1,1,20,1,20)),introduced_by(exists)])),pred,[nodeid(pos(nan,1,1,18,1,20))]),b(not_equal(b(identifier(b),boolean,[nodeid(pos(nan,1,1,24,1,24)),introduced_by(exists)]),b(identifier(c),boolean,[nodeid(pos(nan,1,1,27,1,27)),introduced_by(exists)])),pred,[nodeid(pos(nan,1,1,24,1,27))])),pred,[nodeid(pos(nan,1,1,9,1,27))])),pred,[used_ids([]),nodeid(pos(nan,1,1,1,1,28))])). |
| 2358 | | |
| 2359 | | |
| 2360 | | % |
| 2361 | | must_fail_det(4,"#(e,s).(s<:INT & e:s & e/:s)", b(exists([b(identifier(e),integer,[do_not_optimize_away,nodeid(pos(3,-1,1,3,1,4)),introduced_by(exists)]),b(identifier(s),set(integer),[do_not_optimize_away,nodeid(pos(4,-1,1,5,1,6)),introduced_by(exists)])],b(conjunct(b(conjunct(b(subset(b(identifier(s),set(integer),[nodeid(pos(8,-1,1,9,1,10)),introduced_by(exists)]),b(interval(b(min_int,integer,[nodeid(pos(9,-1,1,12,1,15))]),b(max_int,integer,[nodeid(pos(9,-1,1,12,1,15))])),set(integer),[was(integer_set('INT')),nodeid(pos(9,-1,1,12,1,15))])),pred,[nodeid(pos(7,-1,1,9,1,15))]),b(member(b(identifier(e),integer,[nodeid(pos(11,-1,1,18,1,19)),introduced_by(exists)]),b(identifier(s),set(integer),[nodeid(pos(12,-1,1,20,1,21)),introduced_by(exists)])),pred,[nodeid(pos(10,-1,1,18,1,21))])),pred,[nodeid(pos(6,-1,1,9,1,21))]),b(not_member(b(identifier(e),integer,[nodeid(pos(14,-1,1,24,1,25)),introduced_by(exists)]),b(identifier(s),set(integer),[nodeid(pos(15,-1,1,27,1,28)),introduced_by(exists)])),pred,[nodeid(pos(13,-1,1,24,1,28))])),pred,[nodeid(pos(5,-1,1,9,1,28))])),pred,[used_ids([]),nodeid(pos(2,-1,1,1,1,29))])). |
| 2362 | | |
| 2363 | | % |
| 2364 | | must_fail_det(5,"#(x,y,z,v,xz).(x:BOOL & x/=y & v/=z & x=v & (x=z <=> xz=TRUE) & (xz=FALSE => x=TRUE) & (xz=FALSE => x=FALSE))", b(exists([b(identifier(x),boolean,[do_not_optimize_away,nodeid(pos(3,-1,1,3,1,4)),introduced_by(exists)]),b(identifier(y),boolean,[do_not_optimize_away,nodeid(pos(4,-1,1,5,1,6)),introduced_by(exists)]),b(identifier(z),boolean,[do_not_optimize_away,nodeid(pos(5,-1,1,7,1,8)),introduced_by(exists)]),b(identifier(v),boolean,[do_not_optimize_away,nodeid(pos(6,-1,1,9,1,10)),introduced_by(exists)]),b(identifier(xz),boolean,[do_not_optimize_away,nodeid(pos(7,-1,1,11,1,13)),introduced_by(exists)])],b(conjunct(b(conjunct(b(conjunct(b(conjunct(b(conjunct(b(not_equal(b(identifier(x),boolean,[nodeid(pos(18,-1,1,25,1,26)),introduced_by(exists)]),b(identifier(y),boolean,[nodeid(pos(19,-1,1,28,1,29)),introduced_by(exists)])),pred,[removed_typing,nodeid(pos(17,-1,1,25,1,29))]),b(not_equal(b(identifier(v),boolean,[nodeid(pos(21,-1,1,32,1,33)),introduced_by(exists)]),b(identifier(z),boolean,[nodeid(pos(22,-1,1,35,1,36)),introduced_by(exists)])),pred,[nodeid(pos(20,-1,1,32,1,36))])),pred,[nodeid(pos(12,-1,1,16,1,36))]),b(equal(b(identifier(x),boolean,[nodeid(pos(24,-1,1,39,1,40)),introduced_by(exists)]),b(identifier(v),boolean,[nodeid(pos(25,-1,1,41,1,42)),introduced_by(exists)])),pred,[nodeid(pos(23,-1,1,39,1,42))])),pred,[nodeid(pos(11,-1,1,16,1,42))]),b(equivalence(b(equal(b(identifier(x),boolean,[nodeid(pos(28,-1,1,46,1,47)),introduced_by(exists)]),b(identifier(z),boolean,[nodeid(pos(29,-1,1,48,1,49)),introduced_by(exists)])),pred,[nodeid(pos(27,-1,1,46,1,49))]),b(equal(b(identifier(xz),boolean,[nodeid(pos(31,-1,1,54,1,56)),introduced_by(exists)]),b(boolean_true,boolean,[nodeid(pos(32,-1,1,57,1,61))])),pred,[nodeid(pos(30,-1,1,54,1,61))])),pred,[nodeid(pos(26,-1,1,46,1,61))])),pred,[nodeid(pos(10,-1,1,16,1,61))]),b(implication(b(equal(b(identifier(xz),boolean,[nodeid(pos(35,-1,1,66,1,68)),introduced_by(exists)]),b(boolean_false,boolean,[nodeid(pos(36,-1,1,69,1,74))])),pred,[nodeid(pos(34,-1,1,66,1,74))]),b(equal(b(identifier(x),boolean,[nodeid(pos(38,-1,1,78,1,79)),introduced_by(exists)]),b(boolean_true,boolean,[nodeid(pos(39,-1,1,80,1,84))])),pred,[nodeid(pos(37,-1,1,78,1,84))])),pred,[nodeid(pos(33,-1,1,66,1,84))])),pred,[nodeid(pos(9,-1,1,16,1,84))]),b(implication(b(equal(b(identifier(xz),boolean,[nodeid(pos(42,-1,1,89,1,91)),introduced_by(exists)]),b(boolean_false,boolean,[nodeid(pos(43,-1,1,92,1,97))])),pred,[nodeid(pos(41,-1,1,89,1,97))]),b(equal(b(identifier(x),boolean,[nodeid(pos(45,-1,1,101,1,102)),introduced_by(exists)]),b(boolean_false,boolean,[nodeid(pos(46,-1,1,103,1,108))])),pred,[nodeid(pos(44,-1,1,101,1,108))])),pred,[nodeid(pos(40,-1,1,89,1,108))])),pred,[nodeid(pos(8,-1,1,16,1,108))])),pred,[removed_typing,used_ids([]),nodeid(pos(2,-1,1,1,1,110))])). |
| 2365 | | |
| 2366 | | % |
| 2367 | | must_fail_det(6,"#(x,xz).((x : BOOL & xz : BOOL) & (((x = TRUE) <=> not(x = TRUE)) <=> (xz = TRUE) & ((x = TRUE) <=> not(x = TRUE)) <=> (xz = FALSE)))", b(exists([b(identifier(x),boolean,[do_not_optimize_away,nodeid(pos(nan,1,1,3,1,3)),introduced_by(exists)]),b(identifier(xz),boolean,[do_not_optimize_away,nodeid(pos(nan,1,1,5,1,5)),introduced_by(exists)])],b(conjunct(b(equivalence(b(equivalence(b(equal(b(identifier(x),boolean,[nodeid(pos(nan,1,1,38,1,38)),introduced_by(exists)]),b(boolean_true,boolean,[nodeid(pos(nan,1,1,42,1,42))])),pred,[nodeid(pos(nan,1,1,38,1,42))]),b(negation(b(equal(b(identifier(x),boolean,[nodeid(pos(nan,1,1,56,1,56)),introduced_by(exists)]),b(boolean_true,boolean,[nodeid(pos(nan,1,1,60,1,60))])),pred,[nodeid(pos(nan,1,1,56,1,60))])),pred,[nodeid(pos(nan,1,1,52,1,64))])),pred,[nodeid(pos(nan,1,1,37,1,64))]),b(equal(b(identifier(xz),boolean,[nodeid(pos(nan,1,1,72,1,72)),introduced_by(exists)]),b(boolean_true,boolean,[nodeid(pos(nan,1,1,77,1,77))])),pred,[nodeid(pos(nan,1,1,72,1,77))])),pred,[nodeid(pos(nan,1,1,36,1,81))]),b(equivalence(b(equivalence(b(equal(b(identifier(x),boolean,[nodeid(pos(nan,1,1,87,1,87)),introduced_by(exists)]),b(boolean_true,boolean,[nodeid(pos(nan,1,1,91,1,91))])),pred,[nodeid(pos(nan,1,1,87,1,91))]),b(negation(b(equal(b(identifier(x),boolean,[nodeid(pos(nan,1,1,105,1,105)),introduced_by(exists)]),b(boolean_true,boolean,[nodeid(pos(nan,1,1,109,1,109))])),pred,[nodeid(pos(nan,1,1,105,1,109))])),pred,[nodeid(pos(nan,1,1,101,1,113))])),pred,[nodeid(pos(nan,1,1,86,1,113))]),b(equal(b(identifier(xz),boolean,[nodeid(pos(nan,1,1,121,1,121)),introduced_by(exists)]),b(boolean_false,boolean,[nodeid(pos(nan,1,1,126,1,126))])),pred,[nodeid(pos(nan,1,1,121,1,126))])),pred,[nodeid(pos(nan,1,1,85,1,131))])),pred,[nodeid(pos(nan,1,1,36,1,131))])),pred,[used_ids([]),nodeid(pos(nan,1,1,1,1,133))])). |
| 2368 | | |
| 2369 | | % |
| 2370 | | must_fail_det(7,"#(x,z,x2,xz).((((x : BOOL & z : BOOL) & x2 : BOOL) & xz : BOOL) & (((x2 /= z & x = x2) & ((x = TRUE) <=> (x2 = FALSE)) <=> (xz = TRUE)) & ((x = TRUE) <=> (x2 = FALSE)) <=> (xz = FALSE)))", b(exists([b(identifier(x),boolean,[do_not_optimize_away,nodeid(pos(nan,1,1,3,1,3)),introduced_by(exists)]),b(identifier(z),boolean,[do_not_optimize_away,nodeid(pos(nan,1,1,5,1,5)),introduced_by(exists)]),b(identifier(x2),boolean,[do_not_optimize_away,nodeid(pos(nan,1,1,7,1,7)),introduced_by(exists)]),b(identifier(xz),boolean,[do_not_optimize_away,nodeid(pos(nan,1,1,10,1,10)),introduced_by(exists)])],b(conjunct(b(conjunct(b(conjunct(b(not_equal(b(identifier(x2),boolean,[nodeid(pos(nan,1,1,70,1,70)),introduced_by(exists)]),b(identifier(z),boolean,[nodeid(pos(nan,1,1,76,1,76)),introduced_by(exists)])),pred,[nodeid(pos(nan,1,1,70,1,76))]),b(equal(b(identifier(x),boolean,[nodeid(pos(nan,1,1,80,1,80)),introduced_by(exists)]),b(identifier(x2),boolean,[nodeid(pos(nan,1,1,84,1,84)),introduced_by(exists)])),pred,[nodeid(pos(nan,1,1,80,1,84))])),pred,[nodeid(pos(nan,1,1,70,1,84))]),b(equivalence(b(equivalence(b(equal(b(identifier(x),boolean,[nodeid(pos(nan,1,1,92,1,92)),introduced_by(exists)]),b(boolean_true,boolean,[nodeid(pos(nan,1,1,96,1,96))])),pred,[nodeid(pos(nan,1,1,92,1,96))]),b(equal(b(identifier(x2),boolean,[nodeid(pos(nan,1,1,107,1,107)),introduced_by(exists)]),b(boolean_false,boolean,[nodeid(pos(nan,1,1,112,1,112))])),pred,[nodeid(pos(nan,1,1,107,1,112))])),pred,[nodeid(pos(nan,1,1,91,1,117))]),b(equal(b(identifier(xz),boolean,[nodeid(pos(nan,1,1,125,1,125)),introduced_by(exists)]),b(boolean_true,boolean,[nodeid(pos(nan,1,1,130,1,130))])),pred,[nodeid(pos(nan,1,1,125,1,130))])),pred,[nodeid(pos(nan,1,1,90,1,134))])),pred,[nodeid(pos(nan,1,1,69,1,134))]),b(equivalence(b(equivalence(b(equal(b(identifier(x),boolean,[nodeid(pos(nan,1,1,141,1,141)),introduced_by(exists)]),b(boolean_true,boolean,[nodeid(pos(nan,1,1,145,1,145))])),pred,[nodeid(pos(nan,1,1,141,1,145))]),b(equal(b(identifier(x2),boolean,[nodeid(pos(nan,1,1,156,1,156)),introduced_by(exists)]),b(boolean_false,boolean,[nodeid(pos(nan,1,1,161,1,161))])),pred,[nodeid(pos(nan,1,1,156,1,161))])),pred,[nodeid(pos(nan,1,1,140,1,166))]),b(equal(b(identifier(xz),boolean,[nodeid(pos(nan,1,1,174,1,174)),introduced_by(exists)]),b(boolean_false,boolean,[nodeid(pos(nan,1,1,179,1,179))])),pred,[nodeid(pos(nan,1,1,174,1,179))])),pred,[nodeid(pos(nan,1,1,139,1,184))])),pred,[nodeid(pos(nan,1,1,68,1,184))])),pred,[used_ids([]),nodeid(pos(nan,1,1,1,1,186))])). |
| 2371 | | |
| 2372 | | % |
| 2373 | | must_fail_det(8,"#(a,b).((a : BOOL & b : BOOL) & ((b = TRUE) <=> ((a = TRUE) <=> not(a = TRUE)) & (b = FALSE) <=> ((a = FALSE) <=> (a = TRUE))))", b(exists([b(identifier(a),boolean,[do_not_optimize_away,nodeid(pos(nan,1,1,3,1,3)),introduced_by(exists)]),b(identifier(b),boolean,[do_not_optimize_away,nodeid(pos(nan,1,1,5,1,5)),introduced_by(exists)])],b(conjunct(b(equivalence(b(equal(b(identifier(b),boolean,[nodeid(pos(nan,1,1,35,1,35)),introduced_by(exists)]),b(boolean_true,boolean,[nodeid(pos(nan,1,1,39,1,39))])),pred,[nodeid(pos(nan,1,1,35,1,39))]),b(equivalence(b(equal(b(identifier(a),boolean,[nodeid(pos(nan,1,1,51,1,51)),introduced_by(exists)]),b(boolean_true,boolean,[nodeid(pos(nan,1,1,55,1,55))])),pred,[nodeid(pos(nan,1,1,51,1,55))]),b(negation(b(equal(b(identifier(a),boolean,[nodeid(pos(nan,1,1,69,1,69)),introduced_by(exists)]),b(boolean_true,boolean,[nodeid(pos(nan,1,1,73,1,73))])),pred,[nodeid(pos(nan,1,1,69,1,73))])),pred,[nodeid(pos(nan,1,1,65,1,77))])),pred,[nodeid(pos(nan,1,1,50,1,77))])),pred,[nodeid(pos(nan,1,1,34,1,78))]),b(equivalence(b(equal(b(identifier(b),boolean,[nodeid(pos(nan,1,1,83,1,83)),introduced_by(exists)]),b(boolean_false,boolean,[nodeid(pos(nan,1,1,87,1,87))])),pred,[nodeid(pos(nan,1,1,83,1,87))]),b(equivalence(b(equal(b(identifier(a),boolean,[nodeid(pos(nan,1,1,100,1,100)),introduced_by(exists)]),b(boolean_false,boolean,[nodeid(pos(nan,1,1,104,1,104))])),pred,[nodeid(pos(nan,1,1,100,1,104))]),b(equal(b(identifier(a),boolean,[nodeid(pos(nan,1,1,116,1,116)),introduced_by(exists)]),b(boolean_true,boolean,[nodeid(pos(nan,1,1,120,1,120))])),pred,[nodeid(pos(nan,1,1,116,1,120))])),pred,[nodeid(pos(nan,1,1,99,1,124))])),pred,[nodeid(pos(nan,1,1,82,1,125))])),pred,[nodeid(pos(nan,1,1,34,1,125))])),pred,[used_ids([]),nodeid(pos(nan,1,1,1,1,127))])). |
| 2374 | | |
| 2375 | | % |
| 2376 | | must_fail_det(9,[], % let predicate now also optimizes bool equalities: |
| 2377 | | %"#(a,b,c).(((a : BOOL & b : BOOL) & c : BOOL) & ((((b = TRUE) <=> (a = TRUE => a = FALSE) & b = TRUE) & (a = FALSE => c = FALSE)) & (a = FALSE => c = TRUE)))", |
| 2378 | | b(let_predicate([b(identifier(b),boolean,[nodeid(pos(nan,1,1,5,1,5)),introduced_by(exists)])],[b(boolean_true,boolean,[nodeid(pos(nan,1,1,96,1,96))])],b(exists([b(identifier(a),boolean,[nodeid(pos(nan,1,1,3,1,3)),introduced_by(exists)]),b(identifier(c),boolean,[nodeid(pos(nan,1,1,7,1,7)),introduced_by(exists)])],b(conjunct(b(conjunct(b(equivalence(b(equal(b(identifier(b),boolean,[nodeid(pos(nan,1,1,52,1,52)),introduced_by(exists)]),b(boolean_true,boolean,[nodeid(pos(nan,1,1,56,1,56))])),pred,[nodeid(pos(nan,1,1,52,1,56))]),b(implication(b(equal(b(identifier(a),boolean,[nodeid(pos(nan,1,1,67,1,67)),introduced_by(exists)]),b(boolean_true,boolean,[nodeid(pos(nan,1,1,71,1,71))])),pred,[nodeid(pos(nan,1,1,67,1,71))]),b(equal(b(identifier(a),boolean,[nodeid(pos(nan,1,1,79,1,79)),introduced_by(exists)]),b(boolean_false,boolean,[nodeid(pos(nan,1,1,83,1,83))])),pred,[nodeid(pos(nan,1,1,79,1,83))])),pred,[nodeid(pos(nan,1,1,67,1,83))])),pred,[nodeid(pos(nan,1,1,51,1,88))]),b(implication(b(equal(b(identifier(a),boolean,[nodeid(pos(nan,1,1,105,1,105)),introduced_by(exists)]),b(boolean_false,boolean,[nodeid(pos(nan,1,1,109,1,109))])),pred,[nodeid(pos(nan,1,1,105,1,109))]),b(equal(b(identifier(c),boolean,[nodeid(pos(nan,1,1,118,1,118)),introduced_by(exists)]),b(boolean_false,boolean,[nodeid(pos(nan,1,1,122,1,122))])),pred,[nodeid(pos(nan,1,1,118,1,122))])),pred,[nodeid(pos(nan,1,1,105,1,122))])),pred,[]),b(implication(b(equal(b(identifier(a),boolean,[nodeid(pos(nan,1,1,133,1,133)),introduced_by(exists)]),b(boolean_false,boolean,[nodeid(pos(nan,1,1,137,1,137))])),pred,[nodeid(pos(nan,1,1,133,1,137))]),b(equal(b(identifier(c),boolean,[nodeid(pos(nan,1,1,146,1,146)),introduced_by(exists)]),b(boolean_true,boolean,[nodeid(pos(nan,1,1,150,1,150))])),pred,[nodeid(pos(nan,1,1,146,1,150))])),pred,[nodeid(pos(nan,1,1,133,1,150))])),pred,[])),pred,[used_ids([b]),used_ids([b]),used_ids([a,b,c])])),pred,[nodeid(pos(nan,1,1,1,1,156))])). |
| 2379 | | |
| 2380 | | % |
| 2381 | | must_fail_det(10,"#(a,b,c).(((a : BOOL & b : BOOL) & c : BOOL) & (((b = TRUE) <=> (a = TRUE => a = FALSE) & (c = TRUE) <=> (a = b)) & (c = TRUE) <=> not(a = b)))", b(exists([b(identifier(a),boolean,[do_not_optimize_away,nodeid(pos(nan,1,1,3,1,3)),introduced_by(exists)]),b(identifier(b),boolean,[do_not_optimize_away,nodeid(pos(nan,1,1,5,1,5)),introduced_by(exists)]),b(identifier(c),boolean,[do_not_optimize_away,nodeid(pos(nan,1,1,7,1,7)),introduced_by(exists)])],b(conjunct(b(conjunct(b(equivalence(b(equal(b(identifier(b),boolean,[nodeid(pos(nan,1,1,51,1,51)),introduced_by(exists)]),b(boolean_true,boolean,[nodeid(pos(nan,1,1,55,1,55))])),pred,[nodeid(pos(nan,1,1,51,1,55))]),b(implication(b(equal(b(identifier(a),boolean,[nodeid(pos(nan,1,1,66,1,66)),introduced_by(exists)]),b(boolean_true,boolean,[nodeid(pos(nan,1,1,70,1,70))])),pred,[nodeid(pos(nan,1,1,66,1,70))]),b(equal(b(identifier(a),boolean,[nodeid(pos(nan,1,1,78,1,78)),introduced_by(exists)]),b(boolean_false,boolean,[nodeid(pos(nan,1,1,82,1,82))])),pred,[nodeid(pos(nan,1,1,78,1,82))])),pred,[nodeid(pos(nan,1,1,66,1,82))])),pred,[nodeid(pos(nan,1,1,50,1,87))]),b(equivalence(b(equal(b(identifier(c),boolean,[nodeid(pos(nan,1,1,92,1,92)),introduced_by(exists)]),b(boolean_true,boolean,[nodeid(pos(nan,1,1,96,1,96))])),pred,[nodeid(pos(nan,1,1,92,1,96))]),b(equal(b(identifier(a),boolean,[nodeid(pos(nan,1,1,107,1,107)),introduced_by(exists)]),b(identifier(b),boolean,[nodeid(pos(nan,1,1,111,1,111)),introduced_by(exists)])),pred,[nodeid(pos(nan,1,1,107,1,111))])),pred,[nodeid(pos(nan,1,1,91,1,112))])),pred,[nodeid(pos(nan,1,1,50,1,112))]),b(equivalence(b(equal(b(identifier(c),boolean,[nodeid(pos(nan,1,1,118,1,118)),introduced_by(exists)]),b(boolean_true,boolean,[nodeid(pos(nan,1,1,122,1,122))])),pred,[nodeid(pos(nan,1,1,118,1,122))]),b(negation(b(equal(b(identifier(a),boolean,[nodeid(pos(nan,1,1,136,1,136)),introduced_by(exists)]),b(identifier(b),boolean,[nodeid(pos(nan,1,1,140,1,140)),introduced_by(exists)])),pred,[nodeid(pos(nan,1,1,136,1,140))])),pred,[nodeid(pos(nan,1,1,132,1,141))])),pred,[nodeid(pos(nan,1,1,117,1,141))])),pred,[nodeid(pos(nan,1,1,49,1,141))])),pred,[used_ids([]),nodeid(pos(nan,1,1,1,1,143))]) |
| 2382 | | ). |
| 2383 | | |
| 2384 | | % "#(x,y,z).(((x : BOOL & y : BOOL) & z : BOOL) & ((TRUE:BOOL) => ((x : {TRUE}) <=> (y = TRUE) & (x = y) <=> (z = TRUE)) & x /= y <=> (z = TRUE)))" |
| 2385 | | must_fail_det(11,[], b(exists([b(identifier(x),boolean,[do_not_optimize_away,nodeid(pos(7,1,4,3,4,3))]),b(identifier(y),boolean,[do_not_optimize_away,nodeid(pos(8,1,4,5,4,5))]),b(identifier(z),boolean,[do_not_optimize_away,nodeid(pos(9,1,4,7,4,7))])],b(implication(b(truth,pred,[nodeid(pos(19,1,4,29,4,34))]),b(conjunct(b(conjunct(b(equivalence(b(member(b(identifier(x),boolean,[nodeid(pos(26,1,4,40,4,40))]),b(set_extension([b(boolean_true,boolean,[nodeid(pos(28,1,4,43,4,46))])]),set(boolean),[nodeid(pos(27,1,4,42,4,47))])),pred,[nodeid(pos(25,1,4,40,4,47))]),b(equal(b(identifier(y),boolean,[nodeid(pos(30,1,4,53,4,53))]),b(boolean_true,boolean,[nodeid(pos(31,1,4,55,4,58))])),pred,[nodeid(pos(29,1,4,53,4,58))])),pred,[nodeid(pos(24,1,4,40,4,58))]),b(equivalence(b(equal(b(identifier(x),boolean,[nodeid(pos(34,1,4,64,4,64))]),b(identifier(y),boolean,[nodeid(pos(35,1,4,66,4,66))])),pred,[nodeid(pos(33,1,4,64,4,66))]),b(equal(b(identifier(z),boolean,[nodeid(pos(37,1,4,72,4,72))]),b(boolean_true,boolean,[nodeid(pos(38,1,4,74,4,77))])),pred,[nodeid(pos(36,1,4,72,4,77))])),pred,[nodeid(pos(32,1,4,64,4,77))])),pred,[nodeid(pos(23,1,4,40,4,77))]),b(equivalence(b(not_equal(b(identifier(x),boolean,[nodeid(pos(41,1,4,82,4,82))]),b(identifier(y),boolean,[nodeid(pos(42,1,4,85,4,85))])),pred,[nodeid(pos(40,1,4,82,4,85))]),b(equal(b(identifier(z),boolean,[nodeid(pos(44,1,4,90,4,90))]),b(boolean_true,boolean,[nodeid(pos(45,1,4,92,4,95))])),pred,[nodeid(pos(43,1,4,90,4,95))])),pred,[nodeid(pos(39,1,4,82,4,95))])),pred,[nodeid(pos(22,1,4,40,4,95))])),pred,[nodeid(pos(10,1,4,11,4,95))])),pred,[used_ids([]),nodeid(pos(6,1,4,1,4,97))])). |
| 2386 | | |
| 2387 | | |
| 2388 | | must_fail_det(12,[], %"SIGMA(x,y).(x : 1 .. 10 & y : {1,2}|x) = 111", |
| 2389 | | b(equal(b(general_sum([b(identifier(x),integer,[nodeid(pos(nan,1,1,7,1,7)),introduced_by(general_sum)]),b(identifier(y),integer,[nodeid(pos(nan,1,1,9,1,9)),introduced_by(general_sum)])],b(conjunct(b(member(b(identifier(x),integer,[nodeid(pos(nan,1,1,13,1,13)),introduced_by(general_sum)]),b(interval(b(integer(1),integer,[nodeid(pos(nan,1,1,17,1,17))]),b(integer(10),integer,[nodeid(pos(nan,1,1,22,1,22))])),set(integer),[nodeid(pos(nan,1,1,17,1,22))])),pred,[nodeid(pos(nan,1,1,13,1,22))]),b(member(b(identifier(y),integer,[nodeid(pos(nan,1,1,27,1,27)),introduced_by(general_sum)]),b(set_extension([b(integer(1),integer,[nodeid(pos(nan,1,1,32,1,32))]),b(integer(2),integer,[nodeid(pos(nan,1,1,34,1,34))])]),set(integer),[nodeid(pos(nan,1,1,31,1,35))])),pred,[nodeid(pos(nan,1,1,27,1,35))])),pred,[nodeid(pos(nan,1,1,13,1,35))]),b(identifier(x),integer,[nodeid(pos(nan,1,1,37,1,37)),introduced_by(general_sum)])),integer,[nodeid(pos(nan,1,1,1,1,38))]),b(integer(111),integer,[nodeid(pos(nan,1,1,42,1,42))])),pred,[nodeid(pos(nan,1,1,1,1,42))])). |
| 2390 | | |
| 2391 | | must_fail_det(13,[], %"PI(x,y).(x : 1 .. 10 & y : {1,2}|x) = 111", |
| 2392 | | b(equal(b(general_product([b(identifier(x),integer,[nodeid(pos(nan,1,1,4,1,4)),introduced_by(general_product)]),b(identifier(y),integer,[nodeid(pos(nan,1,1,6,1,6)),introduced_by(general_product)])],b(conjunct(b(member(b(identifier(x),integer,[nodeid(pos(nan,1,1,10,1,10)),introduced_by(general_product)]),b(interval(b(integer(1),integer,[nodeid(pos(nan,1,1,14,1,14))]),b(integer(10),integer,[nodeid(pos(nan,1,1,19,1,19))])),set(integer),[nodeid(pos(nan,1,1,14,1,19))])),pred,[nodeid(pos(nan,1,1,10,1,19))]),b(member(b(identifier(y),integer,[nodeid(pos(nan,1,1,24,1,24)),introduced_by(general_product)]),b(set_extension([b(integer(1),integer,[nodeid(pos(nan,1,1,29,1,29))]),b(integer(2),integer,[nodeid(pos(nan,1,1,31,1,31))])]),set(integer),[nodeid(pos(nan,1,1,28,1,32))])),pred,[nodeid(pos(nan,1,1,24,1,32))])),pred,[nodeid(pos(nan,1,1,10,1,32))]),b(identifier(x),integer,[nodeid(pos(nan,1,1,34,1,34)),introduced_by(general_product)])),integer,[nodeid(pos(nan,1,1,1,1,35))]),b(integer(111),integer,[nodeid(pos(nan,1,1,39,1,39))])),pred,[nodeid(pos(nan,1,1,1,1,39))])). |
| 2393 | | |
| 2394 | | /* |
| 2395 | | must_fail_det(16,"union(ran(%x.((x <: {1,2,3,4} & card(x) > 0) & min(x) = 2|x))) = {1,2,3,4}", |
| 2396 | | b(equal(b(general_union(b(range(b(comprehension_set([b(identifier(x),set(integer),[nodeid(pos(0,0,0,0,0,0))]),b(identifier('_lambda_result_'),set(integer),[lambda_result])],b(conjunct(b(conjunct(b(conjunct(b(subset(b(identifier(x),set(integer),[nodeid(pos(0,0,0,0,0,0))]),b(set_extension([b(integer(1),integer,[nodeid(pos(0,0,0,0,0,0))]),b(integer(2),integer,[nodeid(pos(0,0,0,0,0,0))]),b(integer(3),integer,[nodeid(pos(0,0,0,0,0,0))]),b(integer(4),integer,[nodeid(pos(0,0,0,0,0,0))])]),set(integer),[nodeid(pos(0,0,0,0,0,0))])),pred,[nodeid(pos(0,0,0,0,0,0))]),b(greater(b(card(b(identifier(x),set(integer),[nodeid(pos(0,0,0,0,0,0))])),integer,[nodeid(pos(0,0,0,0,0,0))]),b(integer(0),integer,[nodeid(pos(0,0,0,0,0,0))])),pred,[nodeid(pos(0,0,0,0,0,0))])),pred,[nodeid(pos(0,0,0,0,0,0))]),b(equal(b(min(b(identifier(x),set(integer),[nodeid(pos(0,0,0,0,0,0))])),integer,[contains_wd_condition,nodeid(pos(0,0,0,0,0,0))]),b(integer(2),integer,[nodeid(pos(0,0,0,0,0,0))])),pred,[contains_wd_condition,nodeid(pos(0,0,0,0,0,0))])),pred,[contains_wd_condition,nodeid(pos(0,0,0,0,0,0))]),b(equal(b(identifier('_lambda_result_'),set(integer),[lambda_result]),b(identifier(x),set(integer),[nodeid(pos(0,0,0,0,0,0))])),pred,[])),pred,[contains_wd_condition])),set(couple(set(integer),set(integer))),[contains_wd_condition,was(lambda),generated(quantified_union)])),set(set(integer)),[contains_wd_condition,generated(quantified_union)])),set(integer),[contains_wd_condition,nodeid(pos(0,0,0,0,0,0))]),b(set_extension([b(integer(1),integer,[nodeid(pos(0,0,0,0,0,0))]),b(integer(2),integer,[nodeid(pos(0,0,0,0,0,0))]),b(integer(3),integer,[nodeid(pos(0,0,0,0,0,0))]),b(integer(4),integer,[nodeid(pos(0,0,0,0,0,0))])]),set(integer),[nodeid(pos(0,0,0,0,0,0))])),pred,[contains_wd_condition,nodeid(pos(0,0,0,0,0,0))])). |
| 2397 | | */ |
| 2398 | | |
| 2399 | | |
| 2400 | | % #(z,x,y).(((z : POW(POW(BOOL)) & x : POW(BOOL)) & y : INTEGER) & ((z = {{},{TRUE},{FALSE},{TRUE,FALSE}} & (x : z) <=> (y = 2)) & y > 3)) |
| 2401 | | % check that we detect that z is a complete set, hence x:z and hence y=2 |
| 2402 | | must_fail_det(14,[], %"z = {{},{TRUE},{FALSE},{TRUE,FALSE}} & (x:z <=> y=2) & y>3 ", |
| 2403 | | b(exists([b(identifier(z),set(set(boolean)),[]),b(identifier(x),set(boolean),[]),b(identifier(y),integer,[])],b(conjunct(b(conjunct(b(equal(b(identifier(z),set(set(boolean)),[nodeid(pos(nan,1,1,1,1,1))]),b(set_extension([b(empty_set,set(boolean),[nodeid(pos(nan,1,1,6,1,6))]),b(set_extension([b(boolean_true,boolean,[nodeid(pos(nan,1,1,10,1,10))])]),set(boolean),[nodeid(pos(nan,1,1,9,1,14))]),b(set_extension([b(boolean_false,boolean,[nodeid(pos(nan,1,1,17,1,17))])]),set(boolean),[nodeid(pos(nan,1,1,16,1,22))]),b(set_extension([b(boolean_true,boolean,[nodeid(pos(nan,1,1,25,1,25))]),b(boolean_false,boolean,[nodeid(pos(nan,1,1,30,1,30))])]),set(boolean),[nodeid(pos(nan,1,1,24,1,35))])]),set(set(boolean)),[nodeid(pos(nan,1,1,5,1,36))])),pred,[nodeid(pos(nan,1,1,1,1,36))]),b(equivalence(b(member(b(identifier(x),set(boolean),[nodeid(pos(nan,1,1,41,1,41))]),b(identifier(z),set(set(boolean)),[nodeid(pos(nan,1,1,43,1,43))])),pred,[nodeid(pos(nan,1,1,41,1,43))]),b(equal(b(identifier(y),integer,[nodeid(pos(nan,1,1,49,1,49))]),b(integer(2),integer,[nodeid(pos(nan,1,1,51,1,51))])),pred,[nodeid(pos(nan,1,1,49,1,51))])),pred,[nodeid(pos(nan,1,1,41,1,51))])),pred,[nodeid(pos(nan,1,1,1,1,52))]),b(greater(b(identifier(y),integer,[nodeid(pos(nan,1,1,56,1,56))]),b(integer(3),integer,[nodeid(pos(nan,1,1,58,1,58))])),pred,[nodeid(pos(nan,1,1,56,1,58))])),pred,[nodeid(pos(nan,1,1,1,1,58))])),pred,[used_ids([x,y,z])])). |
| 2404 | | |
| 2405 | | % #(z,x,y).(((z : POW(BOOL * BOOL) & x : BOOL * BOOL) & y : INTEGER) & ((z = {TRUE |-> FALSE,TRUE |-> TRUE,FALSE |-> FALSE,FALSE |-> TRUE} & (x : z) <=> (y = 2)) & y > 3)) |
| 2406 | | % check that we detect that z is a complete set, hence x:z and hence y=2 |
| 2407 | | must_fail_det(15,[], %" z = {(TRUE,FALSE),(TRUE,TRUE),(FALSE,FALSE),(FALSE,TRUE)} & (x:z <=> y=2) & y>3 ", |
| 2408 | | b(exists([b(identifier(z),set(couple(boolean,boolean)),[]),b(identifier(x),couple(boolean,boolean),[]),b(identifier(y),integer,[])],b(conjunct(b(conjunct(b(equal(b(identifier(z),set(couple(boolean,boolean)),[nodeid(pos(nan,1,1,1,1,1))]),b(set_extension([b(couple(b(boolean_true,boolean,[nodeid(pos(nan,1,1,7,1,7))]),b(boolean_false,boolean,[nodeid(pos(nan,1,1,12,1,12))])),couple(boolean,boolean),[nodeid(pos(nan,1,1,6,1,17))]),b(couple(b(boolean_true,boolean,[nodeid(pos(nan,1,1,20,1,20))]),b(boolean_true,boolean,[nodeid(pos(nan,1,1,25,1,25))])),couple(boolean,boolean),[nodeid(pos(nan,1,1,19,1,29))]),b(couple(b(boolean_false,boolean,[nodeid(pos(nan,1,1,32,1,32))]),b(boolean_false,boolean,[nodeid(pos(nan,1,1,38,1,38))])),couple(boolean,boolean),[nodeid(pos(nan,1,1,31,1,43))]),b(couple(b(boolean_false,boolean,[nodeid(pos(nan,1,1,46,1,46))]),b(boolean_true,boolean,[nodeid(pos(nan,1,1,52,1,52))])),couple(boolean,boolean),[nodeid(pos(nan,1,1,45,1,56))])]),set(couple(boolean,boolean)),[nodeid(pos(nan,1,1,5,1,57))])),pred,[nodeid(pos(nan,1,1,1,1,57))]),b(equivalence(b(member(b(identifier(x),couple(boolean,boolean),[nodeid(pos(nan,1,1,62,1,62))]),b(identifier(z),set(couple(boolean,boolean)),[nodeid(pos(nan,1,1,64,1,64))])),pred,[nodeid(pos(nan,1,1,62,1,64))]),b(equal(b(identifier(y),integer,[nodeid(pos(nan,1,1,70,1,70))]),b(integer(2),integer,[nodeid(pos(nan,1,1,72,1,72))])),pred,[nodeid(pos(nan,1,1,70,1,72))])),pred,[nodeid(pos(nan,1,1,62,1,72))])),pred,[nodeid(pos(nan,1,1,1,1,73))]),b(greater(b(identifier(y),integer,[nodeid(pos(nan,1,1,77,1,77))]),b(integer(3),integer,[nodeid(pos(nan,1,1,79,1,79))])),pred,[nodeid(pos(nan,1,1,77,1,79))])),pred,[nodeid(pos(nan,1,1,1,1,79))])),pred,[used_ids([x,y,z])])). |
| 2409 | | |
| 2410 | | % #(z,x,y).(((z : POW(POW(BOOL)) & x : POW(POW(BOOL))) & y : INTEGER) & ((z = {{},{TRUE},{FALSE},{TRUE,FALSE}} & x <: z <=> (y = 2)) & y > 3)) |
| 2411 | | must_fail_det(16,[],b(exists([b(identifier(z),set(set(boolean)),[]),b(identifier(x),set(set(boolean)),[]),b(identifier(y),integer,[])],b(conjunct(b(conjunct(b(equal(b(identifier(z),set(set(boolean)),[nodeid(pos(nan,1,1,1,1,1))]),b(set_extension([b(empty_set,set(boolean),[nodeid(pos(nan,1,1,6,1,6))]),b(set_extension([b(boolean_true,boolean,[nodeid(pos(nan,1,1,10,1,10))])]),set(boolean),[nodeid(pos(nan,1,1,9,1,14))]),b(set_extension([b(boolean_false,boolean,[nodeid(pos(nan,1,1,17,1,17))])]),set(boolean),[nodeid(pos(nan,1,1,16,1,22))]),b(set_extension([b(boolean_true,boolean,[nodeid(pos(nan,1,1,25,1,25))]),b(boolean_false,boolean,[nodeid(pos(nan,1,1,30,1,30))])]),set(boolean),[nodeid(pos(nan,1,1,24,1,35))])]),set(set(boolean)),[nodeid(pos(nan,1,1,5,1,36))])),pred,[nodeid(pos(nan,1,1,1,1,36))]),b(equivalence(b(subset(b(identifier(x),set(set(boolean)),[nodeid(pos(nan,1,1,41,1,41))]),b(identifier(z),set(set(boolean)),[nodeid(pos(nan,1,1,44,1,44))])),pred,[nodeid(pos(nan,1,1,41,1,44))]),b(equal(b(identifier(y),integer,[nodeid(pos(nan,1,1,50,1,50))]),b(integer(2),integer,[nodeid(pos(nan,1,1,52,1,52))])),pred,[nodeid(pos(nan,1,1,50,1,52))])),pred,[nodeid(pos(nan,1,1,41,1,52))])),pred,[nodeid(pos(nan,1,1,1,1,53))]),b(greater(b(identifier(y),integer,[nodeid(pos(nan,1,1,57,1,57))]),b(integer(3),integer,[nodeid(pos(nan,1,1,59,1,59))])),pred,[nodeid(pos(nan,1,1,57,1,59))])),pred,[nodeid(pos(nan,1,1,1,1,59))])),pred,[used_ids([x,y,z])])). |
| 2412 | | |
| 2413 | | % Eval Time: 0 ms (0 ms walltime) |
| 2414 | | % #(x).(x : INTEGER & ([111,222,333,444,555] |>> {x} = [111,222,333,444] & x > 555)) |
| 2415 | | must_fail_det(17,"#(x).(([111,222,333,444,555] |>> {x} = [111,222,333,444] & x > 555))", b(exists([b(identifier(x),integer,[do_not_optimize_away,nodeid(pos(3,-1,1,3,1,3)),introduced_by(exists)])],b(conjunct(b(equal(b(range_subtraction(b(value(avl_set(node((int(3),int(333)),true,0,node((int(1),int(111)),true,1,empty,node((int(2),int(222)),true,0,empty,empty)),node((int(4),int(444)),true,1,empty,node((int(5),int(555)),true,0,empty,empty))))),set(couple(integer,integer)),[nodeid(pos(7,-1,1,8,1,28))]),b(set_extension([b(identifier(x),integer,[nodeid(pos(14,-1,1,35,1,35)),introduced_by(exists)])]),set(integer),[nodeid(pos(13,-1,1,34,1,36))])),set(couple(integer,integer)),[nodeid(pos(6,-1,1,8,1,36))]),b(value(avl_set(node((int(2),int(222)),true,1,node((int(1),int(111)),true,0,empty,empty),node((int(3),int(333)),true,1,empty,node((int(4),int(444)),true,0,empty,empty))))),set(couple(integer,integer)),[nodeid(pos(15,-1,1,40,1,56))])),pred,[nodeid(pos(5,-1,1,8,1,56))]),b(greater(b(identifier(x),integer,[nodeid(pos(21,-1,1,60,1,60)),introduced_by(exists)]),b(integer(555),integer,[nodeid(pos(22,-1,1,64,1,66))])),pred,[nodeid(pos(20,-1,1,60,1,66))])),pred,[nodeid(pos(4,-1,1,8,1,66))])),pred,[used_ids([]),nodeid(pos(2,-1,1,1,1,68))])). |
| 2416 | | |
| 2417 | | |
| 2418 | | % #(m,n).(m:30..100 & n:10..20 & m<n ) |
| 2419 | | must_fail_clpfd_det(101,b(exists([b(identifier(x),integer,[nodeid(pos(nan,1,1,3,1,3))])],b(conjunct(b(equal(b(range_subtraction(b(sequence_extension([b(integer(111),integer,[nodeid(pos(nan,1,1,9,1,9))]),b(integer(222),integer,[nodeid(pos(nan,1,1,13,1,13))]),b(integer(333),integer,[nodeid(pos(nan,1,1,17,1,17))]),b(integer(444),integer,[nodeid(pos(nan,1,1,21,1,21))]),b(integer(555),integer,[nodeid(pos(nan,1,1,25,1,25))])]),set(couple(integer,integer)),[nodeid(pos(nan,1,1,8,1,28))]),b(set_extension([b(identifier(x),integer,[nodeid(pos(nan,1,1,35,1,35)),introduced_by(exists)])]),set(integer),[nodeid(pos(nan,1,1,34,1,36))])),set(couple(integer,integer)),[nodeid(pos(nan,1,1,8,1,36))]),b(sequence_extension([b(integer(111),integer,[nodeid(pos(nan,1,1,41,1,41))]),b(integer(222),integer,[nodeid(pos(nan,1,1,45,1,45))]),b(integer(333),integer,[nodeid(pos(nan,1,1,49,1,49))]),b(integer(444),integer,[nodeid(pos(nan,1,1,53,1,53))])]),set(couple(integer,integer)),[nodeid(pos(nan,1,1,40,1,56))])),pred,[nodeid(pos(nan,1,1,8,1,56))]),b(greater(b(identifier(x),integer,[nodeid(pos(nan,1,1,60,1,60)),introduced_by(exists)]),b(integer(555),integer,[nodeid(pos(nan,1,1,64,1,64))])),pred,[nodeid(pos(nan,1,1,60,1,64))])),pred,[nodeid(pos(nan,1,1,8,1,64))])),pred,[used_ids([]),nodeid(pos(nan,1,1,1,1,68))])). |
| 2420 | | |
| 2421 | | % #(m,n).(m:30..101 & n:10..20 & n*n=m & m/=100) |
| 2422 | | must_fail_clpfd_det(102,b(exists([b(identifier(m),integer,[nodeid(pos(7,1,4,3,4,3))]),b(identifier(n),integer,[nodeid(pos(8,1,4,5,4,5))])],b(conjunct(b(conjunct(b(conjunct(b(member(b(identifier(m),integer,[nodeid(pos(13,1,4,9,4,9))]),b(interval(b(integer(30),integer,[nodeid(pos(15,1,4,11,4,12))]),b(integer(101),integer,[nodeid(pos(16,1,4,15,4,17))])),set(integer),[nodeid(pos(14,1,4,11,4,17))])),pred,[nodeid(pos(12,1,4,9,4,17))]),b(member(b(identifier(n),integer,[nodeid(pos(18,1,4,21,4,21))]),b(interval(b(integer(10),integer,[nodeid(pos(20,1,4,23,4,24))]),b(integer(20),integer,[nodeid(pos(21,1,4,27,4,28))])),set(integer),[nodeid(pos(19,1,4,23,4,28))])),pred,[nodeid(pos(17,1,4,21,4,28))])),pred,[nodeid(pos(11,1,4,9,4,28))]),b(equal(b(multiplication(b(identifier(n),integer,[nodeid(pos(24,1,4,32,4,32))]),b(identifier(n),integer,[nodeid(pos(25,1,4,34,4,34))])),integer,[nodeid(pos(23,1,4,32,4,34))]),b(identifier(m),integer,[nodeid(pos(26,1,4,36,4,36))])),pred,[nodeid(pos(22,1,4,32,4,36))])),pred,[nodeid(pos(10,1,4,9,4,36))]),b(not_equal(b(identifier(m),integer,[nodeid(pos(28,1,4,40,4,40))]),b(integer(100),integer,[nodeid(pos(29,1,4,43,4,45))])),pred,[nodeid(pos(27,1,4,40,4,45))])),pred,[nodeid(pos(9,1,4,9,4,45))])),pred,[used_ids([]),nodeid(pos(6,1,4,1,4,46))])). |
| 2423 | | |
| 2424 | | % #(x,y).(y : BOOL & (x : NATURAL & (((x : {11}) <=> (y = TRUE) & x < 10) & (x : {12}) <=> (y = FALSE)))) |
| 2425 | | must_fail_clpfd_det(103,b(exists([b(identifier(x),integer,[nodeid(pos(7,1,4,3,4,3))]),b(identifier(y),boolean,[nodeid(pos(8,1,4,5,4,5))])],b(conjunct(b(member(b(identifier(x),integer,[nodeid(pos(12,1,4,9,4,9))]),b(integer_set('NATURAL'),set(integer),[nodeid(pos(13,1,4,11,4,17))])),pred,[nodeid(pos(11,1,4,9,4,17))]),b(conjunct(b(conjunct(b(equivalence(b(member(b(identifier(x),integer,[nodeid(pos(21,1,4,32,4,32))]),b(set_extension([b(integer(11),integer,[nodeid(pos(23,1,4,35,4,36))])]),set(integer),[nodeid(pos(22,1,4,34,4,37))])),pred,[nodeid(pos(20,1,4,32,4,37))]),b(equal(b(identifier(y),boolean,[nodeid(pos(25,1,4,43,4,43))]),b(boolean_true,boolean,[nodeid(pos(26,1,4,45,4,48))])),pred,[nodeid(pos(24,1,4,43,4,48))])),pred,[nodeid(pos(19,1,4,32,4,48))]),b(less(b(identifier(x),integer,[nodeid(pos(28,1,4,53,4,53))]),b(integer(10),integer,[nodeid(pos(29,1,4,55,4,56))])),pred,[nodeid(pos(27,1,4,53,4,56))])),pred,[nodeid(pos(18,1,4,32,4,56))]),b(equivalence(b(member(b(identifier(x),integer,[nodeid(pos(32,1,4,61,4,61))]),b(set_extension([b(integer(12),integer,[nodeid(pos(34,1,4,64,4,65))])]),set(integer),[nodeid(pos(33,1,4,63,4,66))])),pred,[nodeid(pos(31,1,4,61,4,66))]),b(equal(b(identifier(y),boolean,[nodeid(pos(36,1,4,72,4,72))]),b(boolean_false,boolean,[nodeid(pos(37,1,4,74,4,78))])),pred,[nodeid(pos(35,1,4,72,4,78))])),pred,[nodeid(pos(30,1,4,61,4,78))])),pred,[nodeid(pos(17,1,4,32,4,78))])),pred,[nodeid(pos(9,1,4,9,4,78))])),pred,[used_ids([]),nodeid(pos(6,1,4,1,4,81))])). |
| 2426 | | |
| 2427 | | |
| 2428 | | % #(x,y).((x : INTEGER & y : INTEGER) & (({x} /<<: {11,12} <=> (y = 3) & x > 12) & y < 3)) |
| 2429 | | must_fail_clpfd_det(104,b(exists([b(identifier(x),integer,[]),b(identifier(y),integer,[])],b(conjunct(b(conjunct(b(equivalence(b(not_subset_strict(b(set_extension([b(identifier(x),integer,[nodeid(pos(nan,1,1,2,1,2))])]),set(integer),[nodeid(pos(nan,1,1,1,1,3))]),b(set_extension([b(integer(11),integer,[nodeid(pos(nan,1,1,11,1,11))]),b(integer(12),integer,[nodeid(pos(nan,1,1,14,1,14))])]),set(integer),[nodeid(pos(nan,1,1,10,1,16))])),pred,[nodeid(pos(nan,1,1,1,1,16))]),b(equal(b(identifier(y),integer,[nodeid(pos(nan,1,1,22,1,22))]),b(integer(3),integer,[nodeid(pos(nan,1,1,24,1,24))])),pred,[nodeid(pos(nan,1,1,22,1,24))])),pred,[nodeid(pos(nan,1,1,1,1,24))]),b(greater(b(identifier(x),integer,[nodeid(pos(nan,1,1,28,1,28))]),b(integer(12),integer,[nodeid(pos(nan,1,1,30,1,30))])),pred,[nodeid(pos(nan,1,1,28,1,30))])),pred,[nodeid(pos(nan,1,1,1,1,30))]),b(less(b(identifier(y),integer,[nodeid(pos(nan,1,1,35,1,35))]),b(integer(3),integer,[nodeid(pos(nan,1,1,37,1,37))])),pred,[nodeid(pos(nan,1,1,35,1,37))])),pred,[nodeid(pos(nan,1,1,1,1,37))])),pred,[used_ids([x,y])])). |
| 2430 | | |
| 2431 | | % #(x,y).((x : 5 .. 10000 & x / y = 19000) & y : 1 .. 100) |
| 2432 | | must_fail_clpfd_det(105,b(exists([b(identifier(x),integer,[]),b(identifier(y),integer,[])],b(conjunct(b(conjunct(b(member(b(identifier(x),integer,[nodeid(pos(nan,1,1,1,1,1))]),b(interval(b(integer(5),integer,[nodeid(pos(nan,1,1,3,1,3))]),b(integer(10000),integer,[nodeid(pos(nan,1,1,6,1,6))])),set(integer),[nodeid(pos(nan,1,1,3,1,6))])),pred,[nodeid(pos(nan,1,1,1,1,6))]),b(equal(b(div(b(identifier(x),integer,[nodeid(pos(nan,1,1,14,1,14))]),b(identifier(y),integer,[nodeid(pos(nan,1,1,16,1,16))])),integer,[contains_wd_condition,nodeid(pos(nan,1,1,14,1,16))]),b(integer(19000),integer,[nodeid(pos(nan,1,1,18,1,18))])),pred,[contains_wd_condition,nodeid(pos(nan,1,1,14,1,18))])),pred,[contains_wd_condition,nodeid(pos(nan,1,1,1,1,18))]),b(member(b(identifier(y),integer,[nodeid(pos(nan,1,1,26,1,26))]),b(interval(b(integer(1),integer,[nodeid(pos(nan,1,1,28,1,28))]),b(integer(100),integer,[nodeid(pos(nan,1,1,31,1,31))])),set(integer),[nodeid(pos(nan,1,1,28,1,31))])),pred,[nodeid(pos(nan,1,1,26,1,31))])),pred,[contains_wd_condition,nodeid(pos(nan,1,1,1,1,31))])),pred,[used_ids([x,y])])). |
| 2433 | | |
| 2434 | | % #(x,y).((x : 500 .. 10000 & 499 / y = x) & y : 1 .. 100) |
| 2435 | | must_fail_clpfd_det(106,b(exists([b(identifier(x),integer,[]),b(identifier(y),integer,[])],b(conjunct(b(conjunct(b(member(b(identifier(x),integer,[nodeid(pos(nan,1,1,1,1,1))]),b(interval(b(integer(500),integer,[nodeid(pos(nan,1,1,3,1,3))]),b(integer(10000),integer,[nodeid(pos(nan,1,1,8,1,8))])),set(integer),[nodeid(pos(nan,1,1,3,1,8))])),pred,[nodeid(pos(nan,1,1,1,1,8))]),b(equal(b(div(b(integer(499),integer,[nodeid(pos(nan,1,1,16,1,16))]),b(identifier(y),integer,[nodeid(pos(nan,1,1,20,1,20))])),integer,[contains_wd_condition,nodeid(pos(nan,1,1,16,1,20))]),b(identifier(x),integer,[nodeid(pos(nan,1,1,22,1,22))])),pred,[contains_wd_condition,nodeid(pos(nan,1,1,16,1,22))])),pred,[contains_wd_condition,nodeid(pos(nan,1,1,1,1,22))]),b(member(b(identifier(y),integer,[nodeid(pos(nan,1,1,26,1,26))]),b(interval(b(integer(1),integer,[nodeid(pos(nan,1,1,28,1,28))]),b(integer(100),integer,[nodeid(pos(nan,1,1,31,1,31))])),set(integer),[nodeid(pos(nan,1,1,28,1,31))])),pred,[nodeid(pos(nan,1,1,26,1,31))])),pred,[contains_wd_condition,nodeid(pos(nan,1,1,1,1,31))])),pred,[used_ids([x,y])])). |
| 2436 | | |
| 2437 | | % #(y,f,x).((((y : 1 .. 1000001 & f : 100001 .. 100005 --> 1 .. 9000) & x : dom(f)) & x : 2 .. 100003) & (x > 5000 => y : 2000001 .. 2000002)) |
| 2438 | | must_fail_clpfd_det(107,b(exists([b(identifier(y),integer,[]),b(identifier(f),set(couple(integer,integer)),[]),b(identifier(x),integer,[])],b(conjunct(b(conjunct(b(conjunct(b(conjunct(b(member(b(identifier(y),integer,[nodeid(pos(nan,1,1,1,1,1))]),b(interval(b(integer(1),integer,[nodeid(pos(nan,1,1,3,1,3))]),b(integer(1000001),integer,[nodeid(pos(nan,1,1,6,1,6))])),set(integer),[nodeid(pos(nan,1,1,3,1,6))])),pred,[nodeid(pos(nan,1,1,1,1,6))]),b(member(b(identifier(f),set(couple(integer,integer)),[nodeid(pos(nan,1,1,16,1,16))]),b(total_function(b(interval(b(integer(100001),integer,[nodeid(pos(nan,1,1,18,1,18))]),b(integer(100005),integer,[nodeid(pos(nan,1,1,26,1,26))])),set(integer),[nodeid(pos(nan,1,1,18,1,26))]),b(interval(b(integer(1),integer,[nodeid(pos(nan,1,1,37,1,37))]),b(integer(9000),integer,[nodeid(pos(nan,1,1,40,1,40))])),set(integer),[nodeid(pos(nan,1,1,37,1,40))])),set(set(couple(integer,integer))),[nodeid(pos(nan,1,1,18,1,40))])),pred,[nodeid(pos(nan,1,1,16,1,40))])),pred,[nodeid(pos(nan,1,1,1,1,40))]),b(member(b(identifier(x),integer,[nodeid(pos(nan,1,1,48,1,48))]),b(domain(b(identifier(f),set(couple(integer,integer)),[nodeid(pos(nan,1,1,54,1,54))])),set(integer),[nodeid(pos(nan,1,1,50,1,55))])),pred,[nodeid(pos(nan,1,1,48,1,55))])),pred,[nodeid(pos(nan,1,1,1,1,55))]),b(member(b(identifier(x),integer,[nodeid(pos(nan,1,1,59,1,59))]),b(interval(b(integer(2),integer,[nodeid(pos(nan,1,1,61,1,61))]),b(integer(100003),integer,[nodeid(pos(nan,1,1,64,1,64))])),set(integer),[nodeid(pos(nan,1,1,61,1,64))])),pred,[nodeid(pos(nan,1,1,59,1,64))])),pred,[nodeid(pos(nan,1,1,1,1,64))]),b(implication(b(greater(b(identifier(x),integer,[nodeid(pos(nan,1,1,74,1,74))]),b(integer(5000),integer,[nodeid(pos(nan,1,1,76,1,76))])),pred,[nodeid(pos(nan,1,1,74,1,76))]),b(member(b(identifier(y),integer,[nodeid(pos(nan,1,1,84,1,84))]),b(interval(b(integer(2000001),integer,[nodeid(pos(nan,1,1,86,1,86))]),b(integer(2000002),integer,[nodeid(pos(nan,1,1,95,1,95))])),set(integer),[nodeid(pos(nan,1,1,86,1,95))])),pred,[nodeid(pos(nan,1,1,84,1,95))])),pred,[nodeid(pos(nan,1,1,74,1,95))])),pred,[nodeid(pos(nan,1,1,1,1,102))])),pred,[used_ids([f,x,y])])). |
| 2439 | | % #(f,x).((f : (BOOL * (123456 .. 123459)) * BOOL --> 1 .. 100 & x : dom(f)) & #(b,y,b2).(((b : BOOL & y : INTEGER) & b2 : BOOL) & (x = (b |-> y) |-> b2 & (y > 123459 or y < 123456)))) |
| 2440 | | must_fail_clpfd_det(108,b(exists([b(identifier(f),set(couple(couple(couple(boolean,integer),boolean),integer)),[]),b(identifier(x),couple(couple(boolean,integer),boolean),[])],b(conjunct(b(conjunct(b(member(b(identifier(f),set(couple(couple(couple(boolean,integer),boolean),integer)),[nodeid(pos(nan,1,1,1,1,1))]),b(total_function(b(cartesian_product(b(cartesian_product(b(bool_set,set(boolean),[nodeid(pos(nan,1,1,5,1,5))]),b(interval(b(integer(123456),integer,[nodeid(pos(nan,1,1,11,1,11))]),b(integer(123459),integer,[nodeid(pos(nan,1,1,19,1,19))])),set(integer),[nodeid(pos(nan,1,1,11,1,19))])),set(couple(boolean,integer)),[nodeid(pos(nan,1,1,5,1,25))]),b(bool_set,set(boolean),[nodeid(pos(nan,1,1,27,1,27))])),set(couple(couple(boolean,integer),boolean)),[nodeid(pos(nan,1,1,5,1,27))]),b(interval(b(integer(1),integer,[nodeid(pos(nan,1,1,37,1,37))]),b(integer(100),integer,[nodeid(pos(nan,1,1,40,1,40))])),set(integer),[nodeid(pos(nan,1,1,37,1,40))])),set(set(couple(couple(couple(boolean,integer),boolean),integer))),[nodeid(pos(nan,1,1,4,1,40))])),pred,[nodeid(pos(nan,1,1,1,1,40))]),b(member(b(identifier(x),couple(couple(boolean,integer),boolean),[nodeid(pos(nan,1,1,46,1,46))]),b(domain(b(identifier(f),set(couple(couple(couple(boolean,integer),boolean),integer)),[nodeid(pos(nan,1,1,52,1,52))])),set(couple(couple(boolean,integer),boolean)),[nodeid(pos(nan,1,1,48,1,53))])),pred,[nodeid(pos(nan,1,1,46,1,53))])),pred,[nodeid(pos(nan,1,1,1,1,53))]),b(exists([b(identifier(b),boolean,[nodeid(pos(nan,1,1,59,1,59)),introduced_by(exists)]),b(identifier(y),integer,[nodeid(pos(nan,1,1,61,1,61)),introduced_by(exists)]),b(identifier(b2),boolean,[nodeid(pos(nan,1,1,63,1,63)),introduced_by(exists)])],b(conjunct(b(equal(b(identifier(x),couple(couple(boolean,integer),boolean),[nodeid(pos(nan,1,1,68,1,68))]),b(couple(b(couple(b(identifier(b),boolean,[nodeid(pos(nan,1,1,71,1,71)),introduced_by(exists)]),b(identifier(y),integer,[nodeid(pos(nan,1,1,73,1,73)),introduced_by(exists)])),couple(boolean,integer),[nodeid(pos(nan,1,1,70,1,77))]),b(identifier(b2),boolean,[nodeid(pos(nan,1,1,75,1,75)),introduced_by(exists)])),couple(couple(boolean,integer),boolean),[nodeid(pos(nan,1,1,70,1,77))])),pred,[nodeid(pos(nan,1,1,68,1,77))]),b(disjunct(b(greater(b(identifier(y),integer,[nodeid(pos(nan,1,1,82,1,82)),introduced_by(exists)]),b(integer(123459),integer,[nodeid(pos(nan,1,1,84,1,84))])),pred,[nodeid(pos(nan,1,1,82,1,84))]),b(less(b(identifier(y),integer,[nodeid(pos(nan,1,1,94,1,94)),introduced_by(exists)]),b(integer(123456),integer,[nodeid(pos(nan,1,1,96,1,96))])),pred,[nodeid(pos(nan,1,1,94,1,96))])),pred,[nodeid(pos(nan,1,1,82,1,96))])),pred,[nodeid(pos(nan,1,1,68,1,102))])),pred,[used_ids([x]),nodeid(pos(nan,1,1,57,1,103))])),pred,[nodeid(pos(nan,1,1,1,1,103))])),pred,[used_ids([f,x])])). |
| 2441 | | % #(f,x,y).((x : INTEGER & y : INTEGER) & ((f : 10 .. 200 --> 1 .. 200000 & x |-> y : f) & (x > 200 or x < 10))) |
| 2442 | | must_fail_clpfd_det(109,b(exists([b(identifier(f),set(couple(integer,integer)),[]),b(identifier(x),integer,[]),b(identifier(y),integer,[])],b(conjunct(b(conjunct(b(member(b(identifier(f),set(couple(integer,integer)),[nodeid(pos(nan,1,1,1,1,1))]),b(total_function(b(interval(b(integer(10),integer,[nodeid(pos(nan,1,1,4,1,4))]),b(integer(200),integer,[nodeid(pos(nan,1,1,8,1,8))])),set(integer),[nodeid(pos(nan,1,1,4,1,8))]),b(interval(b(integer(1),integer,[nodeid(pos(nan,1,1,16,1,16))]),b(integer(200000),integer,[nodeid(pos(nan,1,1,19,1,19))])),set(integer),[nodeid(pos(nan,1,1,16,1,19))])),set(set(couple(integer,integer))),[nodeid(pos(nan,1,1,4,1,19))])),pred,[nodeid(pos(nan,1,1,1,1,19))]),b(member(b(couple(b(identifier(x),integer,[nodeid(pos(nan,1,1,28,1,28))]),b(identifier(y),integer,[nodeid(pos(nan,1,1,32,1,32))])),couple(integer,integer),[nodeid(pos(nan,1,1,28,1,32))]),b(identifier(f),set(couple(integer,integer)),[nodeid(pos(nan,1,1,36,1,36))])),pred,[nodeid(pos(nan,1,1,28,1,36))])),pred,[nodeid(pos(nan,1,1,1,1,36))]),b(disjunct(b(greater(b(identifier(x),integer,[nodeid(pos(nan,1,1,41,1,41))]),b(integer(200),integer,[nodeid(pos(nan,1,1,43,1,43))])),pred,[nodeid(pos(nan,1,1,41,1,43))]),b(less(b(identifier(x),integer,[nodeid(pos(nan,1,1,50,1,50))]),b(integer(10),integer,[nodeid(pos(nan,1,1,52,1,52))])),pred,[nodeid(pos(nan,1,1,50,1,52))])),pred,[nodeid(pos(nan,1,1,41,1,52))])),pred,[nodeid(pos(nan,1,1,1,1,54))])),pred,[used_ids([f,x,y])])). |
| 2443 | | % #(f,b,x).((b : BOOL * BOOL & x : INTEGER) & ((f : BOOL * BOOL --> 100 .. 200000 & b |-> x : f) & (x > 200000 or x < 100))) |
| 2444 | | must_fail_clpfd_det(110,b(exists([b(identifier(f),set(couple(couple(boolean,boolean),integer)),[]),b(identifier(b),couple(boolean,boolean),[]),b(identifier(x),integer,[])],b(conjunct(b(conjunct(b(member(b(identifier(f),set(couple(couple(boolean,boolean),integer)),[nodeid(pos(nan,1,1,1,1,1))]),b(total_function(b(cartesian_product(b(bool_set,set(boolean),[nodeid(pos(nan,1,1,5,1,5))]),b(bool_set,set(boolean),[nodeid(pos(nan,1,1,10,1,10))])),set(couple(boolean,boolean)),[nodeid(pos(nan,1,1,5,1,10))]),b(interval(b(integer(100),integer,[nodeid(pos(nan,1,1,20,1,20))]),b(integer(200000),integer,[nodeid(pos(nan,1,1,25,1,25))])),set(integer),[nodeid(pos(nan,1,1,20,1,25))])),set(set(couple(couple(boolean,boolean),integer))),[nodeid(pos(nan,1,1,4,1,25))])),pred,[nodeid(pos(nan,1,1,1,1,25))]),b(member(b(couple(b(identifier(b),couple(boolean,boolean),[nodeid(pos(nan,1,1,34,1,34))]),b(identifier(x),integer,[nodeid(pos(nan,1,1,38,1,38))])),couple(couple(boolean,boolean),integer),[nodeid(pos(nan,1,1,34,1,38))]),b(identifier(f),set(couple(couple(boolean,boolean),integer)),[nodeid(pos(nan,1,1,42,1,42))])),pred,[nodeid(pos(nan,1,1,34,1,42))])),pred,[nodeid(pos(nan,1,1,1,1,42))]),b(disjunct(b(greater(b(identifier(x),integer,[nodeid(pos(nan,1,1,47,1,47))]),b(integer(200000),integer,[nodeid(pos(nan,1,1,49,1,49))])),pred,[nodeid(pos(nan,1,1,47,1,49))]),b(less(b(identifier(x),integer,[nodeid(pos(nan,1,1,59,1,59))]),b(integer(100),integer,[nodeid(pos(nan,1,1,61,1,61))])),pred,[nodeid(pos(nan,1,1,59,1,61))])),pred,[nodeid(pos(nan,1,1,47,1,61))])),pred,[nodeid(pos(nan,1,1,1,1,64))])),pred,[used_ids([b,f,x])])). |
| 2445 | | % #(f,g).(((f : 10001 .. 10110 --> NATURAL & !(x).(x : dom(f) => f(x) : dom(f))) & g : 20010 .. 20020 --> BOOL) & !(x).(x : dom(f) => f(x) : dom(g))) |
| 2446 | | must_fail_clpfd_det(111,b(exists([b(identifier(f),set(couple(integer,integer)),[]),b(identifier(g),set(couple(integer,boolean)),[])],b(conjunct(b(conjunct(b(conjunct(b(member(b(identifier(f),set(couple(integer,integer)),[nodeid(pos(nan,1,1,2,1,2))]),b(total_function(b(interval(b(integer(10001),integer,[nodeid(pos(nan,1,1,5,1,5))]),b(integer(10110),integer,[nodeid(pos(nan,1,1,12,1,12))])),set(integer),[nodeid(pos(nan,1,1,5,1,12))]),b(integer_set('NATURAL'),set(integer),[nodeid(pos(nan,1,1,22,1,22))])),set(set(couple(integer,integer))),[nodeid(pos(nan,1,1,5,1,22))])),pred,[nodeid(pos(nan,1,1,2,1,22))]),b(forall([b(identifier(x),integer,[nodeid(pos(nan,1,1,33,1,33)),introduced_by(forall)])],b(member(b(identifier(x),integer,[nodeid(pos(nan,1,1,36,1,36)),introduced_by(forall)]),b(domain(b(identifier(f),set(couple(integer,integer)),[nodeid(pos(nan,1,1,42,1,42))])),set(integer),[nodeid(pos(nan,1,1,38,1,43))])),pred,[nodeid(pos(nan,1,1,36,1,43))]),b(member(b(function(b(identifier(f),set(couple(integer,integer)),[nodeid(pos(nan,1,1,48,1,48))]),b(identifier(x),integer,[nodeid(pos(nan,1,1,50,1,50)),introduced_by(forall)])),integer,[contains_wd_condition,nodeid(pos(nan,1,1,48,1,51))]),b(domain(b(identifier(f),set(couple(integer,integer)),[nodeid(pos(nan,1,1,57,1,57))])),set(integer),[nodeid(pos(nan,1,1,53,1,58))])),pred,[contains_wd_condition,nodeid(pos(nan,1,1,48,1,58))])),pred,[used_ids([f]),nodeid(pos(nan,1,1,32,1,59))])),pred,[nodeid(pos(nan,1,1,2,1,59))]),b(member(b(identifier(g),set(couple(integer,boolean)),[nodeid(pos(nan,1,1,63,1,63))]),b(total_function(b(interval(b(integer(20010),integer,[nodeid(pos(nan,1,1,65,1,65))]),b(integer(20020),integer,[nodeid(pos(nan,1,1,72,1,72))])),set(integer),[nodeid(pos(nan,1,1,65,1,72))]),b(bool_set,set(boolean),[nodeid(pos(nan,1,1,82,1,82))])),set(set(couple(integer,boolean))),[nodeid(pos(nan,1,1,65,1,82))])),pred,[nodeid(pos(nan,1,1,63,1,82))])),pred,[nodeid(pos(nan,1,1,2,1,82))]),b(forall([b(identifier(x),integer,[nodeid(pos(nan,1,1,90,1,90)),introduced_by(forall)])],b(member(b(identifier(x),integer,[nodeid(pos(nan,1,1,93,1,93)),introduced_by(forall)]),b(domain(b(identifier(f),set(couple(integer,integer)),[nodeid(pos(nan,1,1,99,1,99))])),set(integer),[nodeid(pos(nan,1,1,95,1,100))])),pred,[nodeid(pos(nan,1,1,93,1,100))]),b(member(b(function(b(identifier(f),set(couple(integer,integer)),[nodeid(pos(nan,1,1,105,1,105))]),b(identifier(x),integer,[nodeid(pos(nan,1,1,107,1,107)),introduced_by(forall)])),integer,[contains_wd_condition,nodeid(pos(nan,1,1,105,1,108))]),b(domain(b(identifier(g),set(couple(integer,boolean)),[nodeid(pos(nan,1,1,114,1,114))])),set(integer),[nodeid(pos(nan,1,1,110,1,115))])),pred,[contains_wd_condition,nodeid(pos(nan,1,1,105,1,115))])),pred,[used_ids([f,g]),nodeid(pos(nan,1,1,89,1,116))])),pred,[nodeid(pos(nan,1,1,2,1,116))])),pred,[used_ids([f,g])])). |
| 2447 | | % #(f,x,y).((x : INTEGER & y : INTEGER) & ((f : 1001 .. 2001 --> 1900 .. 3333 & x |-> y : f) & y + 101 < x)) |
| 2448 | | must_fail_clpfd_det(112,b(exists([b(identifier(f),set(couple(integer,integer)),[]),b(identifier(x),integer,[]),b(identifier(y),integer,[])],b(conjunct(b(conjunct(b(member(b(identifier(f),set(couple(integer,integer)),[nodeid(pos(nan,1,1,1,1,1))]),b(total_function(b(interval(b(integer(1001),integer,[nodeid(pos(nan,1,1,5,1,5))]),b(integer(2001),integer,[nodeid(pos(nan,1,1,11,1,11))])),set(integer),[nodeid(pos(nan,1,1,5,1,11))]),b(interval(b(integer(1900),integer,[nodeid(pos(nan,1,1,20,1,20))]),b(integer(3333),integer,[nodeid(pos(nan,1,1,26,1,26))])),set(integer),[nodeid(pos(nan,1,1,20,1,26))])),set(set(couple(integer,integer))),[nodeid(pos(nan,1,1,5,1,26))])),pred,[nodeid(pos(nan,1,1,1,1,26))]),b(member(b(couple(b(identifier(x),integer,[nodeid(pos(nan,1,1,33,1,33))]),b(identifier(y),integer,[nodeid(pos(nan,1,1,37,1,37))])),couple(integer,integer),[nodeid(pos(nan,1,1,33,1,37))]),b(identifier(f),set(couple(integer,integer)),[nodeid(pos(nan,1,1,41,1,41))])),pred,[nodeid(pos(nan,1,1,33,1,41))])),pred,[nodeid(pos(nan,1,1,1,1,41))]),b(less(b(add(b(identifier(y),integer,[nodeid(pos(nan,1,1,45,1,45))]),b(integer(101),integer,[nodeid(pos(nan,1,1,47,1,47))])),integer,[nodeid(pos(nan,1,1,45,1,47))]),b(identifier(x),integer,[nodeid(pos(nan,1,1,51,1,51))])),pred,[nodeid(pos(nan,1,1,45,1,51))])),pred,[nodeid(pos(nan,1,1,1,1,51))])),pred,[used_ids([f,x,y])])). |
| 2449 | | |
| 2450 | | % #(r,x,y,v,w).((((x : INTEGER & y : INTEGER) & v : INTEGER) & w : INTEGER) & ((((r : 1001 .. 1005 <-> 1000 .. 1099 & x |-> y : r) & v |-> w : r) & x + y = (v + w) + 120) & card(r) = 3)) |
| 2451 | | must_fail_clpfd_det(113,b(exists([b(identifier(r),set(couple(integer,integer)),[]),b(identifier(x),integer,[]),b(identifier(y),integer,[]),b(identifier(v),integer,[]),b(identifier(w),integer,[])],b(conjunct(b(conjunct(b(conjunct(b(conjunct(b(member(b(identifier(r),set(couple(integer,integer)),[nodeid(pos(nan,1,1,1,1,1))]),b(relations(b(interval(b(integer(1001),integer,[nodeid(pos(nan,1,1,4,1,4))]),b(integer(1005),integer,[nodeid(pos(nan,1,1,10,1,10))])),set(integer),[nodeid(pos(nan,1,1,4,1,10))]),b(interval(b(integer(1000),integer,[nodeid(pos(nan,1,1,19,1,19))]),b(integer(1099),integer,[nodeid(pos(nan,1,1,25,1,25))])),set(integer),[nodeid(pos(nan,1,1,19,1,25))])),set(set(couple(integer,integer))),[nodeid(pos(nan,1,1,4,1,25))])),pred,[nodeid(pos(nan,1,1,1,1,25))]),b(member(b(couple(b(identifier(x),integer,[nodeid(pos(nan,1,1,32,1,32))]),b(identifier(y),integer,[nodeid(pos(nan,1,1,36,1,36))])),couple(integer,integer),[nodeid(pos(nan,1,1,32,1,36))]),b(identifier(r),set(couple(integer,integer)),[nodeid(pos(nan,1,1,40,1,40))])),pred,[nodeid(pos(nan,1,1,32,1,40))])),pred,[nodeid(pos(nan,1,1,1,1,40))]),b(member(b(couple(b(identifier(v),integer,[nodeid(pos(nan,1,1,44,1,44))]),b(identifier(w),integer,[nodeid(pos(nan,1,1,48,1,48))])),couple(integer,integer),[nodeid(pos(nan,1,1,44,1,48))]),b(identifier(r),set(couple(integer,integer)),[nodeid(pos(nan,1,1,52,1,52))])),pred,[nodeid(pos(nan,1,1,44,1,52))])),pred,[nodeid(pos(nan,1,1,1,1,52))]),b(equal(b(add(b(identifier(x),integer,[nodeid(pos(nan,1,1,57,1,57))]),b(identifier(y),integer,[nodeid(pos(nan,1,1,59,1,59))])),integer,[nodeid(pos(nan,1,1,57,1,59))]),b(add(b(add(b(identifier(v),integer,[nodeid(pos(nan,1,1,63,1,63))]),b(identifier(w),integer,[nodeid(pos(nan,1,1,65,1,65))])),integer,[nodeid(pos(nan,1,1,63,1,65))]),b(integer(120),integer,[nodeid(pos(nan,1,1,67,1,67))])),integer,[nodeid(pos(nan,1,1,63,1,67))])),pred,[nodeid(pos(nan,1,1,57,1,67))])),pred,[nodeid(pos(nan,1,1,1,1,67))]),b(equal(b(card(b(identifier(r),set(couple(integer,integer)),[nodeid(pos(nan,1,1,78,1,78))])),integer,[contains_wd_condition,nodeid(pos(nan,1,1,73,1,79))]),b(integer(3),integer,[nodeid(pos(nan,1,1,83,1,83))])),pred,[contains_wd_condition,nodeid(pos(nan,1,1,73,1,83))])),pred,[contains_wd_condition,nodeid(pos(nan,1,1,1,1,83))])),pred,[used_ids([r,v,w,x,y])])). |
| 2452 | | |
| 2453 | | % #(r,x,y,v,w).((((x : INTEGER & y : INTEGER) & v : INTEGER) & w : INTEGER) & ((((r : 1001 .. 1005 +-> 1000 .. 1099 & x |-> y : r) & v |-> w : r) & x + y = (v + w) + 120) & card(r) = 3)) |
| 2454 | | must_fail_clpfd_det(114,b(exists([b(identifier(r),set(couple(integer,integer)),[]),b(identifier(x),integer,[]),b(identifier(y),integer,[]),b(identifier(v),integer,[]),b(identifier(w),integer,[])],b(conjunct(b(conjunct(b(conjunct(b(conjunct(b(member(b(identifier(r),set(couple(integer,integer)),[nodeid(pos(nan,1,1,1,1,1))]),b(partial_function(b(interval(b(integer(1001),integer,[nodeid(pos(nan,1,1,4,1,4))]),b(integer(1005),integer,[nodeid(pos(nan,1,1,10,1,10))])),set(integer),[nodeid(pos(nan,1,1,4,1,10))]),b(interval(b(integer(1000),integer,[nodeid(pos(nan,1,1,19,1,19))]),b(integer(1099),integer,[nodeid(pos(nan,1,1,25,1,25))])),set(integer),[nodeid(pos(nan,1,1,19,1,25))])),set(set(couple(integer,integer))),[nodeid(pos(nan,1,1,4,1,25))])),pred,[nodeid(pos(nan,1,1,1,1,25))]),b(member(b(couple(b(identifier(x),integer,[nodeid(pos(nan,1,1,32,1,32))]),b(identifier(y),integer,[nodeid(pos(nan,1,1,36,1,36))])),couple(integer,integer),[nodeid(pos(nan,1,1,32,1,36))]),b(identifier(r),set(couple(integer,integer)),[nodeid(pos(nan,1,1,40,1,40))])),pred,[nodeid(pos(nan,1,1,32,1,40))])),pred,[nodeid(pos(nan,1,1,1,1,40))]),b(member(b(couple(b(identifier(v),integer,[nodeid(pos(nan,1,1,44,1,44))]),b(identifier(w),integer,[nodeid(pos(nan,1,1,48,1,48))])),couple(integer,integer),[nodeid(pos(nan,1,1,44,1,48))]),b(identifier(r),set(couple(integer,integer)),[nodeid(pos(nan,1,1,52,1,52))])),pred,[nodeid(pos(nan,1,1,44,1,52))])),pred,[nodeid(pos(nan,1,1,1,1,52))]),b(equal(b(add(b(identifier(x),integer,[nodeid(pos(nan,1,1,57,1,57))]),b(identifier(y),integer,[nodeid(pos(nan,1,1,59,1,59))])),integer,[nodeid(pos(nan,1,1,57,1,59))]),b(add(b(add(b(identifier(v),integer,[nodeid(pos(nan,1,1,63,1,63))]),b(identifier(w),integer,[nodeid(pos(nan,1,1,65,1,65))])),integer,[nodeid(pos(nan,1,1,63,1,65))]),b(integer(120),integer,[nodeid(pos(nan,1,1,67,1,67))])),integer,[nodeid(pos(nan,1,1,63,1,67))])),pred,[nodeid(pos(nan,1,1,57,1,67))])),pred,[nodeid(pos(nan,1,1,1,1,67))]),b(equal(b(card(b(identifier(r),set(couple(integer,integer)),[nodeid(pos(nan,1,1,78,1,78))])),integer,[contains_wd_condition,nodeid(pos(nan,1,1,73,1,79))]),b(integer(3),integer,[nodeid(pos(nan,1,1,83,1,83))])),pred,[contains_wd_condition,nodeid(pos(nan,1,1,73,1,83))])),pred,[contains_wd_condition,nodeid(pos(nan,1,1,1,1,83))])),pred,[used_ids([r,v,w,x,y])])). |
| 2455 | | % #(r,x,y,v,w).((((x : INTEGER & y : INTEGER) & v : INTEGER) & w : INTEGER) & ((((r : 1001 .. 1005 >+> 1000 .. 1099 & x |-> y : r) & v |-> w : r) & x + y = (v + w) + 104) & card(r) = 2)) |
| 2456 | | must_fail_clpfd_det(115,b(exists([b(identifier(r),set(couple(integer,integer)),[]),b(identifier(x),integer,[]),b(identifier(y),integer,[]),b(identifier(v),integer,[]),b(identifier(w),integer,[])],b(conjunct(b(conjunct(b(conjunct(b(conjunct(b(member(b(identifier(r),set(couple(integer,integer)),[nodeid(pos(nan,1,1,1,1,1))]),b(partial_injection(b(interval(b(integer(1001),integer,[nodeid(pos(nan,1,1,4,1,4))]),b(integer(1005),integer,[nodeid(pos(nan,1,1,10,1,10))])),set(integer),[nodeid(pos(nan,1,1,4,1,10))]),b(interval(b(integer(1000),integer,[nodeid(pos(nan,1,1,19,1,19))]),b(integer(1099),integer,[nodeid(pos(nan,1,1,25,1,25))])),set(integer),[nodeid(pos(nan,1,1,19,1,25))])),set(set(couple(integer,integer))),[nodeid(pos(nan,1,1,4,1,25))])),pred,[nodeid(pos(nan,1,1,1,1,25))]),b(member(b(couple(b(identifier(x),integer,[nodeid(pos(nan,1,1,32,1,32))]),b(identifier(y),integer,[nodeid(pos(nan,1,1,36,1,36))])),couple(integer,integer),[nodeid(pos(nan,1,1,32,1,36))]),b(identifier(r),set(couple(integer,integer)),[nodeid(pos(nan,1,1,40,1,40))])),pred,[nodeid(pos(nan,1,1,32,1,40))])),pred,[nodeid(pos(nan,1,1,1,1,40))]),b(member(b(couple(b(identifier(v),integer,[nodeid(pos(nan,1,1,44,1,44))]),b(identifier(w),integer,[nodeid(pos(nan,1,1,48,1,48))])),couple(integer,integer),[nodeid(pos(nan,1,1,44,1,48))]),b(identifier(r),set(couple(integer,integer)),[nodeid(pos(nan,1,1,52,1,52))])),pred,[nodeid(pos(nan,1,1,44,1,52))])),pred,[nodeid(pos(nan,1,1,1,1,52))]),b(equal(b(add(b(identifier(x),integer,[nodeid(pos(nan,1,1,57,1,57))]),b(identifier(y),integer,[nodeid(pos(nan,1,1,59,1,59))])),integer,[nodeid(pos(nan,1,1,57,1,59))]),b(add(b(add(b(identifier(v),integer,[nodeid(pos(nan,1,1,63,1,63))]),b(identifier(w),integer,[nodeid(pos(nan,1,1,65,1,65))])),integer,[nodeid(pos(nan,1,1,63,1,65))]),b(integer(104),integer,[nodeid(pos(nan,1,1,67,1,67))])),integer,[nodeid(pos(nan,1,1,63,1,67))])),pred,[nodeid(pos(nan,1,1,57,1,67))])),pred,[nodeid(pos(nan,1,1,1,1,67))]),b(equal(b(card(b(identifier(r),set(couple(integer,integer)),[nodeid(pos(nan,1,1,78,1,78))])),integer,[contains_wd_condition,nodeid(pos(nan,1,1,73,1,79))]),b(integer(2),integer,[nodeid(pos(nan,1,1,83,1,83))])),pred,[contains_wd_condition,nodeid(pos(nan,1,1,73,1,83))])),pred,[contains_wd_condition,nodeid(pos(nan,1,1,1,1,83))])),pred,[used_ids([r,v,w,x,y])])). |
| 2457 | | % #(s,x,b,y,b2).(((((s : POW((INTEGER * STRING) * BOOL) & x : INTEGER) & b : BOOL) & y : INTEGER) & b2 : BOOL) & (((s = {((1|->"a")|->TRUE),((2|->"a")|->FALSE),((3|->"b")|->FALSE),((4|->"b")|->FALSE)} & (x |-> "a") |-> b : s) & (y |-> "b") |-> b2 : s) & x > y)) |
| 2458 | | must_fail_clpfd_det(116,b(exists([b(identifier(s),set(couple(couple(integer,string),boolean)),[]),b(identifier(x),integer,[]),b(identifier(b),boolean,[]),b(identifier(y),integer,[]),b(identifier(b2),boolean,[])],b(conjunct(b(conjunct(b(conjunct(b(equal(b(identifier(s),set(couple(couple(integer,string),boolean)),[nodeid(pos(nan,1,1,1,1,1))]),b(value(avl_set(node(((int(2),string(a)),pred_false),true,1,node(((int(1),string(a)),pred_true),true,0,empty,empty),node(((int(3),string(b)),pred_false),true,1,empty,node(((int(4),string(b)),pred_false),true,0,empty,empty))))),set(couple(couple(integer,string),boolean)),[nodeid(pos(nan,1,1,5,1,66))])),pred,[nodeid(pos(nan,1,1,1,1,66))]),b(member(b(couple(b(couple(b(identifier(x),integer,[nodeid(pos(nan,1,1,71,1,71))]),b(string(a),string,[nodeid(pos(nan,1,1,75,1,75))])),couple(integer,string),[nodeid(pos(nan,1,1,71,1,75))]),b(identifier(b),boolean,[nodeid(pos(nan,1,1,81,1,81))])),couple(couple(integer,string),boolean),[nodeid(pos(nan,1,1,71,1,81))]),b(identifier(s),set(couple(couple(integer,string),boolean)),[nodeid(pos(nan,1,1,85,1,85))])),pred,[nodeid(pos(nan,1,1,71,1,85))])),pred,[nodeid(pos(nan,1,1,1,1,85))]),b(member(b(couple(b(couple(b(identifier(y),integer,[nodeid(pos(nan,1,1,89,1,89))]),b(string(b),string,[nodeid(pos(nan,1,1,93,1,93))])),couple(integer,string),[nodeid(pos(nan,1,1,89,1,93))]),b(identifier(b2),boolean,[nodeid(pos(nan,1,1,99,1,99))])),couple(couple(integer,string),boolean),[nodeid(pos(nan,1,1,89,1,99))]),b(identifier(s),set(couple(couple(integer,string),boolean)),[nodeid(pos(nan,1,1,104,1,104))])),pred,[nodeid(pos(nan,1,1,89,1,104))])),pred,[nodeid(pos(nan,1,1,1,1,104))]),b(greater(b(identifier(x),integer,[nodeid(pos(nan,1,1,108,1,108))]),b(identifier(y),integer,[nodeid(pos(nan,1,1,110,1,110))])),pred,[nodeid(pos(nan,1,1,108,1,110))])),pred,[nodeid(pos(nan,1,1,1,1,110))])),pred,[used_ids([b,b2,s,x,y])])). |
| 2459 | | % #(f,v,x).(((f : POW((INTEGER * BOOL) * INTEGER) & v : INTEGER) & x : INTEGER) & ((f = {(11 |-> TRUE) |-> 3,(10 |-> TRUE) |-> 4,(2 |-> FALSE) |-> 5,(3 |-> FALSE) |-> v} & x |-> FALSE : dom(f)) & x |-> TRUE : dom(f))) |
| 2460 | | must_fail_clpfd_det(117,b(exists([b(identifier(f),set(couple(couple(integer,boolean),integer)),[]),b(identifier(v),integer,[]),b(identifier(x),integer,[])],b(conjunct(b(conjunct(b(equal(b(identifier(f),set(couple(couple(integer,boolean),integer)),[nodeid(pos(nan,1,1,1,1,1))]),b(set_extension([b(couple(b(couple(b(integer(11),integer,[nodeid(pos(nan,1,1,5,1,5))]),b(boolean_true,boolean,[nodeid(pos(nan,1,1,10,1,10))])),couple(integer,boolean),[nodeid(pos(nan,1,1,5,1,10))]),b(integer(3),integer,[nodeid(pos(nan,1,1,17,1,17))])),couple(couple(integer,boolean),integer),[nodeid(pos(nan,1,1,5,1,17))]),b(couple(b(couple(b(integer(10),integer,[nodeid(pos(nan,1,1,20,1,20))]),b(boolean_true,boolean,[nodeid(pos(nan,1,1,25,1,25))])),couple(integer,boolean),[nodeid(pos(nan,1,1,20,1,25))]),b(integer(4),integer,[nodeid(pos(nan,1,1,32,1,32))])),couple(couple(integer,boolean),integer),[nodeid(pos(nan,1,1,20,1,32))]),b(couple(b(couple(b(integer(2),integer,[nodeid(pos(nan,1,1,35,1,35))]),b(boolean_false,boolean,[nodeid(pos(nan,1,1,39,1,39))])),couple(integer,boolean),[nodeid(pos(nan,1,1,35,1,39))]),b(integer(5),integer,[nodeid(pos(nan,1,1,47,1,47))])),couple(couple(integer,boolean),integer),[nodeid(pos(nan,1,1,35,1,47))]),b(couple(b(couple(b(integer(3),integer,[nodeid(pos(nan,1,1,49,1,49))]),b(boolean_false,boolean,[nodeid(pos(nan,1,1,53,1,53))])),couple(integer,boolean),[nodeid(pos(nan,1,1,49,1,53))]),b(identifier(v),integer,[nodeid(pos(nan,1,1,61,1,61))])),couple(couple(integer,boolean),integer),[nodeid(pos(nan,1,1,49,1,61))])]),set(couple(couple(integer,boolean),integer)),[nodeid(pos(nan,1,1,4,1,62))])),pred,[nodeid(pos(nan,1,1,1,1,62))]),b(member(b(couple(b(identifier(x),integer,[nodeid(pos(nan,1,1,66,1,66))]),b(boolean_false,boolean,[nodeid(pos(nan,1,1,70,1,70))])),couple(integer,boolean),[nodeid(pos(nan,1,1,66,1,70))]),b(domain(b(identifier(f),set(couple(couple(integer,boolean),integer)),[nodeid(pos(nan,1,1,82,1,82))])),set(couple(integer,boolean)),[nodeid(pos(nan,1,1,78,1,83))])),pred,[nodeid(pos(nan,1,1,66,1,83))])),pred,[nodeid(pos(nan,1,1,1,1,83))]),b(member(b(couple(b(identifier(x),integer,[nodeid(pos(nan,1,1,87,1,87))]),b(boolean_true,boolean,[nodeid(pos(nan,1,1,91,1,91))])),couple(integer,boolean),[nodeid(pos(nan,1,1,87,1,91))]),b(domain(b(identifier(f),set(couple(couple(integer,boolean),integer)),[nodeid(pos(nan,1,1,102,1,102))])),set(couple(integer,boolean)),[nodeid(pos(nan,1,1,98,1,103))])),pred,[nodeid(pos(nan,1,1,87,1,103))])),pred,[nodeid(pos(nan,1,1,1,1,103))])),pred,[used_ids([f,v,x])])). |
| 2461 | | % #(f,x).((f : POW((INTEGER * BOOL) * INTEGER) & x : INTEGER) & ((f = {((2|->FALSE)|->5),((3|->FALSE)|->77),((10|->TRUE)|->4),((11|->TRUE)|->3)} & x |-> FALSE : dom(f)) & x |-> TRUE : dom(f))) |
| 2462 | | must_fail_clpfd_det(118,b(exists([b(identifier(f),set(couple(couple(integer,boolean),integer)),[]),b(identifier(x),integer,[])],b(conjunct(b(conjunct(b(equal(b(identifier(f),set(couple(couple(integer,boolean),integer)),[nodeid(pos(nan,1,1,1,1,1))]),b(value(avl_set(node(((int(3),pred_false),int(77)),true,1,node(((int(2),pred_false),int(5)),true,0,empty,empty),node(((int(10),pred_true),int(4)),true,1,empty,node(((int(11),pred_true),int(3)),true,0,empty,empty))))),set(couple(couple(integer,boolean),integer)),[nodeid(pos(nan,1,1,4,1,63))])),pred,[nodeid(pos(nan,1,1,1,1,63))]),b(member(b(couple(b(identifier(x),integer,[nodeid(pos(nan,1,1,67,1,67))]),b(boolean_false,boolean,[nodeid(pos(nan,1,1,71,1,71))])),couple(integer,boolean),[nodeid(pos(nan,1,1,67,1,71))]),b(domain(b(identifier(f),set(couple(couple(integer,boolean),integer)),[nodeid(pos(nan,1,1,83,1,83))])),set(couple(integer,boolean)),[nodeid(pos(nan,1,1,79,1,84))])),pred,[nodeid(pos(nan,1,1,67,1,84))])),pred,[nodeid(pos(nan,1,1,1,1,84))]),b(member(b(couple(b(identifier(x),integer,[nodeid(pos(nan,1,1,88,1,88))]),b(boolean_true,boolean,[nodeid(pos(nan,1,1,92,1,92))])),couple(integer,boolean),[nodeid(pos(nan,1,1,88,1,92))]),b(domain(b(identifier(f),set(couple(couple(integer,boolean),integer)),[nodeid(pos(nan,1,1,103,1,103))])),set(couple(integer,boolean)),[nodeid(pos(nan,1,1,99,1,104))])),pred,[nodeid(pos(nan,1,1,88,1,104))])),pred,[nodeid(pos(nan,1,1,1,1,104))])),pred,[used_ids([f,x])])). |
| 2463 | | % #(a,v1,v2,w).((((a : POW(struct(x:INTEGER * INTEGER,y:INTEGER)) & v1 : INTEGER) & v2 : INTEGER) & w : INTEGER) & ((a = {rec(x:1 |-> 33,y:22),rec(x:2 |-> 34,y:44),rec(x:3 |-> 34,y:45)} & rec(x:v1 |-> v2,y:w) : a) & (v1 + v2) + w < 56)) |
| 2464 | | must_fail_clpfd_det(119,b(exists([b(identifier(a),set(record([field(x,couple(integer,integer)),field(y,integer)])),[]),b(identifier(v1),integer,[]),b(identifier(v2),integer,[]),b(identifier(w),integer,[])],b(conjunct(b(conjunct(b(equal(b(identifier(a),set(record([field(x,couple(integer,integer)),field(y,integer)])),[nodeid(pos(nan,1,1,1,1,1))]),b(set_extension([b(rec([field(x,b(couple(b(integer(1),integer,[nodeid(pos(nan,1,1,13,1,13))]),b(integer(33),integer,[nodeid(pos(nan,1,1,15,1,15))])),couple(integer,integer),[nodeid(pos(nan,1,1,12,1,17))])),field(y,b(integer(22),integer,[nodeid(pos(nan,1,1,21,1,21))]))]),record([field(x,couple(integer,integer)),field(y,integer)]),[nodeid(pos(nan,1,1,6,1,23))]),b(rec([field(x,b(couple(b(integer(2),integer,[nodeid(pos(nan,1,1,32,1,32))]),b(integer(34),integer,[nodeid(pos(nan,1,1,34,1,34))])),couple(integer,integer),[nodeid(pos(nan,1,1,31,1,36))])),field(y,b(integer(44),integer,[nodeid(pos(nan,1,1,40,1,40))]))]),record([field(x,couple(integer,integer)),field(y,integer)]),[nodeid(pos(nan,1,1,25,1,42))]),b(rec([field(x,b(couple(b(integer(3),integer,[nodeid(pos(nan,1,1,51,1,51))]),b(integer(34),integer,[nodeid(pos(nan,1,1,53,1,53))])),couple(integer,integer),[nodeid(pos(nan,1,1,50,1,55))])),field(y,b(integer(45),integer,[nodeid(pos(nan,1,1,59,1,59))]))]),record([field(x,couple(integer,integer)),field(y,integer)]),[nodeid(pos(nan,1,1,44,1,61))])]),set(record([field(x,couple(integer,integer)),field(y,integer)])),[nodeid(pos(nan,1,1,5,1,62))])),pred,[nodeid(pos(nan,1,1,1,1,62))]),b(member(b(rec([field(x,b(couple(b(identifier(v1),integer,[nodeid(pos(nan,1,1,73,1,73))]),b(identifier(v2),integer,[nodeid(pos(nan,1,1,76,1,76))])),couple(integer,integer),[nodeid(pos(nan,1,1,72,1,78))])),field(y,b(identifier(w),integer,[nodeid(pos(nan,1,1,82,1,82))]))]),record([field(x,couple(integer,integer)),field(y,integer)]),[nodeid(pos(nan,1,1,66,1,83))]),b(identifier(a),set(record([field(x,couple(integer,integer)),field(y,integer)])),[nodeid(pos(nan,1,1,85,1,85))])),pred,[nodeid(pos(nan,1,1,66,1,85))])),pred,[nodeid(pos(nan,1,1,1,1,85))]),b(less(b(add(b(add(b(identifier(v1),integer,[nodeid(pos(nan,1,1,89,1,89))]),b(identifier(v2),integer,[nodeid(pos(nan,1,1,92,1,92))])),integer,[nodeid(pos(nan,1,1,89,1,92))]),b(identifier(w),integer,[nodeid(pos(nan,1,1,95,1,95))])),integer,[nodeid(pos(nan,1,1,89,1,95))]),b(integer(56),integer,[nodeid(pos(nan,1,1,98,1,98))])),pred,[nodeid(pos(nan,1,1,89,1,98))])),pred,[nodeid(pos(nan,1,1,1,1,98))])),pred,[used_ids([a,v1,v2,w])])). |
| 2465 | | % #(n,r1,a,b).((((n : INTEGER & r1 : POW(struct(x:INTEGER,y:INTEGER))) & a : INTEGER) & b : INTEGER) & ((({x|x : struct(x:INTEGER,y:INTEGER) & #(vv,ww).((x = rec(x:ww,y:vv) & vv : 1 .. n) & ww : 33 .. 34)} = r1 & n = 50) & rec(x:a,y:b) : r1) & rec(x:a + 2,y:b) : r1)) |
| 2466 | | must_fail_clpfd_det(120,b(exists([b(identifier(n),integer,[]),b(identifier(r1),set(record([field(x,integer),field(y,integer)])),[]),b(identifier(a),integer,[]),b(identifier(b),integer,[])],b(conjunct(b(conjunct(b(conjunct(b(equal(b(comprehension_set([b(identifier(x),record([field(x,integer),field(y,integer)]),[nodeid(pos(nan,1,1,12,1,12)),introduced_by(comprehension_set)])],b(exists([b(identifier(vv),integer,[nodeid(pos(nan,1,1,6,1,6)),introduced_by(comprehension_set)]),b(identifier(ww),integer,[nodeid(pos(nan,1,1,9,1,9)),introduced_by(comprehension_set)])],b(conjunct(b(conjunct(b(equal(b(identifier(x),record([field(x,integer),field(y,integer)]),[nodeid(pos(nan,1,1,14,1,14)),introduced_by(comprehension_set)]),b(rec([field(x,b(identifier(ww),integer,[nodeid(pos(nan,1,1,22,1,22)),introduced_by(comprehension_set)])),field(y,b(identifier(vv),integer,[nodeid(pos(nan,1,1,27,1,27)),introduced_by(comprehension_set)]))]),record([field(x,integer),field(y,integer)]),[nodeid(pos(nan,1,1,16,1,29))])),pred,[nodeid(pos(nan,1,1,14,1,29))]),b(member(b(identifier(vv),integer,[nodeid(pos(nan,1,1,33,1,33)),introduced_by(comprehension_set)]),b(interval(b(integer(1),integer,[nodeid(pos(nan,1,1,36,1,36))]),b(identifier(n),integer,[nodeid(pos(nan,1,1,39,1,39))])),set(integer),[nodeid(pos(nan,1,1,36,1,39))])),pred,[nodeid(pos(nan,1,1,33,1,39))])),pred,[nodeid(pos(nan,1,1,14,1,39))]),b(member(b(identifier(ww),integer,[nodeid(pos(nan,1,1,43,1,43)),introduced_by(comprehension_set)]),b(interval(b(integer(33),integer,[nodeid(pos(nan,1,1,46,1,46))]),b(integer(34),integer,[nodeid(pos(nan,1,1,50,1,50))])),set(integer),[nodeid(pos(nan,1,1,46,1,50))])),pred,[nodeid(pos(nan,1,1,43,1,50))])),pred,[nodeid(pos(nan,1,1,14,1,50))])),pred,[used_ids([n,vv,ww,x])])),set(record([field(x,integer),field(y,integer)])),[nodeid(pos(nan,1,1,1,1,53))]),b(identifier(r1),set(record([field(x,integer),field(y,integer)])),[nodeid(pos(nan,1,1,55,1,55))])),pred,[nodeid(pos(nan,1,1,1,1,55))]),b(equal(b(identifier(n),integer,[nodeid(pos(nan,1,1,60,1,60))]),b(integer(50),integer,[nodeid(pos(nan,1,1,62,1,62))])),pred,[nodeid(pos(nan,1,1,60,1,62))])),pred,[nodeid(pos(nan,1,1,1,1,62))]),b(member(b(rec([field(x,b(identifier(a),integer,[nodeid(pos(nan,1,1,74,1,74))])),field(y,b(identifier(b),integer,[nodeid(pos(nan,1,1,78,1,78))]))]),record([field(x,integer),field(y,integer)]),[nodeid(pos(nan,1,1,68,1,79))]),b(identifier(r1),set(record([field(x,integer),field(y,integer)])),[nodeid(pos(nan,1,1,81,1,81))])),pred,[nodeid(pos(nan,1,1,68,1,81))])),pred,[nodeid(pos(nan,1,1,1,1,81))]),b(member(b(rec([field(x,b(add(b(identifier(a),integer,[nodeid(pos(nan,1,1,92,1,92))]),b(integer(2),integer,[nodeid(pos(nan,1,1,94,1,94))])),integer,[nodeid(pos(nan,1,1,92,1,94))])),field(y,b(identifier(b),integer,[nodeid(pos(nan,1,1,98,1,98))]))]),record([field(x,integer),field(y,integer)]),[nodeid(pos(nan,1,1,86,1,99))]),b(identifier(r1),set(record([field(x,integer),field(y,integer)])),[nodeid(pos(nan,1,1,101,1,101))])),pred,[nodeid(pos(nan,1,1,86,1,101))])),pred,[nodeid(pos(nan,1,1,1,1,101))])),pred,[used_ids([a,b,n,r1])])). |
| 2467 | | % #(x,y).(y : INTEGER & (((rec(f:x) /= rec(f:y) & x : 1 .. 2) & y = 2) & rec(f:x) /= rec(f:1))) |
| 2468 | | must_fail_clpfd_det(121,b(exists([b(identifier(x),integer,[]),b(identifier(y),integer,[])],b(conjunct(b(conjunct(b(conjunct(b(not_equal(b(rec([field(f,b(identifier(x),integer,[nodeid(pos(nan,1,1,7,1,7))]))]),record([field(f,integer)]),[nodeid(pos(nan,1,1,1,1,8))]),b(rec([field(f,b(identifier(y),integer,[nodeid(pos(nan,1,1,19,1,19))]))]),record([field(f,integer)]),[nodeid(pos(nan,1,1,13,1,20))])),pred,[nodeid(pos(nan,1,1,1,1,20))]),b(member(b(identifier(x),integer,[nodeid(pos(nan,1,1,24,1,24))]),b(interval(b(integer(1),integer,[nodeid(pos(nan,1,1,26,1,26))]),b(integer(2),integer,[nodeid(pos(nan,1,1,29,1,29))])),set(integer),[nodeid(pos(nan,1,1,26,1,29))])),pred,[nodeid(pos(nan,1,1,24,1,29))])),pred,[nodeid(pos(nan,1,1,1,1,29))]),b(equal(b(identifier(y),integer,[nodeid(pos(nan,1,1,33,1,33))]),b(integer(2),integer,[nodeid(pos(nan,1,1,35,1,35))])),pred,[nodeid(pos(nan,1,1,33,1,35))])),pred,[nodeid(pos(nan,1,1,1,1,35))]),b(not_equal(b(rec([field(f,b(identifier(x),integer,[nodeid(pos(nan,1,1,45,1,45))]))]),record([field(f,integer)]),[nodeid(pos(nan,1,1,39,1,46))]),b(rec([field(f,b(integer(1),integer,[nodeid(pos(nan,1,1,57,1,57))]))]),record([field(f,integer)]),[nodeid(pos(nan,1,1,51,1,58))])),pred,[nodeid(pos(nan,1,1,39,1,58))])),pred,[nodeid(pos(nan,1,1,1,1,58))])),pred,[used_ids([x,y])])). |
| 2469 | | % #(x,y).(y : INTEGER & ((((x |-> (1 |-> 2)) /= (y |-> (1 |-> 2)) & x : 1 .. 2) & y = 2) & (x |-> (1 |-> 2)) /= (1 |-> (1 |-> 2)))) |
| 2470 | | must_fail_clpfd_det(122,b(exists([b(identifier(x),integer,[]),b(identifier(y),integer,[])],b(conjunct(b(conjunct(b(conjunct(b(not_equal(b(couple(b(identifier(x),integer,[nodeid(pos(nan,1,1,2,1,2))]),b(couple(b(integer(1),integer,[nodeid(pos(nan,1,1,5,1,5))]),b(integer(2),integer,[nodeid(pos(nan,1,1,7,1,7))])),couple(integer,integer),[nodeid(pos(nan,1,1,4,1,8))])),couple(integer,couple(integer,integer)),[nodeid(pos(nan,1,1,1,1,9))]),b(couple(b(identifier(y),integer,[nodeid(pos(nan,1,1,15,1,15))]),b(couple(b(integer(1),integer,[nodeid(pos(nan,1,1,18,1,18))]),b(integer(2),integer,[nodeid(pos(nan,1,1,20,1,20))])),couple(integer,integer),[nodeid(pos(nan,1,1,17,1,21))])),couple(integer,couple(integer,integer)),[nodeid(pos(nan,1,1,14,1,22))])),pred,[nodeid(pos(nan,1,1,1,1,22))]),b(member(b(identifier(x),integer,[nodeid(pos(nan,1,1,26,1,26))]),b(interval(b(integer(1),integer,[nodeid(pos(nan,1,1,28,1,28))]),b(integer(2),integer,[nodeid(pos(nan,1,1,31,1,31))])),set(integer),[nodeid(pos(nan,1,1,28,1,31))])),pred,[nodeid(pos(nan,1,1,26,1,31))])),pred,[nodeid(pos(nan,1,1,1,1,31))]),b(equal(b(identifier(y),integer,[nodeid(pos(nan,1,1,35,1,35))]),b(integer(2),integer,[nodeid(pos(nan,1,1,37,1,37))])),pred,[nodeid(pos(nan,1,1,35,1,37))])),pred,[nodeid(pos(nan,1,1,1,1,37))]),b(not_equal(b(couple(b(identifier(x),integer,[nodeid(pos(nan,1,1,42,1,42))]),b(couple(b(integer(1),integer,[nodeid(pos(nan,1,1,45,1,45))]),b(integer(2),integer,[nodeid(pos(nan,1,1,47,1,47))])),couple(integer,integer),[nodeid(pos(nan,1,1,44,1,48))])),couple(integer,couple(integer,integer)),[nodeid(pos(nan,1,1,41,1,49))]),b(couple(b(integer(1),integer,[nodeid(pos(nan,1,1,55,1,55))]),b(couple(b(integer(1),integer,[nodeid(pos(nan,1,1,58,1,58))]),b(integer(2),integer,[nodeid(pos(nan,1,1,60,1,60))])),couple(integer,integer),[nodeid(pos(nan,1,1,57,1,61))])),couple(integer,couple(integer,integer)),[nodeid(pos(nan,1,1,54,1,62))])),pred,[nodeid(pos(nan,1,1,41,1,62))])),pred,[nodeid(pos(nan,1,1,1,1,62))])),pred,[used_ids([x,y])])). |
| 2471 | | % #(y,v).(v : INTEGER & (((rec(a:y,b:1,c:1 |-> 2) /= rec(a:v,b:1,c:1 |-> 2) & y : 1 .. 2) & v = 1) & rec(a:1,b:y,c:1 |-> 2) /= rec(a:v,b:2,c:1 |-> 2))) |
| 2472 | | must_fail_clpfd_det(123,b(exists([b(identifier(y),integer,[]),b(identifier(v),integer,[])],b(conjunct(b(conjunct(b(conjunct(b(not_equal(b(rec([field(a,b(identifier(y),integer,[nodeid(pos(nan,1,1,8,1,8))])),field(b,b(integer(1),integer,[nodeid(pos(nan,1,1,12,1,12))])),field(c,b(couple(b(integer(1),integer,[nodeid(pos(nan,1,1,17,1,17))]),b(integer(2),integer,[nodeid(pos(nan,1,1,19,1,19))])),couple(integer,integer),[nodeid(pos(nan,1,1,16,1,20))]))]),record([field(a,integer),field(b,integer),field(c,couple(integer,integer))]),[nodeid(pos(nan,1,1,2,1,21))]),b(rec([field(a,b(identifier(v),integer,[nodeid(pos(nan,1,1,30,1,30))])),field(b,b(integer(1),integer,[nodeid(pos(nan,1,1,34,1,34))])),field(c,b(couple(b(integer(1),integer,[nodeid(pos(nan,1,1,39,1,39))]),b(integer(2),integer,[nodeid(pos(nan,1,1,41,1,41))])),couple(integer,integer),[nodeid(pos(nan,1,1,38,1,42))]))]),record([field(a,integer),field(b,integer),field(c,couple(integer,integer))]),[nodeid(pos(nan,1,1,24,1,43))])),pred,[nodeid(pos(nan,1,1,2,1,43))]),b(member(b(identifier(y),integer,[nodeid(pos(nan,1,1,48,1,48))]),b(interval(b(integer(1),integer,[nodeid(pos(nan,1,1,50,1,50))]),b(integer(2),integer,[nodeid(pos(nan,1,1,53,1,53))])),set(integer),[nodeid(pos(nan,1,1,50,1,53))])),pred,[nodeid(pos(nan,1,1,48,1,53))])),pred,[nodeid(pos(nan,1,1,1,1,53))]),b(equal(b(identifier(v),integer,[nodeid(pos(nan,1,1,57,1,57))]),b(integer(1),integer,[nodeid(pos(nan,1,1,59,1,59))])),pred,[nodeid(pos(nan,1,1,57,1,59))])),pred,[nodeid(pos(nan,1,1,1,1,59))]),b(not_equal(b(rec([field(a,b(integer(1),integer,[nodeid(pos(nan,1,1,70,1,70))])),field(b,b(identifier(y),integer,[nodeid(pos(nan,1,1,74,1,74))])),field(c,b(couple(b(integer(1),integer,[nodeid(pos(nan,1,1,79,1,79))]),b(integer(2),integer,[nodeid(pos(nan,1,1,81,1,81))])),couple(integer,integer),[nodeid(pos(nan,1,1,78,1,82))]))]),record([field(a,integer),field(b,integer),field(c,couple(integer,integer))]),[nodeid(pos(nan,1,1,64,1,83))]),b(rec([field(a,b(identifier(v),integer,[nodeid(pos(nan,1,1,92,1,92))])),field(b,b(integer(2),integer,[nodeid(pos(nan,1,1,96,1,96))])),field(c,b(couple(b(integer(1),integer,[nodeid(pos(nan,1,1,101,1,101))]),b(integer(2),integer,[nodeid(pos(nan,1,1,103,1,103))])),couple(integer,integer),[nodeid(pos(nan,1,1,100,1,104))]))]),record([field(a,integer),field(b,integer),field(c,couple(integer,integer))]),[nodeid(pos(nan,1,1,86,1,105))])),pred,[nodeid(pos(nan,1,1,64,1,105))])),pred,[nodeid(pos(nan,1,1,1,1,106))])),pred,[used_ids([v,y])])). |
| 2473 | | % #(b,y,v).((b : BOOL & v : INTEGER) & ((((b = bool(rec(a:y,b:1,c:1 |-> 2) /= rec(a:v,b:1,c:1 |-> 2)) & y : 1 .. 2) & v = 1) & rec(a:1,b:y,c:1 |-> 2) /= rec(a:v,b:2,c:1 |-> 2)) & b = TRUE)) |
| 2474 | | must_fail_clpfd_det(124,b(exists([b(identifier(b),boolean,[]),b(identifier(y),integer,[]),b(identifier(v),integer,[])],b(conjunct(b(conjunct(b(conjunct(b(conjunct(b(equal(b(identifier(b),boolean,[nodeid(pos(nan,1,1,1,1,1))]),b(convert_bool(b(not_equal(b(rec([field(a,b(identifier(y),integer,[nodeid(pos(nan,1,1,14,1,14))])),field(b,b(integer(1),integer,[nodeid(pos(nan,1,1,18,1,18))])),field(c,b(couple(b(integer(1),integer,[nodeid(pos(nan,1,1,23,1,23))]),b(integer(2),integer,[nodeid(pos(nan,1,1,25,1,25))])),couple(integer,integer),[nodeid(pos(nan,1,1,22,1,26))]))]),record([field(a,integer),field(b,integer),field(c,couple(integer,integer))]),[nodeid(pos(nan,1,1,8,1,27))]),b(rec([field(a,b(identifier(v),integer,[nodeid(pos(nan,1,1,36,1,36))])),field(b,b(integer(1),integer,[nodeid(pos(nan,1,1,40,1,40))])),field(c,b(couple(b(integer(1),integer,[nodeid(pos(nan,1,1,45,1,45))]),b(integer(2),integer,[nodeid(pos(nan,1,1,47,1,47))])),couple(integer,integer),[nodeid(pos(nan,1,1,44,1,48))]))]),record([field(a,integer),field(b,integer),field(c,couple(integer,integer))]),[nodeid(pos(nan,1,1,30,1,49))])),pred,[nodeid(pos(nan,1,1,8,1,49))])),boolean,[nodeid(pos(nan,1,1,3,1,50))])),pred,[nodeid(pos(nan,1,1,1,1,50))]),b(member(b(identifier(y),integer,[nodeid(pos(nan,1,1,54,1,54))]),b(interval(b(integer(1),integer,[nodeid(pos(nan,1,1,56,1,56))]),b(integer(2),integer,[nodeid(pos(nan,1,1,59,1,59))])),set(integer),[nodeid(pos(nan,1,1,56,1,59))])),pred,[nodeid(pos(nan,1,1,54,1,59))])),pred,[nodeid(pos(nan,1,1,1,1,59))]),b(equal(b(identifier(v),integer,[nodeid(pos(nan,1,1,63,1,63))]),b(integer(1),integer,[nodeid(pos(nan,1,1,65,1,65))])),pred,[nodeid(pos(nan,1,1,63,1,65))])),pred,[nodeid(pos(nan,1,1,1,1,65))]),b(not_equal(b(rec([field(a,b(integer(1),integer,[nodeid(pos(nan,1,1,76,1,76))])),field(b,b(identifier(y),integer,[nodeid(pos(nan,1,1,80,1,80))])),field(c,b(couple(b(integer(1),integer,[nodeid(pos(nan,1,1,85,1,85))]),b(integer(2),integer,[nodeid(pos(nan,1,1,87,1,87))])),couple(integer,integer),[nodeid(pos(nan,1,1,84,1,88))]))]),record([field(a,integer),field(b,integer),field(c,couple(integer,integer))]),[nodeid(pos(nan,1,1,70,1,89))]),b(rec([field(a,b(identifier(v),integer,[nodeid(pos(nan,1,1,98,1,98))])),field(b,b(integer(2),integer,[nodeid(pos(nan,1,1,102,1,102))])),field(c,b(couple(b(integer(1),integer,[nodeid(pos(nan,1,1,107,1,107))]),b(integer(2),integer,[nodeid(pos(nan,1,1,109,1,109))])),couple(integer,integer),[nodeid(pos(nan,1,1,106,1,110))]))]),record([field(a,integer),field(b,integer),field(c,couple(integer,integer))]),[nodeid(pos(nan,1,1,92,1,111))])),pred,[nodeid(pos(nan,1,1,70,1,111))])),pred,[nodeid(pos(nan,1,1,1,1,112))]),b(equal(b(identifier(b),boolean,[nodeid(pos(nan,1,1,116,1,116))]),b(boolean_true,boolean,[nodeid(pos(nan,1,1,118,1,118))])),pred,[nodeid(pos(nan,1,1,116,1,118))])),pred,[nodeid(pos(nan,1,1,1,1,118))])),pred,[used_ids([b,v,y])])). |
| 2475 | | % #(a,v1,v2,w).((((a : POW(struct(x:INTEGER * INTEGER,y:INTEGER,z:BOOL)) & v1 : INTEGER) & v2 : INTEGER) & w : INTEGER) & ((a = {rec(x:1 |-> 33,y:22,z:FALSE),rec(x:2 |-> 34,y:44,z:TRUE),rec(x:3 |-> 34,y:45,z:TRUE)} & rec(x:v1 |-> v2,y:w,z:TRUE) : a) & (v1 + v2) + w < 57)) |
| 2476 | | must_fail_clpfd_det(125,b(exists([b(identifier(a),set(record([field(x,couple(integer,integer)),field(y,integer),field(z,boolean)])),[]),b(identifier(v1),integer,[]),b(identifier(v2),integer,[]),b(identifier(w),integer,[])],b(conjunct(b(conjunct(b(equal(b(identifier(a),set(record([field(x,couple(integer,integer)),field(y,integer),field(z,boolean)])),[nodeid(pos(nan,1,1,1,1,1))]),b(set_extension([b(rec([field(x,b(couple(b(integer(1),integer,[nodeid(pos(nan,1,1,13,1,13))]),b(integer(33),integer,[nodeid(pos(nan,1,1,15,1,15))])),couple(integer,integer),[nodeid(pos(nan,1,1,12,1,17))])),field(y,b(integer(22),integer,[nodeid(pos(nan,1,1,21,1,21))])),field(z,b(boolean_false,boolean,[nodeid(pos(nan,1,1,26,1,26))]))]),record([field(x,couple(integer,integer)),field(y,integer),field(z,boolean)]),[nodeid(pos(nan,1,1,6,1,31))]),b(rec([field(x,b(couple(b(integer(2),integer,[nodeid(pos(nan,1,1,40,1,40))]),b(integer(34),integer,[nodeid(pos(nan,1,1,42,1,42))])),couple(integer,integer),[nodeid(pos(nan,1,1,39,1,44))])),field(y,b(integer(44),integer,[nodeid(pos(nan,1,1,48,1,48))])),field(z,b(boolean_true,boolean,[nodeid(pos(nan,1,1,53,1,53))]))]),record([field(x,couple(integer,integer)),field(y,integer),field(z,boolean)]),[nodeid(pos(nan,1,1,33,1,57))]),b(rec([field(x,b(couple(b(integer(3),integer,[nodeid(pos(nan,1,1,66,1,66))]),b(integer(34),integer,[nodeid(pos(nan,1,1,68,1,68))])),couple(integer,integer),[nodeid(pos(nan,1,1,65,1,70))])),field(y,b(integer(45),integer,[nodeid(pos(nan,1,1,74,1,74))])),field(z,b(boolean_true,boolean,[nodeid(pos(nan,1,1,79,1,79))]))]),record([field(x,couple(integer,integer)),field(y,integer),field(z,boolean)]),[nodeid(pos(nan,1,1,59,1,83))])]),set(record([field(x,couple(integer,integer)),field(y,integer),field(z,boolean)])),[nodeid(pos(nan,1,1,5,1,84))])),pred,[nodeid(pos(nan,1,1,1,1,84))]),b(member(b(rec([field(x,b(couple(b(identifier(v1),integer,[nodeid(pos(nan,1,1,95,1,95))]),b(identifier(v2),integer,[nodeid(pos(nan,1,1,98,1,98))])),couple(integer,integer),[nodeid(pos(nan,1,1,94,1,100))])),field(y,b(identifier(w),integer,[nodeid(pos(nan,1,1,104,1,104))])),field(z,b(boolean_true,boolean,[nodeid(pos(nan,1,1,108,1,108))]))]),record([field(x,couple(integer,integer)),field(y,integer),field(z,boolean)]),[nodeid(pos(nan,1,1,88,1,112))]),b(identifier(a),set(record([field(x,couple(integer,integer)),field(y,integer),field(z,boolean)])),[nodeid(pos(nan,1,1,114,1,114))])),pred,[nodeid(pos(nan,1,1,88,1,114))])),pred,[nodeid(pos(nan,1,1,1,1,114))]),b(less(b(add(b(add(b(identifier(v1),integer,[nodeid(pos(nan,1,1,118,1,118))]),b(identifier(v2),integer,[nodeid(pos(nan,1,1,121,1,121))])),integer,[nodeid(pos(nan,1,1,118,1,121))]),b(identifier(w),integer,[nodeid(pos(nan,1,1,124,1,124))])),integer,[nodeid(pos(nan,1,1,118,1,124))]),b(integer(57),integer,[nodeid(pos(nan,1,1,127,1,127))])),pred,[nodeid(pos(nan,1,1,118,1,127))])),pred,[nodeid(pos(nan,1,1,1,1,127))])),pred,[used_ids([a,v1,v2,w])])). |
| 2477 | | % #(x).(x : INTEGER & ((((x > 0 & x mod 50 = 0) & x mod 61 = 0) & x mod 23 = 0) & x < 70150)) |
| 2478 | | must_fail_clpfd_det(126,b(exists([b(identifier(x),integer,[])],b(conjunct(b(conjunct(b(conjunct(b(conjunct(b(greater(b(identifier(x),integer,[nodeid(pos(nan,1,1,1,1,1))]),b(integer(0),integer,[nodeid(pos(nan,1,1,5,1,5))])),pred,[nodeid(pos(nan,1,1,1,1,5))]),b(equal(b(modulo(b(identifier(x),integer,[nodeid(pos(nan,1,1,10,1,10))]),b(integer(50),integer,[nodeid(pos(nan,1,1,16,1,16))])),integer,[contains_wd_condition,nodeid(pos(nan,1,1,10,1,16))]),b(integer(0),integer,[nodeid(pos(nan,1,1,20,1,20))])),pred,[contains_wd_condition,nodeid(pos(nan,1,1,10,1,20))])),pred,[contains_wd_condition,nodeid(pos(nan,1,1,1,1,20))]),b(equal(b(modulo(b(identifier(x),integer,[nodeid(pos(nan,1,1,24,1,24))]),b(integer(61),integer,[nodeid(pos(nan,1,1,30,1,30))])),integer,[contains_wd_condition,nodeid(pos(nan,1,1,24,1,30))]),b(integer(0),integer,[nodeid(pos(nan,1,1,35,1,35))])),pred,[contains_wd_condition,nodeid(pos(nan,1,1,24,1,35))])),pred,[contains_wd_condition,nodeid(pos(nan,1,1,1,1,35))]),b(equal(b(modulo(b(identifier(x),integer,[nodeid(pos(nan,1,1,39,1,39))]),b(integer(23),integer,[nodeid(pos(nan,1,1,45,1,45))])),integer,[contains_wd_condition,nodeid(pos(nan,1,1,39,1,45))]),b(integer(0),integer,[nodeid(pos(nan,1,1,50,1,50))])),pred,[contains_wd_condition,nodeid(pos(nan,1,1,39,1,50))])),pred,[contains_wd_condition,nodeid(pos(nan,1,1,1,1,50))]),b(less(b(identifier(x),integer,[nodeid(pos(nan,1,1,54,1,54))]),b(integer(70150),integer,[nodeid(pos(nan,1,1,56,1,56))])),pred,[nodeid(pos(nan,1,1,54,1,56))])),pred,[contains_wd_condition,nodeid(pos(nan,1,1,1,1,56))])),pred,[used_ids([x])])). |
| 2479 | | % #(x,B,C).(((x : INTEGER & B : INTEGER) & C : BOOL) & (((((({x} : POW({101,102})) <=> B < 20 & x > 103) & B > 0) & B < 100) & (B = 19) <=> (C = TRUE)) & (C = FALSE => B < 20))) |
| 2480 | | must_fail_clpfd_det(127,b(exists([b(identifier(x),integer,[]),b(identifier('B'),integer,[]),b(identifier('C'),boolean,[])],b(conjunct(b(conjunct(b(conjunct(b(conjunct(b(conjunct(b(equivalence(b(member(b(set_extension([b(identifier(x),integer,[nodeid(pos(nan,1,1,3,1,3))])]),set(integer),[nodeid(pos(nan,1,1,2,1,4))]),b(pow_subset(b(value(avl_set(node(int(101),true,1,empty,node(int(102),true,0,empty,empty)))),set(integer),[nodeid(pos(nan,1,1,10,1,18))])),set(set(integer)),[nodeid(pos(nan,1,1,6,1,19))])),pred,[nodeid(pos(nan,1,1,2,1,19))]),b(less(b(identifier('B'),integer,[nodeid(pos(nan,1,1,25,1,25))]),b(integer(20),integer,[nodeid(pos(nan,1,1,27,1,27))])),pred,[nodeid(pos(nan,1,1,25,1,27))])),pred,[nodeid(pos(nan,1,1,2,1,27))]),b(greater(b(identifier(x),integer,[nodeid(pos(nan,1,1,33,1,33))]),b(integer(103),integer,[nodeid(pos(nan,1,1,35,1,35))])),pred,[nodeid(pos(nan,1,1,33,1,35))])),pred,[nodeid(pos(nan,1,1,1,1,35))]),b(greater(b(identifier('B'),integer,[nodeid(pos(nan,1,1,40,1,40))]),b(integer(0),integer,[nodeid(pos(nan,1,1,42,1,42))])),pred,[nodeid(pos(nan,1,1,40,1,42))])),pred,[nodeid(pos(nan,1,1,1,1,42))]),b(less(b(identifier('B'),integer,[nodeid(pos(nan,1,1,46,1,46))]),b(integer(100),integer,[nodeid(pos(nan,1,1,48,1,48))])),pred,[nodeid(pos(nan,1,1,46,1,48))])),pred,[nodeid(pos(nan,1,1,1,1,48))]),b(equivalence(b(equal(b(identifier('B'),integer,[nodeid(pos(nan,1,1,55,1,55))]),b(integer(19),integer,[nodeid(pos(nan,1,1,57,1,57))])),pred,[nodeid(pos(nan,1,1,55,1,57))]),b(equal(b(identifier('C'),boolean,[nodeid(pos(nan,1,1,64,1,64))]),b(boolean_true,boolean,[nodeid(pos(nan,1,1,66,1,66))])),pred,[nodeid(pos(nan,1,1,64,1,66))])),pred,[nodeid(pos(nan,1,1,55,1,66))])),pred,[nodeid(pos(nan,1,1,1,1,70))]),b(implication(b(equal(b(identifier('C'),boolean,[nodeid(pos(nan,1,1,75,1,75))]),b(boolean_false,boolean,[nodeid(pos(nan,1,1,77,1,77))])),pred,[nodeid(pos(nan,1,1,75,1,77))]),b(less(b(identifier('B'),integer,[nodeid(pos(nan,1,1,86,1,86))]),b(integer(20),integer,[nodeid(pos(nan,1,1,88,1,88))])),pred,[nodeid(pos(nan,1,1,86,1,88))])),pred,[nodeid(pos(nan,1,1,75,1,88))])),pred,[nodeid(pos(nan,1,1,1,1,90))])),pred,[used_ids(['B','C',x])])). |
| 2481 | | |
| 2482 | | % Eval Time: 10 ms (0 ms walltime) |
| 2483 | | % #(r,x,y,z).(((r : POW((INTEGER * INTEGER) * INTEGER) & x : INTEGER) & z : INTEGER) & (((r = {((1|->2)|->3),((3|->4)|->5),((6|->7)|->8),((9|->10)|->11),((12|->13)|->14)} & (x |-> y) |-> z : r) & y : 10 .. 13) & z < 11)) |
| 2484 | | must_fail_clpfd_det(128,b(let_predicate([b(identifier(r),set(couple(couple(integer,integer),integer)),[do_not_optimize_away,nodeid(pos(3,-1,1,3,1,3)),introduced_by(exists)])],[b(value(avl_set(node(((int(6),int(7)),int(8)),true,0,node(((int(1),int(2)),int(3)),true,1,empty,node(((int(3),int(4)),int(5)),true,0,empty,empty)),node(((int(9),int(10)),int(11)),true,1,empty,node(((int(12),int(13)),int(14)),true,0,empty,empty))))),set(couple(couple(integer,integer),integer)),[nodeid(pos(29,-1,1,93,1,168))])],b(exists([b(identifier(x),integer,[do_not_optimize_away,nodeid(pos(4,-1,1,5,1,5)),introduced_by(exists)]),b(identifier(y),integer,[do_not_optimize_away,nodeid(pos(5,-1,1,7,1,7)),introduced_by(exists)]),b(identifier(z),integer,[do_not_optimize_away,nodeid(pos(6,-1,1,9,1,9)),introduced_by(exists)])],b(conjunct(b(conjunct(b(member(b(couple(b(couple(b(identifier(x),integer,[nodeid(pos(58,-1,1,173,1,173)),introduced_by(exists)]),b(identifier(y),integer,[nodeid(pos(59,-1,1,179,1,179)),introduced_by(exists)])),couple(integer,integer),[nodeid(pos(57,-1,1,173,1,179))]),b(identifier(z),integer,[nodeid(pos(60,-1,1,186,1,186)),introduced_by(exists)])),couple(couple(integer,integer),integer),[nodeid(pos(56,-1,1,173,1,186))]),b(identifier(r),set(couple(couple(integer,integer),integer)),[nodeid(pos(61,-1,1,190,1,190)),introduced_by(exists)])),pred,[nodeid(pos(55,-1,1,173,1,190))]),b(member(b(identifier(y),integer,[nodeid(pos(63,-1,1,195,1,195)),introduced_by(exists)]),b(interval(b(integer(10),integer,[nodeid(pos(65,-1,1,199,1,200))]),b(integer(13),integer,[nodeid(pos(66,-1,1,205,1,206))])),set(integer),[nodeid(pos(64,-1,1,199,1,206))])),pred,[nodeid(pos(62,-1,1,195,1,206))])),pred,[]),b(less(b(identifier(z),integer,[nodeid(pos(68,-1,1,211,1,211)),introduced_by(exists)]),b(integer(11),integer,[nodeid(pos(69,-1,1,215,1,216))])),pred,[nodeid(pos(67,-1,1,211,1,216))])),pred,[])),pred,[used_ids([r])])),pred,[nodeid(pos(2,-1,1,1,1,218))])). |
| 2485 | | |
| 2486 | | % Eval Time: 0 ms (0 ms walltime) |
| 2487 | | % #(f,a,b,c,x,r).(((((a : INTEGER & b : INTEGER) & c : INTEGER) & x : INTEGER) & r : INTEGER) & ((((((((f : 11 .. 23 +-> 1 .. 10 & f = {a |-> 2,b |-> 3,c |-> 4}) & card({a,b,c}) = 3) & f(x) = r) & a > b) & b > c) & x /= a) & /* falsity */ x /= x) & r /= b)) |
| 2488 | | must_fail_clpfd_det(129,b(exists([b(identifier(f),set(couple(integer,integer)),[]),b(identifier(a),integer,[]),b(identifier(b),integer,[]),b(identifier(c),integer,[]),b(identifier(x),integer,[]),b(identifier(r),integer,[])],b(conjunct(b(conjunct(b(conjunct(b(conjunct(b(conjunct(b(conjunct(b(conjunct(b(conjunct(b(member(b(identifier(f),set(couple(integer,integer)),[nodeid(pos(11,-1,1,1,1,1))]),b(partial_function(b(interval(b(integer(11),integer,[nodeid(pos(14,-1,1,5,1,6))]),b(integer(23),integer,[nodeid(pos(15,-1,1,9,1,10))])),set(integer),[nodeid(pos(13,-1,1,5,1,10))]),b(interval(b(integer(1),integer,[nodeid(pos(17,-1,1,16,1,16))]),b(integer(10),integer,[nodeid(pos(18,-1,1,19,1,20))])),set(integer),[nodeid(pos(16,-1,1,16,1,20))])),set(set(couple(integer,integer))),[nodeid(pos(12,-1,1,5,1,20))])),pred,[nodeid(pos(10,-1,1,1,1,20))]),b(equal(b(identifier(f),set(couple(integer,integer)),[nodeid(pos(20,-1,1,24,1,24))]),b(set_extension([b(couple(b(identifier(a),integer,[nodeid(pos(23,-1,1,29,1,29))]),b(integer(2),integer,[nodeid(pos(24,-1,1,33,1,33))])),couple(integer,integer),[nodeid(pos(22,-1,1,29,1,33))]),b(couple(b(identifier(b),integer,[nodeid(pos(26,-1,1,36,1,36))]),b(integer(3),integer,[nodeid(pos(27,-1,1,40,1,40))])),couple(integer,integer),[nodeid(pos(25,-1,1,36,1,40))]),b(couple(b(identifier(c),integer,[nodeid(pos(29,-1,1,43,1,43))]),b(integer(4),integer,[nodeid(pos(30,-1,1,47,1,47))])),couple(integer,integer),[nodeid(pos(28,-1,1,43,1,47))])]),set(couple(integer,integer)),[nodeid(pos(21,-1,1,28,1,48))])),pred,[nodeid(pos(19,-1,1,24,1,48))])),pred,[nodeid(pos(9,-1,1,1,1,48))]),b(equal(b(card(b(set_extension([b(identifier(a),integer,[nodeid(pos(34,-1,1,58,1,58))]),b(identifier(b),integer,[nodeid(pos(35,-1,1,60,1,60))]),b(identifier(c),integer,[nodeid(pos(36,-1,1,62,1,62))])]),set(integer),[nodeid(pos(33,-1,1,57,1,63))])),integer,[nodeid(pos(32,-1,1,52,1,64))]),b(integer(3),integer,[nodeid(pos(37,-1,1,66,1,66))])),pred,[nodeid(pos(31,-1,1,52,1,66))])),pred,[nodeid(pos(8,-1,1,1,1,66))]),b(equal(b(function(b(identifier(f),set(couple(integer,integer)),[nodeid(pos(40,-1,1,70,1,70))]),b(identifier(x),integer,[nodeid(pos(41,-1,1,72,1,72))])),integer,[contains_wd_condition,nodeid(pos(39,-1,1,70,1,73))]),b(identifier(r),integer,[nodeid(pos(42,-1,1,75,1,75))])),pred,[contains_wd_condition,nodeid(pos(38,-1,1,70,1,75))])),pred,[contains_wd_condition,nodeid(pos(7,-1,1,1,1,75))]),b(greater(b(identifier(a),integer,[nodeid(pos(44,-1,1,79,1,79))]),b(identifier(b),integer,[nodeid(pos(45,-1,1,81,1,81))])),pred,[nodeid(pos(43,-1,1,79,1,81))])),pred,[contains_wd_condition,nodeid(pos(6,-1,1,1,1,81))]),b(greater(b(identifier(b),integer,[nodeid(pos(47,-1,1,85,1,85))]),b(identifier(c),integer,[nodeid(pos(48,-1,1,87,1,87))])),pred,[nodeid(pos(46,-1,1,85,1,87))])),pred,[contains_wd_condition,nodeid(pos(5,-1,1,1,1,87))]),b(not_equal(b(identifier(x),integer,[nodeid(pos(50,-1,1,91,1,91))]),b(identifier(a),integer,[nodeid(pos(51,-1,1,94,1,94))])),pred,[nodeid(pos(49,-1,1,91,1,94))])),pred,[contains_wd_condition,nodeid(pos(4,-1,1,1,1,94))]),b(falsity,pred,[was(not_equal(b(identifier(x),integer,[nodeid(pos(53,-1,1,98,1,98))]),b(identifier(x),integer,[nodeid(pos(54,-1,1,101,1,101))]))),nodeid(pos(52,-1,1,98,1,101))])),pred,[contains_wd_condition,nodeid(pos(3,-1,1,1,1,101))]),b(not_equal(b(identifier(r),integer,[nodeid(pos(56,-1,1,105,1,105))]),b(identifier(b),integer,[nodeid(pos(57,-1,1,108,1,108))])),pred,[nodeid(pos(55,-1,1,105,1,108))])),pred,[contains_wd_condition,nodeid(pos(2,-1,1,1,1,108))])),pred,[used_ids([]),contains_wd_condition])). |
| 2489 | | |
| 2490 | | % Eval Time: 10 ms (0 ms walltime) |
| 2491 | | % #(f,aa,x,y,r,v).((f : POW(INTEGER * (INTEGER * INTEGER)) & r : INTEGER * INTEGER) & ((((((f = {aa |-> (1 |-> aa),x |-> (2 |-> x + 1),y |-> (3 |-> y + 1)} & x : 1 .. 2) & aa : 0 .. 1) & y : 3 .. 5) & r = f(v)) & v : 2 .. 4) & prj1(INTEGER,INTEGER)(r) /: 2 .. 3)) |
| 2492 | | % REQUIRES TRY_FIND_ABORT=FALSE |
| 2493 | | must_fail_clpfd_det(130,b(exists([b(identifier(f),set(couple(integer,couple(integer,integer))),[]),b(identifier(aa),integer,[]),b(identifier(x),integer,[]),b(identifier(y),integer,[]),b(identifier(r),couple(integer,integer),[]),b(identifier(v),integer,[])],b(conjunct(b(conjunct(b(conjunct(b(conjunct(b(conjunct(b(conjunct(b(equal(b(identifier(f),set(couple(integer,couple(integer,integer))),[nodeid(pos(9,-1,1,1,1,1))]),b(set_extension([b(couple(b(identifier(aa),integer,[nodeid(pos(12,-1,1,6,1,7))]),b(couple(b(integer(1),integer,[nodeid(pos(14,-1,1,12,1,12))]),b(identifier(aa),integer,[nodeid(pos(15,-1,1,14,1,15))])),couple(integer,integer),[nodeid(pos(13,-1,1,11,1,16))])),couple(integer,couple(integer,integer)),[nodeid(pos(11,-1,1,6,1,16))]),b(couple(b(identifier(x),integer,[nodeid(pos(17,-1,1,19,1,19))]),b(couple(b(integer(2),integer,[nodeid(pos(19,-1,1,24,1,24))]),b(add(b(identifier(x),integer,[nodeid(pos(21,-1,1,26,1,26))]),b(integer(1),integer,[nodeid(pos(22,-1,1,28,1,28))])),integer,[nodeid(pos(20,-1,1,26,1,28))])),couple(integer,integer),[nodeid(pos(18,-1,1,23,1,29))])),couple(integer,couple(integer,integer)),[nodeid(pos(16,-1,1,19,1,29))]),b(couple(b(identifier(y),integer,[nodeid(pos(24,-1,1,32,1,32))]),b(couple(b(integer(3),integer,[nodeid(pos(26,-1,1,37,1,37))]),b(add(b(identifier(y),integer,[nodeid(pos(28,-1,1,39,1,39))]),b(integer(1),integer,[nodeid(pos(29,-1,1,41,1,41))])),integer,[nodeid(pos(27,-1,1,39,1,41))])),couple(integer,integer),[nodeid(pos(25,-1,1,36,1,42))])),couple(integer,couple(integer,integer)),[nodeid(pos(23,-1,1,32,1,42))])]),set(couple(integer,couple(integer,integer))),[nodeid(pos(10,-1,1,5,1,43))])),pred,[nodeid(pos(8,-1,1,1,1,43))]),b(member(b(identifier(x),integer,[nodeid(pos(31,-1,1,47,1,47))]),b(interval(b(integer(1),integer,[nodeid(pos(33,-1,1,49,1,49))]),b(integer(2),integer,[nodeid(pos(34,-1,1,52,1,52))])),set(integer),[nodeid(pos(32,-1,1,49,1,52))])),pred,[nodeid(pos(30,-1,1,47,1,52))])),pred,[nodeid(pos(7,-1,1,1,1,52))]),b(member(b(identifier(aa),integer,[nodeid(pos(36,-1,1,56,1,57))]),b(interval(b(integer(0),integer,[nodeid(pos(38,-1,1,59,1,59))]),b(integer(1),integer,[nodeid(pos(39,-1,1,62,1,62))])),set(integer),[nodeid(pos(37,-1,1,59,1,62))])),pred,[nodeid(pos(35,-1,1,56,1,62))])),pred,[nodeid(pos(6,-1,1,1,1,62))]),b(member(b(identifier(y),integer,[nodeid(pos(41,-1,1,66,1,66))]),b(interval(b(integer(3),integer,[nodeid(pos(43,-1,1,68,1,68))]),b(integer(5),integer,[nodeid(pos(44,-1,1,71,1,71))])),set(integer),[nodeid(pos(42,-1,1,68,1,71))])),pred,[nodeid(pos(40,-1,1,66,1,71))])),pred,[nodeid(pos(5,-1,1,1,1,71))]),b(equal(b(identifier(r),couple(integer,integer),[nodeid(pos(46,-1,1,75,1,75))]),b(function(b(identifier(f),set(couple(integer,couple(integer,integer))),[nodeid(pos(48,-1,1,79,1,79))]),b(identifier(v),integer,[nodeid(pos(49,-1,1,81,1,81))])),couple(integer,integer),[contains_wd_condition,nodeid(pos(47,-1,1,79,1,82))])),pred,[contains_wd_condition,nodeid(pos(45,-1,1,75,1,82))])),pred,[contains_wd_condition,nodeid(pos(4,-1,1,1,1,82))]),b(member(b(identifier(v),integer,[nodeid(pos(51,-1,1,86,1,86))]),b(interval(b(integer(2),integer,[nodeid(pos(53,-1,1,88,1,88))]),b(integer(4),integer,[nodeid(pos(54,-1,1,91,1,91))])),set(integer),[nodeid(pos(52,-1,1,88,1,91))])),pred,[nodeid(pos(50,-1,1,86,1,91))])),pred,[contains_wd_condition,nodeid(pos(3,-1,1,1,1,91))]),b(not_member(b(first_of_pair(b(identifier(r),couple(integer,integer),[nodeid(pos(60,-1,1,117,1,117))])),integer,[nodeid(pos(56,-1,1,95,1,118))]),b(interval(b(integer(2),integer,[nodeid(pos(62,-1,1,123,1,123))]),b(integer(3),integer,[nodeid(pos(63,-1,1,126,1,126))])),set(integer),[nodeid(pos(61,-1,1,123,1,126))])),pred,[nodeid(pos(55,-1,1,95,1,126))])),pred,[contains_wd_condition,nodeid(pos(2,-1,1,1,1,126))])),pred,[used_ids([]),contains_wd_condition])). |
| 2494 | | |
| 2495 | | % Eval Time: 0 ms (0 ms walltime) |
| 2496 | | % #(f,aa,x,y,r,v).((f : POW(INTEGER * struct(p1:INTEGER,p2:INTEGER)) & r : struct(p1:INTEGER,p2:INTEGER)) & ((((((f = {aa |-> rec(p1:1,p2:aa),x |-> rec(p1:2,p2:x + 1),y |-> rec(p1:3,p2:y + 1)} & x : 1 .. 2) & aa : 0 .. 1) & y : 3 .. 5) & r = f(v)) & v : 2 .. 4) & r'p1 /: 2 .. 3)) |
| 2497 | | % REQUIRES TRY_FIND_ABORT=FALSE |
| 2498 | | must_fail_clpfd_det(131,b(exists([b(identifier(f),set(couple(integer,record([field(p1,integer),field(p2,integer)]))),[]),b(identifier(aa),integer,[]),b(identifier(x),integer,[]),b(identifier(y),integer,[]),b(identifier(r),record([field(p1,integer),field(p2,integer)]),[]),b(identifier(v),integer,[])],b(conjunct(b(conjunct(b(conjunct(b(conjunct(b(conjunct(b(conjunct(b(equal(b(identifier(f),set(couple(integer,record([field(p1,integer),field(p2,integer)]))),[nodeid(pos(9,-1,1,1,1,1))]),b(set_extension([b(couple(b(identifier(aa),integer,[nodeid(pos(12,-1,1,6,1,7))]),b(rec([field(p1,b(integer(1),integer,[nodeid(pos(16,-1,1,18,1,18))])),field(p2,b(identifier(aa),integer,[nodeid(pos(19,-1,1,23,1,24))]))]),record([field(p1,integer),field(p2,integer)]),[nodeid(pos(13,-1,1,11,1,25))])),couple(integer,record([field(p1,integer),field(p2,integer)])),[nodeid(pos(11,-1,1,6,1,25))]),b(couple(b(identifier(x),integer,[nodeid(pos(21,-1,1,28,1,28))]),b(rec([field(p1,b(integer(2),integer,[nodeid(pos(25,-1,1,39,1,39))])),field(p2,b(add(b(identifier(x),integer,[nodeid(pos(29,-1,1,44,1,44))]),b(integer(1),integer,[nodeid(pos(30,-1,1,46,1,46))])),integer,[nodeid(pos(28,-1,1,44,1,46))]))]),record([field(p1,integer),field(p2,integer)]),[nodeid(pos(22,-1,1,32,1,47))])),couple(integer,record([field(p1,integer),field(p2,integer)])),[nodeid(pos(20,-1,1,28,1,47))]),b(couple(b(identifier(y),integer,[nodeid(pos(32,-1,1,50,1,50))]),b(rec([field(p1,b(integer(3),integer,[nodeid(pos(36,-1,1,61,1,61))])),field(p2,b(add(b(identifier(y),integer,[nodeid(pos(40,-1,1,66,1,66))]),b(integer(1),integer,[nodeid(pos(41,-1,1,68,1,68))])),integer,[nodeid(pos(39,-1,1,66,1,68))]))]),record([field(p1,integer),field(p2,integer)]),[nodeid(pos(33,-1,1,54,1,69))])),couple(integer,record([field(p1,integer),field(p2,integer)])),[nodeid(pos(31,-1,1,50,1,69))])]),set(couple(integer,record([field(p1,integer),field(p2,integer)]))),[nodeid(pos(10,-1,1,5,1,70))])),pred,[nodeid(pos(8,-1,1,1,1,70))]),b(member(b(identifier(x),integer,[nodeid(pos(43,-1,1,74,1,74))]),b(interval(b(integer(1),integer,[nodeid(pos(45,-1,1,76,1,76))]),b(integer(2),integer,[nodeid(pos(46,-1,1,79,1,79))])),set(integer),[nodeid(pos(44,-1,1,76,1,79))])),pred,[nodeid(pos(42,-1,1,74,1,79))])),pred,[nodeid(pos(7,-1,1,1,1,79))]),b(member(b(identifier(aa),integer,[nodeid(pos(48,-1,1,83,1,84))]),b(interval(b(integer(0),integer,[nodeid(pos(50,-1,1,86,1,86))]),b(integer(1),integer,[nodeid(pos(51,-1,1,89,1,89))])),set(integer),[nodeid(pos(49,-1,1,86,1,89))])),pred,[nodeid(pos(47,-1,1,83,1,89))])),pred,[nodeid(pos(6,-1,1,1,1,89))]),b(member(b(identifier(y),integer,[nodeid(pos(53,-1,1,93,1,93))]),b(interval(b(integer(3),integer,[nodeid(pos(55,-1,1,95,1,95))]),b(integer(5),integer,[nodeid(pos(56,-1,1,98,1,98))])),set(integer),[nodeid(pos(54,-1,1,95,1,98))])),pred,[nodeid(pos(52,-1,1,93,1,98))])),pred,[nodeid(pos(5,-1,1,1,1,98))]),b(equal(b(identifier(r),record([field(p1,integer),field(p2,integer)]),[nodeid(pos(58,-1,1,102,1,102))]),b(function(b(identifier(f),set(couple(integer,record([field(p1,integer),field(p2,integer)]))),[nodeid(pos(60,-1,1,106,1,106))]),b(identifier(v),integer,[nodeid(pos(61,-1,1,108,1,108))])),record([field(p1,integer),field(p2,integer)]),[contains_wd_condition,nodeid(pos(59,-1,1,106,1,109))])),pred,[contains_wd_condition,nodeid(pos(57,-1,1,102,1,109))])),pred,[contains_wd_condition,nodeid(pos(4,-1,1,1,1,109))]),b(member(b(identifier(v),integer,[nodeid(pos(63,-1,1,113,1,113))]),b(interval(b(integer(2),integer,[nodeid(pos(65,-1,1,115,1,115))]),b(integer(4),integer,[nodeid(pos(66,-1,1,118,1,118))])),set(integer),[nodeid(pos(64,-1,1,115,1,118))])),pred,[nodeid(pos(62,-1,1,113,1,118))])),pred,[contains_wd_condition,nodeid(pos(3,-1,1,1,1,118))]),b(not_member(b(record_field(b(identifier(r),record([field(p1,integer),field(p2,integer)]),[nodeid(pos(69,-1,1,122,1,122))]),p1),integer,[nodeid(pos(68,-1,1,122,1,125))]),b(interval(b(integer(2),integer,[nodeid(pos(72,-1,1,130,1,130))]),b(integer(3),integer,[nodeid(pos(73,-1,1,133,1,133))])),set(integer),[nodeid(pos(71,-1,1,130,1,133))])),pred,[nodeid(pos(67,-1,1,122,1,133))])),pred,[contains_wd_condition,nodeid(pos(2,-1,1,1,1,133))])),pred,[used_ids([]),contains_wd_condition])). |
| 2499 | | |
| 2500 | | % Eval Time: 0 ms (0 ms walltime) |
| 2501 | | % #(x,a).((x = (IF a < 10 THEN 0 ELSE 5 END ) & x : 6 .. 10) & a : 1 .. 23) |
| 2502 | | must_fail_clpfd_det(132,b(exists([b(identifier(x),integer,[]),b(identifier(a),integer,[])],b(conjunct(b(conjunct(b(equal(b(identifier(x),integer,[nodeid(pos(5,-1,1,1,1,1))]),b(if_then_else(b(less(b(identifier(a),integer,[nodeid(pos(8,-1,1,8,1,8))]),b(integer(10),integer,[nodeid(pos(9,-1,1,10,1,11))])),pred,[nodeid(pos(7,-1,1,8,1,11))]),b(integer(0),integer,[nodeid(pos(10,-1,1,18,1,18))]),b(integer(5),integer,[nodeid(pos(11,-1,1,25,1,25))])),integer,[nodeid(pos(6,-1,1,5,1,29))])),pred,[nodeid(pos(4,-1,1,1,1,29))]),b(member(b(identifier(x),integer,[nodeid(pos(13,-1,1,33,1,33))]),b(interval(b(integer(6),integer,[nodeid(pos(15,-1,1,35,1,35))]),b(integer(10),integer,[nodeid(pos(16,-1,1,38,1,39))])),set(integer),[nodeid(pos(14,-1,1,35,1,39))])),pred,[nodeid(pos(12,-1,1,33,1,39))])),pred,[nodeid(pos(3,-1,1,1,1,39))]),b(member(b(identifier(a),integer,[nodeid(pos(18,-1,1,43,1,43))]),b(interval(b(integer(1),integer,[nodeid(pos(20,-1,1,45,1,45))]),b(integer(23),integer,[nodeid(pos(21,-1,1,48,1,49))])),set(integer),[nodeid(pos(19,-1,1,45,1,49))])),pred,[nodeid(pos(17,-1,1,43,1,49))])),pred,[nodeid(pos(2,-1,1,1,1,49))])),pred,[used_ids([])])). |
| 2503 | | |
| 2504 | | % Eval Time: 0 ms (0 ms walltime) |
| 2505 | | % #(x,bb).((x : INTEGER & bb : BOOL) & (((IF x < 10 THEN TRUE ELSE bb END ) = FALSE & x < 20) & (IF x < 12 THEN FALSE ELSE bb END ) = TRUE)) |
| 2506 | | must_fail_clpfd_det(133,b(exists([b(identifier(x),integer,[]),b(identifier(bb),boolean,[])],b(conjunct(b(conjunct(b(equal(b(if_then_else(b(less(b(identifier(x),integer,[nodeid(pos(7,-1,1,4,1,4))]),b(integer(10),integer,[nodeid(pos(8,-1,1,6,1,7))])),pred,[nodeid(pos(6,-1,1,4,1,7))]),b(boolean_true,boolean,[nodeid(pos(9,-1,1,14,1,17))]),b(identifier(bb),boolean,[nodeid(pos(10,-1,1,24,1,25))])),boolean,[nodeid(pos(5,-1,1,1,1,29))]),b(boolean_false,boolean,[nodeid(pos(11,-1,1,33,1,37))])),pred,[nodeid(pos(4,-1,1,1,1,37))]),b(less(b(identifier(x),integer,[nodeid(pos(13,-1,1,41,1,41))]),b(integer(20),integer,[nodeid(pos(14,-1,1,43,1,44))])),pred,[nodeid(pos(12,-1,1,41,1,44))])),pred,[nodeid(pos(3,-1,1,1,1,44))]),b(equal(b(if_then_else(b(less(b(identifier(x),integer,[nodeid(pos(18,-1,1,51,1,51))]),b(integer(12),integer,[nodeid(pos(19,-1,1,53,1,54))])),pred,[nodeid(pos(17,-1,1,51,1,54))]),b(boolean_false,boolean,[nodeid(pos(20,-1,1,61,1,65))]),b(identifier(bb),boolean,[nodeid(pos(21,-1,1,72,1,73))])),boolean,[nodeid(pos(16,-1,1,48,1,77))]),b(boolean_true,boolean,[nodeid(pos(22,-1,1,81,1,84))])),pred,[nodeid(pos(15,-1,1,48,1,84))])),pred,[nodeid(pos(2,-1,1,1,1,84))])),pred,[used_ids([])])). |
| 2507 | | |
| 2508 | | :- endif. |
| 2509 | | |
| 2510 | | test_enabled(130) :- get_preference(find_abort_values,false). |
| 2511 | | test_enabled(131) :- get_preference(find_abort_values,false). |