%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
% define operators 

:- [op].

%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
% define a file within which we unwind singletons

myspace(File) :-
	working_directory(X,X),
	atom_concat(X,'janeeg1.pl',File).

mine(X) :- 
	nonvar(X), 
	myspace(File), 
	predicate_property(X,file(File)).

goal_expansion(Head,Body) :- 
	mine(Head),
	singleton(Head,Body).

clauses(Head,All) :- 
	findall(Head/Body,clause(Head,Body),All).

singleton(Head,Body) :- 
	clauses(Head,[Head/Body]).

term_expansion((X ---> Y),Out) :-
	expand_term((X --> Y),Tmp),
	%tidy(Tmp,Out).
	Out = Tmp.

%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
% genetic syntactic sugar tricks 

%term_expansion(A if B,(A :- B)).
goal_expansion(call(X),X).
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
% forward chaining

fchain :- reset, run(start), report.

:- dynamic used/3.
:- index(used(1,1,0)).

reset :- retractall(used(_,_,_)).

run(Cxt) :- 
	match(   R,Cxt,Vars), 
	select1( R,Cxt,Vars), !,
	act(     R,Cxt,Vars),
	run(Cxt).
run(_).

report :- listing(used).

select1(R,Cxt,Vars) :- 
	not(   used(R,Cxt,Vars)), 
	assert(used(R,Cxt,Vars)).

%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
% 

def(Spec,(type(Functor,Blank) :- Body)) :-
	Spec =.. [Functor|Fields],
	length(Fields,N),
	length(Vars,N),
	Blank =.. [Functor|Vars],
	maplist(def1,Fields,Vars,Constraints),
	l2c(List,Constraints).

l2c([X],X).
l2c([X,Y|Z],(X,Rest)) :- l2c([Y|Z],Rest).

def1(F,V,G) :- print(1), G  =.. [F,V].

%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
% 
%
tidy(T0,T) :- runiv(T0,T).

runiv(Term, Term) :- atomic(Term).
runiv(Term, Term) :- var(Term).
runiv(Term0, Term) :-
	compound(Term0),
    Term0 =..L0,
    once(maplist(runiv1, L0, L)),
    Term =.. L.

runiv1(X = X,true).
runiv1(X is Y,true) :- ground(X), X is Y.
runiv1(H0,H)     :- runiv(H0,H).

%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
% load the spec

spec :- 
	myspace(X),print(loading(X)),nl,load_files([X]).

:- spec.
