Skip to content

Commit

Permalink
removed undefined predicate warnings
Browse files Browse the repository at this point in the history
  • Loading branch information
TeamSPoon committed Apr 19, 2023
1 parent d65166d commit a43b8bd
Show file tree
Hide file tree
Showing 17 changed files with 340 additions and 218 deletions.
Original file line number Diff line number Diff line change
Expand Up @@ -10,7 +10,7 @@
uast,!,
setup_call_cleanup(open('arc-dsl/constants.py',read,In1,[]),read_python(In1),close(In1)),
!.
read_michod_test:- read_sols,read_dsl.
%read_michod_test:- read_sols,read_dsl.

uast:- uast_test.
uast_test:-setup_call_cleanup(open('arc-dsl/dsl.py.uast',read,In3,[]),read_uast_python(In3),close(In3)).
Expand Down
14 changes: 10 additions & 4 deletions packs_sys/logicmoo_agi/prolog/kaggle_arc/arc-dsl/solvers.pl
Original file line number Diff line number Diff line change
Expand Up @@ -34,6 +34,8 @@
fix_type_arg(When,Var:Type,Var,ensure_type(When,Var,Type)).
fix_type_arg(When,Name=Value,Value,ensure_val(When,Name,Value)).

flatten_code(A,B):- flatten(A,B),!.

translate_program(Prop,Merged):- is_list(Prop),
maplist(translate_call(on_enter),Prop,Call,TransIn0),flatten_code(TransIn0,TransIn1),list_to_set(TransIn1,TransIn),
maplist(translate_call(on_leave),Prop,Call,TransOut0),flatten_code(TransOut0,TransOut1),
Expand Down Expand Up @@ -72,24 +74,28 @@
translated_call_patterns([crop,I,TL,BR,O],crop(I,L,T,R,B,O)):- tl_br(TL,T,L),tl_br(BR,B,R).
translated_call_patterns([switch,N1,N2,O],swap_colors(C1,C2,fg,O)):- color_name(N1,C1),color_name(N2,C2).

tl_br(TL,T,L):- arg(1,TL,T),arg(2,TL,L),!.

:- dynamic(p_solve/3).

maybe_jit_one_test(TestID):-
clause(l_solve(TestID,IN,OUT),Program),
(clause(p_solve(TestID,IN,OUT), Body), % -> true;
(
translate_program(Program,Trans),
list_to_conjucts(Trans,Body),
list_to_conjuncts(Trans,Body),
assert_if_new(p_solve(TestID,IN,OUT):- Body),
pp(p_solve(TestID,IN,OUT):- Body))).

into_pygrid(IO,IO).

solve(N,IN,OUT):-
maybe_jit_one_test(N),
fix_testid(N,TestID),
fix_test_name(N,TestID),
forall(kaggle_arc(TestID,ExampleNum,I,O),
once((into_pygrid(I,IN),into_pygrid(O,TOUT))),
(once((into_pygrid(I,IN),into_pygrid(O,TOUT))),
ignore((p_solve(N,IN,OUT),
print_ss(TestID>ExampleNum,OUT,TOUT)))).
print_ss(TestID>ExampleNum,OUT,TOUT))))).

l_solve('67a3c6ac', IN, OUT) :-
[f(vmirror, IN:'Piece', OUT:'Piece')].
Expand Down
144 changes: 144 additions & 0 deletions packs_sys/logicmoo_agi/prolog/kaggle_arc/kaggle_arc.unused
Original file line number Diff line number Diff line change
Expand Up @@ -483,3 +483,147 @@ all_ogs(IO,In,Out,Set):- %member(R,[strict,loose]),
*/
%maybe_ogs(R,In,Out):- find_ogs(X,Y,In,Out)*->R=strict;(ogs_11(X,Y,In,Out),R=loose).

:- arc_history(test_what_unique).
test_what_unique:- get_current_test(TestID), what_unique(TestID,n=0,n>10).


:- arc_history((get_current_test(TestID),what_unique(TestID,n=0,n>10))).
get_new_uniq_dict(Dict):-
ArgDict = _{sharedWith:_SharedWith,object:_Obj,trait:_Trait,groupSizeMask:_GroupSizeMask,
actualGroupSize:_ActualGroupSize,countMask:_CountMask,
actualCount:_ActualCount,otherL:_OtherL,slistL:_ListL,
setL:_SetL,others:_TraitCountSets,how:_How,group:_Group},
(var(Dict)->Dict=ArgDict ; Dict >:< ArgDict).

is_fti_step(most_unique).
most_unique(symmetry_type,VM):-
List = VM.objs,
last(List,Obj),
set(VM.solution)= Obj.




what_unique:- get_current_test(TestID),what_unique(TestID).

what_unique(TestID):-
get_vm(VM),
((VM.id \= (TestID > _ * _)), ndividuator),
get_vm(VM2), explain_uniqueness(VM2.objs).

what_unique(TestID,Dict):- is_vm_map(Dict),!,what_unique_dict(TestID,Dict).
what_unique(TestID,Obj):- get_current_test(TestID),select_group(TestID,Group,_How), member(Obj,Group), must_det_ll(what_unique(TestID,Obj,Group)).
what_unique(TestID,Obj,Group):- (is_group(Group);is_object(Obj)),!,what_unique_obj(TestID,Obj,Group).
what_unique(TestID,CountMask,GroupSizeMask):-
get_new_uniq_dict(Dict),
Dict.groupSizeMask = GroupSizeMask,
Dict.countMask = CountMask,!,
what_unique_dict(TestID,Dict),
report_unique(Dict).

what_unique_obj:- get_current_test(TestID),what_unique_obj(TestID,_,_).
what_unique_obj(TestID,Obj,Group):-
get_new_uniq_dict(Dict),
Dict.group = Group,
Dict.object = Obj,
what_unique_dict(TestID,Dict),
report_unique(Dict).

/*what_unique(TestID,CountMask,GroupSizeMask):-
what_unique(TestID,SharedWith,Obj,Trait,GroupSizeMask,ActualGroupSize,CountMask,ActualCount,OtherL,ListL,SetL,TraitCounts,How),
report_unique(SharedWith,Obj,Trait,GroupSizeMask,ActualGroupSize,CountMask,ActualCount,OtherL,ListL,SetL,TraitCounts,How).
*/
report_unique(Dict):- var(Dict),get_new_uniq_dict(Dict),!,report_unique(Dict).
report_unique(Dict):- var(Dict.actualCount),!,get_current_test(TestID), what_unique_dict(TestID,Dict),report_unique(Dict).
report_unique(Dict):-
must_det_ll((
ArgDict = _{sharedWith:SharedWith,object:Obj,trait:Trait,groupSizeMask:GroupSizeMask,
actualGroupSize:ActualGroupSize,countMask:CountMask,
actualCount:ActualCount,otherL:OtherL,listL:ListL,
setL:SetL,others:TraitCountSets,how:How,group:Group},
(var(Dict)->Dict=ArgDict ; Dict >:< ArgDict),
maplist_e(tersify,TraitCountSets,HTraitSetO),
maplist_e(tersify,SharedWith,SharedWithO),
maplist_e(tersify,Group,GroupO),
maplist_e(tersify,Obj,ObjO),
%(Obj\==[] -> ignore(print_grid(Obj)) ; true),
format('~N'), pp(what_unique(ObjO=[ActualCount/ActualGroupSize-Trait],sharedWith=SharedWithO,
setL/listL=SetL/ListL,others=HTraitSetO,how=How,
groupSizeMask=GroupSizeMask,group:GroupO,countMask=CountMask,otherL=OtherL)))).

maplist_e(P2,A,B):- is_list(A),!,mapgroup(P2,A,B).
maplist_e(P2,A,B):- call(P2,A,B).

:- style_check(-singleton).
%:- arc_history(what_unique(TestID,SharedWith,Obj,Trait,GroupSizeMask,ActualGroupSize,CountMask,ActualCount,OtherL,ListL,SetL,Others,_How)).
:- style_check(+singleton).


obj_exclude(Obj,Group,Others):- var(Obj),!,select(Obj,Group,Others).
obj_exclude(Obj,Group,Others):- select(O,Group,Others),(O==Obj *-> true; Group=Others).


what_unique_dict(TestID,Dict):-
ArgDict = _{sharedWith:SharedWith,object:Obj,trait:Trait,groupSizeMask:GroupSizeMask,
actualGroupSize:ActualGroupSize,countMask:CountMask,
actualCount:ActualCount,otherL:OtherL,listL:ListL,
setL:SetL,others:TraitCountSets,how:How,group:Group},
(var(Dict)->Dict=ArgDict ; Dict >:< ArgDict),
(var(Group)->(select_group(TestID,Group,How));true),
obj_exclude(Obj,Group,Others),
length_criteria(Group,GroupSizeMask),
length(Group,ActualGroupSize),
mapgroup(each_trait,[Obj|Others],[_-ObjT|TraitList]),
member(Trait,ObjT),
\+ too_non_unique(Trait),
\+ too_unique(Trait),
found_in_o(Trait,TraitList,SharedWith),
length_criteria(SharedWith,CountMask),
length(SharedWith,ActualCount),
freeze(B,\+ \+ (member(E,SharedWith), E==B)),
my_partition(=(B-_),TraitList,_Mine,NotMine),
length(NotMine,OtherL),
%dif(WTrait,Trait),
functor(Trait,F,A),functor(WTrait,F,A),
found_in_w(WTrait,NotMine,HTraitList),length(HTraitList,ListL),
sort_safe(HTraitList,HTraitSet),length(HTraitSet,SetL),
findall(C-HTrait,(member(HTrait,HTraitSet),found_in_w(HTrait,NotMine,LS),length(LS,C)),TraitCounts),
sort_safe(TraitCounts,TraitCountSets),
\+ filter_what_unique(TestID,SharedWith,Obj,Trait,GroupSizeMask,ActualGroupSize,CountMask,ActualCount,OtherL,ListL,SetL,How).


explain_uniqueness(GroupWhole):-
object_printables(GroupWhole,Group,GroupPP),
get_current_test(TestID),!,
forall(member(Obj,Group),
(dash_chars,
object_glyph(Obj,G), object_color_glyph_short(Obj,GC), object_grid(Obj,OG),
locally(nb_setval(color_index,[Obj|GroupPP]),print_side_by_side(GC,GroupPP,'explain_uniqueness',_,OG,G)),
dmsg(uobj=Obj),!,
forall(what_unique_obj(TestID,Obj,Group),true))),
dash_chars.


% touching vs each dir
% size2D



:- style_check(-singleton).
filter_what_unique(TestID,SharedWith,Obj,Trait,GroupSizeMask,ActualGroupSize,CountMask,ActualCount,OtherL,ListL,SetL,How):-
OtherL=<1.

filter_what_unique(TestID,SharedWith,Obj,Trait,GroupSizeMask,ActualGroupSize,CountMask,ActualCount,OtherL,ListL,SetL,How):-
ListL=SetL, SetL>1.


/*

With each type of example we can have...

values_all_same|values_all_dif
values_where_1_stand_otherwise
values_where_2_stand_otherwise

*/

4 changes: 2 additions & 2 deletions packs_sys/logicmoo_agi/prolog/kaggle_arc/kaggle_arc_boards.pl
Original file line number Diff line number Diff line change
Expand Up @@ -589,7 +589,7 @@
compute_test_oo_hints(TestID):-
forall(
kaggle_arc_io(TestID,ExampleNum,out,Out1),
(next_example(TestID,ExampleNum,ExampleNum2), kaggle_arc_io(TestID,ExampleNum2,out,Out2),
(next_example_num(TestID,ExampleNum,ExampleNum2), kaggle_arc_io(TestID,ExampleNum2,out,Out2),
maybe_compute_test_oo_hints(TestID,ExampleNum,Out1,Out2))),!.

maybe_compute_test_oo_hints(TestID,ExampleNum,Out1,Out2):-
Expand All @@ -599,7 +599,7 @@
compute_test_ii_hints(TestID):-
forall(
kaggle_arc_io(TestID,ExampleNum,in,In1),
(next_example(TestID,ExampleNum,ExampleNum2), kaggle_arc_io(TestID,ExampleNum2,in,In2),
(next_example_num(TestID,ExampleNum,ExampleNum2), kaggle_arc_io(TestID,ExampleNum2,in,In2),
maybe_compute_test_ii_hints(TestID,ExampleNum,In1,In2))),!.

maybe_compute_test_ii_hints(TestID,ExampleNum,Out1,Out2):- forall(grid_hint_recolor(i-i,Out1,Out2,Hints),add_hint(TestID,ExampleNum,Hints)).
Expand Down
4 changes: 2 additions & 2 deletions packs_sys/logicmoo_agi/prolog/kaggle_arc/kaggle_arc_db.pl
Original file line number Diff line number Diff line change
Expand Up @@ -350,8 +350,8 @@
% globalpoints( [ red-HV0101, silver-point_02_01]),
grid_size(8, 8)]).

pgt2(Obj):- Obj = hv_point(1,1,HV0101),
obj( [ mass(536),
pgt2(Obj):- hv_point(1,1,HV0101),
Obj = obj( [ mass(536),
shape_rep(grav, [ HV0101, point_02_01]),
colors_cc( [ cc(red, 190.0), cc(silver, 132.0), cc(green, 55.0), cc(cyan, 53.0),
cc(blue, 45.0), cc(yellow, 36.0), cc(orange, 25.0)]),
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -103,7 +103,7 @@
%when_in_html(if_wants_output_for(guess_some_relations,guess_some_relations(InC,OutC))),
%when_in_html(if_wants_output_for(sort_some_relations,sort_some_relations(InC,OutC))),

show_object_dependancy(TestID,ExampleNum,InC,OutC),
show_object_dependancy(TestID>ExampleNum,InC,OutC),
if_t( fail,((


Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -394,7 +394,8 @@


indiv_show_pairs_input(_Peers,_Shown,_List,Indv):- nb_current(menu_key,'o'),!, dg(Indv).
indiv_show_pairs_input(_Peers,_Shown,_List,Indv):- get_current_test(TestID), print_info(Indv), ignore(what_unique(TestID,Indv)).
indiv_show_pairs_input(_Peers,_Shown,_List,Indv):- get_current_test(TestID), print_info(Indv),
nop(ignore(what_unique(TestID,Indv))).

indiv_show_pairs_output(_Peers,_Shown,_List,Indv):- nb_current(menu_key,'o'),!, dg(Indv).
%indiv_show_pairs_output(_Peers,_Shown,_List,Indv):- has_prop(pen([cc('black',_)]),Indv),!, dash_chars, nop(show_indiv(Indv)).
Expand Down Expand Up @@ -498,7 +499,7 @@
if_t(nb_current(menu_key,'u'),
(
indv_props_list(O1,S1),indv_props_list(O2,S2),
get_current_test(TestID), ignore(what_unique(TestID,O1)),
get_current_test(TestID), nop(ignore(what_unique(TestID,O1))),
remove_giz(S1,T1),remove_giz(S2,T2),
indv_u_props(O1,IU),indv_u_props(O2,OU),
intersection(T1,T2,Sames,IA,OA),my_maplist(refunctor,Sames,NewSames),
Expand Down Expand Up @@ -1235,6 +1236,8 @@
prop_specifier(F,Prop):- Prop=..[F,_,_].
prop_specifier(Spec,Prop):- Spec=..[F,A],Prop=..[F,A,_].

equiv_props(Prop1,Prop2):- not_differ_props(Prop1,Prop2).

equiv_props(Nil,_,_):- Nil==[],!.
equiv_props([H|T],O1,O2):- is_list(T),!,equiv_props(H,O1,O2),equiv_props(T,O1,O2).
equiv_props(Test,O1,O2):- var(Test),!,
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -518,6 +518,9 @@
size_overlap_cc(FG1,FG2):-
maplist(arg_same(2),FG1,FG2).

arg_same(N,Term,Value):-
arg(N,Term,Same),
Same =@= Value.



Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -365,7 +365,7 @@

guess_how_else([HOW|HOW_ELSE],I,O,Stuff1,Stuff2):-
guess_how(HOW,I,O,MID1,MID2),
maplist(guess_how_else,how,HOW_ELSE,MID1,MID2,Stuff1,Stuff2),!.
maplist(guess_how_else,HOW_ELSE,MID1,MID2,Stuff1,Stuff2),!.
guess_how_else([],I,O,I,O).

guess_how(HOW,I1,O1,Stuff1,Stuff2):-
Expand Down Expand Up @@ -406,14 +406,14 @@
toggle_val(Lst,V):- is_list(Lst),!,member(V,Lst).
toggle_val(N,V):- member(TF,[false,true]), V =..[N,TF].


:- dynamic(arc_cache:indv_flag/2).
is_fti_step(set_indv_flags).
set_indv_flags(X,_VM):- set_indv_flags(X),!.
set_indv_flags(X):- is_list(X),!,maplist(set_indv_flags,X).
set_indv_flags(NV):- NV=..[N,V],assert(indv_flag(N,V)).
set_indv_flags(NV):- NV=..[N,V],retractall(arc_cache:indv_flag(N,_)),assert(arc_cache:indv_flag(N,V)).

is_fti_step(which_tf).
which_tf(Name,True,False,VM):- (indv_flag(Name,true)->run_fti(VM,True);run_fti(VM,False)).
which_tf(Name,True,False,VM):- (arc_cache:indv_flag(Name,true)->run_fti(VM,True);run_fti(VM,False)).

is_fti_step(nop).

Expand Down Expand Up @@ -1504,12 +1504,12 @@


/*
*/
to_props_and_globalpoints(ObjL,_Ans,_GOPoints):- is_grid(ObjL),!,fail.
to_props_and_globalpoints(ObjL,Ans,GOPoints):- get_gpoints_and_props(ObjL,GOPoints,Ans).
ogs_into_obj_props( OutGrid,AnsProps,Obj):- like_object(AnsProps,OutGrid,Obj),!.

*/

like_object(Ans,Out,ObjO):-
get_gpoints_and_props(Ans,GOPoints,Props),
grid_to_gid(Out,GID),grid_size(Out,GH,GV),
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -674,8 +674,7 @@

into_group(G,G,(=)) :- G==[],!.
into_group(P,G,(=)):- is_group(P),!,G=P.
into_group(G, G, _):- plain_var(G),!, %throw(var_into_group(G)),
current_groups(G).
into_group(G, G, _):- plain_var(G),!, throw(var_into_group(G)), nop(current_groups(G)).
into_group(VM,G,(group_to_and_from_vm(VM))):- is_vm(VM),G=VM.objs,is_group(G),!.
into_group(VM,G,(group_to_and_from_vm(VM))):- is_vm(VM),run_fti(VM),G=VM.objs,is_group(G),!.
into_group(G,I, into_grid):- is_grid(G),!,compute_shared_indivs(G,I).
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -784,6 +784,7 @@
aggregates(insideOf(_)).

%is_bg_object(Obj):- get_black(Black),has_prop(pen( [cc(Black,_)]),Obj).
is_bg_object(Obj):- is_mapping(Obj),!,fail.
is_bg_object(Obj):- has_prop(cc(fg,0),Obj),!, \+ is_whole_grid(Obj).
is_bg_object(Obj):- \+ is_object(Obj),sub_var(cc(fg,0),Obj),!.

Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -370,7 +370,7 @@
call(P2,ObjsI,HAD1), call(P2,ObjsO,HAD2),
w_section(show_interesting_compare(P2,Named),
must_det_ll((
show_changed_diffs(t(P2,Named),P2A,HAD1,HAD2)))))).
show_changed_diffs(t(P2,Named),Named,P2A,HAD1,HAD2)))))).

pp_non_nil_e(_,PP):- PP == [],!.
pp_non_nil_e(Named,PP):- nl,listify(PP,LL),wqs(Named),nl,maplist(pp,LL),nl.
Expand Down Expand Up @@ -1621,7 +1621,7 @@
not_care_to_count(elink(_,_)).

not_care_to_count(_):- !, fail.
not_care_to_count(Cmpd):- arg(_,Cmpd,E),is_gridoid(E),!, \+ grid(E).
not_care_to_count(Cmpd):- arg(_,Cmpd,E),is_gridoid(E),!, \+ is_grid(E).
not_care_to_count(Cmpd):- arg(_,Cmpd,E),is_points_list(E),!.
%not_care_to_count(iz(info(_))).
%not_care_to_count(iz(HasNumber)):- sub_term(N,HasNumber),number(N),!.
Expand Down Expand Up @@ -2528,8 +2528,8 @@

get_is_for_ilp(_,_,input, :-(D) ):- get_is_for_ilp(_,_,determination, D ).

get_is_for_ilp(TestID,common,logicmoo_ex,accompany_changed(TestID,P,Same)):-
is_accompany_changed_db(TestID,P,Same).
get_is_for_ilp(TestID,common,logicmoo_ex,is_accompany_changed_db(TestID,IO,P,Same)):-
is_accompany_changed_db(TestID,IO,P,Same).


get_is_for_ilp(_,_,liftcover_ex,D):- read_terms_from_atom(D, '
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -788,7 +788,7 @@

% unify penalizing a resource each failure
upref(Resource,O1,O2):-
resource_value(Resource,Value),
b_get_resource(Resource,Value),
uaf(Value,0,Used,O1,O2),
((Used>0) ->
(plus(Value,-Used,NewValue),b_set_resource(Resource,NewValue))
Expand All @@ -798,6 +798,9 @@
uaf_append(Fm,Fi,Fo,[H1|T], L, [H2|R]) :- uaf(Fm,Fi,Fn,H1,H2),
uaf_append(Fm,Fn,Fo,T, L, R).


b_set_resource(Resource,Value):- b_setval(Resource,Value).
b_get_resource(Resource,Value):- b_getval(Resource,Value).
% append allowing some failures (cells only)


Expand Down Expand Up @@ -1196,6 +1199,8 @@

maybe_into_grid(I,O):- \+ is_grid(I), into_grid(I,O), I \=@=O,!.

constrain_grid(CT,Trig,Grid,GridO):-
constrain_grid(_CntDwn,CT,Trig,Grid,GridO).

%constrain_grid_f(Grid2,GridO):- Grid2=GridO.
%constrain_grid_f(Grid2,Trig,GridO):- constrain_grid(CntDwn,f,Trig,Grid2,GridO),!.
Expand Down
Loading

0 comments on commit a43b8bd

Please sign in to comment.