1%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
    2%
    3% FILE: Wumpus/main_swi.pl
    4%
    5%  AUTHOR    : Stavros Vassos & Sebastian Sardina
    6%  email     : {stavros,ssardina}@cs.toronto.edu
    7%  WWW       : www.cs.toronto.edu/cogrobo
    8%  TESTED    : SWI Prolog 4.0.5 under RedHat Linux 6.2/7.1 
    9%  TYPE CODE : system dependent predicates
   10%
   11% DESCRIPTION: This file is the main file of an IndiGolog application
   12%              of the Wumpus World.
   13%
   14% Written for SWI Prolog http://www.swi-prolog.org/) running under Linux
   15%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
   16%
   17%                             June 15, 2000
   18%
   19% This software was developed by the Cognitive Robotics Group under the
   20% direction of Hector Levesque and Ray Reiter.
   21%
   22%        Do not distribute without permission.
   23%        Include this notice in any copy made.
   24%
   25%
   26%         Copyright (c) 2000 by The University of Toronto,
   27%                        Toronto, Ontario, Canada.
   28%
   29%                          All Rights Reserved
   30%
   31% Permission to use, copy, and modify, this software and its
   32% documentation for non-commercial research purpose is hereby granted
   33% without fee, provided that the above copyright notice appears in all
   34% copies and that both the copyright notice and this permission notice
   35% appear in supporting documentation, and that the name of The University
   36% of Toronto not be used in advertising or publicity pertaining to
   37% distribution of the software without specific, written prior
   38% permission.  The University of Toronto makes no representations about
   39% the suitability of this software for any purpose.  It is provided "as
   40% is" without express or implied warranty.
   41% 
   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% This is the top-level file for a Legolog application program.
   53% It consults all the necessary Legolog prolog files.
   54% In particular, the following is loaded:
   55%
   56%  (1) Load all libraries required. This includes the system dependant
   57%      ones for the specific Prolog plus general libraries
   58%  (2) Load the IndiGolog interpreter and the projector used
   59%  (3) Load the application code itself containing the background theory
   60%      of action plus the high-level program
   61%  (4) Specify which environments should be loaded and how 
   62%  (5) Specify how each action should be executed and how to translate
   63%      exogenous actions
   64%
   65% Moreover, the following is provided:
   66%
   67% -- main: Collects all the procedures named 'mainControl(id)' 
   68%	   and asks the user which one to run. Uses controller/1
   69%
   70%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
   71
   72
   73%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
   74% SET GLOBAL PARAMETERS AND GLOBAL VARIABLES/CONSTANTS USED
   75%  
   76%  These may be options to improve performance and variables/constants used
   77%  around the whole arquitecture
   78%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%	
   79:- dynamic controller/1.	% Stores the user decision on the controller to run
   80
   81:- ensure_loaded('../../lib/logicmoo_workarounds').   82
   83%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
   84% (1) LOAD/COMPILE/IMPORT LIBRARIES, MODULES, ETC that may be required.
   85%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
   86:- include('../../lib/systemvar'). % Global include code and Prolog init
   87:- consult('../../lib/alpha_star'). % Alpha* path finding
   88%:- use_module(library(chr)).
   89%:- reset_backquoted_string.
   90
   91
   92%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
   93% (2,3) CONSULT NECESSARY FILES
   94%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
   95
   96% 1 - Consult the IndiGolog system: top-level and evaluator
   97:- consult('../../Interpreters/indigolog').     % IndiGolog interpreter 
   98:- consult('../../Eval/eval_know').               % LP evaluator
   99
  100% 2 - Consult environment manager 
  101:- consult(['../../Env/env_man.pl']).         % Load environment manager
  102
  103% 3 - Consult application
  104:- consult(wumpus).                          % Application code in IndiGolog
  105
  106
  107
  108
  109%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  110% (4,5) ENVIRONMENTS TO LOAD
  111%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  112:- dynamic wumpus_config/5.  113
  114% In this example the environment manager host:port is fixed
  115server_host('localhost').
  116server_port(_).
  117
  118wumpus_config(indigolog(default),8,10,1,random).  % Default conf: 
  119%wumpus_config(indigolog(default),8,10,1,indigolog(default)). 
  120%wumpus_config(indigolog(default),8,10,1,none).  
  121%wumpus_config(rerun(82),8,10,1,nmar05test(82)).  % Default conf: 
  122
  123% Load simulator, RCX and internet environments
  124:- ['../../Env/dev_managers'].              % Common facts (device_manager/4)
  125load_device(Env, Command, Address) :- 
  126       %  member((Env,Type), [(virtual_wumpus_silent, swi)]),
  127         member((Env,Type), [(virtual_wumpus, swi)]),  
  128       %  member((Env,Type), [(virtual_wumpus_vworld, swi)]),  
  129       % use virtual_wumpus to get the xterm console
  130        (var(Address) -> 
  131             Host=null, Port=null ; 
  132             Address = [Host, Port]
  133        ),
  134        device_manager(Env, Type, Command, [Host, Port]).
  135
  136
  137%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  138% HOW TO EXECUTE ACTIONS: Environment + low-level Code 
  139%        how_to_execute(Action, Environment, Code)     
  140%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  141how_to_execute(Action, virtual_wumpus, Action).
  142%how_to_execute(Action, virtual_wumpus_silent, Action).
  143%how_to_execute(Action, virtual_wumpus_vworld, Action).
  144
  145
  146%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  147%   EXOGENOUS ACTION AND SENSING OUTCOME TRANSLATION   
  148%          translateExogAction(Code, Action)           
  149%          translateSensing(Action, Outcome, Value)    
  150% OBS: If not present, then the translation is 1-1
  151%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  152translateExogAction(CodeAction, Action) :-  actionNum(Action, CodeAction).
  153%translateSensing(_, SensorValue, SensorValue).
  154
  155
  156%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  157% MAIN PREDICATE - evaluate this to run demo
  158%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  159
  160% main/0: Gets IndiGolog to evaluate a chosen mainControl procedure
  161main4:- retractall(controller(_)),
  162	bagof(X,Y^proc(mainControl(X),Y),L),
  163    	(L=[NoContr] -> 
  164		assert(controller(NoContr))
  165    	;
  166        	write('Available Controllers: '), write(L), nl,
  167         	write('Which controller do you want to execute? '), 
  168        	read(NoContr), 
  169	 	assert(controller(NoContr))
  170    	),
  171	indigolog.
  172
  173
  174main:- retractall(controller(_)),
  175	bagof(X,Y^proc(mainControl(X),Y),L),
  176    	(L=[NoContr] -> 
  177		assert(controller(NoContr))
  178    	;
  179        	write('Available Controllers: '), write(L), nl,
  180         	write('Which controller do you want to execute? '), 
  181        	NoContr = 4, 
  182	 	assert(controller(NoContr))
  183    	),
  184	indigolog.
  185
  186
  187
  188full_test :-
  189	member(Size,[8]),
  190	member(PPits,[10,15,20,30,40]),
  191	member(NoGolds,[1,2,4]),
  192	writeln('=================================================='),
  193	write('TEST WUMPUS: '), write((Size,PPits,NoGolds)), nl,
  194	once(retract(wumpus_config(_,_,_,_,_))),
  195	once(retract(gridsize(_))),
  196	assert(gridsize(Size)),
  197		% Set up Size, PPits and NoGolds (only)
  198	assert(wumpus_config(test,Size,PPits,NoGolds,scenario)),
  199	test(301,1),
  200	fail.
  201full_test :- 
  202	writeln('=================================================='),
  203	writeln('DONE!').
  204
  205
  206% test Wumpus Max number of times repetitively
  207test(Max,Max) :-!, 
  208	writeln('FINISHED TESTING....').
  209test(Max,N) :-
  210	write('TESTING INSTANCE: '), write(N),
  211	write(' (Out of '), write(Max), write(' runs)'), nl,
  212	tell('/dev/null'),
  213	retract(wumpus_config(_,Size,PPits,NoGolds,_)),
  214		% Assert the type of execution it is going to be done next!
  215%	assert(wumpus_config(evalnocut(N),Size,PPits,NoGolds,testnewholds(N))),
  216	assert(wumpus_config(nmar05test(N),Size,PPits,NoGolds,random)),
  217	indigolog(mainControl(4)),
  218	sleep(1),
  219	tell(user),
  220	N2 is N+1,
  221	test(Max, N2).
  222
  223
  224
  225%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  226% PREDICATES WITH SYSTEM DEPENDENT CODE
  227%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  228
  229:- set_option(debug_level,4).  230:- set_option(wait_step,0).  231%:- set_option(debug_level,warn_off).
  232
  233
  234
  235%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  236% EOF: Wumpus/main_swi.pl
  237%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  238
  239:-main.