1%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
    2%
    3% FILE: ElevatorLego-BAT/elevator.pl
    4%
    5%       BAT axiomatization of the elevator example
    6%
    7%  AUTHOR : Sebastian Sardina (2001)
    8%  EMAIL  : ssardina@cs.toronto.edu
    9%  WWW    : www.cs.toronto.edu/~ssardina www.cs.toronto.edu/cogrobo
   10%  TYPE   : system independent code
   11%  TESTED : SWI Prolog 5.0.10 http://www.swi-prolog.org
   12%           ECLIPSE 5.4 http://www.icparc.ic.ac.uk/eclipse/
   13%
   14%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
   15%
   16%                             May 18, 2001
   17%
   18% This software was developed by the Cognitive Robotics Group under the
   19% direction of Hector Levesque and Ray Reiter.
   20% 
   21%        Do not distribute without permission.
   22%        Include this notice in any copy made.
   23% 
   24% 
   25%         Copyright (c) 2000 by The University of Toronto,
   26%                        Toronto, Ontario, Canada.
   27% 
   28%                          All Rights Reserved
   29% 
   30% Permission to use, copy, and modify, this software and its
   31% documentation for non-commercial research purpose is hereby granted
   32% without fee, provided that the above copyright notice appears in all
   33% copies and that both the copyright notice and this permission notice
   34% appear in supporting documentation, and that the name of The University
   35% of Toronto not be used in advertising or publicity pertaining to
   36% distribution of the software without specific, written prior
   37% permission.  The University of Toronto makes no representations about
   38% the suitability of this software for any purpose.  It is provided "as
   39% is" without express or implied warranty.
   40% 
   41% THE UNIVERSITY OF TORONTO DISCLAIMS ALL WARRANTIES WITH REGARD TO THIS
   42% SOFTWARE, INCLUDING ALL IMPLIED WARRANTIES OF MERCHANTABILITY AND
   43% FITNESS, IN NO EVENT SHALL THE UNIVERSITY OF TORONTO BE LIABLE FOR ANY
   44% SPECIAL, INDIRECT OR CONSEQUENTIAL DAMAGES OR ANY DAMAGES WHATSOEVER
   45% RESULTING FROM LOSS OF USE, DATA OR PROFITS, WHETHER IN AN ACTION OF
   46% CONTRACT, NEGLIGENCE OR OTHER TORTIOUS ACTION, ARISING OUT OF OR IN
   47% CONNECTION WITH THE USE OR PERFORMANCE OF THIS SOFTWARE.
   48%
   49%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
   50% 
   51%  A basic action theory (BAT) is described with:
   52%
   53% -- fun_fluent(fluent)     : for each functional fluent (non-ground)
   54% -- rel_fluent(fluent)     : for each relational fluent (non-ground)
   55%
   56%           e.g., rel_fluent(painted(C)).
   57%           e.g., fun_fluent(color(C)).
   58%
   59% -- prim_action(action)    : for each primitive action (ground)
   60% -- exog_action(action)    : for each exogenous action (ground)
   61%
   62%           e.g., prim_action(clean(C)) :- domain(C,country).
   63%           e.g., exog_action(painte(C,B)):- domain(C,country), domain(B,color).
   64%
   65% -- senses(action,fluent)  : for each sensing action
   66%
   67%           e.g, poss(check_painted(C),  painted(C)).
   68%
   69% -- poss(action,cond)      : when cond, action is executable
   70%
   71%           e.g, poss(clean(C),   and(painted(C),holding(cleanear))).
   72%
   73% -- initially(fluent,value): fluent has value in S0 (ground)
   74%
   75%          e.g., initially(painted(C), false):- domain(C,country), C\=3.
   76%                initially(painted(3), true).
   77%                initially(color(3), blue).
   78%
   79% -- causes_val(action,fluent,value,cond)
   80%          when cond holds, doing act causes functional fluent to have value
   81%
   82%            e.g., causes_val(paint(C2,V), color(C), V, C = C2).
   83%               or causes_val(paint(C,V), color(C), V, true).
   84%
   85% -- causes_true(action,fluent,cond)
   86%          when cond holds, doing act causes relational fluent to hold
   87% -- causes_false(action,fluent,cond)
   88%          when cond holds, doing act causes relational fluent to not hold
   89%
   90%            e.g., causes_true(paint(C2,_), painted(C), C = C2).
   91%               or causes_true(paint(C,_), painted(C), true).
   92%            e.g., causes_false(clean(C2),  painted(C), C = C2).
   93%               or causes_false(clean(C),  painted(C), true).
   94%
   95% -- sort(name,domain_of_sort).      : all sorts used in the domain
   96%
   97%        e.g., varsort(c, colors).
   98%              varsort(temp, temperature).
   99%              color([blue, green, yellow, red]).       
  100%              temperature([-10,0,10,20,30,40]).
  101%
  102%
  103% A high-level program-controller is described with:
  104%
  105% -- proc(name,P): for each procedure P 
  106% -- simulator(N,P): P is the N exogenous action simulator
  107%
  108% The interface for Lego is described with:
  109%
  110% -- actionNum(action, num)  
  111%         action has RCX code num
  112% -- simulateSensing(action)
  113%         sensing result for action should be asked to the user
  114% -- translateSensing(action, sensorValue, sensorResult) 
  115%         translate the sensorValue of action to sensorResult
  116% -- translateExogAction(codeAction, action) 
  117%         translateSensing action name into codeAction and vice-versa
  118%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  119
  120/* DOMAINS/SORTS */
  121%fl([1,2,3,4,5,6,7,8,9,10]).       % possible floors 
  122fl([1,2,3,4,5,6]).       % possible floors 
  123dir([up,down]).                    % possible directions 
  124temperature([15,20,25,30,35]).     % possible temperatures
  125
  126% There is nothing to do caching on (required becase cache/1 is static)
  127cache(_):-fail.
  128
  129  /*  FLUENTS and CAUSAL LAWS */
  130rel_fluent(directionUp).           % Aiming up?
  131causes_true(turnaround,  directionUp, neg(directionUp)).
  132causes_false(turnaround, directionUp, directionUp).
  133
  134fun_fluent(state).                 % Moving, stopped, or suspended (lost)
  135causes_val(go,              state, moving, true).
  136causes_val(freeze,          state, freezed, true).
  137causes_val(arrive,          state, stopped, true).
  138causes_val(getStuck,        state, stopped, true).
  139causes_val(stop_abnormally, state, suspended, true).
  140
  141
  142rel_fluent(closed(_)). 	           % floor is out of service 
  143causes_true(deny(N),   closed(N), true).
  144causes_false(allow(N), closed(N), true).
  145
  146rel_fluent(light(_,_)).            % light buttons of each floor
  147causes_true(on(N,D),   light(N,D), true).
  148causes_false(off(N,D), light(N,D), true).
  149% Action check(N,D) gives the truth value of light(N,D)
  150senses(check(N,D), light(N,D)).
  151forget(check(N,D), light(N,D)).
  152
  153rel_fluent(fan).                   % the fan is on or off 
  154causes_true(toggle,   fan, neg(fan)).
  155causes_false(toggle,  fan, fan).
  156
  157rel_fluent(alarm).                 % the smoke alarm is on or off 
  158causes_true(smoke,   alarm,  true).
  159causes_false(reset,  alarm,  true).
  160
  161fun_fluent(temp).                  % the temp of the elevator 
  162causes_val(heat,  temp, T, T is temp+5).
  163causes_val(cold,  temp, T, T is temp-5).
  164senses(thermo, temp).
  165
  166fun_fluent(floor).                 % the floor the elevator is on 
  167causes_val(arrive, floor, N, or(and(directionUp,      N is floor + 1),
  168                                and(neg(directionUp), N is floor - 1))).
  169
  170rel_fluent(talking).           % Should we talk loud?
  171causes_true(talk,    talking, true).
  172causes_false(shutup, talking, true).
  173
  174
  175  /*  ACTIONS and PRECONDITIONS*/
  176prim_action(go).                % go to next floor 
  177prim_action(freeze).            % stop moving
  178prim_action(turnaround).        % turn around to change the direction 
  179prim_action(off(N,D))  :- domain(N,fl), 
  180                          domain(D,dir). % turn off button N direction D
  181prim_action(open).              % open elevator door 
  182prim_action(close).             % close elevator door
  183prim_action(toggle).            % toggle the fan 
  184prim_action(ring).              % ring the smoke alarm 
  185prim_action(check(N,D)):- domain(N,fl), 
  186                          domain(D,dir). % sensing action to check lights 
  187prim_action(thermo).            % sensing action to check temperature 
  188
  189prim_action(say(_)).            % say a message
  190
  191exog_action(smoke).              % smoke enters elevator 
  192exog_action(reset).              % smoke detector alarm is reset 
  193exog_action(heat).               % temp=temp+5 
  194exog_action(cold).               % temp=temp-5 
  195exog_action(deny(N)) :- domain(N,fl).   % make floor N not available  
  196exog_action(allow(N)):- domain(N,fl).   % make floor N available  
  197exog_action(on(N,D)) :- domain(N,fl), 
  198                        domain(D,dir). % button (N,D) has been pushed  
  199
  200exog_action(arrive).             % Arrive successfully and stop
  201exog_action(stop_abnormally).    % Stop because confused
  202
  203exog_action(talk).
  204exog_action(shutup).
  205
  206poss(go,     or( and(directionUp, floor < 10),
  207                 and(neg(directionUp), floor > 1)) ).
  208poss(off(N,_), floor = N).
  209poss(check(_,D), or( and(D=up, directionUp),
  210                     and(D=down, neg(directionUp))) ).
  211poss(thermo, true).
  212poss(open,   true).
  213poss(close,  true).
  214poss(toggle, true).
  215poss(ring,   true).
  216poss(freeze, state=moving).
  217poss(turnaround, state = stopped).
  218poss(say(_), true).
  219
  220/* ABBREVIATIONS */
  221proc(too_hot,  temp >= 30).
  222proc(too_cold, temp < 30).
  223proc(below_floor(N), floor < N).
  224proc(above_floor(N), floor > N).
  225
  226
  227
  228  /* INITIAL STATE: elevator is at floor 3, lights 2 and 5 are on */
  229initially(floor, 1). 
  230initially(fan,   false).
  231initially(alarm, false).
  232initially(closed(N),false) :- domain(N,fl).
  233initially(light(1,up),false).
  234%initially(light(N,D),false):- domain(N,fl), domain(D,dir).
  235%initially(temp,25).	% Temperature is unknown in S0 
  236initially(directionUp, true). 
  237initially(state, stopped).
  238initially(talking, true).
  239
  240%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  241% Definitions of complex actions
  242%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  243proc(serve(F,D), [open, close, off(F,D)]).
  244
  245proc(floorOk(F), or(and(directionUp,neg(light(F,up))),
  246                    and(neg(directionUp),neg(light(F,down))))).
  247
  248proc(start_up(X),   [search([star(turnaround),?(directionUp)]),
  249                     searchc(goto(X),'Computing path UP')] ).
  250proc(start_down(X), [search([star(turnaround),?(neg(directionUp))]),
  251                     searchc(goto(X),'Computing path DOWN')] ).
  252
  253% Talk if talking is true
  254proc(talk(M), if(neg(talking), ?(true), say(M))).
  255
  256proc(goto(X), 
  257   pi(f,[?(floor=f),
  258         if(f=X,[serve(f,up), serve(f,down)],
  259                pi(d,[?(or(d=up,d=down)),
  260                      check(f,d), 
  261                      branch(light(f,d)),
  262                      wndet(?(floorOk(f)), serve(f,d)),
  263                      go, sim(arrive), 
  264                      goto(X)]) )])).
  265
  266proc(recover_position, 
  267     pi(m,
  268	[if(directionUp,?(reset(floor, 1,m)),?(reset(floor, -1,m))),
  269         say(m),
  270         ?(get(_))
  271        ])
  272    ). 
  273
  274% reset(Location, Direction): auxiliary predicate
  275reset(Location, Direction, M) :-
  276    (Direction = 1 -> MDir=' going up.' ; MDir=' going down.'),
  277    concat_atom(['**** I got lost heading from waystation ', Location, 
  278                 'while ', MDir,
  279                 '. Please position me between waystations in ',
  280                 ' the correct direction, and type any key when ready: '],M).
  281
  282%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  283%  Main Routine
  284%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  285
  286% THIS IS THE MAIN PROCEDURE FOR INDIGOLOG
  287proc(main,  mainControl(N)) :- controller(N), !.
  288proc(main,  mainControl(1)). % default one
  289
  290
  291
  292% Elevator with alarm
  293proc(mainControl(0), [prioritized_interrupts(
  294        [interrupt(alarm, ring),
  295         interrupt(state = moving, wait),
  296         interrupt(state = suspended, [recover_position, go]),
  297         interrupt(floor=1, [start_up(6), start_down(1)])] )]).
  298
  299% Elevator with alarm and temperature and speech
  300proc(mainControl(1), [thermo, prioritized_interrupts(
  301        [interrupt(and(too_hot,neg(fan)), 
  302                   [talk('Too hot!. Turning on the fan'), toggle]),
  303         interrupt(and(too_cold,fan),
  304                   [talk('Too cold!. Turning off the fan'), toggle]),
  305         interrupt(alarm, search([star(freeze), ?(neg(state=moving)), ring])),
  306         interrupt(state = moving, wait),
  307         interrupt(state = suspended, [recover_position, go]),
  308         interrupt(state = freezed, go),
  309         interrupt(floor = 1, [talk('Planning to go up'),
  310                               start_up(6), 
  311                               talk('Planning to go down'),
  312                               start_down(1)])] )]).
  313
  314% Elevator with alarm and temperature
  315proc(mainControl(2), [thermo, prioritized_interrupts(
  316        [interrupt(or(and(too_hot,neg(fan)),and(too_cold,fan)), toggle),
  317         interrupt(alarm, search([star(freeze), ?(neg(state=moving)), ring])),
  318         interrupt(state = moving, wait),
  319         interrupt(state = suspended, [recover_position, go]),
  320         interrupt(state = freezed, go),
  321         interrupt(floor = 1, [start_up(6), start_down(1)])] )]).
  322
  323
  324%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  325% Action/message mappings - numbers must correspond to NQC code
  326%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  327
  328% actionNum(?Action, ?ActionNumber): Returns ActionNumber associated
  329%     with Action and vice versa. ActionNumber can be sent to the RCX
  330%     for execution of Action. It can be returned from the RCX to
  331%     report the occurrence of exogenous Action
  332actionNum(off(_,_), 0).
  333actionNum(recover_position, 0). % 0 is a general void action
  334actionNum(thermo, 0).
  335
  336actionNum(turnaround, 1).
  337actionNum(go, 2).
  338actionNum(open, 3).
  339actionNum(close, 4).
  340actionNum(ring, 5).
  341actionNum(toggle, 5).
  342actionNum(freeze, 8).
  343
  344actionNum(check(_,_), 7).
  345actionNum(arrive, 20).
  346actionNum(stop_abnormally, 21).
  347actionNum(reset, 22).
  348
  349actionNum(say(M),   say(M, english)).
  350
  351
  352%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  353% Translation of sensor values from RCX
  354%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  355
  356% translateSensing(+Action, +SensorValue, SensingResult): Translate
  357%     the value SensorValue returned by the RCX sensor into a legal
  358%     SensingResult under Action
  359
  360
  361
  362%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  363% EOF: ElevatorLego-BAT/elevator.pl
  364%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%