1%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
    2%
    3%  FILE     : Env/mess_server.pl
    4%
    5%  AUTHOR : Sebastian Sardina (2003)
    6%  EMAIL  : ssardina@cs.toronto.edu
    7%  WWW    : www.cs.toronto.edu/~ssardina www.cs.toronto.edu/cogrobo
    8%  TYPE   : system dependent code
    9%  TESTED : SWI Prolog 5.0.10 www.swi-prolog.org
   10%
   11% An environment to communicate among multiple agents
   12%
   13% To compile it to an executable, run pl -q, consult file [mess_server] and run:
   14%
   15% 	qsave_program(mess,[toplevel(start),stand_alone(true),class(runtime)]).
   16%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
   17%
   18%                             November 15, 2002
   19%
   20% This software was developed by the Cognitive Robotics Group under the
   21% direction of Hector Levesque and Ray Reiter.
   22%
   23%        Do not distribute without permission.
   24%        Include this notice in any copy made.
   25%
   26%
   27%         Copyright (c) 2000 by The University of Toronto,
   28%                        Toronto, Ontario, Canada.
   29%
   30%                          All Rights Reserved
   31%
   32% Permission to use, copy, and modify, this software and its
   33% documentation for non-commercial research purpose is hereby granted
   34% without fee, provided that the above copyright notice appears in all
   35% copies and that both the copyright notice and this permission notice
   36% appear in supporting documentation, and that the name of The University
   37% of Toronto not be used in advertising or publicity pertaining to
   38% distribution of the software without specific, written prior
   39% permission.  The University of Toronto makes no representations about
   40% the suitability of this software for any purpose.  It is provided "as
   41% is" without express or implied warranty.
   42% 
   43% THE UNIVERSITY OF TORONTO DISCLAIMS ALL WARRANTIES WITH REGARD TO THIS
   44% SOFTWARE, INCLUDING ALL IMPLIED WARRANTIES OF MERCHANTABILITY AND
   45% FITNESS, IN NO EVENT SHALL THE UNIVERSITY OF TORONTO BE LIABLE FOR ANY
   46% SPECIAL, INDIRECT OR CONSEQUENTIAL DAMAGES OR ANY DAMAGES WHATSOEVER
   47% RESULTING FROM LOSS OF USE, DATA OR PROFITS, WHETHER IN AN ACTION OF
   48% CONTRACT, NEGLIGENCE OR OTHER TORTIOUS ACTION, ARISING OUT OF OR IN
   49% CONNECTION WITH THE USE OR PERFORMANCE OF THIS SOFTWARE.
   50% 
   51%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
   52:- set_prolog_flag(backquoted_string, true).   53
   54
   55% define how many agent connections will be allowed
   56max_no_agents(10).
   57
   58server(Port) :-
   59	report(['Starting MESSENGER server at port:',Port]),
   60	retractall(agent(_,_,_,_)),
   61	%	
   62        tcp_socket(Socket),
   63        catch(tcp_bind(Socket, Port),_,fail),
   64	max_no_agents(NoAgents),	% how many agents can connect?
   65        tcp_listen(Socket, NoAgents),
   66        tcp_open_socket(Socket, In, _Out),
   67        add_stream_to_pool(In, accept_new_agent(Socket)),
   68        stream_pool_main_loop.
   69
   70
   71
   72accept_new_agent(Socket) :-
   73        tcp_accept(Socket, Slave, PeerIP),
   74        tcp_open_socket(Slave, In, Out),
   75	report(['Adding a new agent from IP: ', PeerIP]),
   76	assert(agent(noname,In,Out,PeerIP)),	% register connection of agent
   77        add_stream_to_pool(In, handle_client(In)).
   82handle_client(In) :-
   83	agent(Agent,In,_,_),
   84	catch(at_end_of_stream(In),E,
   85		(report(['Cannot check if stream is EOF: ',(Agent,In),'--> ',E]),
   86		fail)),
   87	report(['End of file on ',(Agent,In)]),
   88	handle_message(In, unregister).
   89
   90handle_client(In) :-
   91	agent(Agent,In,_,_),
   92	catch(read_term(In, Message, [double_quotes(string)]),E,
   93			report(['Cannot read from ',(Agent,In),'---> ',E])),
   94	report(['Message from ',(Agent,In),' : ',Message]),
   95        handle_message(In, Message).
   96handle_client(_).
  102handle_message(In, unregister) :-
  103	unregister_agent(In).
  104
  105handle_message(In, end_of_file) :-
  106	unregister_agent(In).
  107
  108handle_message(In, register(SAgent)) :-
  109	retract(agent(_,In,Out,PeerIP)),
  110	string_to_atom(SAgent,Agent),
  111	assert(agent(Agent,In,Out,PeerIP)),
  112	tell(server,Agent,ok),
  113	report(['Agent ',Agent,' registered']).
  114
  115handle_message(In, tell(STo,Message)) :-
  116	agent(AgentSrc,In, _, _),
  117	AgentSrc\=noname,
  118	string_to_atom(STo,To),
  119	tell_all(AgentSrc, [To], Message).
  120
  121handle_message(In, broadcast(Message)) :-
  122	agent(AgentSrc,In,_,_),
  123	AgentSrc\=noname,
  124	findall(AgentRcv, (agent(AgentRcv,_,_,_),AgentRcv\=AgentSrc), LAgents),
  125	tell_all(AgentSrc,LAgents,Message).
  126
  127handle_message(In,_) :-
  128	at_end_of_stream(In),
  129	unregister_agent(In).
  130	
  131
  132handle_message(In,Mess) :- 
  133	report(['*************************** Message cannot be handled: ',In, ' - ',Mess]).
  134
  135
  136
  137
  138% TOOLS
  139unregister_agent(In) :-
  140	retract(agent(Agent,In,Out,_PeerIP)),
  141        delete_stream_from_pool(In),
  142	close_socket(In),
  143        close_socket(Out),
  144	report(['Agent ',Agent,' unregistered']).
  145
  146
  147tell(AgentSrc, AgentRcv, Message) :-
  148	agent(AgentRcv,_,Out,_),
  149        write_term(Out, told(AgentSrc,Message), [quoted(true)]),
  150        write(Out, '.'),
  151        nl(Out),
  152        flush_output(Out).
  153
  154tell_all(_,[],_).
  155tell_all(AgentSrc,[AgentRcv|LAgents],Message) :-
  156	catch(tell(AgentSrc, AgentRcv, Message),E,writeln(E)),
  157	tell_all(AgentSrc,LAgents,Message).
  158
  159
  160
  161% Tries to close socket X but catches the exception if not possible
  162close_socket(X) :- catch(close(X),E,report([E])).
  163
  164
  165% report(L): print out list of terms in L
  166report([]) :- nl.
  167report([M|L]) :- write(M), report(L).
  168
  169
  170
  171
  172
  173
  174
  175
  176% start server now at the corresponding port!
  177%:- server(5001).
  178
  179% run the server reading the port number from the 1st argument on the command line
  180start :- run_server_arg.
  181run_server_arg :- 
  182	current_prolog_flag(argv, [_, Port|_]),
  183	catch(atom_number(Port,PortN),_,fail), !,
  184	server(PortN).
  185run_server_arg :- 
  186	report(['First argument has to be the port number to listen to (e.g., ./mess 5001)']),
  187	halt.
  188	
  189
  190
  191
  192
  193%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  194% EOF:  Env/mess_server.pl
  195%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%