Skip to content

Commit

Permalink
ensure_individuals2
Browse files Browse the repository at this point in the history
  • Loading branch information
TeamSPoon committed Apr 28, 2023
1 parent a162376 commit e84acc3
Show file tree
Hide file tree
Showing 3 changed files with 90 additions and 59 deletions.
58 changes: 35 additions & 23 deletions packs_sys/logicmoo_agi/prolog/kaggle_arc/kaggle_arc_howdiff.pl
Original file line number Diff line number Diff line change
Expand Up @@ -206,7 +206,6 @@
obj_grp_atoms(IO,A,[A,PA|Atoms]):- obj_grp_atomslist(IO,A,PA,Atoms).



obj_grp_atomslist(IO,A,PA,Atoms):- \+ \+ see_object_atomslist(IO,A,PA,Atoms), !, see_object_atomslist(IO,A,PA,Atoms).
obj_grp_atomslist(IO,A,PA,Atoms):-
obj_grp_atoms_deep(A,PA,Atoms),
Expand Down Expand Up @@ -335,45 +334,58 @@
diff_groups1(A2,B2,DD).

obj_atoms(PA,PAP):- PA==[],!,PAP=[].
obj_atoms(PA,PAP):- is_grid(PA),globalpoints(PA,GP),!,subobj_atoms(GP,PAP).
obj_atoms(PA,PAP):- must_det_ll((nonvar(PA))),
indv_props_list(PA,MF),
must_det((subobj_atoms(MF,PAP),PAP\==[])),!.
obj_atoms(PA,PAP):- subobj_atoms(PA,PAP),!.

subobj_atoms(PA,PAP):- PA==[],!,PAP=[].
subobj_atoms(PA,PAP):- is_grid(PA),globalpoints(PA,GP),!,subobj_atoms(GP,PAP).
subobj_atoms(PA,PAP):- must_det_ll((nonvar(PA),flatten([PA],M),
findall(E,(member(SE,M),sub_obj_atom(E,SE)),PAP))),!.

never_matom(localpoints(_)).
never_matom(shape_rep(grav,_)).
obj_atoms(PA,PAP):- must_det_ll((nonvar(PA))),is_grid(PA),globalpoints(PA,GP),!,subobj_atoms(points(GP),PAP).
obj_atoms(PA,PAP):- sub_term(E,PA),compound(E),E=obj_atoms(UU),!,subobj_atoms(UU,PAP).
obj_atoms(PA,PAP):- is_list(PA),maplist(obj_atoms,PA,LPA),append(LPA,PAP),!.
obj_atoms(PA,PAP):- is_object(PA),must_det_ll((indv_props_list(PA,MF),subobj_atoms(MF,PAP),PAP\==[])).
obj_atoms(PA,PAP):- into_obj_props1(PA,MF),must_subobj_atoms(MF,PAP),!.
obj_atoms(PA,PAP):- must_subobj_atoms(PA,PAP),!.

%never_matom(localpoints(_)).
%never_matom(shape_rep(grav,_)).
%never_matom(pg(_OG,_,_,_)).
never_matom(giz(_)).
never_matom(globalpoints(_)).
%never_matom(giz(_)).
never_matom(edit(_)).
%never_matom(globalpoints(_)).
verbatum_matom(pg(_,_,_,_)).
relaxed_matom(pg(_,A,B,C),pg(r,A,B,C)).
relaxed_matom(link(A,r),link(A,r)).

must_subobj_atoms(PA,PAP):- must_det_l((subobj_atoms(PA,PAP),PAP\==[])),!.

subobj_atoms(PA,PAP):- PA==[],!,PAP=[].
subobj_atoms(PA,PAP):-
must_det_ll((nonvar(PA),flatten([PA],M),findall(E,(member(SE,M),sub_obj_atom(E,SE)),PAPF))),!,
flatten(PAPF,PAP).

sub_obj_atom(_,E):- var(E),!,fail.
%sub_obj_atom(M,M):- attvar(M),!.
sub_obj_atom(E,E):- \+ compound(E),!.
%sub_obj_atom(E,shape_rep(grav,CP)):- !, is_list(CP),member(E,CP).
sub_obj_atom(_,E):- never_matom(E),!,fail.
sub_obj_atom(E,E):- verbatum_matom(E).
sub_obj_atom(E,L):- is_list(L),!,member(EM,L),sub_obj_atom(E,EM).

sub_obj_atom(R,E):- relaxed_matom(E,R),E\=@=R.
sub_obj_atom(NO,M):- remove_oids(M,MM,EL),EL\==[], !,sub_obj_atom(NO,MM).
sub_obj_atom(M,pg(OG,H,L,_)):- !, ((M = (L/H));(M = (L/OG))).
%sub_obj_atom(E,shape_rep(grav,CP)):- !, is_list(CP),member(E,CP).
sub_obj_atom(M,M).
sub_obj_atom(M,pg(T,P1,R,I)):- !, ((M = extra(R,I,T));(M = extra(R,T,P1)),(M = extra(R,I))). %, \+ (arg(_,M,V),var(V)).

sub_obj_atom(M,M):- arg(_,M,N), number(N),!.
sub_obj_atom(M,M):- arg(_,M,N), is_color(N),!.
sub_obj_atom(M,M):- functor(link,M,_),!.

%sub_obj_atom(M,M):- attvar(M),!.
%sub_obj_atom(A,A).
sub_obj_atom(E,E).
%sub_obj_atom(globalpoints(E),globalpoints(CP)):- !, my_maplist(arg(2),CP,EL),!, (member(E,EL); (E=EL)).
%sub_obj_atom(_,M):- never_matom(M),!,fail.
%sub_obj_atom(A,M):- M = localpoints(_),!,A=M.
%sub_obj_atom(iz(A),iz(A)):-!. % sub_obj_atom(A,M).
sub_obj_atom(A,M):- M=..[F,List],is_list(List),length(List,Len),!,
(A=len(F,Len) ; (interesting_sub_atoms(List,E),A=..[F,E])).

sub_obj_atom(M,M):- functor(link,M,_),!.
sub_obj_atom(E,M):- interesting_sub_atoms(M,E).
%sub_obj_atom(S,M):- special_properties(M,L),!,member(S,L).

interesting_sub_atoms(PA,PAP):- is_grid(PA),globalpoints(PA,GP),!,sub_obj_atom(points(GP),PAP).

interesting_sub_atoms(List,E) :- is_list(List),!,member(EM,List),interesting_sub_atoms(EM,E).
interesting_sub_atoms(E,_):- var(E),!,fail.
interesting_sub_atoms(E,E) :- atomic(E),!.
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -1409,9 +1409,9 @@

add_prior_info_1(_Objs,_ObjsLen,_Common,_VersionsByCount,PropList,PropList).

extra_rank_prop(ObjsLen,Name,N1,pg(_,Name,rankLS,largest)):- ObjsLen==N1,!.
extra_rank_prop(_,Name,1,pg(_,Name,rankLS,smallest)):-!.
extra_rank_prop(_,Name,_,pg(_,Name,rankLS,mediumest)).
extra_rank_prop(ObjsLen,Name,N1,pg(ObjsLen,Name,rankLS,largest)):- ObjsLen==N1,!.
extra_rank_prop(ObjsLen,Name,1,pg(ObjsLen,Name,rankLS,smallest)):-!.
extra_rank_prop(ObjsLen,Name,_,pg(ObjsLen,Name,rankLS,mediumest)).

use_simulars(_):- fail.
use_rank(mass(_)).
Expand Down
85 changes: 52 additions & 33 deletions packs_sys/logicmoo_agi/prolog/kaggle_arc/kaggle_arc_uniqueness.pl
Original file line number Diff line number Diff line change
Expand Up @@ -185,6 +185,7 @@
ensure_individuals1(TestID):- show_prop_counts(TestID), my_assertion(has_individuals(TestID)),!.



has_propcounts(TestID):-
forall(current_example_nums(TestID,ExampleNum),
( \+ \+ (propcounts(TestID, ExampleNum, InOut, count, _, _), sub_var(in,InOut)),
Expand Down Expand Up @@ -358,9 +359,11 @@
print_object_dependancy(TestID),
print_scene_change_rules(TestID),
print_ss(wqs(expected_answer(ExampleNum)),Objs,Expected),
%wots(SS,solve_obj_group(VM,TestID,ExampleNum,ROptions,Objs,ObjsO)),
enter_solve_obj(VM,TestID,ExampleNum,ROptions,Objs,ObjsO),
dash_chars)),!,

once(enter_solve_obj(VM,TestID,ExampleNum,ROptions,Objs,ObjsO)),

must_det_ll((
dash_chars,
print_ss(wqs(solve_via_scene_change_rules(ExampleNum)),Objs,ObjsO),
dash_chars,
Expand Down Expand Up @@ -485,39 +488,48 @@
ObjsO \==[],!.



solve_obj_group(VM,TestID,Ctx,Objs,ObjsO):-
io_to_cntx(IN_OUT,Ctx),
Rule = implies(PSame,edit(P)),
findall(Rule,is_accompany_changed_verified(TestID,IN_OUT,P,PSame), Rules),
apply_rules_to_objects(Strategy,Rules,Objs,Todo),
pp(used_Strategy(Strategy)),
once((maplist(run_todo_output(VM),Todo,ObjsM),flatten_objects(ObjsM,ObjsO))),ObjsO\==[],!.


two_way_mapping(Ways,Obj,Objs,Rules,Rule,RulesRest):-
once((find_prox_mappings(Obj,obj_to_rule,Rules,[Rule|RulesRest]),
find_prox_mappings(Rule,rule_to_objs,Objs,[PickedObj|_]))),
((PickedObj == Obj)-> Ways = two_ways ; Ways = one_way).

apply_rules_to_objects(_,_,[],[]):-!.
apply_rules_to_objects(_,[],_,[]):-!.
apply_rules_to_objects(one_to_one,Rules,Objs,[apply(Rule,Obj)|More]):-
find_prox_mappings(Rule,rule_to_objs,Objs,[PickedObj|_ObjsRest]))),
((PickedObj == Obj)-> Ways = two_ways ; Ways = one_way),
write_atoms_info(Ways,PickedObj),
write_atoms_info(paired2,Rule),
%maplist(write_atoms_info(leftover1),RulesRest),
%maplist(write_atoms_info(leftover2),ObjsRest),
!.

write_atoms_info(N,E):- obj_atoms(E,Atoms),!,%sort(Atoms,AE),
nl,writeln(N=Atoms).

apply_rules_to_objects(_,_,_,[],[]):-!.
apply_rules_to_objects(_,_,[],_,[]):-!.

apply_rules_to_objects(Ways,one_to_one,Rules,Objs,[apply(Rule,Obj)|More]):-
select(Obj,Objs,ObjsRest),
two_way_mapping(_Ways,Obj,Objs,Rules,Rule,RulesRest),
apply_rules_to_objects(one_to_one,RulesRest,ObjsRest,More).

apply_rules_to_objects(each_object,Rules,Objs,[apply(Rule,Obj)|More]):-
two_way_mapping(Ways,Obj,Objs,Rules,Rule,RulesRest),
apply_rules_to_objects(Ways,one_to_one,RulesRest,ObjsRest,More).


apply_rules_to_objects(Ways,each_object,Rules,Objs,[apply(Rule,Obj)|More]):-
member(Rule,Rules),
two_way_mapping(_Ways,Rule,Rules,Objs,Obj,RestObjs),
apply_rules_to_objects(each_object,Rules,RestObjs,More).
two_way_mapping(Ways,Rule,Rules,Objs,Obj,ObjsRest),
apply_rules_to_objects(Ways,each_object,Rules,ObjsRest,More).

apply_rules_to_objects(each_rule,Rules,Objs,[apply(Rule,Obj)|More]):-
apply_rules_to_objects(Ways,each_rule,Rules,Objs,[apply(Rule,Obj)|More]):-
member(Obj,Objs),
two_way_mapping(_Ways,Obj,Objs,Rules,Rule,RulesRest),
apply_rules_to_objects(each_rule,RulesRest,Objs,More).
two_way_mapping(Ways,Obj,Objs,Rules,Rule,RulesRest),
apply_rules_to_objects(Ways,each_rule,RulesRest,Objs,More).


solve_obj_group(VM,TestID,_ExampleNum,_ROptions,Ctx,Objs,ObjsO):-
io_to_cntx(IN_OUT,Ctx),
Rule = implies(obj_atoms(PSame),edit(P)),
findall(Rule,is_accompany_changed_verified(TestID,IN_OUT,P,PSame), Rules),

member(Ways-Strategy,[two_way-one_to_one,two_way-one_to_one,_-_]),
apply_rules_to_objects(Ways,Strategy,Rules,Objs,Todo),
pp(used_Strategy(Ways-Strategy)),
once((maplist(run_todo_output(VM),Todo,ObjsM),flatten_objects(ObjsM,ObjsO))),ObjsO\==[],!.

solve_obj_group(_VM,TestID,_ExampleNum,Ctx,_ROptions,Objs,ObjsO):-
must_det_ll((
Expand Down Expand Up @@ -891,7 +903,7 @@

prop_can1_map(TestID,IN_OUT,P,[C]):-
ensure_props_change(TestID,IN_OUT,P),
map_pairs_info_io(TestID,ExampleNum,Ctx,Step,TypeO,_A,O,USame,Can,UPB2),member(P,UPB2),ok_deduce(P),
map_pairs_info_io(TestID,_ExampleNum,_Ctx,_Step,_TypeO,_A,_O,_USame,Can,UPB2),member(P,UPB2),ok_deduce(P),
member(C,Can),other_val(P,C).


Expand Down Expand Up @@ -1100,6 +1112,7 @@
%pp_ilp(grp(Info,InL,OutL)),!,
assertz_new(arc_cache:map_pairs(TestID,ExampleNum,Ctx,Info,InL,OutL)),
assertz_new(arc_cache:prop_dep(TestID,ExampleNum,Ctx,Info,InL,OutL,USame,InFlatProps,OutFlatProps)),!.
assert_map_pairs(_TestID,_ExampleNum,_Ctx,call(Rule)):-!,must_det_ll(Rule),!.

% print the object dependencies for this test
% =============================================================
Expand All @@ -1109,10 +1122,11 @@
( dash_chars,forall(arc_cache:map_group(TestID,_,_IN_OUT,Group),
once(((dash_chars,dash_chars,pp_ilp(Group),dash_chars,dash_chars)))))),
dash_chars,*/
findall_vset(grp(Info,Pre,Post),arc_cache:map_pairs(TestID,_,_IN_OUT2,Info,Pre,Post),Set),
findall_vset(grp(Info,Pre,Post),arc_cache:map_pairs(TestID,_,_IN_OUT2,Info,Pre,Post),Set1),
maplist(pp_ilp,Set1),
dash_chars,dash_chars,
findall_vset(grp(Info,Pre,Post),pair_obj_info(TestID,_,_,Info,Pre,Post),Set),
maplist(pp_ilp,Set),
findall_vset(grp(Info,Pre,Post),pair_obj_info(TestID,_,_,Info,Pre,Post),Set2),
if_t(Set1 \=@= Set2, maplist(pp_ilp,Set2)),
dash_chars,dash_chars.


Expand Down Expand Up @@ -1322,11 +1336,16 @@
maybe_remove_bg(RHSObjs,RHSObjs1), \=@=(RHSObjs,RHSObjs1),!,
must_det_ll((calc_o_d_recursively(TestID,ExampleNum,IsSwapped,Step,Ctx,Prev,LHSObjs,RHSObjs1,RestLR))).

calc_o_d_recursively(TestID,ExampleNum,IsSwapped,Step,Ctx,Prev,LHSObjs,RHSObjs,RestLR):-
LHSObjs==[], RHSObjs == [], !,
Info = info(Step,IsSwapped,Ctx,leftover,TestID,ExampleNum),
append_LR([call(assert_test_property(TestID,ExampleNum,deps,perfect_balance(Info)))],Prev,RestLR).

calc_o_d_recursively(TestID,ExampleNum,IsSwapped,Step,Ctx,Prev,LHSObjs,RHSObjs,RestLR):-
Info = info(Step,IsSwapped,Ctx,leftover,TestID,ExampleNum),
RHSObjs==[], !, must_det_ll((maplist(into_delete(TestID,ExampleNum,IsSwapped,Step,Ctx,Prev,Info),
LHSObjs,Mappings),append_LR(Prev,Mappings,RestLR))).
RHSObjs==[], !,
must_det_ll((maplist(into_delete(TestID,ExampleNum,IsSwapped,Step,Ctx,Prev,Info),
LHSObjs,Mappings),append_LR(Prev,[call(assert_test_property(TestID,ExampleNum,deps,ignore_rest(Info))),Mappings],RestLR))).

calc_o_d_recursively(TestID,ExampleNum,IsSwapped,_Step,Ctx,Prev,LHSObjs,RHSObjs,RestLR):-
LHSObjs==[], !, must_det_ll((
Expand Down

0 comments on commit e84acc3

Please sign in to comment.