Prolog Experiments for Machine Gardens

First Attempt

A declarative model of the geometry. Here I didn't start from the idea of the machine as an explicit tree. I just started defining what wheels and cogs would be like and then testing if they intersected. While that worked I realised I had no idea how to construct a machine by creating new pieces.

?- [library(clpfd)].

wheel(ID,X,Y,InnerRadius,OuterRadius) :- cog(ID,X,Y,InnerRadius,OuterRadius).
wheel(ID,X,Y,InnerRadius,OuterRadius) :- drive(ID,X,Y,InnerRadius,OuterRadius).
	
wheel(X) :- wheel(X,_,_,_,_).

piece(X) :- 
	wheel(X,_,_,_,_) | rack(X,_,_,_,_,_).
	
distance(A,B,D) :-
	wheel(A,ACX,ACY,_,_),
	wheel(B,BCX,BCY,_,_),
	distance(ACX,ACY,BCX,BCY,D).
	
distance(X1,Y1,X2,Y2,D) :- 
	D is sqrt((X2-X1)^2+(Y2-Y1)^2).
	
overlaps(A,B) :-
    wheel(A,_,_,AIR,_),
    wheel(B,_,_,BIR,_),
	distance(A,B,D),
	D < (AIR+BIR),
	A \== B.
		
engages(A,B) :-
	wheel(A,_,_,AIR,AOR),
    wheel(B,_,_,BIR,BOR),
  	distance(A,B,D),
	D > (AIR+BIR),
	D > (AOR+BOR),
	A \== B.
		
connected(A,B) :- connected(A,B,[]).

connected(A,B,Closed) :-	
	engages(A,B),
	\+ member(B,Closed).

connected(A,B,Closed) :-
	engages(A,Z),
	\+ member(Z,Closed),
	connected(Z,B,[Z|Closed]).
	

ratio_change(S1,R1,R2,S2) :-
	S2 is (S1 * (R1 / R2)).

turning(A,Speed,Direction) :- turning(A,Speed,Direction,[]).

turning(A,Speed,Direction,_) :- turn(A,Speed,Direction),!.
	
turning(A,S2,anticlockwise,Checked) :-
	engages(A,B),
	\+member(B,Checked),
	turning(B,S1,clockwise,[A|Checked]),
	wheel(A,_,_,AIR,_), 
	wheel(B,_,_,BIR,_),
	ratio_change(S1,AIR,BIR,S2),
	!.
	
turning(A,S2,clockwise,Checked) :-
	engages(A,B),
	\+member(B,Checked),	
	turning(B,S1,anticlockwise,[A|Checked]),
	wheel(A,_,_,AIR,_), 
	wheel(B,_,_,BIR,_),
	ratio_change(S1,AIR,BIR,S2),
	!.
	
turn(z1,3000,clockwise).
	
in_range(X,Y,LX,LY,HX,HY) :- 
	X #> LX,
	X #< HX,
	Y #> LY,
	Y #< HY.
	
print_all :-
	wheel(I,_,_,_),
	once(print_one(I)).

	
print_one(I) :-
	wheel(I,X,Y,R),
	write(I),
	write(': ('),
	write(X),
	write(','),
	write(Y),
	write(') '),
	write(R),
%	print_turn(I) |
	nl.
	
print_turn(I) :-
	turning(I,S,D),
	write('; '),
	write(S),
	write('rpm; '),
	write(D),nl.



drive(z1, 0,10,5, 6).
cog(z2,10,10,5,6).
cog(z3,20,10,5,6).
cog(z4,40,10,15,18).
cog(z5,80,0,5,6).

rack(r1,40,40,80,80,5).	

	

Simple Grammar to Define a Cog Machine

My second Prolog experiment. This time using a grammar. This can be used to *construct* all possible new machines. Unfortunately my problem here was that the recursion is "depth first" ie. going off and generating an infinitely deep tree of cogs of the same sort rather than an interestingly varied collection of shallow trees. After this, I realised that despite the simplicity and elegance of using Prolog, I didn't understand the language sufficiently well to make it work for me and reverted to writing my recursive machine builder in Processing. (See the SpiralGarden class). The Prolog experiments were nevertheless valuable in helping me think through the eventual implementation.

piece --> cog.
piece --> rack.

cog --> [bigcog].
cog --> [mediumcog].
cog --> [smallcog].

rack --> [longrack].
rack --> [shortrack].

startchildren --> [-=].
separate --> [::].
endchildren --> [=-].

train(A, B, Depth) :-
	piece(A, B).
	
train(A, C, Depth) :-
	Depth > 0,
	D2 is Depth-1,
	piece(A, B),
	train(B, C, D2).
	
train(A, G, Depth) :-
	Depth > 0,
	D2 is Depth-1,
	piece(A, B),
	startchildren(B, C),
	train(C, D, D2),
	separate(D,E),
	train(E, F, D2),
	endchildren(F,G).

machine(A, B) :-
	train(A, B, 2).