1%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
    2%
    3%  FILE      : Env/lego_ecl.pl
    4%  Time-stamp: <02/11/30 01:33:51 ssardina>
    5%
    6%  Author      : First, by Maurice Pagnucco and Hector J. Levesque
    7%                Then, by Sebastian Sardina
    8%  DESCRIPTION : Prolog code to establish communication with 
    9%                LEGO Mindstorms RCX. This file contains the basic interface
   10%                to open, close, read and write for ECLIPSE Prolog.
   11%  email       : ssardina@cs.toronto.edu
   12%  WWW         : www.cs.toronto.edu/~ssardina
   13%  TYPE CODE   : system dependent predicates
   14%  TESTED      : ECLiPSe 5.5 on RedHat Linux 6.2-8.0
   15%
   16% It is written for ECLiPSe Prolog (http://www.icparc.ic.ac.uk/eclipse/)
   17% running under Linux
   18%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
   19%
   20%                             June 15, 2000
   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%
   55% The following system dependent predicates are provided in this file:
   56%
   57% -- initRcx           : initialize serial port, baud, parity etc. for RCX
   58% -- openRcxRead       : open RCX serial port for reading
   59% -- openRcxWrite      : open RCX serial port for writing
   60% -- closeRcx          : close RCX serial port
   61% -- getRcxByte(-Ascii): get a character from RCX
   62% -- eofRcx            : succeed if there is a character from RCX to read
   63% -- putRcxByte(+Ascii): write a character to RCX
   64% -- currentTime(-Time): current system time measured in seconds
   65% -- waitUntilRcx(+End): optionally wait (busy or suspend) until End
   66%                        system time or until RCX input arrives. 
   67%                        Fails if End is passed
   68%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
   69
   70% rcxStream(-Rcx): Saves the file descriptor currently referring to the open
   71%     serial port Rcx.
   72:- dynamic(rcxStream/1).   73
   74%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
   75% For ECLiPSe Prolog you will need the following version of get/2
   76% to work around the problem that it converts ASCII 13 (carriage return) to
   77% ASCII 10 (newline).
   78% Thanks to Joachim Schimpf (J.Schimpf@icparc.ic.ac.uk) from IC PARC for fix
   79% Apparently this problem will be fixed in the next release (currently 4.2.2).
   80%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
   81%% fixed_get(+Stream, -Ascii): Obtain next Ascii character from Stream
   82%fixed_get(Stream, Ascii) :-
   83%    get_stream_info(Stream, line, L0),
   84%    get(Stream, X),
   85%    (X \== 10 ->
   86%        Ascii = X;
   87%        get_stream_info(Stream, line, L1),
   88%        (L0 == L1 -> Ascii = 13 ; Ascii = X)).
   89%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
   90
   91% Using default Linux serial port /dev/ttyS0
   92% If you change this, make sure to alter it below in initRcx/0 as well
   93
   94% rcxPort(+Port): Location of serial port to which infrared tower is attached
   95%rcxPort('/dev/cua0').
   96rcxPort('/dev/ttyS0').
   97
   98% immediateDelay(+Delay): Amount of time Delay (in seconds) to wait in between
   99%     fetching bytes Linux appears to be much faster than the RCX and this
  100%     delay is used to avoid "splitting" message packets
  101immediateDelay(0.03).
  102
  103% currentTime(-Time): Returns the current system Time in hundredths of seconds
  104currentTime(Time) :-
  105    statistics(session_time, T),
  106    Time is fix(100 * T).
  107
  108% initRcx: Uses stty to initialise the serial port, setting baud rate, etc.
  109%     Make sure that the serial port is set correctly. We use /dev/ttyS0 here.
  110initRcx :-
  111    system('stty -echo -icanon -iexten -isig -icrnl -inpck -istrip -ixon -cstopb cs8 parenb parodd -opost ispeed 2400 ospeed 2400 < /dev/ttyS0').
  112
  113   
  114% openRcxRead: Opens infrared tower (connected to serial port) for reading
  115%     data from RCX
  116openRcxRead:-
  117    rcxPort(Port),
  118    open(Port, read, Rcx), % Open serial port for reading and writing
  119    retract_all(rcxStream(_)),
  120    assert(rcxStream(Rcx)).
  121
  122% openRcxWrite: Opens infrared tower (connected to serial port) for sending
  123%     data to RCX
  124openRcxWrite:-
  125    rcxPort(Port),
  126    open(Port, write, Rcx), % Open serial port for reading and writing
  127    retract_all(rcxStream(_)),
  128    assert(rcxStream(Rcx)).
  129
  130
  131% closeRcx: Closes infrared tower (connected to serial port) if it is
  132%     currently open. This predicate always succeeds
  133closeRcx:-
  134    (rcxStream(Rcx) ->
  135        (close(Rcx), retract_all(rcxStream(Rcx))); true).
  136
  137% eofRcx: Checks whether there is any input data waiting on infrared tower
  138eofRcx :-
  139    rcxStream(Rcx),
  140    select([Rcx], 0, ReadyList),
  141    ReadyList == [].
  142
  143% waitUntilRcx(+End): Optionally wait (busy or suspend) until End system time
  144%     or until RCX input arrives. Fail if End passed
  145waitUntilRcx(End) :-
  146    currentTime(Now),
  147    TimeOut is (End - Now)/100,
  148    TimeOut > 0,
  149    rcxStream(Rcx),
  150    select([Rcx], TimeOut, _).
  151
  152% getRcxByte(-Ascii): Returns the first Ascii character read from infrared
  153%     tower. Blocks if there is no input
  154getRcxByte(Ascii) :-
  155    rcxStream(Rcx),
  156    immediateDelay(Delay),
  157    sleep(Delay),
  158    get(Rcx, Ascii).
  159
  160% putRcxByte(+Ascii): Sends Ascii character to Rcx using infrared tower
  161putRcxByte(Ascii) :-
  162    rcxStream(Rcx),
  163    put(Rcx, Ascii),
  164    flush(Rcx).
  165
  166%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  167% EOF: Env/lego_ecl.pl
  168%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%