###############
# lib
c2l((X,Y),[X|Z]) :- !,c2l(Y,Z).
c2l(X,[X]).

any(X,Min,Max) :- var(X), M is Min + random(Max-Min).
any(X,Min,Max) :- nonvar(X), X >= Min, X <= Max.

any(X,L) :- var(X), length(L,N), M is random(N),nth0(M,L,X).
any(X,L) :- nonvar(X),member(X,L).

bad(X) :- print(X), fail.

################
# macros

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

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

goal_expansion(a Head,Body) :- macro(Head), singleton(Head,Body).

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

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

##############

:- dynamic touch/7.
:- discontiguous touch/5.
:- index(touch(1,1,0,0,1,)).

:- op(1,fy,[(a),(an)]).

term_expansion(( a H :- B),L) :-  !, findall(X,def(H,B,X)         ,L).
term_expansion((an H :- B),L) :-  !, term_expansion((a H :- B   ),L).
term_expansion((an H      ,L) :-     term_expansion((a H :- true),L).
term_expansion(( a H      ,L) :-     term_expansion((a H :- true),L).

def(Head,Body,One) :-
	Head =.. [Functor|Fields],
	specs(Fields,Names,Vars,Rules),
	defPrim(Functor,Vars,Body,Names,Rules,One).

specs([Field],[Name],[Var],Rule) :-	
	spec(Field,Name,Var,Rule).
specs([F1,F2|Fields],[Name|Names],[Var|Vars],(Rule,Rules)) :-
	spec(F1,Name,Var,Rule),
	specs([F2|Fields],Names,Vars,Rules).

spec(Name=Var : a  Type,Name,Var,a(Type,Var)).
spec(Name=Var : an Type,Name,Var,a(Type,Var)).
spec(Name=Var :    Type,Name,Var,  Rule) :- Rule =.. [Type,Var].
spec(Name=Var,          Name,Var,true).
spec(Name:Type,         Name,Var,Rule) :- Rule =.. [Type,Var].
spec(Name,              Name,Var,true) :- nonvar(Name).
spec(Name,              _   ,  _,   _) :- bad(spec(Name)).

defPrim(Functor,Vars,Body,_,Rules,(a Head :- Rules,Body)) :-
	Head =.. [Functor|Vars].

defPrim(Functor,Vars,Body,Names,Rules,Touch) 
	touched(Functor,Vars,Names,Touch).

touched(Functor,Vars,Names,touch(Term0,Name,Old,New,Term)) :-
    nth1(N,Names,Name),
    Term0=..[Functor|Vars],
    functor(Term,Functor,Arity),  
    joinArgs(1,N,Vars,Old,New,L),
    Term=.. [Functor|L],

joinArgs(N,N,[Old|Rest],Old,New,[New|Rest]).
joinArgs(N0,N1,[X|L0],Old,New,[X|L]) :- 
    N0 < N1, 
    N2 is N0 + 1,
    joinArgs(N2,N1,L0,Old,New,L).
