1%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
    2%
    3% FILE: Delivery-BAT/main_swi.pl
    4%
    5%  Author    : Sebastian Sardina
    6%  Time-stamp: <04/01/05 12:59:20 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%
   20%                             March 20, 2001
   21%
   22% This software was developed by the Cognitive Robotics Group under the
   23% direction of Hector Levesque and Ray Reiter.
   24%
   25%        Do not distribute without permission.
   26%        Include this notice in any copy made.
   27%
   28%
   29%         Copyright (c) 2000 by The University of Toronto,
   30%                        Toronto, Ontario, Canada.
   31%
   32%                          All Rights Reserved
   33%
   34% Permission to use, copy, and modify, this software and its
   35% documentation for non-commercial research purpose is hereby granted
   36% without fee, provided that the above copyright notice appears in all
   37% copies and that both the copyright notice and this permission notice
   38% appear in supporting documentation, and that the name of The University
   39% of Toronto not be used in advertising or publicity pertaining to
   40% distribution of the software without specific, written prior
   41% permission.  The University of Toronto makes no representations about
   42% the suitability of this software for any purpose.  It is provided "as
   43% is" without express or implied warranty.
   44% 
   45% THE UNIVERSITY OF TORONTO DISCLAIMS ALL WARRANTIES WITH REGARD TO THIS
   46% SOFTWARE, INCLUDING ALL IMPLIED WARRANTIES OF MERCHANTABILITY AND
   47% FITNESS, IN NO EVENT SHALL THE UNIVERSITY OF TORONTO BE LIABLE FOR ANY
   48% SPECIAL, INDIRECT OR CONSEQUENTIAL DAMAGES OR ANY DAMAGES WHATSOEVER
   49% RESULTING FROM LOSS OF USE, DATA OR PROFITS, WHETHER IN AN ACTION OF
   50% CONTRACT, NEGLIGENCE OR OTHER TORTIOUS ACTION, ARISING OUT OF OR IN
   51% CONNECTION WITH THE USE OR PERFORMANCE OF THIS SOFTWARE.
   52%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
   53% 
   54% This is the top-level file for a Legolog program.
   55% It consults the necessary Legolog prolog files and
   56% defines any additional system-dependent predicates that are required.
   57%
   58% For this example this file defines the following predicates:
   59% -- initializeExog: perform any initialization of other sources of
   60%      exogenous actions that is required
   61% -- finalizeExog: things to do for other sources of exogenous actions
   62%      at end of program
   63% -- checkOtherExog(-ExogList): check whether a request has been
   64%      entered via keyboard
   65%
   66%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
   67
   68%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
   69% (1) LOAD/COMPILE/IMPORT LIBRARIES, MODULES, ETC that may be required.
   70%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
   71:- include('../../lib/systemvar'). % Global include code and Prolog init
   72%:- reset_backquoted_string.
   73
   74:- use_module(library(libgraph)).   75
   76%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
   77% (2,3) CONSULT NECESSARY FILES
   78%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
   79
   80% 1 - Consult IndiGolog system
   81:- consult('../../Interpreters/indigolog').     % IndiGolog interpreter 
   82:- consult('../../Eval/evalbat').               % BAT evaluator
   83
   84% 2 - Consult environment manager 
   85:- consult(['../../Env/env_man.pl']).         % Load environment manager
   86
   87% 3 - Consult application
   88:- consult(delivery).                         % Application code in IndiGolog
   89
   90
   91%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
   92% (4,5) ENVIRONMENTS TO LOAD
   93%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
   94
   95
   96% Port of environment manager has to be fixed in SWI
   97server_port(9113).
   98
   99% Load simulator, RCX and internet environments
  100:- ['../../Env/dev_managers'].              % Common facts (device_manager/4)
  101load_environment(Env, Command, Address) :- 
  102%        member((Env,Type), [(simulator,eclipse), (rcx,eclipse), (internet,swi)]),
  103        member((Env,Type), [(simulator,eclipse), (rcx,eclipse)]),
  104%        member((Env,Type), [(simulator,eclipse)]),
  105        (var(Address) -> 
  106             Host=null, Port=null ; 
  107             Address = [Host, Port]
  108        ),
  109        device_manager(Env, Type, Command, [Host, Port]).
  110
  111
  112           %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  113           % HOW TO EXECUTE ACTIONS: Environment + low-level Code %
  114           %        how_to_execute(Action, Environment, Code)     %
  115           %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  116
  117%how_to_execute(Action, internet, Code) :- 
  118%        actionNum(Action, Code),
  119%        member(Action, [say(_)]), !.   
  120how_to_execute(Action, rcx, Code) :- 
  121        actionNum(Action, Code),
  122        \+ member(Action, [thermo]), !.       % Exceptions 
  123
  124
  125           %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  126           %   EXOGENOUS ACTION AND SENSING OUTCOME TRANSLATION   %
  127           %          translateExogAction(Code, Action)           %
  128           %          translateSensing(Action, Outcome, Value)    %
  129           %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  130
  131translateExogAction(CodeAction, Action) :- actionNum(Action, CodeAction).
  132
  133%translateSensing(check(_,_), SensorValue, true):- 
  134%	number(SensorValue),
  135%	(SensorValue<30 ; SensorValue>40), !.
  136%translateSensing(check(_,_), N, false) :- number(N).
  137
  138
  139        
  140%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  141% MAIN PREDICATE - evaluate this to run demo
  142%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  143
  144%main: Gets IndiGolog to evaluate main control procedure
  145main:- bagof(X,Y^proc(mainControl(X),Y),L),
  146    (L=[NoContr] -> 
  147         indigolog(mainControl(NoContr)) 
  148    ;
  149         write('Available Controllers: '), write(L), nl,
  150         write('Which controller do you want to execute? '), 
  151         read(NoContr), 
  152         indigolog(mainControl(NoContr)) 
  153    ).
  154
  155:- set_option(debug_level,1).  156
  157%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  158% EOF: Delivery-BAT/main_swi.pl
  159%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%