:- [op].

:-ops([fx(set),fx(one),xfy(of),xfx(to),xfx(by)]).


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

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

def1(X,Y,Z) :- once(def2(X,Y,Z)).

def2(X of Y of Z,V,(G1,G2)) :- def1(X of Y,V,G1), def1(X of Z,V,G2).
def2(set  This,V,(member(One,V),G)) :- def1(one  This,One,G).
def2(one  This,V,G) :- G =.. [This,V].
def2(one  N1 to N2 by Inc,  V,(between(0,Steps,N), V is N1+N*Step)) :- 
	Step  is (N2 - N1)/Inc, 
	Steps is floor((N2 - N1)/Step) + 1.

def2(This,       V,G) :- def1(one This,V,G).
def2(F,          V,G) :- def1(one  F,V,G).

thing(posint(_),withinp(0,100),within(0,10^32))

things0(Term) :- thing(Term,_,Zero), type0(
	
	arg(_

	Term =.. [F|Args],

type0(X,Y) :- var(Y),type(X,_,Init), apply(Init,[Y]). 
type(X,Y) :- nonvar(Y),type(X,Check,_), apply(Check,[Y]). 

within(Min,Max,X) :- var(X) -> within0(Min,Max,X) ; within1(Min,Max,X).

within0(Min,Max,X) :- number(X), X >= Min, X =< Max. 
within1(Min,Max,X) :- M = 1000000000, X is Min + random(M)/M*(Max - Min).
