% Manhattan Kick Ball
% Player rules
% mmeri 17.1.2003
% 
% other players considered 25.02.2003 /mmeri
% starting to make version 07.03.2003 /mmeri
    
% parameters

fwidth(10).

flength(L) :-
	fwidth(W),
	L is 2 * W.
full_force(F) :-
	fwidth(Y),
	F is Y / 2.

goal_kick_dist(D) :-
    fwidth(W),
    D is W /2.
    
opponent(1,2).
opponent(2,1).

fdistance([X,Y],[I,J],abs(X-I)+abs(Y-J)).
fdistance_inv([X,Y],[I,J],D) :-
    D    ==  A + B,
    (X - I  ==  A ; I - X == A),
    (Y - J  ==  B ; J - Y == B),
    !.
    
% where one can move in D steps
% fpath(+point1,-point2,+D) inputs +
fpath([WS,LS],[WS,LS],0) :-
    !.
fpath([WS,LS],[WE,LE],D) :-
    flength(L),
    fwidth(W),
    WS > 0, WS < W-1, LS > 0 , LS < L,  
    DN is D - 1,
    fpath([WS+1,LS],[WE,LE],DN),
    !.
fpath([WS,LS],[WE,LE],D) :-
    flength(L),
    fwidth(W),
    WS > 1, WS < W, LS > 0 , LS < L,  
    DN is D - 1,
    fpath([WS-1,LS],[WE,LE],DN),
    !.
fpath([WS,LS],[WE,LE],D) :-
    flength(L),
    fwidth(W),
    WS > 0, WS < W, LS > 0 , LS < L-1,  
    DN is D - 1,
    fpath([WS,LS+1],[WE,LE],DN),
    !.
fpath([WS,LS],[WE,LE],D) :-
    flength(L),
    fwidth(W),
    WS > 0, WS < W, LS > 1 , LS < L,  
    DN is D - 1,
    fpath([WS,LS-1],[WE,LE],DN),
    !.

% 1 -> 1 , 2 -> -1
fdirection(Team_number,-2*Team_number+3).

border(W,L) :-
	W == 0; fwidth(W); L == 0; flength(L).

goal(1,W,L) :-
	fwidth(Wdth),
	flength(Lgth),
	W > Wdth/2 - Wdth/4 - 2, 
	W < Wdth/2 + Wdth/4 + 2,
	L == Lgth.
goal(2,W,L) :-
	fwidth(Wdth),
	W > Wdth/2 - Wdth/4 - 2, 
	W < Wdth/2 + Wdth/4 + 2,
	L == 0.

goal_position(1,[W,L]) :-
	fwidth(Wdth),
	flength(Lgth),
	W > Wdth/2 - Wdth/4 - 2, 
	W < Wdth/2 + Wdth/4 + 2,
	Lgth - L < Wdth/2.

goal_position(2,[W,L]) :-
	fwidth(Wdth),
	W > Wdth/2 - Wdth/4 - 2, 
	W < Wdth/2 + Wdth/4 + 2,
	L < Wdth/2.

goal_center(1,GW,GL) :-
	fwidth(Wdth),
	flength(Lgth),
	GW is Wdth/2,
	GL is Lgth.

goal_center(2,GW,GL) :-
	fwidth(Wdth),
	GW is Wdth/2,
	GL is 0.


position(1,MN,T1,_,W,L) :-
	nth1(MN,T1,[W,L]).

position(2,MN,_,T2,W,L) :-
	nth1(MN,T2,[W,L]).

mate(1,MN,T1,_,W,L) :-
	member([W,L],T1),
	nth1(N,T1,[W,L]),
	N \= MN.	

mate(2,MN,_,T2,W,L) :-
	member([W,L],T2),
	nth1(N,T2,[W,L]),
	N \= MN.	

matex(1,MN,T1,_,N) :-
	member(X,T1),
	nth1(N,T1,X),
	N \= MN.	
matex(2,MN,_,T2,N) :-
	member(X,T2),
	nth1(N,T2,X),
	N \= MN.	

priority_mate_exists_here(My_number,Team) :-
	nth1(My_number,Team,[W,L]),
	nth1(Ind,Team,[W,L]),
	Ind < My_number.

me(1,MN,T1,_,W,L) :-
	nth1(MN,T1,[W,L]).

me(2,MN,_,T2,W,L) :-
	nth1(MN,T2,[W,L]).

my_team(1,Team1,_,Team1).
my_team(2,_,Team2,Team2).

adversary(N,_,T1,T2,W,L) :-
	opponent(N,M),
	mate(M,-1,T1,T2,W,L).

fbetween(M1,M2,M3) :-
	M1 < M3,
	M3 < M2.
fbetween(M1,M2,M3) :-
	M2 < M3,
	M3 < M1.

highest(My_team,Team,[H|T],0,Result) :-	
	!,
	highest(My_team,Team,T,H,Result).	
highest(_,_,[],Best,Best).
highest(My_team,Team,[H|T],Best,Result) :-	
	fdirection(My_team,Direction),
	nth1(H,Team,[_,L]),
	nth1(Best,Team,[_,LB]),
	Direction*L > Direction * LB,
	!,
	highest(My_team,Team,T,H,Result).	
highest(Direction,Team,[_|T],Best,Result) :-
	highest(Direction,Team,T,Best,Result).	

pass_line(N,T1,T2,PN1,PN2) :-
	mate(N,PN1,T1,T2,W,_),
	mate(N,PN2,T1,T2,W,_).

pass_line(N,T1,T2,PN1,PN2) :-
	mate(N,PN1,T1,T2,_,L),
	mate(N,PN2,T1,T2,_,L).

% seems to accept shared positions with the enemy on the receiving end?
clear_pass_line(N,T1,T2,PN1,PN2) :-
	my_team(N,T1,T2,Team),
	nth1(PN1,Team,[W1,L1]),
	matex(N,PN1,T1,T2,PN2),
	nth1(PN2,Team,[W2,L2]),
	W1 == W2,
	L1 \== L2,
	\+((adversary(N,PN1,T1,T2,W1,L3),(fbetween(L1,L2,L3);L2==L3))).

clear_pass_line(N,T1,T2,PN1,PN2) :-
	my_team(N,T1,T2,Team),
	nth1(PN1,Team,[W1,L1]),
	matex(N,PN1,T1,T2,PN2),
	nth1(PN2,Team,[W2,L2]),
	W1 \== W2,
	L1 == L2,
	\+((adversary(N,PN1,T1,T2,W3,L1),fbetween(W1,W2,W3);W2==W3)).

clear_score_line(Direction,_,_,N,I,J,JN) :-
	JN is J + Direction,
	goal(N,I,JN),
	!.

clear_score_line(Direction,T1,T2,_,I,J,J-Direction) :-
	JN is J + Direction,
        \+member([I,JN],T1),
        \+member([I,JN],T2),
	!.

clear_score_line(Direction,T1,T2,N,I,J,GoalPoint) :-
	JN is J + Direction,
        \+member([I,JN],T1),
        \+member([I,JN],T2),
	NN is N + 1,
	clear_score_line(Direction,T1,T2,NN,I,JN,GoalPoint).

clear_attack_line(Direction,_,_,I,J,J-Direction) :-
	JN is J + Direction,
	border(I,JN),
	!.

clear_attack_line(Direction,OTeam,N,I,J,J-Direction) :-
	JN is J + Direction,
	member([X,Y],OTeam),fdistance([X,Y],[I,JN],Dist), Dist < N + 1,
	!.

clear_attack_line(Direction,OTeam,N,I,J,DistanceFree) :-
	JN is J + Direction,
	\+((member([X,Y],OTeam),fdistance([X,Y],[I,JN],Dist), Dist < N + 1)),
	NN is N + 1,
	clear_attack_line(Direction,OTeam,NN,I,JN,DistanceFree).

clear_parallel_line(Direction,_,_,I,J,I-Direction) :-
	IN is I + Direction,
	border(IN,J),
	!.
clear_parallel_line(Direction,OTeam,N,I,J,I-Direction) :-
	IN is I + Direction,
	member([X,Y],OTeam),fdistance([X,Y],[IN,J],Dist), Dist < N + 1,
	!.

clear_parallel_line(Direction,OTeam,N,I,J,DistanceFree) :-
	IN is I + Direction,
	\+((member([X,Y],OTeam),fdistance([X,Y],[IN,J],Dist), Dist < N + 1)),
	NN is N + 1,
	clear_parallel_line(Direction,OTeam,NN,IN,J,DistanceFree).


% most forward
best_pal(My_team,Team,Pals,BPal) :-
	highest(My_team,Team,Pals,0,BPal).

closer([BW,BL],J,I,Team) :-
	nth1(J,Team,[JW,JL]),
	nth1(I,Team,[IW,IL]),
	abs(BW-JW)+abs(BL-JL) < abs(BW-IW)+abs(BL-IL).		

% closest to the ball
ball_pal([BW,BL],Team,P) :-
	member(P,Team),
	nth1(I,Team,P),
	\+((member(Q,Team),nth1(J,Team,Q),closer([BW,BL],J,I,Team))).

closest_enemy(My_number,MTeam,OTeam,Other_number) :-
	nth1(My_number,MTeam,[MW,ML]),
	member([OW,OL],OTeam),
	nth1(Other_number,OTeam,[OW,OL]),	
	fdistance([MW,ML],[OW,OL],D),
	\+((member([OW1,OL1],OTeam),fdistance([MW,ML],[OW1,OL1],D1),D1 < D)).
	

% at a scoring position


% END when told off the field be a nice player and obey - exit the game.
% That is respond END = 4 as your Move.
% 
agent([[[_,_],_,My_team, My_number, Move, Arg1, Arg2],Team1,Team2]) :-
	position(My_team,My_number,Team1,Team2,W,_),
	fwidth(Width),
	(W > Width ; W < 0), % off the field
	nl,
	write(My_team),
	write(' '),
	write(My_number),
	Arg2 is 0,
	Arg1 is 0,
	write(' ... I am out of here ! bye! '),
	nl,
	ttyflush,
	Move is 4, % END
	!.

% KICKING
% 
% towards goal with full force
agent([[[BW,BL],_,My_team,My_number, Move, Arg1, Arg2],Team1,Team2]) :-
	position(My_team,My_number,Team1,Team2,BW,BL),
        goal_position(My_team,[BW,BL]),
	fdirection(My_team,Direction),
	clear_score_line(Direction,Team1,Team2,1,BW,BL,PassLevel),
	Move is 2, % kick
	Arg1 is 0,
	Arg2 is PassLevel-BL,
        goal_kick_dist(D),
        Arg2 < D+1,
	nl,
	Move is 2, % kick
	Arg1 is 0,
	full_force(FullForce),
	fdirection(My_team,Direction),
	Arg2 is Direction*FullForce,
	nl,
	write(My_team),
	write(' ,'),
	write(My_number),
	write(' I kick for goal the ball at '),
	write(BW),
	write(' '),
	write(BL),
	nl,
	ttyflush,
	!.

% 
% passing to the mate with most advanced position   
% 
agent([[[BW,BL],_,My_team,My_number, Move, Arg1, Arg2],Team1,Team2]) :-
	position(My_team,My_number,Team1,Team2,BW,BL),
	setof(Pal,clear_pass_line(My_team,Team1,Team2,My_number,Pal),Pals),
	my_team(My_team,Team1,Team2,Team),
	\+priority_mate_exists_here(My_number,Team),
	best_pal(My_team,Team,Pals,BPal),
	nth1(BPal,Team,[PW,PL]),
	Move is 2, % kick
	Arg1 is PW - BW,
	Arg2 is PL - BL,
	nl,
	write(My_team),
	write(' ,'),
	write(My_number),
	write(' I pass the ball at '),
	write(BW),
	write(' '),
	write(BL),
	write(' to '),
	write(PW),
	write(' '),
	write(PL),
	nl,
	ttyflush,
	!.

% a predicate for passing to oneself forward to a position where oneself
% can get before opponents 
agent([[[BW,BL],_,My_team,My_number, Move, Arg1, Arg2],Team1,Team2]) :-
	position(My_team,My_number,Team1,Team2,BW,BL),
	my_team(My_team,Team1,Team2,Team),
	\+priority_mate_exists_here(My_number,Team),
	opponent(My_team,Other_team),
	my_team(Other_team,Team1,Team2,OTeam),
	fdirection(My_team,Direction),
	clear_attack_line(Direction,OTeam,1,BW,BL,PassLevel),
	PassLevel > 0,
	Move is 2, % kick
	Arg1 is 0,
	Arg2 is PassLevel-BL,
	nl,
	write(My_team),
	write(' ,'),
	write(My_number),
	write(' I pass for myself forward the ball at '),
	write(BW),
	write(' '),
	write(BL),
	write(' distance '),
	write(Arg2),
	nl,
	ttyflush,
	!.

% a predicate for kicking to an equal position (sideways) where oneself
% can get before opponents 
agent([[[BW,BL],_,My_team,My_number, Move, Arg1, Arg2],Team1,Team2]) :-
	position(My_team,My_number,Team1,Team2,BW,BL),
	opponent(My_team,Other_team),
	my_team(Other_team,Team1,Team2,OTeam),
	my_team(My_team,Team1,Team2,Team),
	\+priority_mate_exists_here(My_number,Team),
	Left is -1,
	Right is 1,
	clear_parallel_line(Left,OTeam,1,BW,BL,DistanceFreeMinus),
	clear_parallel_line(Right,OTeam,1,BW,BL,DistanceFreePlus),
	DFM is  DistanceFreeMinus,
	DFP is  DistanceFreePlus,
	write(' Space at sides: right '),
	write(DFP),
	write(' left '),
	write(DFM),
	nl,
	ttyflush,
	(   DFM > DFP -> DistanceFree is -1*DFM ; DistanceFree is DFP),
	Move is 2, 
	Arg1 is DistanceFree, 
	Arg2 is 0, 
	nl,
	write(My_team),
	write(' ,'),
	write(My_number),
	write(' I pass for myself sideways the ball at '),
	write(BW),
	write(' '),
	write(BL),
	write(' distance '),
	write(DistanceFree),
	nl,
	ttyflush,
	!.

% kicking upwards with full force, 
% THIS IS PANIC AND LAST RESORT WHEN TRICKS RUN OUT WHEN I AM AT THE
% BALL
% 
agent([[[BW,BL],_,My_team,My_number, Move, Arg1, Arg2],Team1,Team2]) :-
	position(My_team,My_number,Team1,Team2,BW,BL),
	my_team(My_team,Team1,Team2,Team),
	\+priority_mate_exists_here(My_number,Team),
	Move is 2, % kick
	Arg1 is 0,
	fdirection(My_team,Direction),
	Arg2 is Direction,
	nl,
	write(My_team),
	write(' ,'),
	write(My_number),
	write(' I kick the ball at '),
	write(BW),
	write(' '),
	write(BL),
	nl,
	ttyflush,
	!.

% RUNNING
% 

% its my ball!
agent([[[BW,BL],_,My_team,My_number, Move, Arg1, Arg2],Team1,Team2]) :-
	position(My_team,My_number,Team1,Team2,W,L),
	(   W \== BW ; L \== BL),
	my_team(My_team,Team1,Team2,Team),
	opponent(My_team,Other_team),
	my_team(Other_team,Team1,Team2,OTeam),
	ball_pal([BW,BL],Team,[W,L]),
	ball_pal([BW,BL],OTeam,[OCW,OCL]),
	(abs(OCW-BW)+abs(OCL-BL)) > (abs(W-BW)+abs(L-BL)), % true manhattan stuff
	\+priority_mate_exists_here(My_number,Team),
	DW1 is BW - W,
	DL1 is BL - L,    
	((abs(DW1) < abs(DL1) ->  
	 Arg2 is sign(DL1),
	  Arg1 is 0)
	; 
	(
	Arg1 is sign(DW1),
	 Arg2 is 0)),
	Move is 3,
	write(My_team),
	write(' ,'),
	write(My_number),
	write(' at '),
	write(W),
	write(' ,'),
	write(L),
	write(' I run for the ball'),
	write(' using args  '),
	write(Arg1),
	write(' '),
	write(Arg2),
	nl,
	ttyflush,
	!.

% anglepass formation construction trial , see v5



% trying to get to offencive position.
% this means that since the player is not closest to the ball
% it tries to make it self available for a pass by getting
% the coordinate that it has closest to the coordinate of the 
% ball same as the balls coordinate.
agent([[[BW,BL],_,My_team,My_number, Move, Arg1, Arg2],Team1,Team2]) :-
	position(My_team,My_number,Team1,Team2,W,L),
	(   W \== BW ; L \== BL),
	my_team(My_team,Team1,Team2,Team),
	opponent(My_team,Other_team),
	my_team(Other_team,Team1,Team2,OTeam),
	ball_pal([BW,BL],Team,[CW,CL]),
	ball_pal([BW,BL],OTeam,[OCW,OCL]),
	(abs(OCW-BW)+abs(OCL-BL)) > (abs(CW-BW)+abs(CL-BL)), % true manhattan stuff
	(   W \== CW ; L \== CL),
	\+priority_mate_exists_here(My_number,Team),
	DW1 is BW - W,
	DL1 is BL - L,    
	((abs(DW1) < abs(DL1) ->  
	 Arg1 is sign(DW1),
	  Arg2 is 0)
	; 
	(
	Arg2 is sign(DL1),
	 Arg1 is 0)),
	Move is 3,
	write(My_team),
	write(' ,'),
	write(My_number),
	write(' at '),
	write(W),
	write(' ,'),
	write(L),
	write(' I run for a offensive position'),
	write(' using args  '),
	write(Arg1),
	write(' '),
	write(Arg2),
	nl,
	ttyflush,
	!.

% running to a defensive position
agent([[[BW,BL],_,My_team,My_number, Move, Arg1, Arg2],Team1,Team2]) :-
	position(My_team,My_number,Team1,Team2,W,L),
	(   W \== BW ; L \== BL),
	my_team(My_team,Team1,Team2,Team),
	opponent(My_team,Other_team),
	my_team(Other_team,Team1,Team2,OTeam),
	ball_pal([BW,BL],Team,[CW,CL]),
	ball_pal([BW,BL],OTeam,[OCW,OCL]),
	% the guy from the other team is closest to the ball
	\+((abs(OCW-BW)+abs(OCL-BL)) > (abs(CW-BW)+abs(CL-BL))), % true manhattan stuff
	% im not the one closest to the ball
	(   
	W \== CW ; 
	L \== CL), 
	\+priority_mate_exists_here(My_number,Team),
	DW1 is BW - W, % we go inline with the ball
	DL1 is BL - L,    
	((abs(DW1) < abs(DL1) ->  
	 Arg1 is sign(DW1),
	  Arg2 is 0)
	; 
	(
	Arg2 is sign(DL1),
	 Arg1 is 0)),
	Move is 3,
	write(My_team),
	write(' ,'),
	write(My_number),
	write(' at '),
	write(W),
	write(' ,'),
	write(L),
	write(' I run for a defensive position'),
	write(' using args  '),
	write(Arg1),
	write(' '),
	write(Arg2),
	nl,
	ttyflush,
	!.


% run blindly for the ball
agent([[[BW,BL],_,My_team,My_number, Move, Arg1, Arg2],Team1,Team2]) :-
	position(My_team,My_number,Team1,Team2,W,L),
	nl,
	my_team(My_team,Team1,Team2,Team),
	\+priority_mate_exists_here(My_number,Team),
	DW is BW - W,
	DL is BL - L,    
	((abs(DW) > abs(DL) ->  
	 Arg1 is sign(DW),
	  Arg2 is 0)
	; 
	(
	Arg2 is sign(DL),
	 Arg1 is 0)),
	Move is 3,
	write(My_team),
	write(' ,'),
	write(My_number),
	write(' at '),
	write(W),
	write(' ,'),
	write(L),
	write(' I run for the ball at '),
	write(BW),
	write(' '),
	write(BL),
	write(' using args  '),
	write(Arg1),
	write(' '),
	write(Arg2),
	nl,
	ttyflush,
	!.


%
% if we have ball , I'm not close to it and getting a pass, I run for
% the goal
% 
agent([[[BW,BL],_,My_team,My_number, Move, Arg1, Arg2],Team1,Team2]) :-
	position(My_team,My_number,Team1,Team2,W,L),
	(   W \== BW ; L \== BL),
	my_team(My_team,Team1,Team2,Team),
	opponent(My_team,Other_team),
	my_team(Other_team,Team1,Team2,OTeam),
	ball_pal([BW,BL],Team,[CW,CL]),
	ball_pal([BW,BL],OTeam,[OCW,OCL]),
	(abs(OCW-BW)+abs(OCL-BL)) > (abs(CW-BW)+abs(CL-BL)), % true manhattan stuff
	(   W \== CW ; L \== CL),
	priority_mate_exists_here(My_number,Team), % this already checked but in case	
	goal_center(My_team,GW,GL),	
	DW1 is GW - L,    
	DL1 is GL - L,    
	((abs(DW1) < abs(DL1) ->  
	 Arg1 is sign(DW1),
	  Arg2 is 0)
	; 
	(
	Arg2 is sign(DL1),
	 Arg1 is 0)),
	Move is 3,
	write(My_team),
	write(' ,'),
	write(My_number),
	write(' at '),
	write(W),
	write(' ,'),
	write(L),
	write(' I run for a offensive position'),
	write(' using args  '),
	write(Arg1),
	write(' '),
	write(Arg2),
	nl,
	ttyflush,
	!.

%
% if they have ball , I'm not close to it and getting a pass, I run for
% closest foe
% 
agent([[[BW,BL],_,My_team,My_number, Move, Arg1, Arg2],Team1,Team2]) :-
	position(My_team,My_number,Team1,Team2,W,L),
	(   W \== BW ; L \== BL),
	my_team(My_team,Team1,Team2,Team),
	opponent(My_team,Other_team),
	my_team(Other_team,Team1,Team2,OTeam),
	ball_pal([BW,BL],Team,[CW,CL]),
	ball_pal([BW,BL],OTeam,[OCW,OCL]),
	% the guy from the other team is closest to the ball
	\+((abs(OCW-BW)+abs(OCL-BL)) < (abs(CW-BW)+abs(CL-BL))), % true manhattan stuff
	% im not the one closest to the ball
	(W \== CW ; L \== CL), 
	\+priority_mate_exists_here(My_number,Team),
	closest_enemy(My_number,Team,OTeam,Other_number),
	nth1(Other_number,OTeam,[GW,GL]),
	DL1 is GL - L,    
	DW1 is GW - W, % we go for goal
	((abs(DW1) < abs(DL1) ->  
	 Arg1 is sign(DW1),
	  Arg2 is 0)
	; 
	(
	Arg2 is sign(DL1),
	 Arg1 is 0)),
	Move is 3,
	write(My_team),
	write(' ,'),
	write(My_number),
	write(' at '),
	write(W),
	write(' ,'),
	write(L),
	write(' I run for a defensive position'),
	write(' using args  '),
	write(Arg1),
	write(' '),
	write(Arg2),
	nl,
	ttyflush,
	!.


% widening the game sideways
agent([[[_,_],_,My_team,My_number, Move, Arg1, Arg2],Team1,Team2]) :-
	position(My_team,My_number,Team1,Team2,W,L),
	nl,
	write(My_team),
	write(' '),
	write(My_number),
	write(' ... moving away from the ball sideways my way : '),
	write(W),
	write(' '),
	write(L),
	nl,
	ttyflush,
	Move is 3, %
	Arg1 is (My_number mod 2) * 2 - 1,
	Arg2 is 0,
	!.


% WAITING
% 
% 
agent([[[_,_],_,My_team,My_number, Move, Arg1, Arg2],Team1,Team2]) :-
	position(My_team,My_number,Team1,Team2,W,L),
	nl,
	write(My_team),
	write(' '),
	write(My_number),
	write(' ... and I am waiting in: '),
	write(W),
	write(' '),
	write(L),
	nl,
	ttyflush,
	Move is 1, % wait
	Arg1 is 0,
	Arg2 is 0,
	!.

% UNAWARENESS
% 
agent([[[Bw,Bl],Server_command,My_team, My_number, Move, Arg1, Arg2],Team1,Team2]) :-
	nl,
	write('I see something: '),
	write(Bw),
	write(' '),
	write(Bl),
	write(' '),
	write(Server_command),
	write(' '),
	write(My_team),
	write(' '),
	write(My_number),
	write(' '),
	write(Team1),
	write(' '),
	write(Team2),
	nl,
	ttyflush,
	Move is 0,
	Arg1 is 0,
	Arg2 is 0.


% PRINTING (FOR TESTING)

player([I,J],T) :-
	member([I,J],T).

print_symbol(I,J,B,T1,T2,'W') :-
	player([I,J],T1),
	player([I,J],T2),
	[I,J] == B,
	!.
print_symbol(I,J,B,T1,_,'A') :-
	player([I,J],T1),
	[I,J] == B,
	!.
print_symbol(I,J,B,_,T2,'B') :-
	player([I,J],T2),
	[I,J] == B,
	!.
print_symbol(I,J,_,T1,T2,'X') :-
	player([I,J],T1),
	player([I,J],T2),
	!.
print_symbol(I,J,_,T1,_,'1') :-
	player([I,J],T1),
	!.
print_symbol(I,J,_,_,T2,'2') :-
	player([I,J],T2),
	!.
print_symbol(I,J,B,_,_,'0') :-
	([I,J] == B),
	!.
print_symbol(I,J,B,T1,T2,' ') :-
	\+player([I,J],T1),
	\+player([I,J],T2),
	[I,J] \== B,
	!.
print_symbol(_,_,_,_,_,'?').

print_field_line(_,J,_,_,_) :-
	JL is J - 1,
	flength(L),
	JL == L,
	nl,
	!.

print_field_line(I,J,B,T1,T2) :-
	print_symbol(I,J,B,T1,T2,S),
	write(S),
	JN is J + 1,
	print_field_line(I,JN,B,T1,T2).

print_field(I,_,_,_,_) :-
	IL is I - 1,
	fwidth(IL),
	nl,
	!.

print_field(I,J,B,T1,T2) :-
	nl,
	print_field_line(I,J,B,T1,T2),
	IN is I + 1,
	print_field(IN,0,B,T1,T2).

print_field(B,T1,T2) :-
	I is 0,
	J is 0,
	print_field(I,J,B,T1,T2),
	!.

% TESTING ROUTINES

test(M,W,L) :-
	write('testing the agent'),
	nl,
	print_field([5,5],[[5,3],[3,5],[5,5],[7,5],[5,9]],[[1,15],[4,5],[5,15],[7,15],[9,15]]),
	ttyflush,
	agent([[[5,5],_,1,3,M,W,L],[[5,3],[3,5],[5,5],[7,5],[5,9]],[[1,15],[4,5],[5,15],[7,15],[9,15]]]).

test1(M,W,L) :-
	write('testing (1) the agent '),
	nl,
	print_field([5,15],[[5,3],[3,5],[5,5],[7,5],[5,9]],[[1,15],[4,5],[5,15],[7,15],[9,15]]),
	ttyflush,
	agent([[[5,15],_,2,3,M,W,L],[[5,3],[3,5],[5,5],[7,5],[5,9]],[[1,15],[4,5],[5,15],[7,15],[9,15]]]).


test2(M,W,L) :-
	write('testing(2) the agent'),
	nl,
	print_field([5,15],[[5,3],[3,5],[5,5],[7,5],[5,9]],[[1,15],[4,5],[5,15],[5,17],[9,15]]),
	ttyflush,
	agent([[[5,15],_,2,3,M,W,L],[[5,3],[3,5],[5,5],[7,5],[5,9]],[[1,15],[4,5],[5,15],[5,17],[9,15]]]).

test3(M,W,L) :-
	write('testing(3) the agent, tries to score'),
	nl,
	print_field([4,3],[[5,3],[3,5],[5,5],[7,5],[5,9]],[[1,15],[4,3],[5,15],[5,17],[9,15]]),
	ttyflush,
	agent([[[4,3],_,2,2,M,W,L],[[5,3],[3,5],[5,5],[7,5],[5,9]],[[1,15],[4,3],[5,15],[5,17],[9,15]]]).

test4(M,W,L) :-
	write('testing(4) the agent, is high and team has lost the ball'),
	nl,
	print_field([4,3],[[5,3],[3,5],[5,17],[7,5],[5,9]],[[1,15],[4,3],[5,15],[5,17],[9,15]]),
	ttyflush,
	agent([[[4,3],_,1,3,M,W,L],[[5,3],[3,5],[5,17],[7,5],[5,9]],[[1,15],[4,3],[5,15],[5,17],[9,15]]]).

test5(M,W,L) :-
	write('testing(5) the agent, tries to score'),
	nl,
	print_field([5,17],[[5,3],[3,5],[5,17],[7,5],[5,9]],[[1,15],[4,3],[5,15],[5,17],[9,15]]),
	ttyflush,
	agent([[[5,17],_,1,3,M,W,L],[[5,3],[3,5],[5,17],[7,5],[5,9]],[[1,15],[4,3],[5,15],[5,17],[9,15]]]).

test6(M,W,L) :-
	write('testing(6) the agent, needs to get to support a pal in offence'),
	nl,
	print_field([5,9],[[5,3],[3,5],[5,17],[9,5],[5,8]],[[1,15],[4,3],[5,15],[5,17],[9,15]]),
	ttyflush,
	agent([[[5,9],_,1,4,M,W,L],[[5,3],[3,5],[5,17],[9,5],[5,8]],[[1,15],[4,3],[5,15],[5,17],[9,15]]]).

test7(M,W,L) :-
	write('testing(7) the agent, needs to get to support (inline with ball) defence'),
	nl,
	print_field([10,15],[[5,3],[3,5],[5,17],[9,5],[9,16]],[[1,15],[4,3],[5,15],[5,17],[9,15]]),
	ttyflush,
	agent([[[10,15],_,1,4,M,W,L],[[5,3],[3,5],[5,17],[9,5],[9,16]],[[1,15],[4,3],[5,15],[5,17],[9,15]]]).

test8(M,W,L) :-
	write('testing(8) the agent kicks forward a pass for itself'),
	nl,
	print_field([3,5],[[4,3],[3,5],[5,17],[9,6],[9,16]],[[1,15],[4,3],[5,15],[5,17],[9,15]]),
	ttyflush,
	agent([[[3,5],_,1,2,M,W,L],[[4,3],[3,5],[5,17],[9,6],[9,16]],[[1,15],[4,3],[5,15],[5,17],[9,15]]]).

test9(M,W,L) :-
	write('testing(9) the agent kicks sideways (absolute left field) a pass for itself'),
	nl,
	print_field([3,5],[[4,3],[3,5],[5,17],[9,6],[9,16]],[[1,15],[5,5],[3,7],[5,17],[9,15]]),
	ttyflush,
	agent([[[3,5],_,1,2,M,W,L],[[4,3],[3,5],[5,17],[9,6],[9,16]],[[1,15],[5,5],[3,7],[5,17],[9,15]]]).

test10(M,W,L) :-
	write('testing(10) the agent kicks sideways (absolute right field) a pass for itself'),
	nl,
	print_field([3,5],[[4,3],[3,5],[5,17],[9,6],[9,16]],[[1,15],[2,5],[3,7],[5,17],[9,15]]),
	ttyflush,
	agent([[[3,5],_,1,2,M,W,L],[[4,3],[3,5],[5,17],[9,6],[9,16]],[[1,15],[2,5],[3,7],[5,17],[9,15]]]).


test11(M,W,L) :-
	write('testing(11) the agent, no parallel pass to enemyshared pos'),
	nl,
	print_field([5,5],[[5,10],[3,10],[5,5],[7,5],[10,9]],[[1,15],[4,3],[5,15],[7,5],[9,15]]),
	ttyflush,
	agent([[[5,5],_,1,3,M,W,L],[[5,10],[3,10],[5,5],[7,5],[10,9]],[[1,15],[4,3],[5,10],[7,5],[9,15]]]).

test12(M,W,L) :-
	write('testing(12) the agent, copy of (4) make this a case of being lost'),
	nl,
	print_field([4,3],[[5,3],[3,5],[5,17],[7,5],[5,9]],[[1,15],[4,3],[5,15],[5,17],[9,15]]),
	ttyflush,
	agent([[[4,3],_,1,3,M,W,L],[[5,3],[3,5],[5,17],[7,5],[5,9]],[[1,15],[4,3],[5,15],[5,17],[9,15]]]).

% What do the players in team 2 do
test13(Player,M,W,L) :-
	write('testing(13) the agent, libero action'),
	nl,
	Ball = [5,15],
	We = [[5,3],[3,5],[5,5],[7,5],[5,5]],
	Them = [[5,15],[5,15],[5,10],[5,15],[5,15]],
	print_field(Ball,We,Them),
	ttyflush,
	agent([[Ball,_,2,Player,M,W,L],We,Them]).

test14(Player,M,W,L) :-
	write('testing(14) the agent, libero action 2'),
	nl,
	Ball = [5,15],
	We = [[5,3],[3,5],[5,5],[7,5],[5,10]],
	Them = [[5,15],[5,15],[5,10],[5,15],[5,15]],
	print_field(Ball,We,Them),
	ttyflush,
	agent([[Ball,_,2,Player,M,W,L],We,Them]).

test15(Player,M,W,L) :-
	write('testing(15) widening the game'),
	nl,
	Ball = [5,15],
	We = [[5,3],[3,5],[5,5],[7,5],[5,11]],
	Them = [[5,15],[5,15],[5,10],[5,15],[5,15]],
	print_field(Ball,We,Them),
	ttyflush,
	agent([[Ball,_,2,Player,M,W,L],We,Them]).

% 5,15 has distance 2 to ball
% 1,15 has distance 2 to line passing through the ball
% 4,9 has distance 3 to 1,10  
test16(Player,M,W,L) :-
	write('testing(16) anglepass'),
	nl,
	Ball = [5,13],
	We = [[5,3],[3,5],[5,5],[7,5],[5,9]],
	Them = [[5,15],[1,15],[6,12],[4,9],[6,15]],
%	print_field(Ball,We,Them),
%	ttyflush,
	agent([[Ball,_,2,Player,M,W,L],We,Them]).


test40(Player) :-
	Team1 = [[4,3],[3,5],[5,5],[7,5],[5,9]],
	Team2 = [[1,15],[4,5],[5,15],[7,15],[9,15]],
	print_field([5,5],Team1,Team2),
	clear_pass_line(1,Team1,Team2,3,Pal),
	nth1(Pal,Team1,Player).

test41(M) :-
	Team1 = [[4,3],[3,5],[5,5],[7,5],[5,9]],
	Team2 = [[1,15],[4,5],[5,15],[7,15],[9,15]],
	print_field([5,5],Team1,Team2),
	matex(1,3,Team1,Team2,M),
	clear_pass_line(1,Team1,Team2,3,M).

% give a ball position and get who in each team is closest to it
test42([BW,BL],BPal1,BPal2) :-
	Team1 = [[4,3],[3,5],[5,5],[7,5],[5,9]],
	Team2 = [[1,15],[4,5],[5,15],[7,15],[9,15]],
	print_field([5,5],Team1,Team2),
	ball_pal([BW,BL],Team1,BPal1),
	ball_pal([BW,BL],Team2,BPal2).


agent1([[[BW,BL],_,My_team,My_number, Move, Arg1, Arg2],Team1,Team2]) :-
	position(My_team,My_number,Team1,Team2,W,L),
	my_team(My_team,Team1,Team2,Team),
	opponent(My_team,Other_team),
	my_team(Other_team,Team1,Team2,OTeam),
	ball_pal([BW,BL],Team,[CW,CL]),
	ball_pal([BW,BL],OTeam,[OCW,OCL]),
	(abs(OCW-BW)+abs(OCL-BL)) > (abs(CW-BW)+abs(CL-BL)), % true manhattan stuff
	(   W \== CW ; L \== CL),
        member([W1,L1],Team),
        member(D1B,[2,3,4]);
        D1B is 2,
        fpath([W1,L1],[BW,BL],D1B),
        member([W2,L2],Team),
        (W1 \== W2, L1 \== L2),
        (W2N == BW ; L2N == BL), 
        fpath([W2,L2],[W2N,L2N],D1B),
        fpath([W2N,L2N],[BW,BL],D12),
        D12 > 3,
        D is D1B + 1,
        fpath([W,L],[WN,LN],D),
        fpath([WN,LN],[W2N,L2N],D2Me),
        D2Me > 3,
        fpath([WN,LN],[W1,L1],D1Me),
        D1Me > 4,
	DL is LN - L,    
	DW is WN - W,
	((abs(DW) < abs(DL) ->  
	 Arg1 is sign(DW),
	  Arg2 is 0)
	; 
	(
	Arg2 is sign(DL),
	 Arg1 is 0)),
	nl,
	write(My_team),
	write(' '),
	write(My_number),
	write(' ... anglepass (2)'),
	write(Arg1),
	write(' '),
	write(Arg2),
	nl,
	ttyflush,
	Move is 3, 
	!.





