1%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
    2%
    3% FILE: Elevator/main_ecl.pl
    4%
    5%  Author    : Sebastian Sardina
    6%  Time-stamp: <03/03/31 20:14:37 ssardina>
    7%  email     : ssardina@cs.toronto.edu
    8%  WWW       : www.cs.toronto.edu/~ssardina
    9%  TESTED    : ECLiPSe 5.5 on RedHat Linux 6.2-8.0
   10%  TYPE CODE : system independent predicates
   11%
   12% DESCRIPTION: This file is the main file of an IndiGolog application
   13%              delivery controller with conditional search and planning 
   14%
   15% Written for ECLiPSe Prolog (http://www.icparc.ic.ac.uk/eclipse/)
   16% running under Linux
   17%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
   18%
   19%                             June 15, 2000
   20%
   21% This software was developed by the Cognitive Robotics Group under the
   22% direction of Hector Levesque and Ray Reiter.
   23%
   24%        Do not distribute without permission.
   25%        Include this notice in any copy made.
   26%
   27%
   28%         Copyright (c) 2000 by The University of Toronto,
   29%                        Toronto, Ontario, Canada.
   30%
   31%                          All Rights Reserved
   32%
   33% Permission to use, copy, and modify, this software and its
   34% documentation for non-commercial research purpose is hereby granted
   35% without fee, provided that the above copyright notice appears in all
   36% copies and that both the copyright notice and this permission notice
   37% appear in supporting documentation, and that the name of The University
   38% of Toronto not be used in advertising or publicity pertaining to
   39% distribution of the software without specific, written prior
   40% permission.  The University of Toronto makes no representations about
   41% the suitability of this software for any purpose.  It is provided "as
   42% is" without express or implied warranty.
   43% 
   44% THE UNIVERSITY OF TORONTO DISCLAIMS ALL WARRANTIES WITH REGARD TO THIS
   45% SOFTWARE, INCLUDING ALL IMPLIED WARRANTIES OF MERCHANTABILITY AND
   46% FITNESS, IN NO EVENT SHALL THE UNIVERSITY OF TORONTO BE LIABLE FOR ANY
   47% SPECIAL, INDIRECT OR CONSEQUENTIAL DAMAGES OR ANY DAMAGES WHATSOEVER
   48% RESULTING FROM LOSS OF USE, DATA OR PROFITS, WHETHER IN AN ACTION OF
   49% CONTRACT, NEGLIGENCE OR OTHER TORTIOUS ACTION, ARISING OUT OF OR IN
   50% CONNECTION WITH THE USE OR PERFORMANCE OF THIS SOFTWARE.
   51% 
   52%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
   53% 
   54% This is the top-level file for a Legolog application program.
   55% It consults all the necessary Legolog prolog files.
   56% In particular, the following is loaded:
   57%
   58%  (1) Load all libraries required. This includes the system dependant
   59%      ones for the specific Prolog plus general libraries
   60%  (2) Load the IndiGolog interpreter and the projector used
   61%  (3) Load the application code itself containing the background theory
   62%      of action plus the high-level program
   63%  (4) Specify which environments should be loaded and how 
   64%  (5) Specify how each action should be executed and how to translate
   65%      exogenous actions
   66%
   67% Moreover, the following is provided:
   68%
   69% -- main: Collects all the procedures named 'mainControl(N)' where
   70%          N is the number representing the N-th controller.
   71%          The user can select which controller to execute and the 
   72%          IndiGolog executor will be run on such controller
   73%
   74%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
   75
   76%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
   77% SET GLOBAL PARAMETERS AND GLOBAL VARIABLES/CONSTANTS USED
   78%  
   79%  These may be options to improve performance and variables/constants used
   80%  around the whole arquitecture
   81%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
   82:- set_flag(debug_compile, off).   
   83:- set_flag(variable_names, off).  % To speed up execution
   84
   85type_prolog(ecl).    % Type of Prolog being used
   86
   87% Path is the root path of the IndiGolog system
   88main_dir(Path):- getenv('PATH_INDIGOLOG',Pwd),
   89                 (string(Pwd) -> atom_string(APwd, Pwd) ; APwd=Pwd),
   90                 concat_atom([APwd, '/'], Path).
   91
   92
   93%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
   94% (1) LOAD/COMPILE/IMPORT LIBRARIES, MODULES, ETC that may be required.
   95%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
   96:- lib(scattered).   % Clauses can be not consecutive
   97:- lib(fd).          % Load finite-domain constraint library
   98:- lib(fd_search).   % Load extra finite-domain search algorithms
   99
  100:- use_module(library(tools_ecl)).  101
  102:- ['../../lib/systemvar'].              % Common facts (device_manager/4)
  103
  104%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  105% (2,3) CONSULT NECESSARY FILES
  106%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  107
  108% 1 - Consult IndiGolog system
  109:- ['../../Interpreters/indigolog'].     % IndiGolog interpreter
  110:- ['../../Eval/evalbat'].               % BAT evaluator
  111
  112% 2 - Consult environment manager 
  113:- ['../../Env/env_man.pl'].         % Load environment manager
  114
  115% 4 - Consult application
  116:- [delivery].                 % Golog elevator controller
  117
  118
  119%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  120% (4,5) ENVIRONMENTS TO LOAD
  121%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  122
  123% Port of environment manager is left free and assigned by the OS
  124server_port(X).
  125
  126% Load simulator, RCX and internet environments
  127load_environment(Env, Command, Address) :- 
  128        member(Env, [simulator]),
  129        (var(Address) -> 
  130             Host=null, Port=null ; 
  131             Address = [Host, Port]
  132        ),
  133        device_manager(Env, eclipse, Command, [Host, Port]).
  134        
  135        
  136           %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  137           % HOW TO EXECUTE ACTIONS: Environment + low-level Code %
  138           %        how_to_execute(Action, Environment, Code)     %
  139           %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  140how_to_execute(Action, simulator, Action). % Everything else
  141
  142
  143           %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  144           %   EXOGENOUS ACTION AND SENSING OUTCOME TRANSLATION   %
  145           %          translateExogAction(Code, Action)           %
  146           %          translateSensing(Action, Outcome, Value)    %
  147           %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  148translateExogAction(CodeAction, Action) :- actionNum(Action, CodeAction).
  149
  150translateSensing(senseDoor(_), SensorValue, true):- SensorValue<30, !.
  151translateSensing(senseDoor(_), SensorValue, true):- SensorValue>40, !.
  152translateSensing(senseDoor(_), _, false).
  153
  154
  155%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  156% MAIN PREDICATE - evaluate this to run demo
  157%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  158% main: Gets IndiGolog to evaluate main control procedure
  159main:- bagof(X,Y^proc(mainControl(X),Y),L),
  160    (L=[NoContr] -> 
  161         indigolog(mainControl(NoContr)) 
  162    ;
  163         write('Available Controllers: '), write(L), nl,
  164         write('Which controller do you want to execute? '), 
  165         read(NoContr), 
  166         indigolog(mainControl(NoContr)) 
  167    ).
  168
  169%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  170% PREDICATES WITH SYSTEM DEPENDENT CODE
  171%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  172
  173
  174%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  175% EOF:  Elevator/main_ecl.pl
  176%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%