1%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
    2%
    3% FILE: Env/env_man.pl
    4%
    5%
    6%  AUTHOR : Sebastian Sardina (2004-2006)
    7%  EMAIL  : ssardina@cs.toronto.edu
    8%  WWW    : www.cs.toronto.edu/~ssardina www.cs.toronto.edu/cogrobo
    9%  TYPE   : system dependent code (SWI or ECLIPSE Prolog)
   10%  TESTED : ECLiPSe 5.3 on RedHat Linux 6.2-9.0
   11%                SWI Prolog 5.2.8 under RedHat Linux 6.2/9.0
   12%
   13% DESCRIPTION: The environment manager deals with many multiple devices
   14% by communicating with them via TCP/IP sockets
   15%
   16%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
   17%
   18%                             September, 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-2002 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% THE UNIVERSITY OF TORONTO DISCLAIMS ALL WARRANTIES WITH REGARD TO THIS
   43% SOFTWARE, INCLUDING ALL IMPLIED WARRANTIES OF MERCHANTABILITY AND
   44% FITNESS, IN NO EVENT SHALL THE UNIVERSITY OF TORONTO BE LIABLE FOR ANY
   45% SPECIAL, INDIRECT OR CONSEQUENTIAL DAMAGES OR ANY DAMAGES WHATSOEVER
   46% RESULTING FROM LOSS OF USE, DATA OR PROFITS, WHETHER IN AN ACTION OF
   47% CONTRACT, NEGLIGENCE OR OTHER TORTIOUS ACTION, ARISING OUT OF OR IN
   48% CONNECTION WITH THE USE OR PERFORMANCE OF THIS SOFTWARE.
   49% 
   50%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
   51%
   52% The following system independent predicates are provided:
   53%
   54% -- initialize_EnvManager
   55% -- finalize_EnvManager
   56% -- execute_action(A, H, T, S) : execute action A of type T at history H
   57%                                 and resturn sensing outcome S
   58% -- exog_occurs(LA)		: return a list LA of exog. actions that
   59%				  have occurred (synchronous)
   60% -- indi_exog(Action)          : asserted whenever exog Action occurred
   61% -- set_type_manager(+T)       : set the implementation type of the env manager
   62%
   63%
   64% The following code is required:
   65%
   66% FROM THE INDIGOLOG MAIN CYCLE:
   67%
   68% -- doing_step : IndiGolog is thinking a step
   69% -- abortStep  : abort the computation of the current step
   70% -- exog_action_occurred(LExoAction) 
   71%               : to report a list of exog. actions LExogAction to the top-level
   72%
   73% FROM THE DOMAIN DESCRIPTOR:
   74%
   75% -- server_port(Port)       
   76%	Port to set up the environment manager
   77% -- load_device(Env, Command, Options) 
   78%     	for each environemnt to be loaded
   79% -- how_to_execute(Action, Env, Code)
   80%       Action should be executed in environment Env with using code Code
   81% -- translateExogAction(Code, Action)  
   82%	Code is action Action
   83% -- exog_action(Action) 
   84%	Action is an exogenous action
   85%
   86% ELSEWHERE:
   87%
   88% -- report_message(T, M)       : report messsage M of type T
   89% -- send_data_socket/2
   90% -- receive_list_data_socket/2
   91%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
   92:- dynamic 
   93	got_sensing/2,      % stores sensing outcome for executed actions
   94	got_exogenous/1,    % stores occurred exogenous actions
   95	counter_actions/1,  % Carries a counter for each action performed
   96	env_data/3,         % (Env name, Pid, Socket) of each device
   97	executing_action/3, % Stores the current action being executed
   98	translateExogAction/2,
   99	translateSensing/3, % Translates sensing outcome to high-level sensing
  100	how_to_execute/3,   % Defines how to execute each high-level action
  101	type_manager/1,     % Defines the implementation type of the manager
  102	server_port/1,
  103	server_host/1.	    % Host and port for the environment manager
  104
  105%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  106% CONSTANTS
  107%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  108
  109name_env(manager).   % We are the "environment manager"
  110counter_actions(0).  % Counter for (executed) actions
  111
  112set_option('type_em : set type of environment manager: thread or signal').
  113set_option(type_em, T) 	:- 
  114	set_type_manager(T),
  115	report_message(system(0), ['** EM fixed to ', T]).
  116
  117
  118% Set the type of the environment manager: thread or signal based
  119set_type_manager(T) :- 
  120	atom(T),
  121	member(T, [thread,signal]),
  122        report_message(system(2), 
  123                       ['(EM) Setting environment manager type to: ',T]), 
  124        retractall(type_manager(_)), 
  125        assert(type_manager(T)).
  126set_type_manager(_) :- 
  127        report_message(warning, '(EM) Type of env. manager cannot be set!').
  128
  129type_manager(thread). % Default execution for the env. manager
  130
  131
  132%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  133% INITIALIZATION AND FINALIZATION PART
  134%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  135
  136% A - Initialize environment manager
  137initializeEM :- 
  138          report_message(system(2), '(EM) 1 - Resetting the number of actions...'),
  139	retractall(counter_actions(_)),
  140	assert(counter_actions(0)),
  141          report_message(system(1), '(EM) 2 - Openinig server-input socket...'),
  142    socket(internet, stream, em_socket), % signal when data comes
  143		% Build the Address where the manager will be listeling
  144	(server_host(ServerHost2) -> true ; gethostname(ServerHost2)),
  145    string_to_atom(ServerHost2, ServerHost),
  146    server_port(ServerPort),
  147    Address=ServerHost/ServerPort,
  148    bind(em_socket, Address),
  149    report_message(system(1), bind(em_socket, Address)),
  150          report_message(system(1),'(EM) 3 - Loading different devices...'),
  151    findall(Env, load_device(Env,_, _), LEnv),
  152    (LEnv=[] ->
  153               	report_message(warning,'(EM) No devices defined to load!') 
  154	;
  155				report_message(system(2),['(EM) Devices to load: '|LEnv])            
  156	),
  157    length(LEnv, LengthLEnv),
  158    listen(em_socket, LengthLEnv),
  159    start_env(LEnv, Address), !, % Start each of the devices used (LEnv)
  160          report_message(system(2),'(EM) 4 - Start EM cycle...'),
  161    type_manager(Type),
  162	start_env_cycle(Type).   % Start the env. manager main cycle
  163
  164
  165% The finalization of the EM involves:
  166%	1 - Close all the open device managers
  167%	2 - Terminate EM cycle
  168%	3 - Close EM server socket em_socket
  169%	4 - Report the number of actions that were executed
  170finalizeEM :- 
  171    	report_message(system(2),'(EM) 1 - Closing all device managers...'),
  172    setof(Dev, X^Y^env_data(Dev, X, Y), LDev), % Get all current open devices
  173	close_dev(LDev),	% Close all the devices found
  174	sleep(3), 			% Wait to give time to devices to finish cleanly
  175		!, report_message(system(2), '(EM) 2 - Terminating EM cycle...'), 
  176	catch(wait_for_children,_,true),
  177    type_manager(Type),
  178	finish_env_cycle(Type),   	% Terminate main env. manager cycle
  179		!, report_message(system(2),'(EM) 3 - Closing EM server socket...'), 
  180    safe_close(em_socket),		% Disconnect server socket
  181		!, report_message(system(2),'(EM) 4 - All finished...'),
  182    counter_actions(N),
  183    report_message(system(1),
  184       	['(EM) Finalization of EM completed with *', N, '* executed actions.']).
  185
  186
  187wait_for_children :-
  188	wait(PId, S), !,
  189	(ground(S) -> true ; S=free),
  190        report_message(system(3), ['(EM) Successful proccess waiting: ',(PId,S)]),
  191	wait_for_children.
  192wait_for_children.
  193
  194% Close a stream and always succeed
  195safe_close(StreamId) :-
  196        catch_succ(myclose(StreamId), ['Could not close socket ', StreamId]).
  197myclose(Id) :- close(Id).
  198
  199
  200
  201% B - Initialization and Finalization of the environment manager main cycle
  202%		start_env_cycle/0  : starts EM cycle
  203%		finish_env_cycle/0 : terminates EM cycle
  204%       The EM cycle basically waits for data arriving to any of the open
  205%       connections to the device managers. When it receives a message
  206%	(e.g., sensing outcome, exog. action, closing message) it hanldes it.
  207
  208% B.1 THREAD IMPLEMENTATION (multithreading Prologs like SWI)
  209%	 There is a separated thread to handle incoming data. The thread
  210%	 should BLOCK waiting for data to arrive
  211start_env_cycle(thread) :- 
  212	thread_create(catch(em_cycle_thread,E,
  213		(E=finish -> 
  214		 	report_message(system(2),'(EM) EM cycle finished successfully')
  215		; 
  216		 	report_message(error,['EM Thread Error:',E])
  217		)),_,[alias(em_thread)]).
  218em_cycle_thread :- em_one_cycle(block), !, em_cycle_thread.
  219em_cycle_thread :-	 % if em_one_cycle/1 has nothing to wait, then just terminate
  220	 	report_message(system(5),'(EM) EM cycle finished, no more streams to wait for...').
  221
  222
  223finish_env_cycle(thread) :-
  224	(current_thread(em_thread, running) -> 
  225		% Signal thread explicitly to finish!
  226		thread_signal(em_thread, throw(finish))  
  227	;
  228		% The thread has already finished (because all devices were closed)
  229		true
  230	), 
  231	thread_join(em_thread,_),
  232	report_message(system(3),'(EM) Environment cycle (thread) finished').  
  233
  234
  235
  236
  237% C - em_one_cycle/1 : THIS IS THE MOST IMPORTANT PREDICATE FOR THE EM CYCLE
  238%
  239% 	em_one_cycle(HowToWait) does 1 iteration of the waiting cycle and
  240%	waits HowMuchToWait (seconds) for incoming data from the devices
  241% 	If HowMuchToWait=block then it will BLOCK waiting... (good for threads)
  242em_one_cycle(HowMuchToWait) :-
  243	report_message(system(5),'(EM) Waiting data to arrived at env. manager (block)'),
  244	% Get all the read-streams of the environments sockets
  245	setof(Socket, X^Y^env_data(X, Y, Socket), ListSockets),
  246	% Check which of these streams have data waiting, i.e., the "ready" ones
  247	report_message(system(5), ['(EM) Blocking on environments:: '|ListSockets]),
  248	stream_select(ListSockets, HowMuchToWait, ListSocketsReady),   !, % BLOCK or wait?
  249	% Get back the name of the environments of these "ready" streams
  250	setof(Env, S^X^(member(S, ListSocketsReady),
  251			env_data(Env, X, S)), ListEnvR),
  252	report_message(system(5), ['(EM) Handling messages in devices:: '|ListEnvR]),
  253	% Next, read all the events waiting from these devices
  254	get_events_from_env(ListEnvR, ListEvents),
  255	% Finally, handle all these events
  256	handle_levents(ListEvents).
  257
  258% Given a list of devices that have information on their sockets
  259% collect all the data from them
  260get_events_from_env([], []).
  261get_events_from_env([Env|LEnv], TotalListEvents) :-
  262        env_data(Env, _, SocketEnv),
  263        receive_list_data_socket(SocketEnv, LEventsEnv),
  264        get_events_from_env(LEnv, RestEvents),
  265        append(LEventsEnv, RestEvents, TotalListEvents).
  266
  267
  268%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  269% handle_levents(+LE,-LT): handle list of events LE and return their 
  270%                        types in list LT
  271%
  272% Up to now, events are either a exogenous events or unknown events.
  273%
  274% First handle all events. Then, if there were exogenous event report them
  275% in a list to top-level cycle with exog_action_occurred/1
  276%
  277% 2) Unknown Event: just inform it with message
  278%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  279% Prioritized serving of a list of occurred events
  280
  281% 1 - First serve sensing outcomes 
  282handle_levents(L) :-
  283	member([Sender,[sensing, N, Outcome]], L),
  284	handle_event([Sender,[sensing, N, Outcome]]),
  285	fail.
  286
  287% 2 - Second serve exogenous actions
  288handle_levents(L) :-
  289	member([Sender,[exog_action, CodeAction]], L),
  290	handle_event([Sender,[exog_action, CodeAction]]),
  291	fail.
  292
  293% 3 - Third serve other events
  294handle_levents(L) :-
  295	member([Sender,[T|R]], L),
  296	\+ member(T, [sensing, exog_action]),
  297	handle_event([Sender,[T|R]]),
  298	fail.
  299
  300% 4 - Finally, signal exog_action_occurred/1 if there were exogenous actions
  301handle_levents(_) :-
  302	findall(ExoAction, got_exogenous(ExoAction), LExoAction),
  303	LExoAction\=[],                   % There were exogenous actions
  304	retractall(got_exogenous(_)),
  305	exog_action_occurred(LExoAction), % Report all the actions to top-level
  306	fail.
  307
  308% 5 - Always succeeds as the last step
  309handle_levents(_).
  310
  311
  312
  313
  314
  315
  316
  317
  318
  319% handle_event/1: Handle each *single* event
  320handle_event([_, [sensing, N, OutcomeCode]]) :- !, 
  321	executing_action(N, Action, _),
  322	(translateSensing(Action, OutcomeCode, Outcome) ->  true ; Outcome=OutcomeCode),
  323	assert(got_sensing(N, Outcome)),
  324		report_message(system(5),
  325			['(EM) Sensing outcome arrived for action ',
  326			(N, Action), ' - Sensing Outcome:: ',(OutcomeCode,Outcome)]).
  327
  328handle_event([_, [exog_action, CodeAction]]):- 
  329	(translateExogAction(CodeAction, Action) -> true ; Action=CodeAction),
  330    exog_action(Action), !,
  331	assert(got_exogenous(Action)),
  332        report_message(system(5),
  333	               ['(EM) Exogenous action occurred:: ', (CodeAction, Action)]).
  334
  335handle_event([socket(Socket), [_, end_of_file]]) :- !,  % Env has been closed! 
  336        env_data(Env, _,Socket),                        % remove it
  337        report_message(system(2),['(EM) Device ',Env,' has reported termination!']),
  338        delete_dev(Env).
  339
  340handle_event([Sender, [Type, Message]]):- !, % The event is unknown but with form
  341        report_message(system(5), 
  342        	['(EM) UNKNOWN MESSAGE! Sender: ', Sender,
  343                                   ' ; Type: ' ,Type,' ; Message: ', Message]).
  344
  345handle_event(Data):-                         % The event is completely unknown
  346        report_message(system(5), ['(EM) UNKNOWN and UNSTRUCTURED MESSAGE!:: ', Data]).
  347
  348
  349
  350%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  351% START AND CLOSE DEVICE MANAGERS
  352%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  353
  354% start_env(LEnv, Address) : starts a list of device managers
  355%
  356%  each device is started in a separate xterm window. We pass the 
  357%  Address so that the device knows where to send its data
  358%  Also we receive from the device its address to know where to
  359%  send data to it. 
  360%  env_data/3 stores the Pid and Address of each device started
  361start_env([], _).
  362start_env([Env|LEnv], Address) :-
  363	Address = Host/Port,
  364	load_device(Env, Command, [Host,Port]),
  365	call_to_exec(unix, Command, Command2), % Select right command for exec
  366		report_message(system(5), ['(EM) Command to initialize device ', Env, ': ', Command2]),
  367	exec_group(Command2, [], Pid),
  368	accept(em_socket, From, Env), % Wait until the device connects to socket em_socket  
  369		report_message(system(1), ['(EM) Device ', Env, ' initialized at: ', From]),
  370	assert(env_data(Env, Pid, Env)),
  371	start_env(LEnv, Address).
  372
  373% Tell each device to terminate
  374close_dev([]).
  375close_dev([Env|LEnv]) :-
  376        send_data_socket(Env, [terminate]), % Tell device to terminate
  377        % (delete_dev(Env) -> true ; true),   % not needed, will be deleted automatically
  378        close_dev(LEnv).
  379
  380% Delete all information wrt device Env.
  381% delete_dev/1 is called automatically when the device has reported to be terminated
  382delete_dev(Env) :-
  383        retract(env_data(Env, Pid, SocketEnv)),
  384        %catch((wait(Pid, S) -> true ; true),E,true),
  385	(ground(S) -> true ; S=free),
  386       	report_message(system(3),['(EM) Environment *',Env,'* deleted!',
  387       				  ' - Waiting result: ',(Pid, S)]),
  388        safe_close(SocketEnv).	% Disconnect server socket
  389
  390
  391
  392	
  393
  394
  395%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  396% EXECUTION OF ACTIONS SECTION
  397%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  398
  399% Tell the corresponding device to execute an action
  400% how_to_execute/3 says how (which device and which action code) to
  401%    execute a high-level action
  402% if the action is a sensing action, it waits until observing its outcome
  403execute_action(Action, H, Type, N2, Outcome) :-
  404		% Increment action counter by 1 and store action information
  405	retract(counter_actions(N)),
  406	N2 is N+1,
  407	assert(counter_actions(N2)),	% Update action counter
  408	assert(executing_action(N2, Action, H)), % Store new action to execute
  409		% Learn how Action should be executed (Env, Code of action)
  410	map_execution(Action, Env, Code),   % From domain spec
  411		% Send "execute" message to corresponding device
  412	report_message(system(2), 
  413		['(EM) Start to execute the following action: ',(N2, Action, Env, Code)]),
  414	env_data(Env, _, SocketEnv),
  415	send_data_socket(SocketEnv, [execute, N2, Type, Code]),
  416	report_message(system(3),
  417		['(EM) Action ',N2,' sent to device ',Env,' - Waiting for sensing outcome to arrive']),!,
  418		% Busy waiting for sensing outcome to arrive (ALWAYS)
  419	repeat,   
  420	got_sensing(N2, Outcome),
  421	retract(executing_action(N2, _, _)),
  422	retract(got_sensing(N2, _)), !,
  423	report_message(system(2), 
  424		['(EM) Action *', (N2, Action, Env, Code), '* completed with outcome: ',Outcome]).
  425execute_action(_, _, _, N, failed) :- counter_actions(N).
  426
  427
  428% Find an adequate device manager that can execute Action and it is active
  429map_execution(Action, Env, Code) :-
  430        how_to_execute(Action, Env, Code),
  431        env_data(Env, _, _), !.  % The device is running 
  432% Otherwise, try to run Action in the simulator device 
  433map_execution(Action, simulator, Action) :- env_data(simulator, _, _), !.
  434
  435% Otherwise, try to run Action in the simulator device 
  436map_execution(Action, _, _) :-
  437        report_message(warning, ['(EM) Action *', Action, 
  438	                      '* cannot be mapped to any device for execution!']),
  439	fail.
  440
  441
  442
  443
  444% Exogenous actions are handled async., so there is no need to handle
  445% sync. exogenous actions. It is always empty.
  446exog_occurs([]).
  447
  448%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  449% EOF:  Env/env_man.pl
  450%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%