Home » Archimedes archive » Acorn User » AU 1995-04.adf » !StarInfo_StarInfo » Miskin/!CompInfo/Zcode/h/PARSER

Miskin/!CompInfo/Zcode/h/PARSER

This website contains an archive of files for the Acorn Electron, BBC Micro, Acorn Archimedes, Commodore 16 and Commodore 64 computers, which Dominic Ford has rescued from his private collection of floppy disks and cassettes.

Some of these files were originally commercial releases in the 1980s and 1990s, but they are now widely available online. I assume that copyright over them is no longer being asserted. If you own the copyright and would like files to be removed, please contact me.

Tape/disk: Home » Archimedes archive » Acorn User » AU 1995-04.adf » !StarInfo_StarInfo
Filename: Miskin/!CompInfo/Zcode/h/PARSER
Read OK:
File size: 1B5EC bytes
Load address: 0000
Exec address: 0000
File contents
! ----------------------------------------------------------------------------
!  "PARSER":  the core of the Inform library, and the parser
!
!  Supplied for use with Inform 5
!
!  (c) Graham Nelson, 1993/4, but freely usable
! ----------------------------------------------------------------------------

Constant LibSerial "941007";
Constant LibRelease "5/5";

! ----------------------------------------------------------------------------
!  Attribute and property definitions
!  The compass, directions, darkness and player objects
!  Definitions of fake actions
!  Library global variables
!  Private parser variables
!  Keyboard reading
!  Parser, level 0: outer shell, conversation, errors
!                1: grammar lines
!                2: tokens
!                3: object lists
!                4: scope and ambiguity resolving
!                5: object comparisons
!                6: word comparisons
!                7: reading words and moving tables about
!  Main game loop
!  Action processing
!  Menus
!  Time: timers and daemons
!  Considering light
!  Changing player personality
!  Printing short names
! ----------------------------------------------------------------------------

! ----------------------------------------------------------------------------
! Declare the attributes and properties.  Note that properties "preroutine"
! and "postroutine" default to $ffff which forces them to be two bytes long:
! similarly, "timeleft" sometimes needs to be over 256, so it's flagged long
! ----------------------------------------------------------------------------

System_file;

Attribute animate;
Attribute clothing;
Attribute concealed;
Attribute container;
Attribute direction;
Attribute door;
Attribute edible;
Attribute enterable;
Attribute female;
Attribute general;
Attribute light;
Attribute lockable;
Attribute locked;
Attribute moved;
Attribute on;
Attribute open;
Attribute openable;
Attribute proper;
Attribute scenery;
Attribute scored;
Attribute static;
Attribute supporter;
Attribute switchable;
Attribute talkable;
Attribute transparent;
Attribute visited;
Attribute workflag;
Attribute worn;

Attribute absent alias female;      !  Please, no psychoanalysis

Property additive before $ffff;
Property additive after  $ffff;
Property additive life   $ffff;

Property long n_to;  Property long s_to; !  Slightly wastefully, these are
Property long e_to;  Property long w_to; !  long (they might be routines)
Property long ne_to; Property long se_to;
Property long nw_to; Property long sw_to;
Property long u_to;  Property long d_to;
Property long in_to; Property long out_to;

Property door_to     alias n_to;     !  For economy: these properties are
Property when_closed alias s_to;     !  used only by objects which
Property with_key    alias e_to;     !  aren't rooms
Property door_dir    alias w_to;     !
Property invent      alias u_to;     !
Property plural      alias d_to;     !

Property initial;
Property when_open   alias initial;
Property when_on     alias initial;
Property when_off    alias when_closed;
Property long description;
Property additive describe $ffff;
Property article "a";

Property cant_go "You can't go that way.";

Property long found_in;         !  For fiddly reasons this can't alias

Property long time_left;
Property long number;
Property additive time_out $ffff;
Property daemon alias time_out;
Property additive each_turn $ffff;

Property capacity 100;

Property long short_name;
Property long parse_name;

! The following definitions, commented out, define pre-Inform 5.2 and now
! obselete names as aliases for the standard names:

! Property preroutine alias before; Property desc        alias description;
! Property postroutine alias after; Property longdesc    alias description;
! Property liferoutine alias life;  Property timeleft    alias time_left;
! Property initpos     alias initial;
! Property portalto    alias door_to;
! Property closedpos   alias when_closed;
! Property dirprop     alias door_dir;
! Property cantgo      alias cant_go;
! Attribute portal alias door;

! ----------------------------------------------------------------------------
! Construct the compass - a dummy object containing the directions, which also
! represent the walls in whatever room the player is in
! ----------------------------------------------------------------------------

Object compass "compass" nothing has concealed;
Object n_obj "north wall" compass      
  with name "n" "north" "wall",           article "the", door_dir n_to
  has  scenery;
Object s_obj "south wall" compass      
  with name "s" "south" "wall",           article "the", door_dir s_to
  has  scenery;
Object e_obj "east wall" compass      
  with name "e" "east" "wall",            article "the", door_dir e_to
   has  scenery;
Object w_obj "west wall" compass       
  with name "w" "west" "wall",            article "the", door_dir w_to
   has  scenery;
Object ne_obj "northeast wall" compass 
  with name "ne" "northeast" "wall",      article "the", door_dir ne_to
  has  scenery;
Object nw_obj "northwest wall" compass
  with name "nw" "northwest" "wall",      article "the", door_dir nw_to
  has  scenery;
Object se_obj "southeast wall" compass
  with name "se" "southeast" "wall",      article "the", door_dir se_to
  has  scenery;
Object sw_obj "southwest wall" compass
  with name "sw" "southwest" "wall",      article "the", door_dir sw_to
  has  scenery;
Object u_obj "ceiling" compass         
  with name "u" "up" "ceiling",           article "the", door_dir u_to
   has  scenery;
Object d_obj "floor" compass
  with name "d" "down" "floor",           article "the", door_dir d_to
   has  scenery;
Object out_obj "outside" compass
  with                                    article "the", door_dir out_to
   has  scenery;
Object in_obj "inside" compass
  with                                    article "the", door_dir in_to
   has  scenery;


! ----------------------------------------------------------------------------
! The other dummy object is "Darkness", not really a place but it has to be
! an object so that the name on the status line can be "Darkness":
! we also create the player object
! ----------------------------------------------------------------------------

Object thedark "Darkness" nothing
  with description "It is pitch dark, and you can't see a thing.";

Object selfobj "yourself" thedark
  with description "As good-looking as ever.", number thedark,
       before $ffff, after $ffff, life $ffff, each_turn $ffff,
       time_out $ffff, describe $ffff, capacity 100,
       parse_name 0, short_name 0
  has  concealed animate proper transparent;

! ----------------------------------------------------------------------------
! Fake actions: treated as if they were actions, when calling
! routines attached to objects
! ----------------------------------------------------------------------------

Fake_Action LetGo;
Fake_Action Receive;
Fake_Action Order;
Fake_Action TheSame;
Fake_Action PluralFound;

! ----------------------------------------------------------------------------
! Globals: note that the first one defined gives the status line place, the
! next two the score/turns
! ----------------------------------------------------------------------------

Global location = 1;
Global sline1 = 0;
Global sline2 = 0;

Global the_time = $ffff;
Global time_rate = 1;
Global time_step = 0;

Global score = 0;
Global turns = 1;
Global player;

Global lightflag = 1;
Global real_location = thedark;
Global print_player_flag = 0;
Global deadflag = 0;

Global inventory_stage = 1;

Global transcript_mode = 0;

Global last_score = 0;
Global notify_mode = 1;       ! Score notification

Global places_score = 0;
Global things_score = 0;
Global lookmode = 1;
Global lastdesc = 0;

Global top_object = 0;

! ----------------------------------------------------------------------------
! Parser variables accessible to the rest of the game
! ----------------------------------------------------------------------------

Global buffer          string 120;   ! Text buffer
Global parse           string 64;    ! List of parsed addresses of words
Global inputobjs       data 32;      ! To hold parameters
Global toomany_flag    = 0;          ! Flag for "take all made too many"
Global actor           = 0;          ! Person asked to do something
Global action          = 0;          ! Thing he is asked to do
Global inp1            = 0;          ! First parameter
Global inp2            = 0;          ! Second parameter
Global self            = 0;          ! Object whose routines are being run
Global noun            = 0;          ! First noun
Global second          = 0;          ! Second noun
Global multiple_object data 64;      ! List of multiple parameters
Global special_word    = 0;          ! Dictionary address of "special"
Global special_number  = 0;          ! The number, if a number was typed
Global special_number2 = 0;          ! Second number, if two numbers typed
Global parsed_number   = 0;          ! For user-supplied parsing routines
global multiflag;                    ! Multiple-object flag
global notheld_mode  = 0;            ! To do with implicit taking
global onotheld_mode = 0;            !
global meta;                         ! Verb is a meta-command (such as "save")
global reason_code;                  ! Reason for calling a life
global sw__var         = 0;          ! Switch variable (used for embeddeds)

#IFV5;
global undo_flag = 0;                ! Can the interpreter provide "undo"?
#ENDIF;

global parser_trace = 0;             ! Set this to 1 to make the parser trace
                                     ! tokens and lines
global debug_flag = 0;               ! For debugging information

! ----------------------------------------------------------------------------
! Main (putting it here ensures it is the first routine, as it must be)
! ----------------------------------------------------------------------------

[ Main;
  player=selfobj;
  PlayTheGame();
];

! ----------------------------------------------------------------------------
! The parser, beginning with variables private to itself:
! ----------------------------------------------------------------------------

global buffer2   string 120;    ! Buffers for supplementary questions
global parse2    string 64;     !
global parse3    string 64;     !

global wn;                      ! Word number (counts from 1)
global num_words;               ! Number of words typed
global verb_word;               ! Verb word (eg, take in "take all" or
                                ! "dwarf, take all") - address in dictionary
global verb_wordnum;            ! and the number in typing order (eg, 1 or 3)

global multi_mode;              ! Multiple mode
global multi_wanted;            ! Number of things needed in multitude
global multi_had;               ! Number of things actually found
global multi_context;           ! What token the multi-object was accepted for

global pattern data 16;         ! For the current pattern match
global pcount;                  ! and a marker within it
global pattern2 data 16;        ! And another, which stores the best match
global pcount2;                 ! so far

global parameters;              ! Parameters (objects) entered so far

global nsns;                    ! Number of special_numbers entered so far

global inferfrom;               ! The point from which the rest of the
                                ! command must be inferred
global inferword;               ! And the preposition inferred

global oops_from = 0;           ! The "first mistake" point, where oops acts
global saved_oops = 0;          ! Used in working this out
global oops_heap data 10;       ! Used temporarily by "oops" routine

global match_list data 128;     ! An array of matched objects so far
global match_classes data 128;  ! An array of equivalence classes for them
global number_matched;          ! How many items in it?  (0 means none)
global number_of_classes;       ! How many equivalence classes?
global match_length;            ! How many typed words long are these matches?
global match_from;              ! At what word of the input do they begin?

global parser_action;           ! For the use of the parser when calling
global parser_one;              ! user-supplied routines
global parser_two;              !

global vague_word;              ! Records which vague word ("it", "them", ...)
                                ! caused an error
global vague_obj;               ! And what it was thought to refer to

global itobj=0;                 ! The object which is currently "it"
global himobj=0;                ! The object which is currently "him"
global herobj=0;                ! The object which is currently "her"

global lookahead;               ! The token after the object now being matched
global indef_mode;              ! "Indefinite" mode - ie, "take a brick" is in
                                ! this mode
global indef_type;              ! Bit-map holding types of specification
global indef_wanted;            ! Number of items wanted (100 for all)
global indef_guess_p;           ! Plural-guessing flag
global allow_plurals;           ! Whether they are presently allowed or not
global not_holding;             ! Object to be automatically taken as an
                                ! implicit command
global kept_results data 32;    ! The delayed command (while the take happens)

global saved_wn;                ! These are temporary variables for Parser()
global saved_token;             ! (which hasn't enough spare local variables)

global held_back_mode = 0;      ! Flag: is there some input from last time
global hb_wn = 0;               ! left over?  (And a save value for wn)

global best_etype;              ! Error number used within parser
global etype;                   ! Error number used for individual lines

global last_command_from;       ! For sorting out "then again"
global last_command_to;         !

global token_was;               ! For noun filtering by user routines

global advance_warning;         ! What a later-named thing will be

global placed_in_flag;          ! To do with PlaceInScope
global length_of_noun;          ! Set by NounDomain to number of words in noun

global action_to_be;            ! So the parser can "cheat" in one case
global dont_infer;              ! Another dull flag

global et_flag = 0;             ! Processing "each_turn" mode

global scope_token;             ! For scope:Routine tokens
global scope_error;
global scope_stage;

#IFV5;
global just_undone = 0;         ! Can't have two successive UNDOs
#ENDIF;

! ----------------------------------------------------------------------------
!  The comma_word is a special word, used to substitute commas in the input
! ----------------------------------------------------------------------------

Dictionary comma_word   "xcomma";

! ----------------------------------------------------------------------------
!  In Advanced games only, the DrawStatusLine routine does just that: this is
!  provided explicitly so that it can be Replace'd to change the style, and
!  as written it emulates the ordinary Standard game status line, which is
!  drawn in hardware
! ----------------------------------------------------------------------------
#IFV5;
[ DrawStatusLine i;
   @split_window 1; @set_window 1; @set_cursor 1 1; style reverse;
   spaces (0->33)-1;
   @set_cursor 1 2;  PrintShortName(location);
   if ((0->1)&2 == 0)
   {   @set_cursor 1 51; print "Score: ", sline1;
       @set_cursor 1 64; print "Moves: ", sline2;
   }
   else
   {   @set_cursor 1 51; print "Time: ";
       i=sline1%12; if (i<10) print " ";
       if (i==0) i=12;
       print i, ":";
       if (sline2<10) print "0";
       print sline2;
       if ((sline1/12) > 0) print " pm"; else print " am";
   }
   @set_cursor 1 1; style roman; @set_window 0;
];
#ENDIF;

! ----------------------------------------------------------------------------
!  The Keyboard routine actually receives the player's words,
!  putting the words in "a_buffer" and their dictionary addresses in
!  "a_table".  It is assumed that the table is the same one on each
!  (standard) call.
!
!  It can also be used by miscellaneous routines in the game to ask
!  yes-no questions and the like, without invoking the rest of the parser.
!
!  Return the number of words typed
! ----------------------------------------------------------------------------

[ Keyboard  a_buffer a_table  nw i w x1 x2;

    DisplayStatus();
    .FreshInput;

!  Save the start of the table, in case "oops" needs to restore it
!  to the previous time's table

    for i 0 to 9 { put oops_heap byte i a_table->i; }

!  Print the prompt, and read in the words and dictionary addresses

    print "^>";
    #IFV3; read a_buffer a_table; #ENDIF;
    #IFV5; read a_buffer a_table DrawStatusLine; #ENDIF;
    nw=a_table->1;

!  If the line was blank, get a fresh line
    if (nw == 0)
    { print "I beg your pardon?^"; jump FreshInput; }

!  Unless the opening word was "oops" or its abbreviation "o", return

    w=a_table-->1;
    if (w == #n$o or 'oops') jump DoOops;

#IFV5;
!  Undo handling

    if (w == 'undo')
    {   if (undo_flag==0)
        {   print "[Your interpreter does not provide ~undo~.  Sorry!]^";
            jump FreshInput;
        }
        if (undo_flag==1) jump UndoFailed;
        if (just_undone==1)
        {   print "[Can't ~undo~ twice in succession.  Sorry!]^";
            jump FreshInput;
        }
        restore_undo i;
        if (i==0)
        {   .UndoFailed;
            print "~Undo~ failed.  [Not every interpreter provides it.]^";
        }
        jump FreshInput;
    }
    save_undo i;
    just_undone=0;
    undo_flag=2;
    if (i==-1) undo_flag=0;
    if (i==0) undo_flag=1;
    if (i==2)
    {   print "^", object location, "^[Previous turn undone]^";
        just_undone=1;
        jump FreshInput;
    }
#ENDIF;

    return nw;

    .DoOops;
    if (oops_from == 0)
    {   print "Sorry, that can't be corrected.^"; jump FreshInput; }
    if (nw == 1)
    {   print "Think nothing of it.^"; jump FreshInput; }
    if (nw > 2)
    {   print "~Oops~ can only correct a single word.^"; jump FreshInput; }

!  So now we know: there was a previous mistake, and the player has
!  attempted to correct a single word of it.
!
!  Oops is very primitive: it gets the text buffer wrong, for instance.
!
!  Take out the 4-byte table entry for the supplied correction:
!  restore the 10 bytes at the front of the table, which were over-written
!  by what the user just typed: and then replace the oops_from word entry
!  with the correction one.
!
    x1=a_table-->3; x2=a_table-->4;
    for i 0 to 9 { put a_table byte i oops_heap->i; }
    w=2*oops_from - 1;
    put a_table word w x1;
    inc w;
    put a_table word w x1;

    return nw;
];

Constant STUCK_PE     1;
Constant UPTO_PE      2;
Constant CANTSEE_PE   3;
Constant TOOLIT_PE    4;
Constant NOTHELD_PE   5;
Constant MULTI_PE     6;
Constant MMULTI_PE    7;
Constant VAGUE_PE     8;
Constant EXCEPT_PE    9;
Constant ANIMA_PE     10;
Constant VERB_PE      11;
Constant SCENERY_PE   12;
Constant ITGONE_PE    13;
Constant JUNKAFTER_PE 14;
Constant TOOFEW_PE    15;
Constant NOTHING_PE   16;
Constant NUMBER_PE    17;
Constant ASKSCOPE_PE  18;

! ----------------------------------------------------------------------------
!  The Parser routine is the heart of the parser.
!
!  It returns only when a sensible request has been made, and puts into the
!  "results" buffer:
!
!  Word 0 = The action number
!  Word 1 = Number of parameters
!  Words 2, 3, ... = The parameters (object numbers), but
!                    00 means "multiple object list goes here"
!                    01 means "special word goes here"
!
!  (Some of the global variables above are really local variables for this
!  routine, because the Z-machine only allows up to 15 local variables per
!  routine, and Parser runs out.)
!
!  To simplify the picture a little, a rough map of this routine is:
!
!  (A)    Get the input, do "oops" and "again"
!  (B)    Is it a direction, and so an implicit "go"?  If so go to (K)
!  (C)    Is anyone being addressed?
!  (D)    Get the verb: try all the syntax lines for that verb
!  (E)        Go through each token in the syntax line
!  (F)           Check (or infer) an adjective
!  (G)            Check to see if the syntax is finished, and if so return
!  (H)    Cheaply parse otherwise unrecognised conversation and return
!  (I)    Print best possible error message
!  (J)    Retry the whole lot
!  (K)    Last thing: check for "then" and further instructions(s), return.
!
!  The strategic points (A) to (K) are marked in the commentary.
!
!  Note that there are three different places where a return can happen.
!
! ----------------------------------------------------------------------------

[ Parser  results   syntax line num_lines line_address i j
                    token l m;

!  **** (A) ****

!  Firstly, in "not held" mode, we still have a command left over from last
!  time (eg, the user typed "eat biscuit", which was parsed as "take biscuit"
!  last time, with "eat biscuit" tucked away until now).  So we return that.

    if (notheld_mode==1)
    {   for (i=0:i<8:i++) results-->i=kept_results-->i;
        notheld_mode=0; rtrue;
    }

    if (held_back_mode==1)
    {   held_back_mode=0;
        for (i=0:i<64:i++) parse->i=parse2->i;
        new_line;
        jump ReParse;
    }

  .ReType;

    Keyboard(buffer,parse);

  .ReParse;

!  Initially assume the command is aimed at the player, and the verb
!  is the first word

    num_words=parse->1;
    verb_wordnum=1;
    actor=player;
    token_was = 0; ! In case we're still in "user-filter" mode from last round
    scope_token = 0;

!  Begin from what we currently think is the verb word

  .BeginCommand;
    wn=verb_wordnum;
    verb_word = NextWord();

!  Now try for "again" or "g", which are special cases:
!  don't allow "again" if nothing has previously been typed;
!  simply copy the previous parse table and ReParse with that

    if (verb_word==#n$g) verb_word='again';
    if (verb_word=='again')
    {   if (parse3->1==0)
        {   print "You can hardly repeat that.^"; jump ReType; }
        for (i=0:i<64:i++) parse->i=parse3->i;
        jump ReParse;
    }

!  Save the present parse table in case of an "again" next time

    if (verb_word~='again')
        for (i=0:i<64:i++)
            parse3->i=parse->i;

!  If the first word is not recognised, give a user-supplied routine
!  the chance to work out what it is:

    if (verb_word==0 && actor==player) verb_word=UnknownVerb(verb_word);

!  But if it still isn't, then it can't be either the name of
!  an animate creature or a verb, so give an error at once.

    if (verb_word==0)
    {   best_etype=VERB_PE;
        jump GiveError;
    }

!  **** (B) ****

!  If the first word is not listed as a verb, it must be a direction
!  or the name of someone to talk to
!  (NB: better avoid having a Mr Take or Mrs Inventory around...)

    if (((verb_word->#dict_par1) & 1) == 0)
    {   

!  So is the first word an object contained in the special object "compass"
!  (i.e., a direction)?  This needs use of NounDomain, a routine which
!  does the object matching, returning the object number, or 0 if none found,
!  or 1000 if it has restructured the parse table so that the whole parse
!  must be begun again...

        wn=verb_wordnum;
        l=NounDomain(compass,0,0); if (l==1000) jump ReParse;

!  If it is a direction, send back the results:
!  action=GoSub, no of arguments=1, argument 1=the direction.

        if (l~=0)
        {   results-->0 = ##Go;
            results-->1 = 1;
            results-->2 = l;
            jump LookForMore;
        }

!  **** (C) ****

!  Only check for a comma (a "someone, do something" command) if we are
!  not already in the middle of one.  (This simplification stops us from
!  worrying about "robot, wizard, you are an idiot", telling the robot to
!  tell the wizard that she is an idiot.)

        if (actor==player)
            for (j=2:j<=num_words:j++)
            {   i=NextWord(); if (i==comma_word) jump Conversation;
            }

!  The initial word was something, but not a verb - give UnknownVerb
!  a chance to restore it to health.
         
        if (actor==player)
        {   verb_word=UnknownVerb(verb_word);
            if (verb_word~=0) jump VerbAccepted;
        }

        best_etype=VERB_PE; jump GiveError;

!  NextWord nudges the word number wn on by one each time, so we've now
!  advanced past a comma.  (A comma is a word all on its own in the table.)

      .Conversation;
        j=wn-1;
        if (j==1) { print "You can't begin with a comma.^"; jump ReType; }

!  Use NounDomain (in the context of "animate creature") to see if the
!  words make sense as the name of someone held or nearby

        wn=1; lookahead=1;
        l=NounDomain(player,location,6); if (l==1000) jump ReParse;

        if (l==0) { print "You seem to want to talk to someone, \
                         but I can't see whom.^"; jump ReType; }

!  The object addressed must at least be "talkable" if not actually "animate"
!  (the distinction allows, for instance, a microphone to be spoken to,
!  without the parser thinking that the microphone is human).

        if (l hasnt animate && l hasnt talkable)
        {   print "You can't talk to "; DefArt(l); print ".^"; jump ReType; }

!  Check that there aren't any mystery words between the end of the person's
!  name and the comma (eg, throw out "dwarf sdfgsdgs, go north").

        if (wn~=j)
        {   print "To talk to someone, try ~someone, hello~ or some such.^";
            jump ReType;
        }

!  The player has now successfully named someone.  Adjust "him", "her", "it":

        ResetVagueWords(l);

!  Set the global variable "actor", adjust the number of the first word,
!  and begin parsing again from there.

        verb_wordnum=j+1; actor=l;
        jump BeginCommand;
    }

!  **** (D) ****

   .VerbAccepted;

!  We now definitely have a verb, not a direction, whether we got here by the
!  "take ..." or "person, take ..." method.  Get the meta flag for this verb:

    meta=((verb_word->#dict_par1) & 2)/2;

!  Now let i be the corresponding verb number, stored in the dictionary entry
!  (in a peculiar 255-n fashion for traditional Infocom reasons)...

    i=$ff-(verb_word->#dict_par2);

!  ...then look up the i-th entry in the verb table, whose address is at word
!  7 in the Z-machine (in the header), so as to get the address of the syntax
!  table for the given verb...

    syntax=(0-->7)-->i;

!  ...and then see how many lines (ie, different patterns corresponding to the
!  same verb) are stored in the parse table...

    num_lines=(syntax->0)-1;

!  ...and now go through them all, one by one.
!  To prevent vague_word 0 being misunderstood,

   vague_word='it'; vague_obj=itobj;

   if (parser_trace>=1)
   {    print "[Parsing for the verb '"; print_addr verb_word;
        print "' (", num_lines+1, " lines)]^";
   }

   best_etype=STUCK_PE;
!  "best_etype" is the current failure-to-match error - it is by default
!  the least informative one, "don't understand that sentence"


!  **** (E) ****

    for (line=0:line<=num_lines:line++)
    {   line_address = syntax+1+line*8;

        if (parser_trace>=1)
        {   print "[Line ", line, ": ", line_address->0, " parameters: ";
            for (pcount=1:pcount<=6:pcount++)
            {   token=line_address->pcount;
                print token, " ";
            }
            print " -> action ", line_address->7, "]^";
        }

!  We aren't in "not holding" or inferring modes, and haven't entered
!  any parameters on the line yet, or any special numbers; the multiple
!  object is still empty.

        not_holding=0;
        inferfrom=0;
        parameters=0;
        nsns=0;
        multiple_object-->0 = 0;
        etype=STUCK_PE;
        action_to_be = line_address->7;

!  Put the word marker back to just after the verb

        wn=verb_wordnum+1;

!  An individual "line" contains six tokens...  There's a preliminary pass
!  first, to parse late tokens early if necessary (because of mi or me)

        advance_warning=-1;
        for (i=0,pcount=1:pcount<=6:pcount++)
        {   scope_token=0;
            token=line_address->pcount;
            if (token<180) i++;
            if (token==4 or 5 && i==1)
            {   if (parser_trace>=2) print " [Trying look-ahead]^";
                pcount++;
                while (pcount<=6 && line_address->pcount>=180) pcount++;
                token=line_address->(pcount-1);
                if (token>=180)
                {   j=AdjectiveAddress(token);

                    !  Now look for word with j, move wn, parse next
                    !  token...
                    while (wn <= num_words)
                    {   if (NextWord()==j)
                        {   l = NounDomain(location,actor,token);
                            if (parser_trace>=2)
                            {   print " [Forward token parsed: ";
                                if (l==1000) print "re-parse request]^";
                                if (l==1) print "but multiple found]^";
                                if (l==0) print "hit error ", etype, "]^";
                            }
                            if (l==1000) jump ReParse;
                            if (l>=2)
                            {   advance_warning = l;
                                if (parser_trace>=3)
                                {   DefArt(l); print "]^";
                                }
                            }
                        }
                    }
                }
            }
        }

!  And now start again, properly, forearmed or not as the case may be.

        not_holding=0;
        inferfrom=0;
        parameters=0;
        nsns=0;
        multiple_object-->0 = 0;
        etype=STUCK_PE;
        action_to_be = line_address->7;
        wn=verb_wordnum+1;

!  "Pattern" gradually accumulates what has been recognised so far,
!  so that it may be reprinted by the parser later on

        for (pcount=1:pcount<=6:pcount++)
        {   pattern-->pcount=0;

            token=line_address->pcount;

            if (parser_trace>=2)
            {   print " [Token ",pcount, " is ", token, ": ";
                if (token<16)
                {   if (token==0) print "<noun> or null";
                    if (token==1) print "<held>";
                    if (token==2) print "<multi>";
                    if (token==3) print "<multiheld>";
                    if (token==4) print "<multiexcept>";
                    if (token==5) print "<multiinside>";
                    if (token==6) print "<creature>";
                    if (token==7) print "<special>";
                    if (token==8) print "<number>";
                }
                if (token>=16 && token<48)
                    print "<noun filter by routine ",token-16, ">";
                if (token>=48 && token<80)
                    print "<general parse by routine ",token-48, ">";
                if (token>=80 && token<128)
                    print "<scope parse by routine ",token-80, ">";
                if (token>=128 && token<180)
                    print "<noun filter by attribute ",token-128, ">";
                if (token>180)
                {   print "<adjective ",255-token, " '";
                    print_addr AdjectiveAddress(token); print "'>";
                }
                print " at word number ", wn, "]^";
            }

!  Lookahead is set to the token after this one, or 8 if there isn't one.
!  (Complicated because the line is padded with 0's.)

            m=pcount+1; lookahead=8;
            if (m<=6) lookahead=line_address->m;
            if (lookahead==0)
            {   m=parameters; if (token<=7) m++;
                if (m>=line_address->0) lookahead=8;
            }

!  **** (F) ****

!  When the token is a large number, it must be an adjective:
!  remember the adjective number in the "pattern".

            if (token>180)
            {   pattern-->pcount = 1000+token;

!  If we've run out of the player's input, but still have parameters to
!  specify, we go into "infer" mode, remembering where we are and the
!  adjective we are inferring...

                if (wn > num_words)
                {   if (inferfrom==0 && parameters<line_address->0)
                    { inferfrom=pcount; inferword=token; }

!  Otherwise, this line must be wrong.

                    if (inferfrom==0) break;
                }

!  Whereas, if the player has typed something here, see if it is the
!  required adjective... if it's wrong, the line must be wrong,
!  but if it's right, the token is passed (jump to finish this token).

                if (wn <= num_words && token~=Adjective()) break;
                jump TokenPassed;
            }

!  **** (G) ****
!  Check now to see if the player has entered enough parameters...
!  (since line_address->0 is the number of them)

            if (parameters == line_address->0)
            {  

!  If the player has entered enough parameters already but there's still
!  text to wade through: store the pattern away so as to be able to produce
!  a decent error message if this turns out to be the best we ever manage,
!  and in the mean time give up on this line

!  However, if the superfluous text begins with a comma, "and" or "then" then
!  take that to be the start of another instruction

                if (wn <= num_words)
                {   l=NextWord();
                    if (l=='then' or comma_word)
                    {   held_back_mode=1; hb_wn=wn-1; }
                    else
                    {   for (m=0:m<8:m++) pattern2-->m=pattern-->m;
                        pcount2=pcount;
                        etype=UPTO_PE; break;
                    }
                }

!  Now, we may need to revise the multiple object because of the single one
!  we now know (but didn't when the list was drawn up).

                if (parameters>=1 && results-->2 == 0)
                {   l=ReviseMulti(results-->3);
                    if (l~=0) { etype=l; break; }
                }
                if (parameters>=2 && results-->3 == 0)
                {   l=ReviseMulti(results-->2);
                    if (l~=0) { etype=l; break; }
                }

                if (parser_trace>=1)
                    print "[Line successfully parsed]^";

!  At this point the line has worked out perfectly, and it's a matter of
!  sending the results back...
!  ...pausing to explain any inferences made (using the pattern)...

                if (inferfrom~=0)
                {   print "("; PrintCommand(inferfrom,1); print ")^";
                }

!  ...and to copy the action number, and the number of parameters...

                results-->1 = line_address->0;
                results-->0 = line_address->7;

!  ...and to reset "it"-style objects to the first of these parameters, if
!  there is one (and it really is an object)...

                if (parameters > 0 && results-->2 >= 2)
                    ResetVagueWords(results-->2);

!  ...and declare the user's input to be error free...

                oops_from = 0;

!  ...and worry about the case where an object was allowed as a parameter
!  even though the player wasn't holding it and should have been: in this
!  event, keep the results for next time round, go into "not holding" mode,
!  and for now tell the player what's happening and return a "take" request
!  instead...

                if (not_holding~=0 && actor==player)
                {   notheld_mode=1;
                    for (i=0:i<8:i++) kept_results-->i = results-->i;
                    results-->0 = ##Take;
                    results-->1 = 1;
                    results-->2 = not_holding;
                    print "(first taking "; DefArt(not_holding); print ")^";
                }

!  (Notice that implicit takes are only generated for the player, and not
!  for other actors.  This avoids entirely logical, but misleading, text
!  being printed.)

!  ...and finish.

                if (held_back_mode==1) { wn=hb_wn; jump LookForMore; }
                rtrue;
            }

!  Otherwise, the player still has at least one parameter to specify: an
!  object of some kind is expected, and this we hand over to:

            l=ParseObjectList(results,token);
            if (parser_trace>=3)
            {   print "  [Parse object list replied with";
                if (l==1000) print " re-parse request]^";
                if (l==0) print " token failed, error type ", etype, "]^";
                if (l==1) print " token accepted]^";
            }
            if (l==1000) jump ReParse;
            if (l==0)    break;

!  The token has been successfully passed; we are ready for the next.

            .TokenPassed;
        }

!  But if we get here it means that the line failed somewhere, so we continue
!  the outer for loop and try the next line...

        if (etype>best_etype) best_etype=etype;
   }

!  So that if we get here, each line for the specified verb has failed.

!  **** (H) ****

  .GiveError;
        etype=best_etype;

!  Errors are handled differently depending on who was talking.

!  If the command was addressed to somebody else (eg, "dwarf, sfgh") then
!  it is taken as conversation which the parser has no business in disallowing.
!  In order to make it easier for the host game to work out what was said, the
!  "verb" word (eg, "sfgh") is parsed as a number and as a dictionary entry,
!  and the parser returns as if the player had typed
!
!     answer sfgh to dwarf   
!
!  with the globals special_word and special_number set accordingly.

!  (This is convenient for, say, "computer, 2451" or "guard, blue").

    if (actor~=player)
    {   special_number=TryNumber(verb_wordnum);
        wn=verb_wordnum;
        special_word=NextWord();
        action=##Answer;
        inp1=1; inp2=actor; actor=player;
        rtrue;
    }

!  **** (I) ****

!  If the player was the actor (eg, in "take dfghh") the error must be printed,
!  and fresh input called for.  In three cases the oops word must be jiggled.

    if (ParserError(etype)~=0) jump ReType;

    if (etype==STUCK_PE)
             {   print "I didn't understand that sentence.^"; oops_from=1; }
    if (etype==UPTO_PE)
             {   print "I only understood you as far as wanting to ";
                 for (m=0:m<8:m++) pattern-->m = pattern2-->m;
                 pcount=pcount2; PrintCommand(0,1); print ".^";
             }
    if (etype==CANTSEE_PE)
             {   print "You can't see any such thing.^";
                 oops_from=saved_oops; }
    if (etype==TOOLIT_PE)
                 print "You seem to have said too little!^";
    if (etype==NOTHELD_PE)
             {   print "You aren't holding that!^";
                 oops_from=saved_oops; }
    if (etype==MULTI_PE)
                 print "You can't use multiple objects with that verb.^";
    if (etype==MMULTI_PE)
                 print "You can only use multiple objects once on a line.^";
    if (etype==VAGUE_PE)
             {   print "I'm not sure what ~"; print_addr vague_word;
                 print "~ refers to.^"; }
    if (etype==EXCEPT_PE)
                 print "You excepted something not included anyway!^";
    if (etype==ANIMA_PE)
                 print "You can only do that to something animate.^";
    if (etype==VERB_PE)
                 print "That's not a verb I recognise.^";
    if (etype==SCENERY_PE)
                 print "That's not something you need to refer to \
                        in the course of this game.^";
    if (etype==ITGONE_PE)
             {   print "You can't see ~"; print_addr vague_word;
                 print "~ ("; DefArt(vague_obj); print ") at the moment.^"; }
    if (etype==JUNKAFTER_PE)
                 print "I didn't understand the way that finished.^";
    if (etype==TOOFEW_PE)
             {   if (multi_had==0) print "None";
                 else { print "Only "; EnglishNumber(multi_had); }
                 print " of those ";
                 if (multi_had==1) print "is"; else print "are";
                 print " available.^"; }
    if (etype==NOTHING_PE)
             {   if (multi_wanted==100) print "Nothing to do!^";
                 else print "There are none at all available!^";  }
    if (etype==NUMBER_PE)
                 print "I didn't understand that number.^";
    if (etype==ASKSCOPE_PE)
    {            scope_stage=3; indirect(scope_error); }

!  **** (J) ****

!  And go (almost) right back to square one...

    jump ReType;

!  ...being careful not to go all the way back, to avoid infinite repetition
!  of a deferred command causing an error.


!  **** (K) ****

!  At this point, the return value is all prepared, and we are only looking
!  to see if there is a "then" followed by subsequent instruction(s).
    
   .LookForMore;

   if (wn>num_words) rtrue;

   i=NextWord();
   if (i=='then' || i==comma_word)
   {   if (wn>num_words)
       { parse2->1=(parse2->1)-1; held_back_mode = 0; rtrue; }
       if (actor==player) j=0; else j=verb_wordnum-1;
       last_command_from = j+1; last_command_to = wn-2;
       i=NextWord();
       if (i=='again' or #n$g)
       {   for (i=0: i<j: i++)
           {   parse2-->(2*i+1) = parse-->(2*i+1);
               parse2-->(2*i+2) = parse-->(2*i+2);
           }
           for (i=last_command_from:i<=last_command_to:i++, j++)
           {   parse2-->(2+2*j) = parse-->(2*i);
               parse2-->(1+2*j) = parse-->(2*i-1);
           }
           for (i=wn:i<=num_words:i++, j++)
           {   parse2-->(2+2*j) = parse-->(2*i);
               parse2-->(1+2*j) = parse-->(2*i-1);
           }
           parse2->1=j; held_back_mode = 1; rtrue;
       }
       else wn--;
       for (i=0: i<j: i++)
       {   parse2-->(2*i+1) = parse-->(2*i+1);
           parse2-->(2*i+2) = parse-->(2*i+2);
       }
       for (i=wn:i<=num_words:i++, j++)
       {   parse2-->(2+2*j) = parse-->(2*i);
           parse2-->(1+2*j) = parse-->(2*i-1);
       }
       parse2->1=j; held_back_mode = 1; rtrue;
   }
   best_etype=UPTO_PE; jump GiveError;
];

! ----------------------------------------------------------------------------
!  NumberWord - fairly self-explanatory
! ----------------------------------------------------------------------------

[ NumberWord o;
  if (o=='one') return 1;
  if (o=='two') return 2;
  if (o=='three') return 3;
  if (o=='four') return 4;
  if (o=='five') return 5;
  if (o=='six') return 6;
  if (o=='seven') return 7;
  if (o=='eight') return 8;
  if (o=='nine') return 9;
  if (o=='ten') return 10;
  if (o=='eleven') return 11;
  if (o=='twelve') return 12;
  if (o=='thirteen') return 13;
  if (o=='fourteen') return 14;
  if (o=='fifteen') return 15;
  if (o=='sixteen') return 16;
  if (o=='seventeen') return 17;
  if (o=='eighteen') return 18;
  if (o=='nineteen') return 19;
  if (o=='twenty') return 20;
  return 0;
];

! ----------------------------------------------------------------------------
!  Descriptors()
!
!  Handles descriptive words like "my", "his", "another" and so on.
!  Skips "the", and leaves wn pointing to the first misunderstood word.
!
!  Allowed to set up for a plural only if allow_p is set
!
!  Returns error number, or 0 if no error occurred
! ----------------------------------------------------------------------------

Constant OTHER_BIT    1;     !  These will be used in Adjudicate()
Constant MY_BIT       2;     !  to disambiguate choices
Constant THAT_BIT     4;
Constant PLURAL_BIT   8;
Constant ITS_BIT     16;
Constant HIS_BIT     32;
Constant LIT_BIT     64;
Constant UNLIT_BIT  128;

[ Descriptors context  o flag n;

   indef_mode=0; indef_type=0; indef_wanted=0; indef_guess_p=0;

   for (flag=1:flag==1:)
   {   o=NextWord(); flag=0;
       if (o=='the') flag=1;
       if (o==#n$a or 'an' or 'any' || o=='either' or 'anything')
                            { indef_mode=1; flag=1; }
       if (o=='another' or 'other')
                            { indef_mode=1; flag=1;
                              indef_type = indef_type | OTHER_BIT; }
       if (o=='my' or 'this' or 'these')
                            { indef_mode=1; flag=1;
                              indef_type = indef_type | MY_BIT; }
       if (o=='that' or 'those')
                            { indef_mode=1; flag=1;
                              indef_type = indef_type | THAT_BIT; }
       if (o=='its')
                            { indef_mode=1; flag=1;
                              indef_type = indef_type | ITS_BIT; }
       if (o=='his')
                            { indef_mode=1; flag=1;
                              indef_type = indef_type | HIS_BIT; }
       if (o=='lit' or 'lighted')
                            { indef_mode=1; flag=1;
                              indef_type = indef_type | LIT_BIT; }
       if (o=='unlit')
                            { indef_mode=1; flag=1;
                              indef_type = indef_type | UNLIT_BIT; }
       if (o=='all' or 'each' or 'every' || o=='everything')
                            { indef_mode=1; flag=1; indef_wanted=100;
                              indef_type = indef_type | PLURAL_BIT; }
       if (allow_plurals==1)
       {   n=NumberWord(o);
           if (n>1)         { indef_guess_p=1;
                              indef_mode=1; flag=1; indef_wanted=n;
                              indef_type = indef_type | PLURAL_BIT; }
       }
       if (flag==1 && NextWord() ~= 'of') wn--;  ! Skip 'of' after these
   }
   wn--;
   if ((indef_wanted > 0) && (context<2 || context>5)) return MULTI_PE;
   return 0;
];

! ----------------------------------------------------------------------------
!  ParseObjectList: Parses tokens 0 to 8, from the current word number wn
!
!  Returns:
!    1000 for "reconstructed input, please re-parse from scratch"
!    1    for "token accepted"
!    0    for "token failed"
!
!  (A)            Preliminaries and special/number tokens
!  (B)            Actual object names (mostly subcontracted!)
!  (C)            and/but and so on
!  (D)            Returning an accepted token
!
! ----------------------------------------------------------------------------

[ ParseObjectList results token  l o i j k
                                 and_parity single_object desc_wn many_flag;

    many_flag=0; and_parity=1; multiple_object->0 = 0; dont_infer=0;

!  **** (A) ****
!  We expect to find a list of objects next in what the player's typed.

  .ObjectList;

   if (parser_trace>=3) print "  [Object list from word ", wn, "]^";

!  Take an advance look at the next word: if it's "it" or "them", and these
!  are unset, set the appropriate error number and give up on the line
!  (if not, these are still parsed in the usual way - it is not assumed
!  that they still refer to something in scope)

    o=NextWord(); wn--;
    if (o=='it' or 'them')
    {   vague_word=o; vague_obj=itobj;
        if (itobj==0) { etype=VAGUE_PE; return 0; }
    }
    if (o=='him')
    {   vague_word=o; vague_obj=himobj;
        if (himobj==0) { etype=VAGUE_PE; return 0; }
    }
    if (o=='her')
    {   vague_word=o; vague_obj=herobj;
        if (herobj==0) { etype=VAGUE_PE; return 0; }
    }
    if (o=='me' or 'myself' or 'self')
    {   vague_word=o; vague_obj=player;
    }

!  Firstly, get rid of tokens 7 and 8 ("special" and "number"), and
!  tokens which are entirely handed out to outside routines

    if (token==7)
    {   l=TryNumber(wn);
        if (l~=-1000)
        {   if (nsns==0) special_number=l; else special_number2=l;
            nsns++;
            if (parser_trace>=3)
                print "  [Read special as the number ", l, "]^";
        }
        if (parser_trace>=3)
            print "  [Read special word at word number ", wn, "]^";
        special_word=NextWord(); single_object=1; jump PassToken;
    }
    if (token==8)
    {   l=TryNumber(wn++);
        if (l==-1000) { etype=NUMBER_PE; rfalse; }
        if (parser_trace>=3) print "  [Read number as ", l, "]^";
        if (nsns++==0) special_number=l; else special_number2=l;
        single_object=1; jump PassToken;
    }

    if (token>=48 && token<80)
    {   l=indirect(#preactions_table-->(token-48));
        if (parser_trace>=3)
            print "  [Outside parsing routine returned ", l, "]^";
        if (l<0) rfalse;
        if (l==1)
        {   if (nsns==0) special_number=parsed_number;
            else special_number2=parsed_number;
            nsns++;
        }
        single_object=l; jump PassToken;
    }

    if (token>=80 && token<128)
    {   scope_token = #preactions_table-->(token-80);
        scope_stage = 1;
        l=indirect(scope_token);
        if (parser_trace>=3)
            print "  [Scope routine returned multiple-flag of ", l, "]^";
        if (l==1) token=2; else token=0;
    }

    token_was=0;
    if (token>=16)
    {   token_was = token;
        token=0;
    }

!  Otherwise, we have one of the tokens 0 to 6, all of which really do mean
!  that objects are expected.

!  So now we parse any descriptive words

    allow_plurals = 1; desc_wn = wn;
    .TryAgain;

    l=Descriptors(token); if (l~=0) { etype=l; return 0; }

!  **** (B) ****

!  This is an actual specified object, and is therefore where a typing error
!  is most likely to occur, so we set:

    oops_from=wn;

!  In either case below we use NounDomain, giving it the token number as
!  context, and two places to look: among the actor's possessions, and in the
!  present location.  (Note that the order depends on which is likeliest.)

!  So, two cases.  Case 1: token not equal to "held" (so, no implicit takes)
!  but we may well be dealing with multiple objects

    if (token~=1)
    {   i=multiple_object-->0;
        if (parser_trace>=3)
            print "  [Calling NounDomain on location and actor]^";
        l=NounDomain(location, actor, token);
        if (l==1000) return l;                    ! Reparse after Q&A
        if (l==0) { etype=CantSee(); jump FailToken; }  ! Choose best error
        if (parser_trace>=3)
        {   if (l>1)
            {   print "  [ND returned "; DefArt(l); print "]^"; }
            else
            {   print "  [ND appended to the multiple object list:^";
                k=multiple_object-->0;
                for (j=i+1:j<=k:j++)
                {   print "  Entry ", j, ": "; CDefArt(multiple_object-->j);
                    print " (", multiple_object-->j, ")^";
                }
                print "  List now has size ", k, "]^";
            }
        }
        if (l==1)
        {   if (many_flag==0)
            {   many_flag=1;
            }
            else                                  ! Merge with earlier ones
            {   k=multiple_object-->0;            ! (with either parity)
                multiple_object-->0 = i;
                for (j=i+1:j<=k:j++)
                {   if (and_parity==1) MultiAdd(multiple_object-->j);
                    else MultiSub(multiple_object-->j);
                }
        if (parser_trace>=3)
            print "  [Merging ", k-i, " new objects to the ", i, " old ones]^";
            }
        }
        else 
        {   if (token==6 && l hasnt animate)      ! Animation as required
            {   etype=ANIMA_PE; jump FailToken; } ! for token 6
            if (many_flag==0)
                single_object = l;
            else
            {   if (and_parity==1) MultiAdd(l); else MultiSub(l);
                if (parser_trace>=3)
                {   print "  [Combining "; DefArt(single_object);
                    print " with list]^";
                }
            }
        }
    }

!  Case 2: token is "held" (which fortunately can't take multiple objects)
!  and may generate an implicit take

    if (token==1)
    {   l=NounDomain(actor,location,token);       ! Same as above...
        if (l==1000) return l;
        if (l==0) { etype=CantSee(); return l; }

!  ...until it produces something not held by the actor.  Then an implicit
!  take must be tried.  If this is already happening anyway, things are too
!  confused and we have to give up (but saving the oops marker so as to get
!  it on the right word afterwards).
!  The point of this last rule is that a sequence like
!
!      > read newspaper
!      (taking the newspaper first)
!      The dwarf unexpectedly prevents you from taking the newspaper!
!
!  should not be allowed to go into an infinite repeat - read becomes
!  take then read, but take has no effect, so read becomes take then read...
!  Anyway for now all we do is record the number of the object to take.

        o=parent(l);
        if (o~=actor)
        {   if (notheld_mode==1)
            {   saved_oops=oops_from; etype=NOTHELD_PE; jump FailToken;
            }
            not_holding = l;
            if (parser_trace>=3)
            {   print "  [Allowing object "; DefArt(l); print " for now]^";
            }
        }
        single_object = l;
    }

!  The following moves the word marker to just past the named object...

    wn = oops_from + match_length;

!  **** (C) ****

!  Object(s) specified now: is that the end of the list, or have we reached
!  "and", "but" and so on?  If so, create a multiple-object list if we
!  haven't already (and are allowed to).

    .NextInList;

    o=NextWord();

    if (o=='and' or 'but' or 'except' || o==comma_word)
    {
        if (parser_trace>=3)
        {   print "  [Read '"; print_addr o; print "']^";
        }

        if (token<2 || token>=6) { etype=MULTI_PE; jump FailToken; }

        if (o=='but' or 'except') and_parity = 1-and_parity;

        if (many_flag==0)
        {   multiple_object-->0 = 1;
            multiple_object-->1 = single_object;
            many_flag=1;
            if (parser_trace>=3)
            {   print "  [Making new list from ";
                DefArt(single_object); print "]^";
            }
        }
        dont_infer = 1; inferfrom=0;              ! Don't print (inferences)
        jump ObjectList;                          ! And back around
    }

    wn--;   ! Word marker back to first not-understood word

!  **** (D) ****

!  Happy or unhappy endings:

    .PassToken;

    if (many_flag==1) single_object=0;
    else
    {   if (indef_mode==1 && indef_type & PLURAL_BIT ~= 0)
        {   if (indef_wanted<100 && indef_wanted>1)
            {   multi_had=1; multi_wanted=indef_wanted;
                etype=TOOFEW_PE;
                jump FailToken;
            }
        }
    }
    results-->(parameters+2) = single_object;
    parameters++;
    pattern-->pcount = single_object;
    return 1;

    .FailToken;

!  If we were only guessing about it being a plural, try again but only
!  allowing singulars (so that words like "six" are not swallowed up as
!  Descriptors)

    if (allow_plurals==1 && indef_guess_p==1)
    {   allow_plurals=0; wn=desc_wn; jump TryAgain;
    }
    return 0;
];

! ----------------------------------------------------------------------------
!  NounDomain does the most substantial part of parsing an object name.
!
!  It is given two "domains" - usually a location and then the actor who is
!  looking - and a context (i.e. token type), and returns:
!
!   0    if no match at all could be made,
!   1    if a multiple object was made,
!   k    if object k was the one decided upon,
!   1000 if it asked a question of the player and consequently rewrote all
!        the player's input, so that the whole parser should start again
!        on the rewritten input.
!
!   In the case when it returns 1<k<1000, it also sets the variable
!   length_of_noun to the number of words in the input text matched to the
!   noun.
!   In the case k=1, the multiple objects are added to multiple_object by
!   hand (not by MultiAdd, because we want to allow duplicates).
! ----------------------------------------------------------------------------

[ NounDomain domain1 domain2 context  first_word i j k l oldw
                                      answer_words marker;

  if (parser_trace>=4) print "   [NounDomain called at word ", wn, "^";

  match_length=0; number_matched=0; match_from=wn; placed_in_flag=0;

  SearchScope(domain1, domain2, context);

  if (parser_trace>=4) print "   [ND made ", number_matched, " matches]^";

  wn=match_from+match_length;

!  If nothing worked at all, leave with the word marker skipped past the
!  first unmatched word...

  if (number_matched==0) { wn++; rfalse; }

!  Suppose that there really were some words being parsed (i.e., we did
!  not just infer).  If so, and if there was only one match, it must be
!  right and we return it...


  if (match_from <= num_words)
  {   if (number_matched==1) { i=match_list-->0; return i; }

!  ...now suppose that there was more typing to come, i.e. suppose that
!  the user entered something beyond this noun.  Use the lookahead token
!  to check that if an adjective comes next, it is the right one.  (If
!  not then there must be a mistake like "press red buttno" where "red"
!  has been taken for the noun in the mistaken belief that "buttno" is
!  some preposition or other.)
!
!  If nothing ought to follow, then similarly there must be a mistake,
!  (unless what does follow is just a full stop, and or comma)

      if (wn<=num_words)
      {   if (lookahead==8)
          {   i=NextWord(); wn--;
              if (i~='and' or comma_word or 'then') rfalse;
          }
          if (lookahead>8)
          {   if (lookahead~=Adjective()) { wn--; rfalse; }
              wn--;
          }
      }
  }

!  Now look for a good choice, if there's more than one choice...

  number_of_classes=0;
  
  if (number_matched==1) i=match_list-->0;
  if (number_matched>1)
  {   i=Adjudicate(context);
      if (i==-1) rfalse;
      if (i==1) rtrue;       !  Adjudicate has made a multiple
                             !  object, and we pass it on
  }

!  If i is non-zero here, one of two things is happening: either
!  (a) an inference has been successfully made that object i is
!      the intended one from the user's specification, or
!  (b) the user finished typing some time ago, but we've decided
!      on i because it's the only possible choice.
!  In either case we have to keep the pattern up to date,
!  note that an inference has been made and return.
!  (Except, we don't note which of a pile of identical objects.)

  if (i~=0)
  {   if (dont_infer==1) return i;
      if (inferfrom==0) inferfrom=pcount;
      pattern-->pcount = i;
      return i;
  }

!  If we get here, there was no obvious choice of object to make.  If in
!  fact we've already gone past the end of the player's typing (which
!  means the match list must contain every object in scope, regardless
!  of its name), then it's foolish to give an enormous list to choose
!  from - instead we go and ask a more suitable question...

  if (match_from > num_words) jump Incomplete;

!  Now we print up the question, using the equivalence classes as worked
!  out by Adjudicate() so as not to repeat ourselves on plural objects...

  if (context==6) print "Who"; else print "Which";
  print " do you mean, ";
  j=number_of_classes; marker=0;
  for (i=1:i<=number_of_classes:i++)
  {   
      while (((match_classes-->marker) ~= i)
             && ((match_classes-->marker) ~= -i)) marker++;
      k=match_list-->marker;

      if (match_classes-->marker > 0) DefArt(k); else InDefArt(k);

      if (i<j-1)  print ", ";
      if (i==j-1) print " or ";
  }
  print "?^";

!  ...and get an answer:

  .WhichOne;
  answer_words=Keyboard(buffer2, parse2);

  first_word=(parse2-->1);

!  Take care of "all", because that does something too clever here to do
!  later on:

  if ((first_word=='all' or 'both' or 'everything')
      || (first_word=='every' or 'each'))
  {   
      if (context>=2 && context<=5)
      {   l=multiple_object-->0;
          for (i=0:i<number_matched:i++)
          {   k=match_list-->i;
              multiple_object-->(i+1+l) = k;
          }
          multiple_object-->0 = number_matched+l;
          rtrue;
      }
      print "Sorry, you can only have one item here.  Which one exactly?^";
      jump WhichOne;
  }

!  If the first word of the reply can be interpreted as a verb, then
!  assume that the player has ignored the question and given a new
!  command altogether.
!  (This is one time when it's convenient that the directions are
!  not themselves verbs - thus, "north" as a reply to "Which, the north
!  or south door" is not treated as a fresh command but as an answer.)

  j=first_word->#dict_par1;
  if (0~=j&1)
  {   Copy(buffer, buffer2);
      Copy(parse, parse2);
      return 1000;
  }

!  Now we insert the answer into the original typed command, as
!  words additionally describing the same object
!  (eg, > take red button
!       Which one, ...
!       > music
!  becomes "take music red button".  The parser will thus have three
!  words to work from next time, not two.)
!
!  To do this we use MoveWord which copies in a word.

  oldw=parse->1;
  parse->1 = answer_words+oldw;

  for (k=oldw+answer_words : k>match_from : k--)
      MoveWord(k, parse, k-answer_words);

  for (k=1:k<=answer_words:k++)
      MoveWord(match_from+k-1, parse2, k);

!  Having reconstructed the input, we warn the parser accordingly
!  and get out.

  return 1000;

!  Now we come to the question asked when the input has run out
!  and can't easily be guessed (eg, the player typed "take" and there
!  were plenty of things which might have been meant).

  .Incomplete;

  if (context==6) print "Whom"; else print "What";
  print " do you want";
  if (actor~=player) { print " "; DefArt(actor); }
  print " to "; PrintCommand(0,1); print "?^";

  answer_words=Keyboard(buffer2, parse2);

  first_word=(parse2-->1);

!  Once again, if the reply looks like a command, give it to the
!  parser to get on with and forget about the question...

  j=first_word->#dict_par1;
  if (0~=j&1)
  {   Copy(buffer, buffer2);
      Copy(parse, parse2);
      return 1000;
  }

!  ...but if we have a genuine answer, then we adjoin the words
!  typed onto the expression.  But if we've just inferred a
!  preposition which wasn't actually there, then we need to
!  adjoin that as well.  (NB: two consecutive prepositions will
!  cause trouble here!)

  oldw=parse->1;
  if (inferfrom==0)
      for (k=1:k<=answer_words:k++)
          MoveWord(match_from+k-1, parse2, k);
  else
  {   for (k=1:k<=answer_words:k++)
          MoveWord(match_from+k, parse2, k);
      parse2-->1 = AdjectiveAddress(inferword);
      MoveWord(match_from, parse2, 1);
      answer_words++;
  }
  parse->1 = answer_words+oldw;

!  And go back to the parser.
  return 1000;
];

! ----------------------------------------------------------------------------
!  The Adjudicate routine tries to see if there is an obvious choice, when
!  faced with a list of objects (the match_list) each of which matches the
!  player's specification equally well.
!
!  To do this it makes use of the context (the token type being worked on).
!  It counts up the number of obvious choices for the given context
!  (all to do with where a candidate is, except for 6 (animate) which is to
!  do with whether it is animate or not);
!
!  if only one obvious choice is found, that is returned;
!
!  if we are in indefinite mode (don't care which) one of the obvious choices
!    is returned, or if there is no obvious choice then an unobvious one is
!    made;
!
!  at this stage, we work out whether the objects are distinguishable from
!    each other or not: if they are all indistinguishable from each other,
!    then choose one, it doesn't matter which;
!
!  otherwise, 0 (meaning, unable to decide) is returned (but remember that
!    the equivalence classes we've just worked out will be needed by other
!    routines to clear up this mess, so we can't economise on working them
!    out).
!
!  Returns -1 if an error occurred
! ----------------------------------------------------------------------------

[ Adjudicate context i j good_ones last n ultimate flag offset;

  if (parser_trace>=4)
      print "   [Adjudicating match list of size ", number_matched, "^";

  j=number_matched-1; good_ones=0; last=match_list-->0;
  for (i=0:i<=j:i++)
  {   n=match_list-->i;
      if (n hasnt concealed)
      {   ultimate=n;
          do
              ultimate=parent(ultimate);
          until (ultimate==location or actor or 0);

          if (context==0 && ultimate==location &&
              (token_was==0 || UserFilter(n)==1)) { good_ones++; last=n; }
          if (context==1 && parent(n)==actor)     { good_ones++; last=n; }
          if (context==2 && ultimate==location)   { good_ones++; last=n; }
          if (context==3 && parent(n)==actor)     { good_ones++; last=n; }

          if (context==4 or 5)
          {   if (advance_warning==-1)
              {   if (parent(n)==actor) { good_ones++; last=n; }
              }
              else
              {   if (context==4 && parent(n)==actor && n~=advance_warning)
                  { good_ones++; last=n; }
                  if (context==5 && parent(n)==actor && n in advance_warning)
                  { good_ones++; last=n; }
              }
          }
          if (context==6 && n has animate)        { good_ones++; last=n; }
      }
  }
  if (good_ones==1) return last;

  if (indef_mode==1 && indef_type & PLURAL_BIT ~= 0)
  {   if (context<2 || context>5) { etype=MULTI_PE; return -1; }
      i=0; number_of_classes=1; offset=multiple_object-->0;
      for (j=BestGuess():j~=-1 && i<indef_wanted:j=BestGuess())
      {   if (j hasnt concealed && j hasnt worn)
          {   flag=1;
              if (context==3 or 4 && parent(j)~=actor) flag=0;
              if (flag==1)
              {   i++; multiple_object-->(i+offset) = j;
                  if (parser_trace>=4)
                      print "   Accepting it^";
              }
              else
              {   if (parser_trace>=4)
                      print "   Rejecting it^";
              }
          }
      }
      if (i<indef_wanted && indef_wanted<100)
      {   etype=TOOFEW_PE; multi_wanted=indef_wanted;
          multi_had=multiple_object-->0;
          return -1;
      }
      multiple_object-->0 = i+offset;
      multi_context=context;
      if (parser_trace>=4)
          print "   Made multiple object of size ", i, "]^";
      return 1;
  }

  for (i=0:i<number_matched:i++) match_classes-->i=0;

  n=1;
  for (i=0:i<number_matched:i++)
      if (match_classes-->i==0)
      {   match_classes-->i=n++; flag=0;
          for (j=i+1:j<number_matched:j++)
              if (match_classes-->j==0
                  && Identical(match_list-->i, match_list-->j)==1)
              {   flag=1;
                  match_classes-->j=match_classes-->i;
              }
          if (flag==1) match_classes-->i = 1-n;
      }
  n--;

  if (parser_trace>=4)
  {   print "   Difficult adjudication with ", n, " equivalence classes:^";
      for (i=0:i<number_matched:i++)
      {   print "   "; CDefArt(match_list-->i);
          print " (", match_list-->i, ")  ---  ",match_classes-->i, "^";
      }
  }

  number_of_classes = n;

  if (n>1 && indef_mode==0)
  {   if (parser_trace>=4)
          print "   Unable to decide: it's a draw.]^";
      jump FailToken;
  }

!  When the player is really vague, or there's a single collection of
!  indistinguishable objects to choose from, choose the one the player
!  most recently acquired, or if the player has none of them, then
!  the one most recently put where it is.

  if (indef_mode==0) indef_type=0;
  if (n==1) dont_infer = 1;

  return BestGuess();
];

! ----------------------------------------------------------------------------
!  ReviseMulti  revises the multiple object which already exists, in the
!    light of information which has come along since then (i.e., the second
!    parameter).  It returns a parser error number, or else 1 if all is well.
!    This only ever throws things out, never adds new ones.
! ----------------------------------------------------------------------------

[ ReviseMulti second_p  i low;

  if (parser_trace>=4)
      print "   Revising the multiple object list^";

  if (multi_context==4 or 5)
  {   for (i=1, low=0:i<=multiple_object-->0:i++)
      {   if ( (multi_context==4 && multiple_object-->i ~= second_p)
               || (multi_context==5 && multiple_object-->i in second_p))
          {   low++; multiple_object-->low = multiple_object-->i;
          }
      }
      multiple_object-->0 = low;
  }

  if (multi_context==2)
  {   for (i=1, low=0:i<=multiple_object-->0:i++)
          if (parent(multiple_object-->i)==location) low++;
      if (parser_trace>=4)
          print "   Token 2 plural case: number on floor ", low, "^";
      if (verb_word=='take' or 'get' || low>0)
      {   for (i=1, low=0:i<=multiple_object-->0:i++)
          {   if (parent(multiple_object-->i)==location)
              {   low++; multiple_object-->low = multiple_object-->i;
              }
          }
          multiple_object-->0 = low;
      }
  }

  i=multiple_object-->0;
  if (i==0) return NOTHING_PE;
  return 0;
];

! ----------------------------------------------------------------------------
!  ScoreMatchL  scores the match list for quality in terms of what the
!  player has vaguely asked for.  Points are awarded for conforming with
!  requirements like "my", and so on.  If the score is less than the
!  threshold, block out the entry to -1.
!  The scores are put in the match_classes array, which we can safely
!  reuse by now.
! ----------------------------------------------------------------------------

[ ScoreMatchL  its_owner its_score obj i threshold a_s l_s;

  if (indef_type & OTHER_BIT ~= 0) threshold=4;
  if (indef_type & MY_BIT ~= 0)    threshold=threshold+4;
  if (indef_type & THAT_BIT ~= 0)  threshold=threshold+4;
  if (indef_type & ITS_BIT ~= 0)   threshold=threshold+4;
  if (indef_type & HIS_BIT ~= 0)   threshold=threshold+4;
  if (indef_type & LIT_BIT ~= 0)   threshold=threshold+4;
  if (indef_type & UNLIT_BIT ~= 0) threshold=threshold+4;

  if (parser_trace>=4) print "   Scoring match list with type ", indef_type,
      ", threshold ", threshold, ":^";

  a_s = 3; l_s = 2;
  if (action_to_be == ##Take or ##Remove) { a_s=2; l_s=3; }

  for (i=0:i<number_matched:i++)
  {   obj = match_list-->i; its_owner = parent(obj); its_score=0;
      if (its_owner==actor)   its_score=3;
      if (its_owner==location) its_score=2;
      if (its_score==0 && its_owner~=compass) its_score=1;

      if (indef_type & OTHER_BIT ~=0
          &&  obj~=itobj or himobj or herobj)
          its_score=its_score+4;
      if (indef_type & MY_BIT ~=0  &&  its_owner==actor)
          its_score=its_score+4;
      if (indef_type & THAT_BIT ~=0  &&  its_owner==location)
          its_score=its_score+4;
      if (indef_type & LIT_BIT ~=0  &&  obj has light)
          its_score=its_score+4;
      if (indef_type & UNLIT_BIT ~=0  &&  obj hasnt light)
          its_score=its_score+4;
      if (indef_type & ITS_BIT ~=0  &&  its_owner==itobj)
          its_score=its_score+4;
      if (indef_type & HIS_BIT ~=0  &&  its_owner has animate
          && GetGender(its_owner)==1)
          its_score=its_score+4;

      if (its_score < threshold) match_list-->i=-1;
      else
      {   match_classes-->i=its_score;
          if (parser_trace >= 4)
          {   print "   "; CDefArt(match_list-->i);
              print " (", match_list-->i, ") in "; DefArt(its_owner);
              print " scores ",its_score, "^";
          }
      }
  }
  number_of_classes=2;
];

! ----------------------------------------------------------------------------
!  BestGuess makes the best guess it can out of the match list, assuming that
!  everything in the match list is textually as good as everything else;
!  however it ignores items marked as -1, and so marks anything it chooses.
!  It returns -1 if there are no possible choices.
! ----------------------------------------------------------------------------

[ BestGuess  earliest its_score best i;

  if (number_of_classes==1) ScoreMatchL();

  earliest=0; best=-1;
  for (i=0:i<number_matched:i++)
  {   if (match_list-->i >= 0)
      {   its_score=match_classes-->i;
          if (its_score>best) { best=its_score; earliest=i; }
      }
  }
  if (parser_trace>=4)
  {   if (best<0)
          print "   Best guess ran out of choices^";
      else
      {   print "   Best guess "; DefArt(match_list-->earliest);
          print  " (", match_list-->earliest, ")^";
      }
  }
  if (best<0) return -1;
  i=match_list-->earliest;
  match_list-->earliest=-1;
  return i;
];

! ----------------------------------------------------------------------------
!  Identical decides whether or not two objects can be distinguished from
!  each other by anything the player can type.  If not, it returns true.
! ----------------------------------------------------------------------------

[ Identical o1 o2 p1 p2 n1 n2 i j flag;

!  print "Id on ", o1, " (", object o1, ") and ", o2, " (", object o2, ")^";

  if (o1==o2) rtrue;  ! This should never happen, but to be on the safe side
  if (o1==0 || o2==0) rfalse;  ! Similarly
  if (parent(o1)==compass || parent(o2)==compass) rfalse; ! Saves time

!  What complicates things is that o1 or o2 might have a parsing routine,
!  so the parser can't know from here whether they are or aren't the same.
!  If they have different parsing routines, we simply assume they're
!  different.  If they have the same routine (which they probably got from
!  a class definition) then the decision process is as follows:
!
!     the routine is called (with self being o1, not that it matters)
!       with noun and second being set to o1 and o2, and action being set
!       to the fake action TheSame.  If it returns -1, they are found
!       identical; if -2, different; and if >=0, then the usual method
!       is used instead.

  if (o1.parse_name~=0 || o2.parse_name~=0)
  {   if (o1.parse_name ~= o2.parse_name) rfalse;
      parser_action=##TheSame; parser_one=o1; parser_two=o2;
      j=wn; i=RunRoutines(o1,parse_name); wn=j;
      if (i==-1) rtrue; if (i==-2) rfalse;
  }

!  This is the default algorithm: do they have the same words in their
!  "name" (i.e. property no. 1) properties.  (Note that the following allows
!  for repeated words and words in different orders.)

  p1 = o1.&1; n1 = (o1.#1)/2;
  p2 = o2.&1; n2 = (o2.#1)/2;

!  for (i=0:i<n1:i++) { print_addr p1-->i; print " "; } new_line;
!  for (i=0:i<n2:i++) { print_addr p2-->i; print " "; } new_line;

  for (i=0:i<n1:i++)
  {   flag=0;
      for (j=0:j<n2:j++)
          if (p1-->i == p2-->j) flag=1;
      if (flag==0) rfalse;
  }

  for (j=0:j<n2:j++)
  {   flag=0;
      for (i=0:i<n1:i++)
          if (p1-->i == p2-->j) flag=1;
      if (flag==0) rfalse;
  }

!  print "Which are identical!^";
  rtrue;
];

! ----------------------------------------------------------------------------
!  PrintCommand reconstructs the command as it presently reads, from
!  the pattern which has been built up
!
!  If from is 0, it starts with the verb: then it goes through the pattern.
!  The other parameter is "emptyf" - a flag: if 0, it goes up to pcount:
!  if 1, it goes up to pcount-1.
!
!  Note that verbs and prepositions are printed out of the dictionary:
!  and that since the dictionary may only preserve the first six characters
!  of a word (in a V3 game), we have to hand-code the longer words needed.
!
!  (Recall that pattern entries are 0 for "multiple object", 1 for "special
!  word", 2 to 999 are object numbers and 1000+n means the preposition n)
! ----------------------------------------------------------------------------

[ PrintCommand from emptyf i j k f;
  if from==0
  {   i=verb_word; from=1; f=1;
#IFV3;
      if (i=='inventory') { print "take an inventory"; jump VerbPrinted; }
      if (i=='examine')   { print "examine";           jump VerbPrinted; }
      if (i=='discard')   { print "discard";           jump VerbPrinted; }
      if (i=='swallow')   { print "swallow";           jump VerbPrinted; }
      if (i=='embrace')   { print "embrace";           jump VerbPrinted; }
      if (i=='squeeze')   { print "squeeze";           jump VerbPrinted; }
      if (i=='purchase')  { print "purchase";          jump VerbPrinted; }
      if (i=='unscrew')   { print "unscrew";           jump VerbPrinted; }
      if (i=='describe')  { print "describe";          jump VerbPrinted; }
      if (i=='uncover')   { print "uncover";           jump VerbPrinted; }
      if (i=='discard')   { print "discard";           jump VerbPrinted; }
      if (i=='transfer')  { print "transfer";          jump VerbPrinted; }
#ENDIF;
      if (i==#n$l)         { print "look";              jump VerbPrinted; }
      if (i==#n$z)         { print "wait";              jump VerbPrinted; }
      if (i==#n$x)         { print "examine";           jump VerbPrinted; }
      if (i==#n$i or 'inv') { print "inventory";        jump VerbPrinted; }
      if (PrintVerb(i)==0) print_addr i;
  }
  .VerbPrinted;
  j=pcount-emptyf;
  for (k=from:k<=j:k++)
  {   if (f==1) print_char ' ';
      i=pattern-->k;
      if (i==0) { print "those things"; jump TokenPrinted; }
      if (i==1) { print "that"; jump TokenPrinted; }
      if (i>=1000)
      {   i=AdjectiveAddress(i-1000);
#IFV3;
          if (i=='against') { print "against";      jump TokenPrinted; }
#ENDIF;
          print_addr i;
      }
      else DefArt(i);
      .TokenPrinted;
      f=1;
  }
];

! ----------------------------------------------------------------------------
!  The CantSee routine returns a good error number for the situation where
!  the last word looked at didn't seem to refer to any object in context.
!
!  The idea is that: if the actor is in a location (but not inside something
!  like, for instance, a tank which is in that location) then an attempt to
!  refer to one of the words listed as meaningful-but-irrelevant there
!  will cause "you don't need to refer to that in this game" rather than
!  "no such thing" or "what's 'it'?".
!  (The advantage of not having looked at "irrelevant" local nouns until now
!  is that it stops them from clogging up the ambiguity-resolving process.
!  Thus game objects always triumph over scenery.)
! ----------------------------------------------------------------------------

[ CantSee  i w e;
    saved_oops=oops_from;

    if (scope_token~=0) { scope_error = scope_token; return ASKSCOPE_PE; }

    wn--; w=NextWord();
    e=CANTSEE_PE;
    if (w==vague_word) e=ITGONE_PE;
    i=parent(actor);
    if (i has visited && Refers(i,w)==1) e=SCENERY_PE;
    if (etype>e) return etype;
    return e;
];

! ----------------------------------------------------------------------------
!  The MultiAdd routine adds object "o" to the multiple-object-list.
!
!  This is only allowed to hold 63 objects at most, at which point it ignores
!  any new entries (and sets a global flag so that a warning may later be
!  printed if need be).
! ----------------------------------------------------------------------------

[ MultiAdd o i j;
  i=multiple_object-->0;
  if i==63 { toomany_flag=1; rtrue; }
  for (j=1:j<=i:j++)
      if (o==multiple_object-->j) 
          rtrue;
  i++;
  multiple_object-->i = o;
  multiple_object-->0 = i;
];

! ----------------------------------------------------------------------------
!  The MultiSub routine deletes object "o" from the multiple-object-list.
!
!  It returns 0 if the object was there in the first place, and 9 (because
!  this is the appropriate error number in Parser()) if it wasn't.
! ----------------------------------------------------------------------------

[ MultiSub o i j k et;
  i=multiple_object-->0; et=0;
  for (j=1:j<=i:j++)
      if (o==multiple_object-->j)
      {   for (k=j:k<=i:k++)
              multiple_object-->k = multiple_object-->(k+1);
          multiple_object-->0 = --i;
          return et;
      }
  et=9; return et;
];

! ----------------------------------------------------------------------------
!  The MultiFilter routine goes through the multiple-object-list and throws
!  out anything without the given attribute "attr" set.
! ----------------------------------------------------------------------------

[ MultiFilter attr  i j o;
  .MFiltl;
  i=multiple_object-->0;
  for (j=1:j<=i:j++)
  {   o=multiple_object-->j;
      if (o hasnt attr) { MultiSub(o); jump Mfiltl; }
  }
];

! ----------------------------------------------------------------------------
!  The UserFilter routine consults the user's filter (or checks on attribute)
!  to see what already-accepted nouns are acceptable
! ----------------------------------------------------------------------------

[ UserFilter obj;

  if (token_was>=128)
  {   if (obj has (token_was-128)) rtrue;
      rfalse;
  }
  noun=obj;
  return (indirect(#preactions_table-->(token_was-16)));
];

! ----------------------------------------------------------------------------
!  MoveWord copies word at2 from parse buffer b2 to word at1 in "parse"
!  (the main parse buffer)
! ----------------------------------------------------------------------------

[ MoveWord at1 b2 at2 x y;
  x=at1*2-1; y=at2*2-1;
  parse-->x++ = b2-->y++;
  parse-->x = b2-->y;
];

! ----------------------------------------------------------------------------
!  SearchScope  domain1 domain2 context
!
!  Works out what objects are in scope (possibly asking an outside routine),
!  but does not look at anything the player has typed.
! ----------------------------------------------------------------------------

[ SearchScope domain1 domain2 context i;

  i=0;
!  Everything is in scope to the debugging commands

#ifdef DEBUG;
  if (verb_word == 'purloin' or 'tree' or 'abstract')
  {   for (i=selfobj+1:i<=top_object:i++) PlaceInScope(i);
      rtrue;
  }
#endif;

!  First, a scope token gets priority here:

  if (scope_token ~= 0)
  {   scope_stage=2;
      if (indirect(scope_token)~=0) rtrue;
  }

!  Next, call any user-supplied routine adding things to the scope,
!  which may circumvent the usual routines altogether if they return true:

  if (domain1==actor)
  {   if (InScope(domain1)~=0) rtrue;
  }
  else if (domain2==actor)
  {   if (InScope(domain2)~=0) rtrue;
  }

!  Pick up everything in the location except the actor's possessions;
!  then go through those.  (This ensures the actor's possessions are in
!  scope even in Darkness.)

  if (context==5 && advance_warning ~= -1)       !  Scope for multiinside
  {   ScopeWithin(advance_warning, 0, context);  !  is different
  }
  else
  {   ScopeWithin(domain1, domain2, context);
      ScopeWithin(domain2,0,context);
  }
];

! ----------------------------------------------------------------------------
!  PlaceInScope is provided for routines outside the library, and is not
!  called within the parser (except for debugging purposes).
! ----------------------------------------------------------------------------

[ PlaceInScope thing;

   if (et_flag==1) { DoEachTurn(thing); rtrue; }
   wn=match_from; TryGivenObject(thing); placed_in_flag=1;
];

! ----------------------------------------------------------------------------
!  DoEachTurn
! ----------------------------------------------------------------------------

[ DoEachTurn thing j;
  if (parser_trace>=5)
  {   print "[Considering each_turn for "; DefArt(thing); print "]^"; }
  j=thing.each_turn; if (j==0) rtrue;
  if ((j-#strings_offset)>=0) { print_paddr j; new_line; rtrue; }
  RunRoutines(thing,each_turn);
];

! ----------------------------------------------------------------------------
!  ScopeWithin looks for objects in the domain which make textual sense
!  and puts them in the match list.  (However, it does not recurse through
!  the second argument.)
! ----------------------------------------------------------------------------

[ ScopeWithin domain nosearch context i;

   if (domain==0) rtrue;

!  multiexcept doesn't have second parameter in scope
   if (context==4 && domain==advance_warning) rtrue;

!  Special rule: the directions (interpreted as the 12 walls of a room) are
!  always in context.  (So, e.g., "examine north wall" is always legal.)
!  (Unless we're parsing something like "all", because it would just slow
!  things down then.)

   if (indef_mode==0 && domain==location && et_flag==0) ScopeWithin(compass);

!  Look through the objects in the domain

   objectloop (domain in domain)
   { 

!  In each_turn mode, we're going through calling e_t for everything in
!  scope and not doing any parsing at all:

      if (et_flag==1) { DoEachTurn(domain); jump DontAccept; }

!  If we're beyond the end of the user's typing, accept everything
!  (NounDomain will sort things out)

      if (match_from > num_words) { MakeMatch(domain,1); jump DontAccept; }

!  "it" or "them" matches to the it-object only.  (Note that (1) this means
!  that "it" will only be understood if the object in question is still
!  in context, and (2) only one match can ever be made in this case.)

      wn=match_from;
      i=NounWord();
      if (i==1 && itobj==domain)   MakeMatch(itobj,1);
      if (i==2 && himobj==domain)  MakeMatch(himobj,1);
      if (i==3 && herobj==domain)  MakeMatch(herobj,1);
      if (i==4 && player==domain)  MakeMatch(player,1);

!  Construing the current word as the start of a noun, can it refer to the
!  object?

      wn--; TryGivenObject(domain);

      .DontAccept;

!  Shall we consider the possessions of the current object, as well?
!  Only if it's a container (so, for instance, if a dwarf carries a
!  sword, then "drop sword" will not be accepted, but "dwarf, drop sword"
!  will).
!  Also, only if there are such possessions.
!
!  Notice that the rules have been changed here recently, and that this is
!  crucial to the parser's "scope rules".  Previously only containers could
!  be "transparent" but now the parser can see "into" anything flagged as
!  transparent - such as a dwarf whose sword you can get at.

      if (child(domain)~=0
          && domain ~= nosearch
          && (domain has supporter
              || domain has transparent
              || (domain has container && domain has open)))
          ScopeWithin(domain,0,context);
  }
];

! ----------------------------------------------------------------------------
!  MakeMatch looks at how good a match is.  If it's the best so far, then
!  wipe out all the previous matches and start a new list with this one.
!  If it's only as good as the best so far, add it to the list.
!  If it's worse, ignore it altogether.
!
!  The idea is that "red panic button" is better than "red button" or "panic".
!
!  number_matched (the number of words matched) is set to the current level
!  of quality.
!
!  If PlaceInScope has complicated matters, we also need not to match
!  something a second time.
! ----------------------------------------------------------------------------

[ MakeMatch obj quality i;
   if (parser_trace>=5) print "    Match with quality ",quality,"^";
   if (token_was~=0 && UserFilter(obj)==0)
   {   if (parser_trace>=5) print "    Match filtered out^";
       rtrue;
   }
   if (quality < match_length) rtrue;
   if (quality > match_length) { match_length=quality; number_matched=0; }
   else
   {   if (placed_in_flag==1)
       {   for (i=0:i<number_matched:i++)
               if (match_list-->i==obj) rtrue;
       }
   }
   match_list-->number_matched++ = obj;
   if (parser_trace>=5) print "    Match added to list^";
];

! ----------------------------------------------------------------------------
!  TryGivenObject tries to match as many words as possible in what has been
!  typed to the given object, obj.  If it manages any words matched at all,
!  it calls MakeMatch to say so.  There is no return value.
! ----------------------------------------------------------------------------

[ TryGivenObject obj threshold k;

   if (parser_trace>=5)
   {   print "    Trying "; DefArt(obj);
       print " (", obj, ") at word ", wn, "^";
   }

!  If input has run out and we're in indefinite mode, then always match,
!  with only quality 0 (this saves time).

   if (indef_mode ~=0 && wn > parse->1) { MakeMatch(obj,0); rfalse; }

!  Ask the object to parse itself if necessary, sitting up and taking notice
!  if it says the plural was used:

   if (obj.parse_name~=0)
   {   parser_action=-1;
       k=RunRoutines(obj,parse_name);
       if (k>0)
       {   if (parser_action == ##PluralFound)
           {   if (allow_plurals == 0) jump NoWordsMatch;
               if (indef_mode==0)
               {   indef_mode=1; indef_type=0; indef_wanted=0; }
               indef_type=indef_type | PLURAL_BIT;
               if (indef_wanted==0) indef_wanted=100;
           }
           MakeMatch(obj,k); rfalse;
       }
       if (k==0) jump NoWordsMatch;
   }

!  The default algorithm is simply to count up how many words pass the
!  Refers test:

   if (0 == Refers(obj,NounWord()))
   {   .NoWordsMatch;
       if (indef_mode~=0) MakeMatch(obj,0);
       rfalse;
   }

   threshold=1;

   while (0~=Refers(obj,NextWord())) threshold++;
   MakeMatch(obj,threshold);

   if (parser_trace>=5) print "    Matched^";
];

! ----------------------------------------------------------------------------
!  Refers works out whether the word with dictionary address wd can refer to
!  the object obj, by seeing if wd is listed in the "names" property of obj.
! ----------------------------------------------------------------------------

[ Refers obj wd   k l m;
    if (obj==0) rfalse;
    k=obj.&1; l=(obj.#1)/2-1;
    for (m=0:m<=l:m++)
        if (wd==k-->m) rtrue;
    rfalse;
];

! ----------------------------------------------------------------------------
!  NounWord (which takes no arguments) returns:
!
!   1  if the next word is "it" or "them",
!   2  if the next word is "him",
!   3  if the next word is "her",
!   4  if "me", "myself", "self"
!   0  if the next word is unrecognised or does not carry the "noun" bit in
!      its dictionary entry,
!   or the address in the dictionary if it is a recognised noun.
!
!  The "current word" marker moves on one.
! ----------------------------------------------------------------------------

[ NounWord i;
   i=NextWord();
   if (i=='it' or 'them') return 1;
   if (i=='him') return 2;
   if (i=='her') return 3;
   if (i=='me' or 'myself' or 'self') return 4;
   if (i==0) rfalse;
   if ((i->#dict_par1)&128 == 0) rfalse;
   return i;
];

! ----------------------------------------------------------------------------
!  Adjective (which takes no arguments) returns:
!
!   0  if the next word is listed in the dictionary as possibly an adjective,
!   or its adjective number if it is.
!
!  The "current word" marker moves on one.
! ----------------------------------------------------------------------------

[ Adjective i j;
   j=NextWord();
   if (j==0) rfalse;
   i=j->#dict_par1;
   if (i&8 == 0) rfalse;
   return(j->#dict_par3);
];

! ----------------------------------------------------------------------------
!  AdjectiveAddress works out the address in the dictionary of the word
!  corresponding to the given adjective number.
!
!  It should never produce the given error (which would mean that Inform
!  had set up the adjectives table incorrectly).
! ----------------------------------------------------------------------------

[ AdjectiveAddress number m;
   m=#adjectives_table;
   for (::)
   {   if (number==m-->1) return m-->0;
       m=m+4;
   }
   m=#adjectives_table;
   print "<Adjective not found>";
   return m;
];

! ----------------------------------------------------------------------------
!  NextWord (which takes no arguments) returns:
!
!  0            if the next word is unrecognised,
!  comma_word   if it is a comma character
!               (which is treated oddly by the Z-machine, hence the code)
!  or the dictionary address if it is recognised.
!
!  The "current word" marker is moved on.
! ----------------------------------------------------------------------------

[ NextWord i j k;

   if (wn > parse->1) { wn++; rfalse; }
   i=wn*2-1; wn++;
   j=parse-->i;
   if (j==0)
   {   k=wn*4-3; i=buffer->(parse->k);
       if (i==',') j=comma_word;
       if (i=='.') j='then';
   }
   return j;
];   

! ----------------------------------------------------------------------------
!  TryNumber is the only routine which really does any character-level
!  parsing, since that's normally left to the Z-machine.
!  It takes word number "wordnum" and tries to parse it as an (unsigned)
!  decimal number, returning
!
!  -1000                if it is not a number
!  the number           if it has between 1 and 4 digits
!  10000                if it has 5 or more digits.
!
!  (The danger of allowing 5 digits is that Z-machine integers are only
!  16 bits long, and anyway this isn't meant to be perfect.)
!
!  Using NumberWord, it also catches "one" up to "twenty".
!
!  Note that a game can provide a ParseNumber routine which takes priority,
!  to enable parsing of odder numbers ("x45y12", say).
! ----------------------------------------------------------------------------

[ TryNumber wordnum   i j c num len mul tot d digit;

   i=wn; wn=wordnum; j=NextWord(); wn=i;
   j=NumberWord(j); if (j>=1) return j;

   i=wordnum*4+1; j=parse->i; num=j+buffer; len=parse->(i-1);

   tot=ParseNumber(num, len);  if (tot~=0) return tot;

   if (len>=4) mul=1000;
   if (len==3) mul=100;
   if (len==2) mul=10;
   if (len==1) mul=1;

   tot=0; c=0; len=len-1;

   for (c=0:c<=len:c++)
   {   digit=num->c;
       if (digit=='0') { d=0; jump digok; }
       if (digit=='1') { d=1; jump digok; }
       if (digit=='2') { d=2; jump digok; }
       if (digit=='3') { d=3; jump digok; }
       if (digit=='4') { d=4; jump digok; }
       if (digit=='5') { d=5; jump digok; }
       if (digit=='6') { d=6; jump digok; }
       if (digit=='7') { d=7; jump digok; }
       if (digit=='8') { d=8; jump digok; }
       if (digit=='9') { d=9; jump digok; }
       return -1000;
     .digok;
       tot=tot+mul*d; mul=mul/10;
   }
   if (len>3) tot=10000;
   return tot;
];

! ----------------------------------------------------------------------------
!  ResetVagueWords does, assuming that i was the object last referred to
! ----------------------------------------------------------------------------

[ ResetVagueWords i;
   if (i has animate)
   {   if (GetGender(i)==1) himobj=i;
       else herobj=i;
   }
   else itobj=i;
];

! ----------------------------------------------------------------------------
!  GetGender returns 0 if the given animate object is female, and 1 if male
!  (not all games will want such a simple decision function!)
! ----------------------------------------------------------------------------

[ GetGender person;
   if (person hasnt female) rtrue;
   rfalse;
];

! ----------------------------------------------------------------------------
!  For copying buffers
! ----------------------------------------------------------------------------

[ Copy bto bfrom i size;
   size=bto->0;
   for (i=1:i<=size:i++) bto->i=bfrom->i;
];

! ----------------------------------------------------------------------------
!  End of the parser proper: the remaining routines are its front end.
! ----------------------------------------------------------------------------

[ DisplayStatus;
   if (the_time==$ffff)
   {   sline1=score; sline2=turns; }
   else
   {   sline1=the_time/60; sline2=the_time%60; }
];

[ SetTime t s;
   the_time=t; time_rate=s; time_step=0;
   if (s<0) time_step=0-s;
];

[ PlayTheGame i j k l aflag;

   top_object = #largest_object-255;

   Initialise();

   last_score = score;
   move player to location;
   while (parent(location)~=0) location=parent(location);
   objectloop (i in player) give i moved;
   player.capacity = MAX_CARRIED;

   Banner();

   LookSub();

   for (i=1:i<=100:i++) j=random(i);

   while deadflag==0
   {   if (score ~= last_score)
       {   if (notify_mode==1)
           {   print "^[Your score has just gone ";
               if (last_score > score) { i=last_score-score; print "down"; }
               else { i=score-last_score; print "up"; }
               print " by "; EnglishNumber(i); print " point";
               if (i>1) print "s"; print ".]^";
           }
           last_score=score;
       }
       .Error;
       inp1=0; inp2=0; action=0; meta=0;
       Parser(inputobjs);

       onotheld_mode=notheld_mode; notheld_mode=0;

       if (actor~=player)
       {   action=inputobjs-->0;
           inp1=inputobjs-->2;
           inp2=inputobjs-->3;
           if (action==##GiveR)
           {   inp2=inputobjs-->2;
               inp1=inputobjs-->3; action=##Give;
           }
           if (RunLife(actor,##Order)==0)
           {   CDefArt(actor); print " has better things to do.^"; }
           jump timeslice;
       }

       if (toomany_flag==1)
       {   toomany_flag=0;
           print "(considering the first sixteen objects only)^";
       }
       aflag=0;
       if (action~=0) aflag=1;
       if (action==0) action=inputobjs-->0;

       if (aflag==0)
       {   i=inputobjs-->1;
           inp1=inputobjs-->2;
           inp2=inputobjs-->3;
       }
       else i=2;

       if (i==0) { inp1=0; inp2=0; }
       if (i==1) { inp2=0; }

       multiflag=0;
       if (i==0) Process(0,0,action);
       else
       {   if (inp1~=0) Process(inp1,inp2,action);
           else
           {   multiflag=1;
               j=multiple_object-->0;
               if (j==0) { print "Nothing to do!^"; jump Error; }
               for (k=1:k<=j:k++)
               {   l=multiple_object-->k; PrintShortName(l); print ": ";
                   Process(l,inp2,action);
               }
           }
       }

       .timeslice;
       if (notheld_mode==1) meta=1;
       if (deadflag==0 && meta==0) Time();
   }

   if (deadflag~=2) AfterLife();
   if (deadflag==0) jump Error;

   print "^^    ***";
   if (deadflag==1) print " You have died ";
   if (deadflag==2) print " You have won ";
   if (deadflag>2)  { print " "; DeathMessage(); print " "; }
   print "***^^^";
   ScoreSub();
   DisplayStatus();

   .RRQPL;
   print "^Would you like to RESTART, RESTORE a saved game";
   if (TASKS_PROVIDED==0)
       print ", give the FULL score for that game";
   if (deadflag==2 && AMUSING_PROVIDED==0)
       print ", see some suggestions for AMUSING things to do";
   print " or QUIT?^";
   .RRQL;
   print "> ";
   #IFV3; read buffer parse; #ENDIF;
   #IFV5; read buffer parse DrawStatusLine; #ENDIF;
   i=parse-->1;
   if (i=='quit' or #w$q) quit;
   if (i=='restart')      restart;
   if (i=='restore')      { RestoreSub(); jump RRQPL; }
   if (i=='fullscore' or 'full' && TASKS_PROVIDED==0)
   {   new_line; FullScoreSub(); jump RRQPL; }
   if (deadflag==2 && i=='amusing' && AMUSING_PROVIDED==0)
   {   new_line; Amusing(); jump RRQPL; }
#IFV5;
   if (i=='undo')
   {   if (undo_flag==0)
       {   print "[Your interpreter does not provide ~undo~.  Sorry!]^";
           jump RRQPL;
       }
       if (undo_flag==1) jump UndoFailed2;
       restore_undo i;
       if (i==0)
       {   .UndoFailed2;
            print "~Undo~ failed.  [Not all interpreters provide it.]^";
       }
       jump RRQPL;
   }
#ENDIF;
   print "Please give one of the answers above.^";
   jump RRQL;
];

[ RunRoutines ofobj fromprop i j k l m;

   if (ofobj==thedark) ofobj=real_location;
   if (ofobj.fromprop==$ffff) rfalse;

#IFDEF DEBUG;
 if (debug_flag & 1 ~= 0 && fromprop~=short_name)
 { print "[Running ";
   if (fromprop==before)   { print "before";   jump DebugPrt; }
   if (fromprop==after)    { print "after";    jump DebugPrt; }
   if (fromprop==life)     { print "life";     jump DebugPrt; }
   if (fromprop==each_turn) { print "each_turn"; jump DebugPrt; }
   if (fromprop==describe) { print "describe"; jump DebugPrt; }
   if (fromprop==initial)  { print "initial";  jump DebugPrt; }
   if (fromprop==n_to)     { print "n_to/door_to";   jump DebugPrt; }
   if (fromprop==s_to)     { print "s_to";   jump DebugPrt; }
   if (fromprop==e_to)     { print "e_to";   jump DebugPrt; }
   if (fromprop==w_to)     { print "w_to/door_dir";   jump DebugPrt; }
   if (fromprop==ne_to)    { print "ne_to";   jump DebugPrt; }
   if (fromprop==nw_to)    { print "nw_to";   jump DebugPrt; }
   if (fromprop==se_to)    { print "se_to";   jump DebugPrt; }
   if (fromprop==sw_to)    { print "sw_to";   jump DebugPrt; }
   if (fromprop==u_to)     { print "u_to/invent";   jump DebugPrt; }
   if (fromprop==d_to)     { print "d_to/plural";   jump DebugPrt; }
   if (fromprop==in_to)    { print "in_to";   jump DebugPrt; }
   if (fromprop==out_to)   { print "out_to";   jump DebugPrt; }
   if (fromprop==time_out) { print "daemon/time_out";   jump DebugPrt; }
   if (fromprop==parse_name) { print "parse_name";   jump DebugPrt; }
   print "property ",fromprop;
   .DebugPrt;
   print " for ", object ofobj,"]^";
 }
#ENDIF;

   j=ofobj.&fromprop; k=ofobj.#fromprop; m=self; self=ofobj;
   noun=inp1; second=inp2;
   if (fromprop==life) sw__var=reason_code;
   else sw__var=action;
   for (i=0:i<k/2:i++)
   {   l=indirect(j-->i);
       if (l~=0) { self=m; return l; }
   }
   self=m;
   rfalse;
];

#ifdef DEBUG;
[ TraceAction source;
  print "[Action ", action;
  if (noun~=0)   { print " with noun ";  DefArt(noun);   }
  if (second~=0) { print " and second "; DefArt(second); }
  if (source==1) print " (from outside)"; else print " (from parser)";
  print "]^";
];
#endif;

[ R_Process acti i j sn ss sa sse;
   sn=inp1; ss=inp2; sa=action; sse=self;
   inp1 = i; inp2 = j; noun=i; second=j; action=acti;

#IFDEF DEBUG;
   if (debug_flag & 2 ~= 0) TraceAction(1);
#ENDIF;

   if (meta~=1)
   {   if (GamePreRoutine()~=0) jump Subside;
       if (RunRoutines(player,before)~=0) jump Subside;
       if (location~=0 && RunRoutines(location,before)~=0) jump Subside;
       if (inp1>1 && RunRoutines(inp1,before)~=0) jump Subside;
   }
   indirect(#actions_table-->action);
   self=sse; inp1=sn; noun=sn; inp2=ss; second=ss; action=sa; rfalse;
   .Subside;
   self=sse; inp1=sn; noun=sn; inp2=ss; second=ss; action=sa; rtrue;
];

[ Process i j acti;
   inp1 = i; inp2 = j; noun=i; second=j; action=acti;
   if (inp1==1) noun=special_number;
   if (inp2==1)
   {   if (inp1==1) second=special_number2;
       else second=special_number;
   }
#IFDEF DEBUG;
   if (debug_flag & 2 ~= 0) TraceAction(0);
#ENDIF;
   if (meta~=1)
   {   if (GamePreRoutine()~=0) rtrue;
       if (RunRoutines(player,before)~=0) jump Subside;
       if (location~=0 && RunRoutines(location,before)~=0) rtrue;
       if (inp1>1 && RunRoutines(inp1,before)~=0) rtrue;
   }
   indirect(#actions_table-->action);
];

[ RunLife a j;
   reason_code = j; return RunRoutines(a,life);
];

[ AfterRoutines;

   if (RunRoutines(player,after)~=0) rtrue;
   if (location~=0 && RunRoutines(location,after)~=0) rtrue;
   if (inp1>1 && RunRoutines(inp1,after)~=0) rtrue;

   return GamePostRoutine();
];

[ LAfterRoutines;
   if (location~=0 && RunRoutines(location,after)~=0) rtrue;
   return GamePostRoutine();
];

[ Banner i;
#IFV5; style bold; #ENDIF;
   print_paddr #Story;
#IFV5; style roman; #ENDIF;
   print_paddr #Headline;
   print "Release ", (0-->1) & $03ff, " / Serial number ";
   for (i=18:i<24:i++) print_char 0->i;
#IFV3;
  print "  (Compiled by Inform v"; inversion;
#ENDIF;
#IFV5;
  print " / Interpreter ", 0->$1e, " Version ", char 0->$1f,
        "^(Compiled by Inform v"; inversion;
#ENDIF;
#ifdef DEBUG;
  print " D";
#endif;
  print ")^";
];

[ VersionSub;
  Banner(); print "Library release "; print_paddr #LibRelease;
  print " serial number "; print_paddr #LibSerial;
  new_line;
];

#IFV5;
Global pretty_flag=1;
#ENDIF;
Global item_width=8;
Global item_name="Nameless item";
Global menu_item=0;
Global menu_choices="";

[ LowKey_Menu menu_choices EntryR ChoiceR lines main_title i;

  menu_item=0;
  lines=indirect(EntryR);
  main_title=item_name;

  print "--- "; print_paddr main_title; print " ---^^";
  print_paddr menu_choices;

   .LKML;
  print "^Type a number from 1 to ", lines, " or press ENTER.^> ";

   #IFV3; read buffer parse; #ENDIF;
   #IFV5; read buffer parse DrawStatusLine; #ENDIF;
   i=parse-->1;
   if (i=='quit' or #w$q || parse->1==0)
   {   if (deadflag==0) <<Look>>;
       rfalse;
   }
   i=TryNumber(1);
   if (i<1 || i>lines) jump LKML;
   menu_item=i;
   indirect(ChoiceR);
   jump LKML;
];

#IFV3;
[ DoMenu menu_choices EntryR ChoiceR;
  LowKey_Menu(menu_choices,EntryR,ChoiceR);
];
#ENDIF;

#IFV5;
Global menu_nesting = 0;
[ DoMenu menu_choices EntryR ChoiceR
         lines main_title main_wid cl i j oldcl pkey;
  if (pretty_flag==0)
  {   LowKey_Menu(menu_choices,EntryR,ChoiceR);
      rfalse;
  }
  menu_nesting++;
  menu_item=0;
  lines=indirect(EntryR);
  main_title=item_name; main_wid=item_width;
  cl=7;
  .ReDisplay;
      oldcl=0;
      erase_window $ffff;
      i=lines+7;
      split_window i;
      i = 0->33;
      if i==0 { i=80; }
      set_window 1;
      set_cursor 1 1;
      style reverse;
      spaces(i); j=i/2-main_wid;
      set_cursor 1 j;
      print_paddr main_title;
      set_cursor 2 1; spaces(i);
      set_cursor 2 2; print "N = next subject";
      j=i-12; set_cursor 2 j; print "P = previous";
      set_cursor 3 1; spaces(i);
      set_cursor 3 2; print "RETURN = read subject";
      j=i-17; set_cursor 3 j;
      if (menu_nesting==1)
          print "  Q = resume game";
      else
          print "Q = previous menu";
      style roman;
      set_cursor 5 2; font off;

      print_paddr menu_choices;

      .KeyLoop;
      if (cl~=oldcl)
      {   if (oldcl>0) { set_cursor oldcl 4; print " "; }
          set_cursor cl 4; print ">";
      }
      oldcl=cl;
      read_char 1 0 0 pkey;
      if (pkey=='N' or 'n' or 130)
          { cl++; if (cl==7+lines) cl=7; jump KeyLoop; }
      if (pkey=='P' or 'p' or 129)
          { cl--; if (cl==6)  cl=6+lines; jump KeyLoop; }
      if (pkey=='Q' or 'q') { jump QuitHelp; }
      if (pkey==10 or 13)
      {   set_window 0; font on;
          new_line; new_line; new_line;

          menu_item=cl-6;
          indirect(EntryR);

          erase_window $ffff;
          split_window 1;
          i = 0->33; if i==0 { i=80; }
          set_window 1; set_cursor 1 1; style reverse; spaces(i);
          j=i/2-item_width;
          set_cursor 1 j;
          print_paddr item_name;
          style roman; set_window 0; new_line;

          if (indirect(ChoiceR)==2) jump ReDisplay;

          print "^[Please press SPACE.]^";
          read_char 1 0 0 pkey; jump ReDisplay;
      }
      jump KeyLoop;
      .QuitHelp;
      menu_nesting--; if (menu_nesting>0) rfalse;
      font on; set_cursor 1 1;
      erase_window $ffff; set_window 0;
      new_line; new_line; new_line;
      if (deadflag==0) <<Look>>;
];  
#ENDIF;

Default MAX_TIMERS  32;
Global active_timers = 0;
Global the_timers  data MAX_TIMERS;
Global timer_flags data MAX_TIMERS;

[ TimerE; "** Too many timers/daemons! Increase MAX_TIMERS **"; ];
[ TimerE2 obj; print "** Object "; PrintShortName(obj);
      " has no time_left property! **";
];

[ StartTimer obj timer i;
   for (i=0:i<active_timers:i++)
       if (the_timers->i==0) jump FoundTSlot;
   i=active_timers++;
   if (i==MAX_TIMERS) TimerE();
   .FoundTSlot;
   if (obj.&time_left==0) TimerE2(obj);
   the_timers->i=obj; timer_flags->i=1; obj.time_left=timer;
];

[ StopTimer obj i;
   for (i=0:i<active_timers:i++)
       if (the_timers->i==obj) jump FoundTSlot2;
   rfalse;
   .FoundTSlot2;
   if (obj.&time_left==0) TimerE2(obj);
   the_timers->i=0; obj.time_left=0;
];

[ StartDaemon obj i;
   for (i=0:i<active_timers:i++)
       if (the_timers->i==0) jump FoundTSlot3;
   i=active_timers++;
   if (i==MAX_TIMERS) TimerE();
   .FoundTSlot3;
   the_timers->i=obj; timer_flags->i=2;
];

[ StopDaemon obj i;
   for (i=0:i<active_timers:i++)
       if (the_timers->i==obj) jump FoundTSlot4;
   rfalse;
   .FoundTSlot4;
   the_timers->i=0;
];

[ Time i j;

   turns++;
   if (the_time~=$ffff)
   {   if (time_rate>=0) the_time=the_time+time_rate;
       else
       {   time_step--;
           if (time_step==0)
           {   the_time++;
               time_step = -time_rate;
           }
       }
       the_time=the_time % 1440;
   }
#IFDEF DEBUG;
   if (debug_flag & 4 ~= 0)
   {   for (i=0: i<active_timers: i++)
       {   j=the_timers->i;
           print i, ": "; PrintShortName(j);
           if (j~=0)
           {   if (timer_flags->i==2) print ": daemon";
               else
               { print ": timer with ", j.time_left, " turns to go"; }
           }
           new_line;
       }
   }
#ENDIF;
   for (i=0: deadflag==0 && i<active_timers: i++)
   {   j=the_timers->i;
       if (j~=0)
       {   if (timer_flags->i==2) RunRoutines(j,daemon);
           else
           {   if (j.time_left==0)
               {   StopTimer(j);
                   RunRoutines(j,time_out);
               }
               else
                   j.time_left=j.time_left-1;
           }
       }
   }
   if (deadflag==0)
   {   et_flag=1; verb_word=0;
       DoEachTurn(location);
       SearchScope(location,player,0);
       et_flag=0;
   }
   if (deadflag==0) TimePasses();
   if (deadflag==0)
   {   AdjustLight();
       objectloop (i in player)
           if (i hasnt moved)
           {   give i moved;
               if (noun has scored)
               {   score=score+OBJECT_SCORE;
                   things_score=things_score+OBJECT_SCORE;
               }
           }
   }
];

[ AdjustLight flag i;
   i=lightflag;
   lightflag=OffersLight(parent(player));

   if (i==0 && lightflag==1)
   {   location=real_location;
       if (flag==0)
       {   new_line; <Look>; }
   }

   if (i==1 && lightflag==0)
   {   real_location=location; location=thedark;
       if (flag==0)
           "^It is now pitch dark in here!";
   }
];

[ OffersLight i j;
   if (i==0) rfalse;
   if (i has light) rtrue;
   objectloop (j in i)
       if (HasLightSource(j)==1) rtrue;
   if (i has supporter || i has transparent ||
       i has enterable || (i has container && i has open))
       return OffersLight(parent(i));
   rfalse;
];

[ HasLightSource i;
   if (i==0) rfalse;
   if (i has light) rtrue;
   if (i has supporter || i has transparent ||
       i has enterable || (i has container && i has open))
   {   objectloop (i in i)
           if (HasLightSource(i)==1) rtrue;
   }
   rfalse;
];

[ SayProS x;
  if (x==0) print "is unset";
  else { print "means "; DefArt(x); }
];

[ PronounsSub;
  print "At the moment, ~it~ "; SayProS(itobj);
  print ", ~him~ "; SayProS(himobj);
  if (player==selfobj) print " and"; else print ",";
  print " ~her~ "; SayProS(herobj);
  if (player==selfobj) ".";
  print " and ~me~ means ", object player; ".";
];

[ ChangePlayer obj flag i;
  if (obj.&number==0) "** Player obj must have number prop **";
  give player ~transparent ~concealed;
  player.number=real_location; player=obj;
  give player transparent concealed animate proper;
  i=player; while(parent(i)~=0) i=parent(i); location=i;
  real_location=player.number;
  if (real_location==0) real_location=location;
  lightflag=OffersLight(parent(player));
  if (lightflag==0) location=thedark;
  print_player_flag=flag;
];

[ Indefart o;
   if (o hasnt proper) { print_paddr o.article; print " "; }
   PrintShortName(o);
];

[ Defart o;
   if (o hasnt proper) print "the "; PrintShortName(o);
];

[ CDefart o;
   if (o hasnt proper) print "The "; PrintShortName(o);
];

[ PrintShortName o i;
   if (o==0) { print "nothing"; rtrue; }
   if (o>top_object) { print "<no such object>"; rtrue; }
   if (o==player) { print "yourself"; rtrue; }
   i=o.short_name;
   if ((i-#strings_offset)>=0) { print_paddr i; rtrue; }
   if (RunRoutines(o,short_name)~=0) rtrue;
   print_obj o;
];

! ----------------------------------------------------------------------------
00000000  21 20 2d 2d 2d 2d 2d 2d  2d 2d 2d 2d 2d 2d 2d 2d  |! --------------|
00000010  2d 2d 2d 2d 2d 2d 2d 2d  2d 2d 2d 2d 2d 2d 2d 2d  |----------------|
*
00000040  2d 2d 2d 2d 2d 2d 2d 2d  2d 2d 2d 2d 2d 2d 0a 21  |--------------.!|
00000050  20 20 22 50 41 52 53 45  52 22 3a 20 20 74 68 65  |  "PARSER":  the|
00000060  20 63 6f 72 65 20 6f 66  20 74 68 65 20 49 6e 66  | core of the Inf|
00000070  6f 72 6d 20 6c 69 62 72  61 72 79 2c 20 61 6e 64  |orm library, and|
00000080  20 74 68 65 20 70 61 72  73 65 72 0a 21 0a 21 20  | the parser.!.! |
00000090  20 53 75 70 70 6c 69 65  64 20 66 6f 72 20 75 73  | Supplied for us|
000000a0  65 20 77 69 74 68 20 49  6e 66 6f 72 6d 20 35 0a  |e with Inform 5.|
000000b0  21 0a 21 20 20 28 63 29  20 47 72 61 68 61 6d 20  |!.!  (c) Graham |
000000c0  4e 65 6c 73 6f 6e 2c 20  31 39 39 33 2f 34 2c 20  |Nelson, 1993/4, |
000000d0  62 75 74 20 66 72 65 65  6c 79 20 75 73 61 62 6c  |but freely usabl|
000000e0  65 0a 21 20 2d 2d 2d 2d  2d 2d 2d 2d 2d 2d 2d 2d  |e.! ------------|
000000f0  2d 2d 2d 2d 2d 2d 2d 2d  2d 2d 2d 2d 2d 2d 2d 2d  |----------------|
*
00000130  0a 0a 43 6f 6e 73 74 61  6e 74 20 4c 69 62 53 65  |..Constant LibSe|
00000140  72 69 61 6c 20 22 39 34  31 30 30 37 22 3b 0a 43  |rial "941007";.C|
00000150  6f 6e 73 74 61 6e 74 20  4c 69 62 52 65 6c 65 61  |onstant LibRelea|
00000160  73 65 20 22 35 2f 35 22  3b 0a 0a 21 20 2d 2d 2d  |se "5/5";..! ---|
00000170  2d 2d 2d 2d 2d 2d 2d 2d  2d 2d 2d 2d 2d 2d 2d 2d  |----------------|
*
000001b0  2d 2d 2d 2d 2d 2d 2d 2d  2d 0a 21 20 20 41 74 74  |---------.!  Att|
000001c0  72 69 62 75 74 65 20 61  6e 64 20 70 72 6f 70 65  |ribute and prope|
000001d0  72 74 79 20 64 65 66 69  6e 69 74 69 6f 6e 73 0a  |rty definitions.|
000001e0  21 20 20 54 68 65 20 63  6f 6d 70 61 73 73 2c 20  |!  The compass, |
000001f0  64 69 72 65 63 74 69 6f  6e 73 2c 20 64 61 72 6b  |directions, dark|
00000200  6e 65 73 73 20 61 6e 64  20 70 6c 61 79 65 72 20  |ness and player |
00000210  6f 62 6a 65 63 74 73 0a  21 20 20 44 65 66 69 6e  |objects.!  Defin|
00000220  69 74 69 6f 6e 73 20 6f  66 20 66 61 6b 65 20 61  |itions of fake a|
00000230  63 74 69 6f 6e 73 0a 21  20 20 4c 69 62 72 61 72  |ctions.!  Librar|
00000240  79 20 67 6c 6f 62 61 6c  20 76 61 72 69 61 62 6c  |y global variabl|
00000250  65 73 0a 21 20 20 50 72  69 76 61 74 65 20 70 61  |es.!  Private pa|
00000260  72 73 65 72 20 76 61 72  69 61 62 6c 65 73 0a 21  |rser variables.!|
00000270  20 20 4b 65 79 62 6f 61  72 64 20 72 65 61 64 69  |  Keyboard readi|
00000280  6e 67 0a 21 20 20 50 61  72 73 65 72 2c 20 6c 65  |ng.!  Parser, le|
00000290  76 65 6c 20 30 3a 20 6f  75 74 65 72 20 73 68 65  |vel 0: outer she|
000002a0  6c 6c 2c 20 63 6f 6e 76  65 72 73 61 74 69 6f 6e  |ll, conversation|
000002b0  2c 20 65 72 72 6f 72 73  0a 21 20 20 20 20 20 20  |, errors.!      |
000002c0  20 20 20 20 20 20 20 20  20 20 31 3a 20 67 72 61  |          1: gra|
000002d0  6d 6d 61 72 20 6c 69 6e  65 73 0a 21 20 20 20 20  |mmar lines.!    |
000002e0  20 20 20 20 20 20 20 20  20 20 20 20 32 3a 20 74  |            2: t|
000002f0  6f 6b 65 6e 73 0a 21 20  20 20 20 20 20 20 20 20  |okens.!         |
00000300  20 20 20 20 20 20 20 33  3a 20 6f 62 6a 65 63 74  |       3: object|
00000310  20 6c 69 73 74 73 0a 21  20 20 20 20 20 20 20 20  | lists.!        |
00000320  20 20 20 20 20 20 20 20  34 3a 20 73 63 6f 70 65  |        4: scope|
00000330  20 61 6e 64 20 61 6d 62  69 67 75 69 74 79 20 72  | and ambiguity r|
00000340  65 73 6f 6c 76 69 6e 67  0a 21 20 20 20 20 20 20  |esolving.!      |
00000350  20 20 20 20 20 20 20 20  20 20 35 3a 20 6f 62 6a  |          5: obj|
00000360  65 63 74 20 63 6f 6d 70  61 72 69 73 6f 6e 73 0a  |ect comparisons.|
00000370  21 20 20 20 20 20 20 20  20 20 20 20 20 20 20 20  |!               |
00000380  20 36 3a 20 77 6f 72 64  20 63 6f 6d 70 61 72 69  | 6: word compari|
00000390  73 6f 6e 73 0a 21 20 20  20 20 20 20 20 20 20 20  |sons.!          |
000003a0  20 20 20 20 20 20 37 3a  20 72 65 61 64 69 6e 67  |      7: reading|
000003b0  20 77 6f 72 64 73 20 61  6e 64 20 6d 6f 76 69 6e  | words and movin|
000003c0  67 20 74 61 62 6c 65 73  20 61 62 6f 75 74 0a 21  |g tables about.!|
000003d0  20 20 4d 61 69 6e 20 67  61 6d 65 20 6c 6f 6f 70  |  Main game loop|
000003e0  0a 21 20 20 41 63 74 69  6f 6e 20 70 72 6f 63 65  |.!  Action proce|
000003f0  73 73 69 6e 67 0a 21 20  20 4d 65 6e 75 73 0a 21  |ssing.!  Menus.!|
00000400  20 20 54 69 6d 65 3a 20  74 69 6d 65 72 73 20 61  |  Time: timers a|
00000410  6e 64 20 64 61 65 6d 6f  6e 73 0a 21 20 20 43 6f  |nd daemons.!  Co|
00000420  6e 73 69 64 65 72 69 6e  67 20 6c 69 67 68 74 0a  |nsidering light.|
00000430  21 20 20 43 68 61 6e 67  69 6e 67 20 70 6c 61 79  |!  Changing play|
00000440  65 72 20 70 65 72 73 6f  6e 61 6c 69 74 79 0a 21  |er personality.!|
00000450  20 20 50 72 69 6e 74 69  6e 67 20 73 68 6f 72 74  |  Printing short|
00000460  20 6e 61 6d 65 73 0a 21  20 2d 2d 2d 2d 2d 2d 2d  | names.! -------|
00000470  2d 2d 2d 2d 2d 2d 2d 2d  2d 2d 2d 2d 2d 2d 2d 2d  |----------------|
*
000004b0  2d 2d 2d 2d 2d 0a 0a 21  20 2d 2d 2d 2d 2d 2d 2d  |-----..! -------|
000004c0  2d 2d 2d 2d 2d 2d 2d 2d  2d 2d 2d 2d 2d 2d 2d 2d  |----------------|
*
00000500  2d 2d 2d 2d 2d 0a 21 20  44 65 63 6c 61 72 65 20  |-----.! Declare |
00000510  74 68 65 20 61 74 74 72  69 62 75 74 65 73 20 61  |the attributes a|
00000520  6e 64 20 70 72 6f 70 65  72 74 69 65 73 2e 20 20  |nd properties.  |
00000530  4e 6f 74 65 20 74 68 61  74 20 70 72 6f 70 65 72  |Note that proper|
00000540  74 69 65 73 20 22 70 72  65 72 6f 75 74 69 6e 65  |ties "preroutine|
00000550  22 0a 21 20 61 6e 64 20  22 70 6f 73 74 72 6f 75  |".! and "postrou|
00000560  74 69 6e 65 22 20 64 65  66 61 75 6c 74 20 74 6f  |tine" default to|
00000570  20 24 66 66 66 66 20 77  68 69 63 68 20 66 6f 72  | $ffff which for|
00000580  63 65 73 20 74 68 65 6d  20 74 6f 20 62 65 20 74  |ces them to be t|
00000590  77 6f 20 62 79 74 65 73  20 6c 6f 6e 67 3a 0a 21  |wo bytes long:.!|
000005a0  20 73 69 6d 69 6c 61 72  6c 79 2c 20 22 74 69 6d  | similarly, "tim|
000005b0  65 6c 65 66 74 22 20 73  6f 6d 65 74 69 6d 65 73  |eleft" sometimes|
000005c0  20 6e 65 65 64 73 20 74  6f 20 62 65 20 6f 76 65  | needs to be ove|
000005d0  72 20 32 35 36 2c 20 73  6f 20 69 74 27 73 20 66  |r 256, so it's f|
000005e0  6c 61 67 67 65 64 20 6c  6f 6e 67 0a 21 20 2d 2d  |lagged long.! --|
000005f0  2d 2d 2d 2d 2d 2d 2d 2d  2d 2d 2d 2d 2d 2d 2d 2d  |----------------|
*
00000630  2d 2d 2d 2d 2d 2d 2d 2d  2d 2d 0a 0a 53 79 73 74  |----------..Syst|
00000640  65 6d 5f 66 69 6c 65 3b  0a 0a 41 74 74 72 69 62  |em_file;..Attrib|
00000650  75 74 65 20 61 6e 69 6d  61 74 65 3b 0a 41 74 74  |ute animate;.Att|
00000660  72 69 62 75 74 65 20 63  6c 6f 74 68 69 6e 67 3b  |ribute clothing;|
00000670  0a 41 74 74 72 69 62 75  74 65 20 63 6f 6e 63 65  |.Attribute conce|
00000680  61 6c 65 64 3b 0a 41 74  74 72 69 62 75 74 65 20  |aled;.Attribute |
00000690  63 6f 6e 74 61 69 6e 65  72 3b 0a 41 74 74 72 69  |container;.Attri|
000006a0  62 75 74 65 20 64 69 72  65 63 74 69 6f 6e 3b 0a  |bute direction;.|
000006b0  41 74 74 72 69 62 75 74  65 20 64 6f 6f 72 3b 0a  |Attribute door;.|
000006c0  41 74 74 72 69 62 75 74  65 20 65 64 69 62 6c 65  |Attribute edible|
000006d0  3b 0a 41 74 74 72 69 62  75 74 65 20 65 6e 74 65  |;.Attribute ente|
000006e0  72 61 62 6c 65 3b 0a 41  74 74 72 69 62 75 74 65  |rable;.Attribute|
000006f0  20 66 65 6d 61 6c 65 3b  0a 41 74 74 72 69 62 75  | female;.Attribu|
00000700  74 65 20 67 65 6e 65 72  61 6c 3b 0a 41 74 74 72  |te general;.Attr|
00000710  69 62 75 74 65 20 6c 69  67 68 74 3b 0a 41 74 74  |ibute light;.Att|
00000720  72 69 62 75 74 65 20 6c  6f 63 6b 61 62 6c 65 3b  |ribute lockable;|
00000730  0a 41 74 74 72 69 62 75  74 65 20 6c 6f 63 6b 65  |.Attribute locke|
00000740  64 3b 0a 41 74 74 72 69  62 75 74 65 20 6d 6f 76  |d;.Attribute mov|
00000750  65 64 3b 0a 41 74 74 72  69 62 75 74 65 20 6f 6e  |ed;.Attribute on|
00000760  3b 0a 41 74 74 72 69 62  75 74 65 20 6f 70 65 6e  |;.Attribute open|
*
00000780  61 62 6c 65 3b 0a 41 74  74 72 69 62 75 74 65 20  |able;.Attribute |
00000790  70 72 6f 70 65 72 3b 0a  41 74 74 72 69 62 75 74  |proper;.Attribut|
000007a0  65 20 73 63 65 6e 65 72  79 3b 0a 41 74 74 72 69  |e scenery;.Attri|
000007b0  62 75 74 65 20 73 63 6f  72 65 64 3b 0a 41 74 74  |bute scored;.Att|
000007c0  72 69 62 75 74 65 20 73  74 61 74 69 63 3b 0a 41  |ribute static;.A|
000007d0  74 74 72 69 62 75 74 65  20 73 75 70 70 6f 72 74  |ttribute support|
000007e0  65 72 3b 0a 41 74 74 72  69 62 75 74 65 20 73 77  |er;.Attribute sw|
000007f0  69 74 63 68 61 62 6c 65  3b 0a 41 74 74 72 69 62  |itchable;.Attrib|
00000800  75 74 65 20 74 61 6c 6b  61 62 6c 65 3b 0a 41 74  |ute talkable;.At|
00000810  74 72 69 62 75 74 65 20  74 72 61 6e 73 70 61 72  |tribute transpar|
00000820  65 6e 74 3b 0a 41 74 74  72 69 62 75 74 65 20 76  |ent;.Attribute v|
00000830  69 73 69 74 65 64 3b 0a  41 74 74 72 69 62 75 74  |isited;.Attribut|
00000840  65 20 77 6f 72 6b 66 6c  61 67 3b 0a 41 74 74 72  |e workflag;.Attr|
00000850  69 62 75 74 65 20 77 6f  72 6e 3b 0a 0a 41 74 74  |ibute worn;..Att|
00000860  72 69 62 75 74 65 20 61  62 73 65 6e 74 20 61 6c  |ribute absent al|
00000870  69 61 73 20 66 65 6d 61  6c 65 3b 20 20 20 20 20  |ias female;     |
00000880  20 21 20 20 50 6c 65 61  73 65 2c 20 6e 6f 20 70  | !  Please, no p|
00000890  73 79 63 68 6f 61 6e 61  6c 79 73 69 73 0a 0a 50  |sychoanalysis..P|
000008a0  72 6f 70 65 72 74 79 20  61 64 64 69 74 69 76 65  |roperty additive|
000008b0  20 62 65 66 6f 72 65 20  24 66 66 66 66 3b 0a 50  | before $ffff;.P|
000008c0  72 6f 70 65 72 74 79 20  61 64 64 69 74 69 76 65  |roperty additive|
000008d0  20 61 66 74 65 72 20 20  24 66 66 66 66 3b 0a 50  | after  $ffff;.P|
000008e0  72 6f 70 65 72 74 79 20  61 64 64 69 74 69 76 65  |roperty additive|
000008f0  20 6c 69 66 65 20 20 20  24 66 66 66 66 3b 0a 0a  | life   $ffff;..|
00000900  50 72 6f 70 65 72 74 79  20 6c 6f 6e 67 20 6e 5f  |Property long n_|
00000910  74 6f 3b 20 20 50 72 6f  70 65 72 74 79 20 6c 6f  |to;  Property lo|
00000920  6e 67 20 73 5f 74 6f 3b  20 21 20 20 53 6c 69 67  |ng s_to; !  Slig|
00000930  68 74 6c 79 20 77 61 73  74 65 66 75 6c 6c 79 2c  |htly wastefully,|
00000940  20 74 68 65 73 65 20 61  72 65 0a 50 72 6f 70 65  | these are.Prope|
00000950  72 74 79 20 6c 6f 6e 67  20 65 5f 74 6f 3b 20 20  |rty long e_to;  |
00000960  50 72 6f 70 65 72 74 79  20 6c 6f 6e 67 20 77 5f  |Property long w_|
00000970  74 6f 3b 20 21 20 20 6c  6f 6e 67 20 28 74 68 65  |to; !  long (the|
00000980  79 20 6d 69 67 68 74 20  62 65 20 72 6f 75 74 69  |y might be routi|
00000990  6e 65 73 29 0a 50 72 6f  70 65 72 74 79 20 6c 6f  |nes).Property lo|
000009a0  6e 67 20 6e 65 5f 74 6f  3b 20 50 72 6f 70 65 72  |ng ne_to; Proper|
000009b0  74 79 20 6c 6f 6e 67 20  73 65 5f 74 6f 3b 0a 50  |ty long se_to;.P|
000009c0  72 6f 70 65 72 74 79 20  6c 6f 6e 67 20 6e 77 5f  |roperty long nw_|
000009d0  74 6f 3b 20 50 72 6f 70  65 72 74 79 20 6c 6f 6e  |to; Property lon|
000009e0  67 20 73 77 5f 74 6f 3b  0a 50 72 6f 70 65 72 74  |g sw_to;.Propert|
000009f0  79 20 6c 6f 6e 67 20 75  5f 74 6f 3b 20 20 50 72  |y long u_to;  Pr|
00000a00  6f 70 65 72 74 79 20 6c  6f 6e 67 20 64 5f 74 6f  |operty long d_to|
00000a10  3b 0a 50 72 6f 70 65 72  74 79 20 6c 6f 6e 67 20  |;.Property long |
00000a20  69 6e 5f 74 6f 3b 20 50  72 6f 70 65 72 74 79 20  |in_to; Property |
00000a30  6c 6f 6e 67 20 6f 75 74  5f 74 6f 3b 0a 0a 50 72  |long out_to;..Pr|
00000a40  6f 70 65 72 74 79 20 64  6f 6f 72 5f 74 6f 20 20  |operty door_to  |
00000a50  20 20 20 61 6c 69 61 73  20 6e 5f 74 6f 3b 20 20  |   alias n_to;  |
00000a60  20 20 20 21 20 20 46 6f  72 20 65 63 6f 6e 6f 6d  |   !  For econom|
00000a70  79 3a 20 74 68 65 73 65  20 70 72 6f 70 65 72 74  |y: these propert|
00000a80  69 65 73 20 61 72 65 0a  50 72 6f 70 65 72 74 79  |ies are.Property|
00000a90  20 77 68 65 6e 5f 63 6c  6f 73 65 64 20 61 6c 69  | when_closed ali|
00000aa0  61 73 20 73 5f 74 6f 3b  20 20 20 20 20 21 20 20  |as s_to;     !  |
00000ab0  75 73 65 64 20 6f 6e 6c  79 20 62 79 20 6f 62 6a  |used only by obj|
00000ac0  65 63 74 73 20 77 68 69  63 68 0a 50 72 6f 70 65  |ects which.Prope|
00000ad0  72 74 79 20 77 69 74 68  5f 6b 65 79 20 20 20 20  |rty with_key    |
00000ae0  61 6c 69 61 73 20 65 5f  74 6f 3b 20 20 20 20 20  |alias e_to;     |
00000af0  21 20 20 61 72 65 6e 27  74 20 72 6f 6f 6d 73 0a  |!  aren't rooms.|
00000b00  50 72 6f 70 65 72 74 79  20 64 6f 6f 72 5f 64 69  |Property door_di|
00000b10  72 20 20 20 20 61 6c 69  61 73 20 77 5f 74 6f 3b  |r    alias w_to;|
00000b20  20 20 20 20 20 21 0a 50  72 6f 70 65 72 74 79 20  |     !.Property |
00000b30  69 6e 76 65 6e 74 20 20  20 20 20 20 61 6c 69 61  |invent      alia|
00000b40  73 20 75 5f 74 6f 3b 20  20 20 20 20 21 0a 50 72  |s u_to;     !.Pr|
00000b50  6f 70 65 72 74 79 20 70  6c 75 72 61 6c 20 20 20  |operty plural   |
00000b60  20 20 20 61 6c 69 61 73  20 64 5f 74 6f 3b 20 20  |   alias d_to;  |
00000b70  20 20 20 21 0a 0a 50 72  6f 70 65 72 74 79 20 69  |   !..Property i|
00000b80  6e 69 74 69 61 6c 3b 0a  50 72 6f 70 65 72 74 79  |nitial;.Property|
00000b90  20 77 68 65 6e 5f 6f 70  65 6e 20 20 20 61 6c 69  | when_open   ali|
00000ba0  61 73 20 69 6e 69 74 69  61 6c 3b 0a 50 72 6f 70  |as initial;.Prop|
00000bb0  65 72 74 79 20 77 68 65  6e 5f 6f 6e 20 20 20 20  |erty when_on    |
00000bc0  20 61 6c 69 61 73 20 69  6e 69 74 69 61 6c 3b 0a  | alias initial;.|
00000bd0  50 72 6f 70 65 72 74 79  20 77 68 65 6e 5f 6f 66  |Property when_of|
00000be0  66 20 20 20 20 61 6c 69  61 73 20 77 68 65 6e 5f  |f    alias when_|
00000bf0  63 6c 6f 73 65 64 3b 0a  50 72 6f 70 65 72 74 79  |closed;.Property|
00000c00  20 6c 6f 6e 67 20 64 65  73 63 72 69 70 74 69 6f  | long descriptio|
00000c10  6e 3b 0a 50 72 6f 70 65  72 74 79 20 61 64 64 69  |n;.Property addi|
00000c20  74 69 76 65 20 64 65 73  63 72 69 62 65 20 24 66  |tive describe $f|
00000c30  66 66 66 3b 0a 50 72 6f  70 65 72 74 79 20 61 72  |fff;.Property ar|
00000c40  74 69 63 6c 65 20 22 61  22 3b 0a 0a 50 72 6f 70  |ticle "a";..Prop|
00000c50  65 72 74 79 20 63 61 6e  74 5f 67 6f 20 22 59 6f  |erty cant_go "Yo|
00000c60  75 20 63 61 6e 27 74 20  67 6f 20 74 68 61 74 20  |u can't go that |
00000c70  77 61 79 2e 22 3b 0a 0a  50 72 6f 70 65 72 74 79  |way.";..Property|
00000c80  20 6c 6f 6e 67 20 66 6f  75 6e 64 5f 69 6e 3b 20  | long found_in; |
00000c90  20 20 20 20 20 20 20 20  21 20 20 46 6f 72 20 66  |        !  For f|
00000ca0  69 64 64 6c 79 20 72 65  61 73 6f 6e 73 20 74 68  |iddly reasons th|
00000cb0  69 73 20 63 61 6e 27 74  20 61 6c 69 61 73 0a 0a  |is can't alias..|
00000cc0  50 72 6f 70 65 72 74 79  20 6c 6f 6e 67 20 74 69  |Property long ti|
00000cd0  6d 65 5f 6c 65 66 74 3b  0a 50 72 6f 70 65 72 74  |me_left;.Propert|
00000ce0  79 20 6c 6f 6e 67 20 6e  75 6d 62 65 72 3b 0a 50  |y long number;.P|
00000cf0  72 6f 70 65 72 74 79 20  61 64 64 69 74 69 76 65  |roperty additive|
00000d00  20 74 69 6d 65 5f 6f 75  74 20 24 66 66 66 66 3b  | time_out $ffff;|
00000d10  0a 50 72 6f 70 65 72 74  79 20 64 61 65 6d 6f 6e  |.Property daemon|
00000d20  20 61 6c 69 61 73 20 74  69 6d 65 5f 6f 75 74 3b  | alias time_out;|
00000d30  0a 50 72 6f 70 65 72 74  79 20 61 64 64 69 74 69  |.Property additi|
00000d40  76 65 20 65 61 63 68 5f  74 75 72 6e 20 24 66 66  |ve each_turn $ff|
00000d50  66 66 3b 0a 0a 50 72 6f  70 65 72 74 79 20 63 61  |ff;..Property ca|
00000d60  70 61 63 69 74 79 20 31  30 30 3b 0a 0a 50 72 6f  |pacity 100;..Pro|
00000d70  70 65 72 74 79 20 6c 6f  6e 67 20 73 68 6f 72 74  |perty long short|
00000d80  5f 6e 61 6d 65 3b 0a 50  72 6f 70 65 72 74 79 20  |_name;.Property |
00000d90  6c 6f 6e 67 20 70 61 72  73 65 5f 6e 61 6d 65 3b  |long parse_name;|
00000da0  0a 0a 21 20 54 68 65 20  66 6f 6c 6c 6f 77 69 6e  |..! The followin|
00000db0  67 20 64 65 66 69 6e 69  74 69 6f 6e 73 2c 20 63  |g definitions, c|
00000dc0  6f 6d 6d 65 6e 74 65 64  20 6f 75 74 2c 20 64 65  |ommented out, de|
00000dd0  66 69 6e 65 20 70 72 65  2d 49 6e 66 6f 72 6d 20  |fine pre-Inform |
00000de0  35 2e 32 20 61 6e 64 20  6e 6f 77 0a 21 20 6f 62  |5.2 and now.! ob|
00000df0  73 65 6c 65 74 65 20 6e  61 6d 65 73 20 61 73 20  |selete names as |
00000e00  61 6c 69 61 73 65 73 20  66 6f 72 20 74 68 65 20  |aliases for the |
00000e10  73 74 61 6e 64 61 72 64  20 6e 61 6d 65 73 3a 0a  |standard names:.|
00000e20  0a 21 20 50 72 6f 70 65  72 74 79 20 70 72 65 72  |.! Property prer|
00000e30  6f 75 74 69 6e 65 20 61  6c 69 61 73 20 62 65 66  |outine alias bef|
00000e40  6f 72 65 3b 20 50 72 6f  70 65 72 74 79 20 64 65  |ore; Property de|
00000e50  73 63 20 20 20 20 20 20  20 20 61 6c 69 61 73 20  |sc        alias |
00000e60  64 65 73 63 72 69 70 74  69 6f 6e 3b 0a 21 20 50  |description;.! P|
00000e70  72 6f 70 65 72 74 79 20  70 6f 73 74 72 6f 75 74  |roperty postrout|
00000e80  69 6e 65 20 61 6c 69 61  73 20 61 66 74 65 72 3b  |ine alias after;|
00000e90  20 50 72 6f 70 65 72 74  79 20 6c 6f 6e 67 64 65  | Property longde|
00000ea0  73 63 20 20 20 20 61 6c  69 61 73 20 64 65 73 63  |sc    alias desc|
00000eb0  72 69 70 74 69 6f 6e 3b  0a 21 20 50 72 6f 70 65  |ription;.! Prope|
00000ec0  72 74 79 20 6c 69 66 65  72 6f 75 74 69 6e 65 20  |rty liferoutine |
00000ed0  61 6c 69 61 73 20 6c 69  66 65 3b 20 20 50 72 6f  |alias life;  Pro|
00000ee0  70 65 72 74 79 20 74 69  6d 65 6c 65 66 74 20 20  |perty timeleft  |
00000ef0  20 20 61 6c 69 61 73 20  74 69 6d 65 5f 6c 65 66  |  alias time_lef|
00000f00  74 3b 0a 21 20 50 72 6f  70 65 72 74 79 20 69 6e  |t;.! Property in|
00000f10  69 74 70 6f 73 20 20 20  20 20 61 6c 69 61 73 20  |itpos     alias |
00000f20  69 6e 69 74 69 61 6c 3b  0a 21 20 50 72 6f 70 65  |initial;.! Prope|
00000f30  72 74 79 20 70 6f 72 74  61 6c 74 6f 20 20 20 20  |rty portalto    |
00000f40  61 6c 69 61 73 20 64 6f  6f 72 5f 74 6f 3b 0a 21  |alias door_to;.!|
00000f50  20 50 72 6f 70 65 72 74  79 20 63 6c 6f 73 65 64  | Property closed|
00000f60  70 6f 73 20 20 20 61 6c  69 61 73 20 77 68 65 6e  |pos   alias when|
00000f70  5f 63 6c 6f 73 65 64 3b  0a 21 20 50 72 6f 70 65  |_closed;.! Prope|
00000f80  72 74 79 20 64 69 72 70  72 6f 70 20 20 20 20 20  |rty dirprop     |
00000f90  61 6c 69 61 73 20 64 6f  6f 72 5f 64 69 72 3b 0a  |alias door_dir;.|
00000fa0  21 20 50 72 6f 70 65 72  74 79 20 63 61 6e 74 67  |! Property cantg|
00000fb0  6f 20 20 20 20 20 20 61  6c 69 61 73 20 63 61 6e  |o      alias can|
00000fc0  74 5f 67 6f 3b 0a 21 20  41 74 74 72 69 62 75 74  |t_go;.! Attribut|
00000fd0  65 20 70 6f 72 74 61 6c  20 61 6c 69 61 73 20 64  |e portal alias d|
00000fe0  6f 6f 72 3b 0a 0a 21 20  2d 2d 2d 2d 2d 2d 2d 2d  |oor;..! --------|
00000ff0  2d 2d 2d 2d 2d 2d 2d 2d  2d 2d 2d 2d 2d 2d 2d 2d  |----------------|
*
00001030  2d 2d 2d 2d 0a 21 20 43  6f 6e 73 74 72 75 63 74  |----.! Construct|
00001040  20 74 68 65 20 63 6f 6d  70 61 73 73 20 2d 20 61  | the compass - a|
00001050  20 64 75 6d 6d 79 20 6f  62 6a 65 63 74 20 63 6f  | dummy object co|
00001060  6e 74 61 69 6e 69 6e 67  20 74 68 65 20 64 69 72  |ntaining the dir|
00001070  65 63 74 69 6f 6e 73 2c  20 77 68 69 63 68 20 61  |ections, which a|
00001080  6c 73 6f 0a 21 20 72 65  70 72 65 73 65 6e 74 20  |lso.! represent |
00001090  74 68 65 20 77 61 6c 6c  73 20 69 6e 20 77 68 61  |the walls in wha|
000010a0  74 65 76 65 72 20 72 6f  6f 6d 20 74 68 65 20 70  |tever room the p|
000010b0  6c 61 79 65 72 20 69 73  20 69 6e 0a 21 20 2d 2d  |layer is in.! --|
000010c0  2d 2d 2d 2d 2d 2d 2d 2d  2d 2d 2d 2d 2d 2d 2d 2d  |----------------|
*
00001100  2d 2d 2d 2d 2d 2d 2d 2d  2d 2d 0a 0a 4f 62 6a 65  |----------..Obje|
00001110  63 74 20 63 6f 6d 70 61  73 73 20 22 63 6f 6d 70  |ct compass "comp|
00001120  61 73 73 22 20 6e 6f 74  68 69 6e 67 20 68 61 73  |ass" nothing has|
00001130  20 63 6f 6e 63 65 61 6c  65 64 3b 0a 4f 62 6a 65  | concealed;.Obje|
00001140  63 74 20 6e 5f 6f 62 6a  20 22 6e 6f 72 74 68 20  |ct n_obj "north |
00001150  77 61 6c 6c 22 20 63 6f  6d 70 61 73 73 20 20 20  |wall" compass   |
00001160  20 20 20 0a 20 20 77 69  74 68 20 6e 61 6d 65 20  |   .  with name |
00001170  22 6e 22 20 22 6e 6f 72  74 68 22 20 22 77 61 6c  |"n" "north" "wal|
00001180  6c 22 2c 20 20 20 20 20  20 20 20 20 20 20 61 72  |l",           ar|
00001190  74 69 63 6c 65 20 22 74  68 65 22 2c 20 64 6f 6f  |ticle "the", doo|
000011a0  72 5f 64 69 72 20 6e 5f  74 6f 0a 20 20 68 61 73  |r_dir n_to.  has|
000011b0  20 20 73 63 65 6e 65 72  79 3b 0a 4f 62 6a 65 63  |  scenery;.Objec|
000011c0  74 20 73 5f 6f 62 6a 20  22 73 6f 75 74 68 20 77  |t s_obj "south w|
000011d0  61 6c 6c 22 20 63 6f 6d  70 61 73 73 20 20 20 20  |all" compass    |
000011e0  20 20 0a 20 20 77 69 74  68 20 6e 61 6d 65 20 22  |  .  with name "|
000011f0  73 22 20 22 73 6f 75 74  68 22 20 22 77 61 6c 6c  |s" "south" "wall|
00001200  22 2c 20 20 20 20 20 20  20 20 20 20 20 61 72 74  |",           art|
00001210  69 63 6c 65 20 22 74 68  65 22 2c 20 64 6f 6f 72  |icle "the", door|
00001220  5f 64 69 72 20 73 5f 74  6f 0a 20 20 68 61 73 20  |_dir s_to.  has |
00001230  20 73 63 65 6e 65 72 79  3b 0a 4f 62 6a 65 63 74  | scenery;.Object|
00001240  20 65 5f 6f 62 6a 20 22  65 61 73 74 20 77 61 6c  | e_obj "east wal|
00001250  6c 22 20 63 6f 6d 70 61  73 73 20 20 20 20 20 20  |l" compass      |
00001260  0a 20 20 77 69 74 68 20  6e 61 6d 65 20 22 65 22  |.  with name "e"|
00001270  20 22 65 61 73 74 22 20  22 77 61 6c 6c 22 2c 20  | "east" "wall", |
00001280  20 20 20 20 20 20 20 20  20 20 20 61 72 74 69 63  |           artic|
00001290  6c 65 20 22 74 68 65 22  2c 20 64 6f 6f 72 5f 64  |le "the", door_d|
000012a0  69 72 20 65 5f 74 6f 0a  20 20 20 68 61 73 20 20  |ir e_to.   has  |
000012b0  73 63 65 6e 65 72 79 3b  0a 4f 62 6a 65 63 74 20  |scenery;.Object |
000012c0  77 5f 6f 62 6a 20 22 77  65 73 74 20 77 61 6c 6c  |w_obj "west wall|
000012d0  22 20 63 6f 6d 70 61 73  73 20 20 20 20 20 20 20  |" compass       |
000012e0  0a 20 20 77 69 74 68 20  6e 61 6d 65 20 22 77 22  |.  with name "w"|
000012f0  20 22 77 65 73 74 22 20  22 77 61 6c 6c 22 2c 20  | "west" "wall", |
00001300  20 20 20 20 20 20 20 20  20 20 20 61 72 74 69 63  |           artic|
00001310  6c 65 20 22 74 68 65 22  2c 20 64 6f 6f 72 5f 64  |le "the", door_d|
00001320  69 72 20 77 5f 74 6f 0a  20 20 20 68 61 73 20 20  |ir w_to.   has  |
00001330  73 63 65 6e 65 72 79 3b  0a 4f 62 6a 65 63 74 20  |scenery;.Object |
00001340  6e 65 5f 6f 62 6a 20 22  6e 6f 72 74 68 65 61 73  |ne_obj "northeas|
00001350  74 20 77 61 6c 6c 22 20  63 6f 6d 70 61 73 73 20  |t wall" compass |
00001360  0a 20 20 77 69 74 68 20  6e 61 6d 65 20 22 6e 65  |.  with name "ne|
00001370  22 20 22 6e 6f 72 74 68  65 61 73 74 22 20 22 77  |" "northeast" "w|
00001380  61 6c 6c 22 2c 20 20 20  20 20 20 61 72 74 69 63  |all",      artic|
00001390  6c 65 20 22 74 68 65 22  2c 20 64 6f 6f 72 5f 64  |le "the", door_d|
000013a0  69 72 20 6e 65 5f 74 6f  0a 20 20 68 61 73 20 20  |ir ne_to.  has  |
000013b0  73 63 65 6e 65 72 79 3b  0a 4f 62 6a 65 63 74 20  |scenery;.Object |
000013c0  6e 77 5f 6f 62 6a 20 22  6e 6f 72 74 68 77 65 73  |nw_obj "northwes|
000013d0  74 20 77 61 6c 6c 22 20  63 6f 6d 70 61 73 73 0a  |t wall" compass.|
000013e0  20 20 77 69 74 68 20 6e  61 6d 65 20 22 6e 77 22  |  with name "nw"|
000013f0  20 22 6e 6f 72 74 68 77  65 73 74 22 20 22 77 61  | "northwest" "wa|
00001400  6c 6c 22 2c 20 20 20 20  20 20 61 72 74 69 63 6c  |ll",      articl|
00001410  65 20 22 74 68 65 22 2c  20 64 6f 6f 72 5f 64 69  |e "the", door_di|
00001420  72 20 6e 77 5f 74 6f 0a  20 20 68 61 73 20 20 73  |r nw_to.  has  s|
00001430  63 65 6e 65 72 79 3b 0a  4f 62 6a 65 63 74 20 73  |cenery;.Object s|
00001440  65 5f 6f 62 6a 20 22 73  6f 75 74 68 65 61 73 74  |e_obj "southeast|
00001450  20 77 61 6c 6c 22 20 63  6f 6d 70 61 73 73 0a 20  | wall" compass. |
00001460  20 77 69 74 68 20 6e 61  6d 65 20 22 73 65 22 20  | with name "se" |
00001470  22 73 6f 75 74 68 65 61  73 74 22 20 22 77 61 6c  |"southeast" "wal|
00001480  6c 22 2c 20 20 20 20 20  20 61 72 74 69 63 6c 65  |l",      article|
00001490  20 22 74 68 65 22 2c 20  64 6f 6f 72 5f 64 69 72  | "the", door_dir|
000014a0  20 73 65 5f 74 6f 0a 20  20 68 61 73 20 20 73 63  | se_to.  has  sc|
000014b0  65 6e 65 72 79 3b 0a 4f  62 6a 65 63 74 20 73 77  |enery;.Object sw|
000014c0  5f 6f 62 6a 20 22 73 6f  75 74 68 77 65 73 74 20  |_obj "southwest |
000014d0  77 61 6c 6c 22 20 63 6f  6d 70 61 73 73 0a 20 20  |wall" compass.  |
000014e0  77 69 74 68 20 6e 61 6d  65 20 22 73 77 22 20 22  |with name "sw" "|
000014f0  73 6f 75 74 68 77 65 73  74 22 20 22 77 61 6c 6c  |southwest" "wall|
00001500  22 2c 20 20 20 20 20 20  61 72 74 69 63 6c 65 20  |",      article |
00001510  22 74 68 65 22 2c 20 64  6f 6f 72 5f 64 69 72 20  |"the", door_dir |
00001520  73 77 5f 74 6f 0a 20 20  68 61 73 20 20 73 63 65  |sw_to.  has  sce|
00001530  6e 65 72 79 3b 0a 4f 62  6a 65 63 74 20 75 5f 6f  |nery;.Object u_o|
00001540  62 6a 20 22 63 65 69 6c  69 6e 67 22 20 63 6f 6d  |bj "ceiling" com|
00001550  70 61 73 73 20 20 20 20  20 20 20 20 20 0a 20 20  |pass         .  |
00001560  77 69 74 68 20 6e 61 6d  65 20 22 75 22 20 22 75  |with name "u" "u|
00001570  70 22 20 22 63 65 69 6c  69 6e 67 22 2c 20 20 20  |p" "ceiling",   |
00001580  20 20 20 20 20 20 20 20  61 72 74 69 63 6c 65 20  |        article |
00001590  22 74 68 65 22 2c 20 64  6f 6f 72 5f 64 69 72 20  |"the", door_dir |
000015a0  75 5f 74 6f 0a 20 20 20  68 61 73 20 20 73 63 65  |u_to.   has  sce|
000015b0  6e 65 72 79 3b 0a 4f 62  6a 65 63 74 20 64 5f 6f  |nery;.Object d_o|
000015c0  62 6a 20 22 66 6c 6f 6f  72 22 20 63 6f 6d 70 61  |bj "floor" compa|
000015d0  73 73 0a 20 20 77 69 74  68 20 6e 61 6d 65 20 22  |ss.  with name "|
000015e0  64 22 20 22 64 6f 77 6e  22 20 22 66 6c 6f 6f 72  |d" "down" "floor|
000015f0  22 2c 20 20 20 20 20 20  20 20 20 20 20 61 72 74  |",           art|
00001600  69 63 6c 65 20 22 74 68  65 22 2c 20 64 6f 6f 72  |icle "the", door|
00001610  5f 64 69 72 20 64 5f 74  6f 0a 20 20 20 68 61 73  |_dir d_to.   has|
00001620  20 20 73 63 65 6e 65 72  79 3b 0a 4f 62 6a 65 63  |  scenery;.Objec|
00001630  74 20 6f 75 74 5f 6f 62  6a 20 22 6f 75 74 73 69  |t out_obj "outsi|
00001640  64 65 22 20 63 6f 6d 70  61 73 73 0a 20 20 77 69  |de" compass.  wi|
00001650  74 68 20 20 20 20 20 20  20 20 20 20 20 20 20 20  |th              |
00001660  20 20 20 20 20 20 20 20  20 20 20 20 20 20 20 20  |                |
00001670  20 20 20 20 20 20 61 72  74 69 63 6c 65 20 22 74  |      article "t|
00001680  68 65 22 2c 20 64 6f 6f  72 5f 64 69 72 20 6f 75  |he", door_dir ou|
00001690  74 5f 74 6f 0a 20 20 20  68 61 73 20 20 73 63 65  |t_to.   has  sce|
000016a0  6e 65 72 79 3b 0a 4f 62  6a 65 63 74 20 69 6e 5f  |nery;.Object in_|
000016b0  6f 62 6a 20 22 69 6e 73  69 64 65 22 20 63 6f 6d  |obj "inside" com|
000016c0  70 61 73 73 0a 20 20 77  69 74 68 20 20 20 20 20  |pass.  with     |
000016d0  20 20 20 20 20 20 20 20  20 20 20 20 20 20 20 20  |                |
000016e0  20 20 20 20 20 20 20 20  20 20 20 20 20 20 20 61  |               a|
000016f0  72 74 69 63 6c 65 20 22  74 68 65 22 2c 20 64 6f  |rticle "the", do|
00001700  6f 72 5f 64 69 72 20 69  6e 5f 74 6f 0a 20 20 20  |or_dir in_to.   |
00001710  68 61 73 20 20 73 63 65  6e 65 72 79 3b 0a 0a 0a  |has  scenery;...|
00001720  21 20 2d 2d 2d 2d 2d 2d  2d 2d 2d 2d 2d 2d 2d 2d  |! --------------|
00001730  2d 2d 2d 2d 2d 2d 2d 2d  2d 2d 2d 2d 2d 2d 2d 2d  |----------------|
*
00001760  2d 2d 2d 2d 2d 2d 2d 2d  2d 2d 2d 2d 2d 2d 0a 21  |--------------.!|
00001770  20 54 68 65 20 6f 74 68  65 72 20 64 75 6d 6d 79  | The other dummy|
00001780  20 6f 62 6a 65 63 74 20  69 73 20 22 44 61 72 6b  | object is "Dark|
00001790  6e 65 73 73 22 2c 20 6e  6f 74 20 72 65 61 6c 6c  |ness", not reall|
000017a0  79 20 61 20 70 6c 61 63  65 20 62 75 74 20 69 74  |y a place but it|
000017b0  20 68 61 73 20 74 6f 20  62 65 0a 21 20 61 6e 20  | has to be.! an |
000017c0  6f 62 6a 65 63 74 20 73  6f 20 74 68 61 74 20 74  |object so that t|
000017d0  68 65 20 6e 61 6d 65 20  6f 6e 20 74 68 65 20 73  |he name on the s|
000017e0  74 61 74 75 73 20 6c 69  6e 65 20 63 61 6e 20 62  |tatus line can b|
000017f0  65 20 22 44 61 72 6b 6e  65 73 73 22 3a 0a 21 20  |e "Darkness":.! |
00001800  77 65 20 61 6c 73 6f 20  63 72 65 61 74 65 20 74  |we also create t|
00001810  68 65 20 70 6c 61 79 65  72 20 6f 62 6a 65 63 74  |he player object|
00001820  0a 21 20 2d 2d 2d 2d 2d  2d 2d 2d 2d 2d 2d 2d 2d  |.! -------------|
00001830  2d 2d 2d 2d 2d 2d 2d 2d  2d 2d 2d 2d 2d 2d 2d 2d  |----------------|
*
00001860  2d 2d 2d 2d 2d 2d 2d 2d  2d 2d 2d 2d 2d 2d 2d 0a  |---------------.|
00001870  0a 4f 62 6a 65 63 74 20  74 68 65 64 61 72 6b 20  |.Object thedark |
00001880  22 44 61 72 6b 6e 65 73  73 22 20 6e 6f 74 68 69  |"Darkness" nothi|
00001890  6e 67 0a 20 20 77 69 74  68 20 64 65 73 63 72 69  |ng.  with descri|
000018a0  70 74 69 6f 6e 20 22 49  74 20 69 73 20 70 69 74  |ption "It is pit|
000018b0  63 68 20 64 61 72 6b 2c  20 61 6e 64 20 79 6f 75  |ch dark, and you|
000018c0  20 63 61 6e 27 74 20 73  65 65 20 61 20 74 68 69  | can't see a thi|
000018d0  6e 67 2e 22 3b 0a 0a 4f  62 6a 65 63 74 20 73 65  |ng.";..Object se|
000018e0  6c 66 6f 62 6a 20 22 79  6f 75 72 73 65 6c 66 22  |lfobj "yourself"|
000018f0  20 74 68 65 64 61 72 6b  0a 20 20 77 69 74 68 20  | thedark.  with |
00001900  64 65 73 63 72 69 70 74  69 6f 6e 20 22 41 73 20  |description "As |
00001910  67 6f 6f 64 2d 6c 6f 6f  6b 69 6e 67 20 61 73 20  |good-looking as |
00001920  65 76 65 72 2e 22 2c 20  6e 75 6d 62 65 72 20 74  |ever.", number t|
00001930  68 65 64 61 72 6b 2c 0a  20 20 20 20 20 20 20 62  |hedark,.       b|
00001940  65 66 6f 72 65 20 24 66  66 66 66 2c 20 61 66 74  |efore $ffff, aft|
00001950  65 72 20 24 66 66 66 66  2c 20 6c 69 66 65 20 24  |er $ffff, life $|
00001960  66 66 66 66 2c 20 65 61  63 68 5f 74 75 72 6e 20  |ffff, each_turn |
00001970  24 66 66 66 66 2c 0a 20  20 20 20 20 20 20 74 69  |$ffff,.       ti|
00001980  6d 65 5f 6f 75 74 20 24  66 66 66 66 2c 20 64 65  |me_out $ffff, de|
00001990  73 63 72 69 62 65 20 24  66 66 66 66 2c 20 63 61  |scribe $ffff, ca|
000019a0  70 61 63 69 74 79 20 31  30 30 2c 0a 20 20 20 20  |pacity 100,.    |
000019b0  20 20 20 70 61 72 73 65  5f 6e 61 6d 65 20 30 2c  |   parse_name 0,|
000019c0  20 73 68 6f 72 74 5f 6e  61 6d 65 20 30 0a 20 20  | short_name 0.  |
000019d0  68 61 73 20 20 63 6f 6e  63 65 61 6c 65 64 20 61  |has  concealed a|
000019e0  6e 69 6d 61 74 65 20 70  72 6f 70 65 72 20 74 72  |nimate proper tr|
000019f0  61 6e 73 70 61 72 65 6e  74 3b 0a 0a 21 20 2d 2d  |ansparent;..! --|
00001a00  2d 2d 2d 2d 2d 2d 2d 2d  2d 2d 2d 2d 2d 2d 2d 2d  |----------------|
*
00001a40  2d 2d 2d 2d 2d 2d 2d 2d  2d 2d 0a 21 20 46 61 6b  |----------.! Fak|
00001a50  65 20 61 63 74 69 6f 6e  73 3a 20 74 72 65 61 74  |e actions: treat|
00001a60  65 64 20 61 73 20 69 66  20 74 68 65 79 20 77 65  |ed as if they we|
00001a70  72 65 20 61 63 74 69 6f  6e 73 2c 20 77 68 65 6e  |re actions, when|
00001a80  20 63 61 6c 6c 69 6e 67  0a 21 20 72 6f 75 74 69  | calling.! routi|
00001a90  6e 65 73 20 61 74 74 61  63 68 65 64 20 74 6f 20  |nes attached to |
00001aa0  6f 62 6a 65 63 74 73 0a  21 20 2d 2d 2d 2d 2d 2d  |objects.! ------|
00001ab0  2d 2d 2d 2d 2d 2d 2d 2d  2d 2d 2d 2d 2d 2d 2d 2d  |----------------|
*
00001af0  2d 2d 2d 2d 2d 2d 0a 0a  46 61 6b 65 5f 41 63 74  |------..Fake_Act|
00001b00  69 6f 6e 20 4c 65 74 47  6f 3b 0a 46 61 6b 65 5f  |ion LetGo;.Fake_|
00001b10  41 63 74 69 6f 6e 20 52  65 63 65 69 76 65 3b 0a  |Action Receive;.|
00001b20  46 61 6b 65 5f 41 63 74  69 6f 6e 20 4f 72 64 65  |Fake_Action Orde|
00001b30  72 3b 0a 46 61 6b 65 5f  41 63 74 69 6f 6e 20 54  |r;.Fake_Action T|
00001b40  68 65 53 61 6d 65 3b 0a  46 61 6b 65 5f 41 63 74  |heSame;.Fake_Act|
00001b50  69 6f 6e 20 50 6c 75 72  61 6c 46 6f 75 6e 64 3b  |ion PluralFound;|
00001b60  0a 0a 21 20 2d 2d 2d 2d  2d 2d 2d 2d 2d 2d 2d 2d  |..! ------------|
00001b70  2d 2d 2d 2d 2d 2d 2d 2d  2d 2d 2d 2d 2d 2d 2d 2d  |----------------|
*
00001bb0  0a 21 20 47 6c 6f 62 61  6c 73 3a 20 6e 6f 74 65  |.! Globals: note|
00001bc0  20 74 68 61 74 20 74 68  65 20 66 69 72 73 74 20  | that the first |
00001bd0  6f 6e 65 20 64 65 66 69  6e 65 64 20 67 69 76 65  |one defined give|
00001be0  73 20 74 68 65 20 73 74  61 74 75 73 20 6c 69 6e  |s the status lin|
00001bf0  65 20 70 6c 61 63 65 2c  20 74 68 65 0a 21 20 6e  |e place, the.! n|
00001c00  65 78 74 20 74 77 6f 20  74 68 65 20 73 63 6f 72  |ext two the scor|
00001c10  65 2f 74 75 72 6e 73 0a  21 20 2d 2d 2d 2d 2d 2d  |e/turns.! ------|
00001c20  2d 2d 2d 2d 2d 2d 2d 2d  2d 2d 2d 2d 2d 2d 2d 2d  |----------------|
*
00001c60  2d 2d 2d 2d 2d 2d 0a 0a  47 6c 6f 62 61 6c 20 6c  |------..Global l|
00001c70  6f 63 61 74 69 6f 6e 20  3d 20 31 3b 0a 47 6c 6f  |ocation = 1;.Glo|
00001c80  62 61 6c 20 73 6c 69 6e  65 31 20 3d 20 30 3b 0a  |bal sline1 = 0;.|
00001c90  47 6c 6f 62 61 6c 20 73  6c 69 6e 65 32 20 3d 20  |Global sline2 = |
00001ca0  30 3b 0a 0a 47 6c 6f 62  61 6c 20 74 68 65 5f 74  |0;..Global the_t|
00001cb0  69 6d 65 20 3d 20 24 66  66 66 66 3b 0a 47 6c 6f  |ime = $ffff;.Glo|
00001cc0  62 61 6c 20 74 69 6d 65  5f 72 61 74 65 20 3d 20  |bal time_rate = |
00001cd0  31 3b 0a 47 6c 6f 62 61  6c 20 74 69 6d 65 5f 73  |1;.Global time_s|
00001ce0  74 65 70 20 3d 20 30 3b  0a 0a 47 6c 6f 62 61 6c  |tep = 0;..Global|
00001cf0  20 73 63 6f 72 65 20 3d  20 30 3b 0a 47 6c 6f 62  | score = 0;.Glob|
00001d00  61 6c 20 74 75 72 6e 73  20 3d 20 31 3b 0a 47 6c  |al turns = 1;.Gl|
00001d10  6f 62 61 6c 20 70 6c 61  79 65 72 3b 0a 0a 47 6c  |obal player;..Gl|
00001d20  6f 62 61 6c 20 6c 69 67  68 74 66 6c 61 67 20 3d  |obal lightflag =|
00001d30  20 31 3b 0a 47 6c 6f 62  61 6c 20 72 65 61 6c 5f  | 1;.Global real_|
00001d40  6c 6f 63 61 74 69 6f 6e  20 3d 20 74 68 65 64 61  |location = theda|
00001d50  72 6b 3b 0a 47 6c 6f 62  61 6c 20 70 72 69 6e 74  |rk;.Global print|
00001d60  5f 70 6c 61 79 65 72 5f  66 6c 61 67 20 3d 20 30  |_player_flag = 0|
00001d70  3b 0a 47 6c 6f 62 61 6c  20 64 65 61 64 66 6c 61  |;.Global deadfla|
00001d80  67 20 3d 20 30 3b 0a 0a  47 6c 6f 62 61 6c 20 69  |g = 0;..Global i|
00001d90  6e 76 65 6e 74 6f 72 79  5f 73 74 61 67 65 20 3d  |nventory_stage =|
00001da0  20 31 3b 0a 0a 47 6c 6f  62 61 6c 20 74 72 61 6e  | 1;..Global tran|
00001db0  73 63 72 69 70 74 5f 6d  6f 64 65 20 3d 20 30 3b  |script_mode = 0;|
00001dc0  0a 0a 47 6c 6f 62 61 6c  20 6c 61 73 74 5f 73 63  |..Global last_sc|
00001dd0  6f 72 65 20 3d 20 30 3b  0a 47 6c 6f 62 61 6c 20  |ore = 0;.Global |
00001de0  6e 6f 74 69 66 79 5f 6d  6f 64 65 20 3d 20 31 3b  |notify_mode = 1;|
00001df0  20 20 20 20 20 20 20 21  20 53 63 6f 72 65 20 6e  |       ! Score n|
00001e00  6f 74 69 66 69 63 61 74  69 6f 6e 0a 0a 47 6c 6f  |otification..Glo|
00001e10  62 61 6c 20 70 6c 61 63  65 73 5f 73 63 6f 72 65  |bal places_score|
00001e20  20 3d 20 30 3b 0a 47 6c  6f 62 61 6c 20 74 68 69  | = 0;.Global thi|
00001e30  6e 67 73 5f 73 63 6f 72  65 20 3d 20 30 3b 0a 47  |ngs_score = 0;.G|
00001e40  6c 6f 62 61 6c 20 6c 6f  6f 6b 6d 6f 64 65 20 3d  |lobal lookmode =|
00001e50  20 31 3b 0a 47 6c 6f 62  61 6c 20 6c 61 73 74 64  | 1;.Global lastd|
00001e60  65 73 63 20 3d 20 30 3b  0a 0a 47 6c 6f 62 61 6c  |esc = 0;..Global|
00001e70  20 74 6f 70 5f 6f 62 6a  65 63 74 20 3d 20 30 3b  | top_object = 0;|
00001e80  0a 0a 21 20 2d 2d 2d 2d  2d 2d 2d 2d 2d 2d 2d 2d  |..! ------------|
00001e90  2d 2d 2d 2d 2d 2d 2d 2d  2d 2d 2d 2d 2d 2d 2d 2d  |----------------|
*
00001ed0  0a 21 20 50 61 72 73 65  72 20 76 61 72 69 61 62  |.! Parser variab|
00001ee0  6c 65 73 20 61 63 63 65  73 73 69 62 6c 65 20 74  |les accessible t|
00001ef0  6f 20 74 68 65 20 72 65  73 74 20 6f 66 20 74 68  |o the rest of th|
00001f00  65 20 67 61 6d 65 0a 21  20 2d 2d 2d 2d 2d 2d 2d  |e game.! -------|
00001f10  2d 2d 2d 2d 2d 2d 2d 2d  2d 2d 2d 2d 2d 2d 2d 2d  |----------------|
*
00001f50  2d 2d 2d 2d 2d 0a 0a 47  6c 6f 62 61 6c 20 62 75  |-----..Global bu|
00001f60  66 66 65 72 20 20 20 20  20 20 20 20 20 20 73 74  |ffer          st|
00001f70  72 69 6e 67 20 31 32 30  3b 20 20 20 21 20 54 65  |ring 120;   ! Te|
00001f80  78 74 20 62 75 66 66 65  72 0a 47 6c 6f 62 61 6c  |xt buffer.Global|
00001f90  20 70 61 72 73 65 20 20  20 20 20 20 20 20 20 20  | parse          |
00001fa0  20 73 74 72 69 6e 67 20  36 34 3b 20 20 20 20 21  | string 64;    !|
00001fb0  20 4c 69 73 74 20 6f 66  20 70 61 72 73 65 64 20  | List of parsed |
00001fc0  61 64 64 72 65 73 73 65  73 20 6f 66 20 77 6f 72  |addresses of wor|
00001fd0  64 73 0a 47 6c 6f 62 61  6c 20 69 6e 70 75 74 6f  |ds.Global inputo|
00001fe0  62 6a 73 20 20 20 20 20  20 20 64 61 74 61 20 33  |bjs       data 3|
00001ff0  32 3b 20 20 20 20 20 20  21 20 54 6f 20 68 6f 6c  |2;      ! To hol|
00002000  64 20 70 61 72 61 6d 65  74 65 72 73 0a 47 6c 6f  |d parameters.Glo|
00002010  62 61 6c 20 74 6f 6f 6d  61 6e 79 5f 66 6c 61 67  |bal toomany_flag|
00002020  20 20 20 20 3d 20 30 3b  20 20 20 20 20 20 20 20  |    = 0;        |
00002030  20 20 21 20 46 6c 61 67  20 66 6f 72 20 22 74 61  |  ! Flag for "ta|
00002040  6b 65 20 61 6c 6c 20 6d  61 64 65 20 74 6f 6f 20  |ke all made too |
00002050  6d 61 6e 79 22 0a 47 6c  6f 62 61 6c 20 61 63 74  |many".Global act|
00002060  6f 72 20 20 20 20 20 20  20 20 20 20 20 3d 20 30  |or           = 0|
00002070  3b 20 20 20 20 20 20 20  20 20 20 21 20 50 65 72  |;          ! Per|
00002080  73 6f 6e 20 61 73 6b 65  64 20 74 6f 20 64 6f 20  |son asked to do |
00002090  73 6f 6d 65 74 68 69 6e  67 0a 47 6c 6f 62 61 6c  |something.Global|
000020a0  20 61 63 74 69 6f 6e 20  20 20 20 20 20 20 20 20  | action         |
000020b0  20 3d 20 30 3b 20 20 20  20 20 20 20 20 20 20 21  | = 0;          !|
000020c0  20 54 68 69 6e 67 20 68  65 20 69 73 20 61 73 6b  | Thing he is ask|
000020d0  65 64 20 74 6f 20 64 6f  0a 47 6c 6f 62 61 6c 20  |ed to do.Global |
000020e0  69 6e 70 31 20 20 20 20  20 20 20 20 20 20 20 20  |inp1            |
000020f0  3d 20 30 3b 20 20 20 20  20 20 20 20 20 20 21 20  |= 0;          ! |
00002100  46 69 72 73 74 20 70 61  72 61 6d 65 74 65 72 0a  |First parameter.|
00002110  47 6c 6f 62 61 6c 20 69  6e 70 32 20 20 20 20 20  |Global inp2     |
00002120  20 20 20 20 20 20 20 3d  20 30 3b 20 20 20 20 20  |       = 0;     |
00002130  20 20 20 20 20 21 20 53  65 63 6f 6e 64 20 70 61  |     ! Second pa|
00002140  72 61 6d 65 74 65 72 0a  47 6c 6f 62 61 6c 20 73  |rameter.Global s|
00002150  65 6c 66 20 20 20 20 20  20 20 20 20 20 20 20 3d  |elf            =|
00002160  20 30 3b 20 20 20 20 20  20 20 20 20 20 21 20 4f  | 0;          ! O|
00002170  62 6a 65 63 74 20 77 68  6f 73 65 20 72 6f 75 74  |bject whose rout|
00002180  69 6e 65 73 20 61 72 65  20 62 65 69 6e 67 20 72  |ines are being r|
00002190  75 6e 0a 47 6c 6f 62 61  6c 20 6e 6f 75 6e 20 20  |un.Global noun  |
000021a0  20 20 20 20 20 20 20 20  20 20 3d 20 30 3b 20 20  |          = 0;  |
000021b0  20 20 20 20 20 20 20 20  21 20 46 69 72 73 74 20  |        ! First |
000021c0  6e 6f 75 6e 0a 47 6c 6f  62 61 6c 20 73 65 63 6f  |noun.Global seco|
000021d0  6e 64 20 20 20 20 20 20  20 20 20 20 3d 20 30 3b  |nd          = 0;|
000021e0  20 20 20 20 20 20 20 20  20 20 21 20 53 65 63 6f  |          ! Seco|
000021f0  6e 64 20 6e 6f 75 6e 0a  47 6c 6f 62 61 6c 20 6d  |nd noun.Global m|
00002200  75 6c 74 69 70 6c 65 5f  6f 62 6a 65 63 74 20 64  |ultiple_object d|
00002210  61 74 61 20 36 34 3b 20  20 20 20 20 20 21 20 4c  |ata 64;      ! L|
00002220  69 73 74 20 6f 66 20 6d  75 6c 74 69 70 6c 65 20  |ist of multiple |
00002230  70 61 72 61 6d 65 74 65  72 73 0a 47 6c 6f 62 61  |parameters.Globa|
00002240  6c 20 73 70 65 63 69 61  6c 5f 77 6f 72 64 20 20  |l special_word  |
00002250  20 20 3d 20 30 3b 20 20  20 20 20 20 20 20 20 20  |  = 0;          |
00002260  21 20 44 69 63 74 69 6f  6e 61 72 79 20 61 64 64  |! Dictionary add|
00002270  72 65 73 73 20 6f 66 20  22 73 70 65 63 69 61 6c  |ress of "special|
00002280  22 0a 47 6c 6f 62 61 6c  20 73 70 65 63 69 61 6c  |".Global special|
00002290  5f 6e 75 6d 62 65 72 20  20 3d 20 30 3b 20 20 20  |_number  = 0;   |
000022a0  20 20 20 20 20 20 20 21  20 54 68 65 20 6e 75 6d  |       ! The num|
000022b0  62 65 72 2c 20 69 66 20  61 20 6e 75 6d 62 65 72  |ber, if a number|
000022c0  20 77 61 73 20 74 79 70  65 64 0a 47 6c 6f 62 61  | was typed.Globa|
000022d0  6c 20 73 70 65 63 69 61  6c 5f 6e 75 6d 62 65 72  |l special_number|
000022e0  32 20 3d 20 30 3b 20 20  20 20 20 20 20 20 20 20  |2 = 0;          |
000022f0  21 20 53 65 63 6f 6e 64  20 6e 75 6d 62 65 72 2c  |! Second number,|
00002300  20 69 66 20 74 77 6f 20  6e 75 6d 62 65 72 73 20  | if two numbers |
00002310  74 79 70 65 64 0a 47 6c  6f 62 61 6c 20 70 61 72  |typed.Global par|
00002320  73 65 64 5f 6e 75 6d 62  65 72 20 20 20 3d 20 30  |sed_number   = 0|
00002330  3b 20 20 20 20 20 20 20  20 20 20 21 20 46 6f 72  |;          ! For|
00002340  20 75 73 65 72 2d 73 75  70 70 6c 69 65 64 20 70  | user-supplied p|
00002350  61 72 73 69 6e 67 20 72  6f 75 74 69 6e 65 73 0a  |arsing routines.|
00002360  67 6c 6f 62 61 6c 20 6d  75 6c 74 69 66 6c 61 67  |global multiflag|
00002370  3b 20 20 20 20 20 20 20  20 20 20 20 20 20 20 20  |;               |
00002380  20 20 20 20 20 21 20 4d  75 6c 74 69 70 6c 65 2d  |     ! Multiple-|
00002390  6f 62 6a 65 63 74 20 66  6c 61 67 0a 67 6c 6f 62  |object flag.glob|
000023a0  61 6c 20 6e 6f 74 68 65  6c 64 5f 6d 6f 64 65 20  |al notheld_mode |
000023b0  20 3d 20 30 3b 20 20 20  20 20 20 20 20 20 20 20  | = 0;           |
000023c0  20 21 20 54 6f 20 64 6f  20 77 69 74 68 20 69 6d  | ! To do with im|
000023d0  70 6c 69 63 69 74 20 74  61 6b 69 6e 67 0a 67 6c  |plicit taking.gl|
000023e0  6f 62 61 6c 20 6f 6e 6f  74 68 65 6c 64 5f 6d 6f  |obal onotheld_mo|
000023f0  64 65 20 3d 20 30 3b 20  20 20 20 20 20 20 20 20  |de = 0;         |
00002400  20 20 20 21 0a 67 6c 6f  62 61 6c 20 6d 65 74 61  |   !.global meta|
00002410  3b 20 20 20 20 20 20 20  20 20 20 20 20 20 20 20  |;               |
00002420  20 20 20 20 20 20 20 20  20 20 21 20 56 65 72 62  |          ! Verb|
00002430  20 69 73 20 61 20 6d 65  74 61 2d 63 6f 6d 6d 61  | is a meta-comma|
00002440  6e 64 20 28 73 75 63 68  20 61 73 20 22 73 61 76  |nd (such as "sav|
00002450  65 22 29 0a 67 6c 6f 62  61 6c 20 72 65 61 73 6f  |e").global reaso|
00002460  6e 5f 63 6f 64 65 3b 20  20 20 20 20 20 20 20 20  |n_code;         |
00002470  20 20 20 20 20 20 20 20  20 21 20 52 65 61 73 6f  |         ! Reaso|
00002480  6e 20 66 6f 72 20 63 61  6c 6c 69 6e 67 20 61 20  |n for calling a |
00002490  6c 69 66 65 0a 67 6c 6f  62 61 6c 20 73 77 5f 5f  |life.global sw__|
000024a0  76 61 72 20 20 20 20 20  20 20 20 20 3d 20 30 3b  |var         = 0;|
000024b0  20 20 20 20 20 20 20 20  20 20 21 20 53 77 69 74  |          ! Swit|
000024c0  63 68 20 76 61 72 69 61  62 6c 65 20 28 75 73 65  |ch variable (use|
000024d0  64 20 66 6f 72 20 65 6d  62 65 64 64 65 64 73 29  |d for embeddeds)|
000024e0  0a 0a 23 49 46 56 35 3b  0a 67 6c 6f 62 61 6c 20  |..#IFV5;.global |
000024f0  75 6e 64 6f 5f 66 6c 61  67 20 3d 20 30 3b 20 20  |undo_flag = 0;  |
00002500  20 20 20 20 20 20 20 20  20 20 20 20 20 20 21 20  |              ! |
00002510  43 61 6e 20 74 68 65 20  69 6e 74 65 72 70 72 65  |Can the interpre|
00002520  74 65 72 20 70 72 6f 76  69 64 65 20 22 75 6e 64  |ter provide "und|
00002530  6f 22 3f 0a 23 45 4e 44  49 46 3b 0a 0a 67 6c 6f  |o"?.#ENDIF;..glo|
00002540  62 61 6c 20 70 61 72 73  65 72 5f 74 72 61 63 65  |bal parser_trace|
00002550  20 3d 20 30 3b 20 20 20  20 20 20 20 20 20 20 20  | = 0;           |
00002560  20 20 21 20 53 65 74 20  74 68 69 73 20 74 6f 20  |  ! Set this to |
00002570  31 20 74 6f 20 6d 61 6b  65 20 74 68 65 20 70 61  |1 to make the pa|
00002580  72 73 65 72 20 74 72 61  63 65 0a 20 20 20 20 20  |rser trace.     |
00002590  20 20 20 20 20 20 20 20  20 20 20 20 20 20 20 20  |                |
*
000025b0  21 20 74 6f 6b 65 6e 73  20 61 6e 64 20 6c 69 6e  |! tokens and lin|
000025c0  65 73 0a 67 6c 6f 62 61  6c 20 64 65 62 75 67 5f  |es.global debug_|
000025d0  66 6c 61 67 20 3d 20 30  3b 20 20 20 20 20 20 20  |flag = 0;       |
000025e0  20 20 20 20 20 20 20 20  21 20 46 6f 72 20 64 65  |        ! For de|
000025f0  62 75 67 67 69 6e 67 20  69 6e 66 6f 72 6d 61 74  |bugging informat|
00002600  69 6f 6e 0a 0a 21 20 2d  2d 2d 2d 2d 2d 2d 2d 2d  |ion..! ---------|
00002610  2d 2d 2d 2d 2d 2d 2d 2d  2d 2d 2d 2d 2d 2d 2d 2d  |----------------|
*
00002650  2d 2d 2d 0a 21 20 4d 61  69 6e 20 28 70 75 74 74  |---.! Main (putt|
00002660  69 6e 67 20 69 74 20 68  65 72 65 20 65 6e 73 75  |ing it here ensu|
00002670  72 65 73 20 69 74 20 69  73 20 74 68 65 20 66 69  |res it is the fi|
00002680  72 73 74 20 72 6f 75 74  69 6e 65 2c 20 61 73 20  |rst routine, as |
00002690  69 74 20 6d 75 73 74 20  62 65 29 0a 21 20 2d 2d  |it must be).! --|
000026a0  2d 2d 2d 2d 2d 2d 2d 2d  2d 2d 2d 2d 2d 2d 2d 2d  |----------------|
*
000026e0  2d 2d 2d 2d 2d 2d 2d 2d  2d 2d 0a 0a 5b 20 4d 61  |----------..[ Ma|
000026f0  69 6e 3b 0a 20 20 70 6c  61 79 65 72 3d 73 65 6c  |in;.  player=sel|
00002700  66 6f 62 6a 3b 0a 20 20  50 6c 61 79 54 68 65 47  |fobj;.  PlayTheG|
00002710  61 6d 65 28 29 3b 0a 5d  3b 0a 0a 21 20 2d 2d 2d  |ame();.];..! ---|
00002720  2d 2d 2d 2d 2d 2d 2d 2d  2d 2d 2d 2d 2d 2d 2d 2d  |----------------|
*
00002760  2d 2d 2d 2d 2d 2d 2d 2d  2d 0a 21 20 54 68 65 20  |---------.! The |
00002770  70 61 72 73 65 72 2c 20  62 65 67 69 6e 6e 69 6e  |parser, beginnin|
00002780  67 20 77 69 74 68 20 76  61 72 69 61 62 6c 65 73  |g with variables|
00002790  20 70 72 69 76 61 74 65  20 74 6f 20 69 74 73 65  | private to itse|
000027a0  6c 66 3a 0a 21 20 2d 2d  2d 2d 2d 2d 2d 2d 2d 2d  |lf:.! ----------|
000027b0  2d 2d 2d 2d 2d 2d 2d 2d  2d 2d 2d 2d 2d 2d 2d 2d  |----------------|
*
000027f0  2d 2d 0a 0a 67 6c 6f 62  61 6c 20 62 75 66 66 65  |--..global buffe|
00002800  72 32 20 20 20 73 74 72  69 6e 67 20 31 32 30 3b  |r2   string 120;|
00002810  20 20 20 20 21 20 42 75  66 66 65 72 73 20 66 6f  |    ! Buffers fo|
00002820  72 20 73 75 70 70 6c 65  6d 65 6e 74 61 72 79 20  |r supplementary |
00002830  71 75 65 73 74 69 6f 6e  73 0a 67 6c 6f 62 61 6c  |questions.global|
00002840  20 70 61 72 73 65 32 20  20 20 20 73 74 72 69 6e  | parse2    strin|
00002850  67 20 36 34 3b 20 20 20  20 20 21 0a 67 6c 6f 62  |g 64;     !.glob|
00002860  61 6c 20 70 61 72 73 65  33 20 20 20 20 73 74 72  |al parse3    str|
00002870  69 6e 67 20 36 34 3b 20  20 20 20 20 21 0a 0a 67  |ing 64;     !..g|
00002880  6c 6f 62 61 6c 20 77 6e  3b 20 20 20 20 20 20 20  |lobal wn;       |
00002890  20 20 20 20 20 20 20 20  20 20 20 20 20 20 20 21  |               !|
000028a0  20 57 6f 72 64 20 6e 75  6d 62 65 72 20 28 63 6f  | Word number (co|
000028b0  75 6e 74 73 20 66 72 6f  6d 20 31 29 0a 67 6c 6f  |unts from 1).glo|
000028c0  62 61 6c 20 6e 75 6d 5f  77 6f 72 64 73 3b 20 20  |bal num_words;  |
000028d0  20 20 20 20 20 20 20 20  20 20 20 20 20 21 20 4e  |             ! N|
000028e0  75 6d 62 65 72 20 6f 66  20 77 6f 72 64 73 20 74  |umber of words t|
000028f0  79 70 65 64 0a 67 6c 6f  62 61 6c 20 76 65 72 62  |yped.global verb|
00002900  5f 77 6f 72 64 3b 20 20  20 20 20 20 20 20 20 20  |_word;          |
00002910  20 20 20 20 20 21 20 56  65 72 62 20 77 6f 72 64  |     ! Verb word|
00002920  20 28 65 67 2c 20 74 61  6b 65 20 69 6e 20 22 74  | (eg, take in "t|
00002930  61 6b 65 20 61 6c 6c 22  20 6f 72 0a 20 20 20 20  |ake all" or.    |
00002940  20 20 20 20 20 20 20 20  20 20 20 20 20 20 20 20  |                |
00002950  20 20 20 20 20 20 20 20  20 20 20 20 21 20 22 64  |            ! "d|
00002960  77 61 72 66 2c 20 74 61  6b 65 20 61 6c 6c 22 29  |warf, take all")|
00002970  20 2d 20 61 64 64 72 65  73 73 20 69 6e 20 64 69  | - address in di|
00002980  63 74 69 6f 6e 61 72 79  0a 67 6c 6f 62 61 6c 20  |ctionary.global |
00002990  76 65 72 62 5f 77 6f 72  64 6e 75 6d 3b 20 20 20  |verb_wordnum;   |
000029a0  20 20 20 20 20 20 20 20  20 21 20 61 6e 64 20 74  |         ! and t|
000029b0  68 65 20 6e 75 6d 62 65  72 20 69 6e 20 74 79 70  |he number in typ|
000029c0  69 6e 67 20 6f 72 64 65  72 20 28 65 67 2c 20 31  |ing order (eg, 1|
000029d0  20 6f 72 20 33 29 0a 0a  67 6c 6f 62 61 6c 20 6d  | or 3)..global m|
000029e0  75 6c 74 69 5f 6d 6f 64  65 3b 20 20 20 20 20 20  |ulti_mode;      |
000029f0  20 20 20 20 20 20 20 20  21 20 4d 75 6c 74 69 70  |        ! Multip|
00002a00  6c 65 20 6d 6f 64 65 0a  67 6c 6f 62 61 6c 20 6d  |le mode.global m|
00002a10  75 6c 74 69 5f 77 61 6e  74 65 64 3b 20 20 20 20  |ulti_wanted;    |
00002a20  20 20 20 20 20 20 20 20  21 20 4e 75 6d 62 65 72  |        ! Number|
00002a30  20 6f 66 20 74 68 69 6e  67 73 20 6e 65 65 64 65  | of things neede|
00002a40  64 20 69 6e 20 6d 75 6c  74 69 74 75 64 65 0a 67  |d in multitude.g|
00002a50  6c 6f 62 61 6c 20 6d 75  6c 74 69 5f 68 61 64 3b  |lobal multi_had;|
00002a60  20 20 20 20 20 20 20 20  20 20 20 20 20 20 20 21  |               !|
00002a70  20 4e 75 6d 62 65 72 20  6f 66 20 74 68 69 6e 67  | Number of thing|
00002a80  73 20 61 63 74 75 61 6c  6c 79 20 66 6f 75 6e 64  |s actually found|
00002a90  0a 67 6c 6f 62 61 6c 20  6d 75 6c 74 69 5f 63 6f  |.global multi_co|
00002aa0  6e 74 65 78 74 3b 20 20  20 20 20 20 20 20 20 20  |ntext;          |
00002ab0  20 21 20 57 68 61 74 20  74 6f 6b 65 6e 20 74 68  | ! What token th|
00002ac0  65 20 6d 75 6c 74 69 2d  6f 62 6a 65 63 74 20 77  |e multi-object w|
00002ad0  61 73 20 61 63 63 65 70  74 65 64 20 66 6f 72 0a  |as accepted for.|
00002ae0  0a 67 6c 6f 62 61 6c 20  70 61 74 74 65 72 6e 20  |.global pattern |
00002af0  64 61 74 61 20 31 36 3b  20 20 20 20 20 20 20 20  |data 16;        |
00002b00  20 21 20 46 6f 72 20 74  68 65 20 63 75 72 72 65  | ! For the curre|
00002b10  6e 74 20 70 61 74 74 65  72 6e 20 6d 61 74 63 68  |nt pattern match|
00002b20  0a 67 6c 6f 62 61 6c 20  70 63 6f 75 6e 74 3b 20  |.global pcount; |
00002b30  20 20 20 20 20 20 20 20  20 20 20 20 20 20 20 20  |                |
00002b40  20 21 20 61 6e 64 20 61  20 6d 61 72 6b 65 72 20  | ! and a marker |
00002b50  77 69 74 68 69 6e 20 69  74 0a 67 6c 6f 62 61 6c  |within it.global|
00002b60  20 70 61 74 74 65 72 6e  32 20 64 61 74 61 20 31  | pattern2 data 1|
00002b70  36 3b 20 20 20 20 20 20  20 20 21 20 41 6e 64 20  |6;        ! And |
00002b80  61 6e 6f 74 68 65 72 2c  20 77 68 69 63 68 20 73  |another, which s|
00002b90  74 6f 72 65 73 20 74 68  65 20 62 65 73 74 20 6d  |tores the best m|
00002ba0  61 74 63 68 0a 67 6c 6f  62 61 6c 20 70 63 6f 75  |atch.global pcou|
00002bb0  6e 74 32 3b 20 20 20 20  20 20 20 20 20 20 20 20  |nt2;            |
00002bc0  20 20 20 20 20 21 20 73  6f 20 66 61 72 0a 0a 67  |     ! so far..g|
00002bd0  6c 6f 62 61 6c 20 70 61  72 61 6d 65 74 65 72 73  |lobal parameters|
00002be0  3b 20 20 20 20 20 20 20  20 20 20 20 20 20 20 21  |;              !|
00002bf0  20 50 61 72 61 6d 65 74  65 72 73 20 28 6f 62 6a  | Parameters (obj|
00002c00  65 63 74 73 29 20 65 6e  74 65 72 65 64 20 73 6f  |ects) entered so|
00002c10  20 66 61 72 0a 0a 67 6c  6f 62 61 6c 20 6e 73 6e  | far..global nsn|
00002c20  73 3b 20 20 20 20 20 20  20 20 20 20 20 20 20 20  |s;              |
00002c30  20 20 20 20 20 20 21 20  4e 75 6d 62 65 72 20 6f  |      ! Number o|
00002c40  66 20 73 70 65 63 69 61  6c 5f 6e 75 6d 62 65 72  |f special_number|
00002c50  73 20 65 6e 74 65 72 65  64 20 73 6f 20 66 61 72  |s entered so far|
00002c60  0a 0a 67 6c 6f 62 61 6c  20 69 6e 66 65 72 66 72  |..global inferfr|
00002c70  6f 6d 3b 20 20 20 20 20  20 20 20 20 20 20 20 20  |om;             |
00002c80  20 20 21 20 54 68 65 20  70 6f 69 6e 74 20 66 72  |  ! The point fr|
00002c90  6f 6d 20 77 68 69 63 68  20 74 68 65 20 72 65 73  |om which the res|
00002ca0  74 20 6f 66 20 74 68 65  0a 20 20 20 20 20 20 20  |t of the.       |
00002cb0  20 20 20 20 20 20 20 20  20 20 20 20 20 20 20 20  |                |
00002cc0  20 20 20 20 20 20 20 20  20 21 20 63 6f 6d 6d 61  |         ! comma|
00002cd0  6e 64 20 6d 75 73 74 20  62 65 20 69 6e 66 65 72  |nd must be infer|
00002ce0  72 65 64 0a 67 6c 6f 62  61 6c 20 69 6e 66 65 72  |red.global infer|
00002cf0  77 6f 72 64 3b 20 20 20  20 20 20 20 20 20 20 20  |word;           |
00002d00  20 20 20 20 21 20 41 6e  64 20 74 68 65 20 70 72  |    ! And the pr|
00002d10  65 70 6f 73 69 74 69 6f  6e 20 69 6e 66 65 72 72  |eposition inferr|
00002d20  65 64 0a 0a 67 6c 6f 62  61 6c 20 6f 6f 70 73 5f  |ed..global oops_|
00002d30  66 72 6f 6d 20 3d 20 30  3b 20 20 20 20 20 20 20  |from = 0;       |
00002d40  20 20 20 20 21 20 54 68  65 20 22 66 69 72 73 74  |    ! The "first|
00002d50  20 6d 69 73 74 61 6b 65  22 20 70 6f 69 6e 74 2c  | mistake" point,|
00002d60  20 77 68 65 72 65 20 6f  6f 70 73 20 61 63 74 73  | where oops acts|
00002d70  0a 67 6c 6f 62 61 6c 20  73 61 76 65 64 5f 6f 6f  |.global saved_oo|
00002d80  70 73 20 3d 20 30 3b 20  20 20 20 20 20 20 20 20  |ps = 0;         |
00002d90  20 21 20 55 73 65 64 20  69 6e 20 77 6f 72 6b 69  | ! Used in worki|
00002da0  6e 67 20 74 68 69 73 20  6f 75 74 0a 67 6c 6f 62  |ng this out.glob|
00002db0  61 6c 20 6f 6f 70 73 5f  68 65 61 70 20 64 61 74  |al oops_heap dat|
00002dc0  61 20 31 30 3b 20 20 20  20 20 20 20 21 20 55 73  |a 10;       ! Us|
00002dd0  65 64 20 74 65 6d 70 6f  72 61 72 69 6c 79 20 62  |ed temporarily b|
00002de0  79 20 22 6f 6f 70 73 22  20 72 6f 75 74 69 6e 65  |y "oops" routine|
00002df0  0a 0a 67 6c 6f 62 61 6c  20 6d 61 74 63 68 5f 6c  |..global match_l|
00002e00  69 73 74 20 64 61 74 61  20 31 32 38 3b 20 20 20  |ist data 128;   |
00002e10  20 20 21 20 41 6e 20 61  72 72 61 79 20 6f 66 20  |  ! An array of |
00002e20  6d 61 74 63 68 65 64 20  6f 62 6a 65 63 74 73 20  |matched objects |
00002e30  73 6f 20 66 61 72 0a 67  6c 6f 62 61 6c 20 6d 61  |so far.global ma|
00002e40  74 63 68 5f 63 6c 61 73  73 65 73 20 64 61 74 61  |tch_classes data|
00002e50  20 31 32 38 3b 20 20 21  20 41 6e 20 61 72 72 61  | 128;  ! An arra|
00002e60  79 20 6f 66 20 65 71 75  69 76 61 6c 65 6e 63 65  |y of equivalence|
00002e70  20 63 6c 61 73 73 65 73  20 66 6f 72 20 74 68 65  | classes for the|
00002e80  6d 0a 67 6c 6f 62 61 6c  20 6e 75 6d 62 65 72 5f  |m.global number_|
00002e90  6d 61 74 63 68 65 64 3b  20 20 20 20 20 20 20 20  |matched;        |
00002ea0  20 20 21 20 48 6f 77 20  6d 61 6e 79 20 69 74 65  |  ! How many ite|
00002eb0  6d 73 20 69 6e 20 69 74  3f 20 20 28 30 20 6d 65  |ms in it?  (0 me|
00002ec0  61 6e 73 20 6e 6f 6e 65  29 0a 67 6c 6f 62 61 6c  |ans none).global|
00002ed0  20 6e 75 6d 62 65 72 5f  6f 66 5f 63 6c 61 73 73  | number_of_class|
00002ee0  65 73 3b 20 20 20 20 20  20 20 21 20 48 6f 77 20  |es;       ! How |
00002ef0  6d 61 6e 79 20 65 71 75  69 76 61 6c 65 6e 63 65  |many equivalence|
00002f00  20 63 6c 61 73 73 65 73  3f 0a 67 6c 6f 62 61 6c  | classes?.global|
00002f10  20 6d 61 74 63 68 5f 6c  65 6e 67 74 68 3b 20 20  | match_length;  |
00002f20  20 20 20 20 20 20 20 20  20 20 21 20 48 6f 77 20  |          ! How |
00002f30  6d 61 6e 79 20 74 79 70  65 64 20 77 6f 72 64 73  |many typed words|
00002f40  20 6c 6f 6e 67 20 61 72  65 20 74 68 65 73 65 20  | long are these |
00002f50  6d 61 74 63 68 65 73 3f  0a 67 6c 6f 62 61 6c 20  |matches?.global |
00002f60  6d 61 74 63 68 5f 66 72  6f 6d 3b 20 20 20 20 20  |match_from;     |
00002f70  20 20 20 20 20 20 20 20  20 21 20 41 74 20 77 68  |         ! At wh|
00002f80  61 74 20 77 6f 72 64 20  6f 66 20 74 68 65 20 69  |at word of the i|
00002f90  6e 70 75 74 20 64 6f 20  74 68 65 79 20 62 65 67  |nput do they beg|
00002fa0  69 6e 3f 0a 0a 67 6c 6f  62 61 6c 20 70 61 72 73  |in?..global pars|
00002fb0  65 72 5f 61 63 74 69 6f  6e 3b 20 20 20 20 20 20  |er_action;      |
00002fc0  20 20 20 20 20 21 20 46  6f 72 20 74 68 65 20 75  |     ! For the u|
00002fd0  73 65 20 6f 66 20 74 68  65 20 70 61 72 73 65 72  |se of the parser|
00002fe0  20 77 68 65 6e 20 63 61  6c 6c 69 6e 67 0a 67 6c  | when calling.gl|
00002ff0  6f 62 61 6c 20 70 61 72  73 65 72 5f 6f 6e 65 3b  |obal parser_one;|
00003000  20 20 20 20 20 20 20 20  20 20 20 20 20 20 21 20  |              ! |
00003010  75 73 65 72 2d 73 75 70  70 6c 69 65 64 20 72 6f  |user-supplied ro|
00003020  75 74 69 6e 65 73 0a 67  6c 6f 62 61 6c 20 70 61  |utines.global pa|
00003030  72 73 65 72 5f 74 77 6f  3b 20 20 20 20 20 20 20  |rser_two;       |
00003040  20 20 20 20 20 20 20 21  0a 0a 67 6c 6f 62 61 6c  |       !..global|
00003050  20 76 61 67 75 65 5f 77  6f 72 64 3b 20 20 20 20  | vague_word;    |
00003060  20 20 20 20 20 20 20 20  20 20 21 20 52 65 63 6f  |          ! Reco|
00003070  72 64 73 20 77 68 69 63  68 20 76 61 67 75 65 20  |rds which vague |
00003080  77 6f 72 64 20 28 22 69  74 22 2c 20 22 74 68 65  |word ("it", "the|
00003090  6d 22 2c 20 2e 2e 2e 29  0a 20 20 20 20 20 20 20  |m", ...).       |
000030a0  20 20 20 20 20 20 20 20  20 20 20 20 20 20 20 20  |                |
000030b0  20 20 20 20 20 20 20 20  20 21 20 63 61 75 73 65  |         ! cause|
000030c0  64 20 61 6e 20 65 72 72  6f 72 0a 67 6c 6f 62 61  |d an error.globa|
000030d0  6c 20 76 61 67 75 65 5f  6f 62 6a 3b 20 20 20 20  |l vague_obj;    |
000030e0  20 20 20 20 20 20 20 20  20 20 20 21 20 41 6e 64  |           ! And|
000030f0  20 77 68 61 74 20 69 74  20 77 61 73 20 74 68 6f  | what it was tho|
00003100  75 67 68 74 20 74 6f 20  72 65 66 65 72 20 74 6f  |ught to refer to|
00003110  0a 0a 67 6c 6f 62 61 6c  20 69 74 6f 62 6a 3d 30  |..global itobj=0|
00003120  3b 20 20 20 20 20 20 20  20 20 20 20 20 20 20 20  |;               |
00003130  20 20 21 20 54 68 65 20  6f 62 6a 65 63 74 20 77  |  ! The object w|
00003140  68 69 63 68 20 69 73 20  63 75 72 72 65 6e 74 6c  |hich is currentl|
00003150  79 20 22 69 74 22 0a 67  6c 6f 62 61 6c 20 68 69  |y "it".global hi|
00003160  6d 6f 62 6a 3d 30 3b 20  20 20 20 20 20 20 20 20  |mobj=0;         |
00003170  20 20 20 20 20 20 20 21  20 54 68 65 20 6f 62 6a  |       ! The obj|
00003180  65 63 74 20 77 68 69 63  68 20 69 73 20 63 75 72  |ect which is cur|
00003190  72 65 6e 74 6c 79 20 22  68 69 6d 22 0a 67 6c 6f  |rently "him".glo|
000031a0  62 61 6c 20 68 65 72 6f  62 6a 3d 30 3b 20 20 20  |bal herobj=0;   |
000031b0  20 20 20 20 20 20 20 20  20 20 20 20 20 21 20 54  |             ! T|
000031c0  68 65 20 6f 62 6a 65 63  74 20 77 68 69 63 68 20  |he object which |
000031d0  69 73 20 63 75 72 72 65  6e 74 6c 79 20 22 68 65  |is currently "he|
000031e0  72 22 0a 0a 67 6c 6f 62  61 6c 20 6c 6f 6f 6b 61  |r"..global looka|
000031f0  68 65 61 64 3b 20 20 20  20 20 20 20 20 20 20 20  |head;           |
00003200  20 20 20 20 21 20 54 68  65 20 74 6f 6b 65 6e 20  |    ! The token |
00003210  61 66 74 65 72 20 74 68  65 20 6f 62 6a 65 63 74  |after the object|
00003220  20 6e 6f 77 20 62 65 69  6e 67 20 6d 61 74 63 68  | now being match|
00003230  65 64 0a 67 6c 6f 62 61  6c 20 69 6e 64 65 66 5f  |ed.global indef_|
00003240  6d 6f 64 65 3b 20 20 20  20 20 20 20 20 20 20 20  |mode;           |
00003250  20 20 20 21 20 22 49 6e  64 65 66 69 6e 69 74 65  |   ! "Indefinite|
00003260  22 20 6d 6f 64 65 20 2d  20 69 65 2c 20 22 74 61  |" mode - ie, "ta|
00003270  6b 65 20 61 20 62 72 69  63 6b 22 20 69 73 20 69  |ke a brick" is i|
00003280  6e 0a 20 20 20 20 20 20  20 20 20 20 20 20 20 20  |n.              |
00003290  20 20 20 20 20 20 20 20  20 20 20 20 20 20 20 20  |                |
000032a0  20 20 21 20 74 68 69 73  20 6d 6f 64 65 0a 67 6c  |  ! this mode.gl|
000032b0  6f 62 61 6c 20 69 6e 64  65 66 5f 74 79 70 65 3b  |obal indef_type;|
000032c0  20 20 20 20 20 20 20 20  20 20 20 20 20 20 21 20  |              ! |
000032d0  42 69 74 2d 6d 61 70 20  68 6f 6c 64 69 6e 67 20  |Bit-map holding |
000032e0  74 79 70 65 73 20 6f 66  20 73 70 65 63 69 66 69  |types of specifi|
000032f0  63 61 74 69 6f 6e 0a 67  6c 6f 62 61 6c 20 69 6e  |cation.global in|
00003300  64 65 66 5f 77 61 6e 74  65 64 3b 20 20 20 20 20  |def_wanted;     |
00003310  20 20 20 20 20 20 20 21  20 4e 75 6d 62 65 72 20  |       ! Number |
00003320  6f 66 20 69 74 65 6d 73  20 77 61 6e 74 65 64 20  |of items wanted |
00003330  28 31 30 30 20 66 6f 72  20 61 6c 6c 29 0a 67 6c  |(100 for all).gl|
00003340  6f 62 61 6c 20 69 6e 64  65 66 5f 67 75 65 73 73  |obal indef_guess|
00003350  5f 70 3b 20 20 20 20 20  20 20 20 20 20 20 21 20  |_p;           ! |
00003360  50 6c 75 72 61 6c 2d 67  75 65 73 73 69 6e 67 20  |Plural-guessing |
00003370  66 6c 61 67 0a 67 6c 6f  62 61 6c 20 61 6c 6c 6f  |flag.global allo|
00003380  77 5f 70 6c 75 72 61 6c  73 3b 20 20 20 20 20 20  |w_plurals;      |
00003390  20 20 20 20 20 21 20 57  68 65 74 68 65 72 20 74  |     ! Whether t|
000033a0  68 65 79 20 61 72 65 20  70 72 65 73 65 6e 74 6c  |hey are presentl|
000033b0  79 20 61 6c 6c 6f 77 65  64 20 6f 72 20 6e 6f 74  |y allowed or not|
000033c0  0a 67 6c 6f 62 61 6c 20  6e 6f 74 5f 68 6f 6c 64  |.global not_hold|
000033d0  69 6e 67 3b 20 20 20 20  20 20 20 20 20 20 20 20  |ing;            |
000033e0  20 21 20 4f 62 6a 65 63  74 20 74 6f 20 62 65 20  | ! Object to be |
000033f0  61 75 74 6f 6d 61 74 69  63 61 6c 6c 79 20 74 61  |automatically ta|
00003400  6b 65 6e 20 61 73 20 61  6e 0a 20 20 20 20 20 20  |ken as an.      |
00003410  20 20 20 20 20 20 20 20  20 20 20 20 20 20 20 20  |                |
00003420  20 20 20 20 20 20 20 20  20 20 21 20 69 6d 70 6c  |          ! impl|
00003430  69 63 69 74 20 63 6f 6d  6d 61 6e 64 0a 67 6c 6f  |icit command.glo|
00003440  62 61 6c 20 6b 65 70 74  5f 72 65 73 75 6c 74 73  |bal kept_results|
00003450  20 64 61 74 61 20 33 32  3b 20 20 20 20 21 20 54  | data 32;    ! T|
00003460  68 65 20 64 65 6c 61 79  65 64 20 63 6f 6d 6d 61  |he delayed comma|
00003470  6e 64 20 28 77 68 69 6c  65 20 74 68 65 20 74 61  |nd (while the ta|
00003480  6b 65 20 68 61 70 70 65  6e 73 29 0a 0a 67 6c 6f  |ke happens)..glo|
00003490  62 61 6c 20 73 61 76 65  64 5f 77 6e 3b 20 20 20  |bal saved_wn;   |
000034a0  20 20 20 20 20 20 20 20  20 20 20 20 20 21 20 54  |             ! T|
000034b0  68 65 73 65 20 61 72 65  20 74 65 6d 70 6f 72 61  |hese are tempora|
000034c0  72 79 20 76 61 72 69 61  62 6c 65 73 20 66 6f 72  |ry variables for|
000034d0  20 50 61 72 73 65 72 28  29 0a 67 6c 6f 62 61 6c  | Parser().global|
000034e0  20 73 61 76 65 64 5f 74  6f 6b 65 6e 3b 20 20 20  | saved_token;   |
000034f0  20 20 20 20 20 20 20 20  20 20 21 20 28 77 68 69  |          ! (whi|
00003500  63 68 20 68 61 73 6e 27  74 20 65 6e 6f 75 67 68  |ch hasn't enough|
00003510  20 73 70 61 72 65 20 6c  6f 63 61 6c 20 76 61 72  | spare local var|
00003520  69 61 62 6c 65 73 29 0a  0a 67 6c 6f 62 61 6c 20  |iables)..global |
00003530  68 65 6c 64 5f 62 61 63  6b 5f 6d 6f 64 65 20 3d  |held_back_mode =|
00003540  20 30 3b 20 20 20 20 20  20 21 20 46 6c 61 67 3a  | 0;      ! Flag:|
00003550  20 69 73 20 74 68 65 72  65 20 73 6f 6d 65 20 69  | is there some i|
00003560  6e 70 75 74 20 66 72 6f  6d 20 6c 61 73 74 20 74  |nput from last t|
00003570  69 6d 65 0a 67 6c 6f 62  61 6c 20 68 62 5f 77 6e  |ime.global hb_wn|
00003580  20 3d 20 30 3b 20 20 20  20 20 20 20 20 20 20 20  | = 0;           |
00003590  20 20 20 20 21 20 6c 65  66 74 20 6f 76 65 72 3f  |    ! left over?|
000035a0  20 20 28 41 6e 64 20 61  20 73 61 76 65 20 76 61  |  (And a save va|
000035b0  6c 75 65 20 66 6f 72 20  77 6e 29 0a 0a 67 6c 6f  |lue for wn)..glo|
000035c0  62 61 6c 20 62 65 73 74  5f 65 74 79 70 65 3b 20  |bal best_etype; |
000035d0  20 20 20 20 20 20 20 20  20 20 20 20 20 21 20 45  |             ! E|
000035e0  72 72 6f 72 20 6e 75 6d  62 65 72 20 75 73 65 64  |rror number used|
000035f0  20 77 69 74 68 69 6e 20  70 61 72 73 65 72 0a 67  | within parser.g|
00003600  6c 6f 62 61 6c 20 65 74  79 70 65 3b 20 20 20 20  |lobal etype;    |
00003610  20 20 20 20 20 20 20 20  20 20 20 20 20 20 20 21  |               !|
00003620  20 45 72 72 6f 72 20 6e  75 6d 62 65 72 20 75 73  | Error number us|
00003630  65 64 20 66 6f 72 20 69  6e 64 69 76 69 64 75 61  |ed for individua|
00003640  6c 20 6c 69 6e 65 73 0a  0a 67 6c 6f 62 61 6c 20  |l lines..global |
00003650  6c 61 73 74 5f 63 6f 6d  6d 61 6e 64 5f 66 72 6f  |last_command_fro|
00003660  6d 3b 20 20 20 20 20 20  20 21 20 46 6f 72 20 73  |m;       ! For s|
00003670  6f 72 74 69 6e 67 20 6f  75 74 20 22 74 68 65 6e  |orting out "then|
00003680  20 61 67 61 69 6e 22 0a  67 6c 6f 62 61 6c 20 6c  | again".global l|
00003690  61 73 74 5f 63 6f 6d 6d  61 6e 64 5f 74 6f 3b 20  |ast_command_to; |
000036a0  20 20 20 20 20 20 20 20  21 0a 0a 67 6c 6f 62 61  |        !..globa|
000036b0  6c 20 74 6f 6b 65 6e 5f  77 61 73 3b 20 20 20 20  |l token_was;    |
000036c0  20 20 20 20 20 20 20 20  20 20 20 21 20 46 6f 72  |           ! For|
000036d0  20 6e 6f 75 6e 20 66 69  6c 74 65 72 69 6e 67 20  | noun filtering |
000036e0  62 79 20 75 73 65 72 20  72 6f 75 74 69 6e 65 73  |by user routines|
000036f0  0a 0a 67 6c 6f 62 61 6c  20 61 64 76 61 6e 63 65  |..global advance|
00003700  5f 77 61 72 6e 69 6e 67  3b 20 20 20 20 20 20 20  |_warning;       |
00003710  20 20 21 20 57 68 61 74  20 61 20 6c 61 74 65 72  |  ! What a later|
00003720  2d 6e 61 6d 65 64 20 74  68 69 6e 67 20 77 69 6c  |-named thing wil|
00003730  6c 20 62 65 0a 0a 67 6c  6f 62 61 6c 20 70 6c 61  |l be..global pla|
00003740  63 65 64 5f 69 6e 5f 66  6c 61 67 3b 20 20 20 20  |ced_in_flag;    |
00003750  20 20 20 20 20 20 21 20  54 6f 20 64 6f 20 77 69  |      ! To do wi|
00003760  74 68 20 50 6c 61 63 65  49 6e 53 63 6f 70 65 0a  |th PlaceInScope.|
00003770  67 6c 6f 62 61 6c 20 6c  65 6e 67 74 68 5f 6f 66  |global length_of|
00003780  5f 6e 6f 75 6e 3b 20 20  20 20 20 20 20 20 20 20  |_noun;          |
00003790  21 20 53 65 74 20 62 79  20 4e 6f 75 6e 44 6f 6d  |! Set by NounDom|
000037a0  61 69 6e 20 74 6f 20 6e  75 6d 62 65 72 20 6f 66  |ain to number of|
000037b0  20 77 6f 72 64 73 20 69  6e 20 6e 6f 75 6e 0a 0a  | words in noun..|
000037c0  67 6c 6f 62 61 6c 20 61  63 74 69 6f 6e 5f 74 6f  |global action_to|
000037d0  5f 62 65 3b 20 20 20 20  20 20 20 20 20 20 20 20  |_be;            |
000037e0  21 20 53 6f 20 74 68 65  20 70 61 72 73 65 72 20  |! So the parser |
000037f0  63 61 6e 20 22 63 68 65  61 74 22 20 69 6e 20 6f  |can "cheat" in o|
00003800  6e 65 20 63 61 73 65 0a  67 6c 6f 62 61 6c 20 64  |ne case.global d|
00003810  6f 6e 74 5f 69 6e 66 65  72 3b 20 20 20 20 20 20  |ont_infer;      |
00003820  20 20 20 20 20 20 20 20  21 20 41 6e 6f 74 68 65  |        ! Anothe|
00003830  72 20 64 75 6c 6c 20 66  6c 61 67 0a 0a 67 6c 6f  |r dull flag..glo|
00003840  62 61 6c 20 65 74 5f 66  6c 61 67 20 3d 20 30 3b  |bal et_flag = 0;|
00003850  20 20 20 20 20 20 20 20  20 20 20 20 20 21 20 50  |             ! P|
00003860  72 6f 63 65 73 73 69 6e  67 20 22 65 61 63 68 5f  |rocessing "each_|
00003870  74 75 72 6e 22 20 6d 6f  64 65 0a 0a 67 6c 6f 62  |turn" mode..glob|
00003880  61 6c 20 73 63 6f 70 65  5f 74 6f 6b 65 6e 3b 20  |al scope_token; |
00003890  20 20 20 20 20 20 20 20  20 20 20 20 21 20 46 6f  |            ! Fo|
000038a0  72 20 73 63 6f 70 65 3a  52 6f 75 74 69 6e 65 20  |r scope:Routine |
000038b0  74 6f 6b 65 6e 73 0a 67  6c 6f 62 61 6c 20 73 63  |tokens.global sc|
000038c0  6f 70 65 5f 65 72 72 6f  72 3b 0a 67 6c 6f 62 61  |ope_error;.globa|
000038d0  6c 20 73 63 6f 70 65 5f  73 74 61 67 65 3b 0a 0a  |l scope_stage;..|
000038e0  23 49 46 56 35 3b 0a 67  6c 6f 62 61 6c 20 6a 75  |#IFV5;.global ju|
000038f0  73 74 5f 75 6e 64 6f 6e  65 20 3d 20 30 3b 20 20  |st_undone = 0;  |
00003900  20 20 20 20 20 20 20 21  20 43 61 6e 27 74 20 68  |       ! Can't h|
00003910  61 76 65 20 74 77 6f 20  73 75 63 63 65 73 73 69  |ave two successi|
00003920  76 65 20 55 4e 44 4f 73  0a 23 45 4e 44 49 46 3b  |ve UNDOs.#ENDIF;|
00003930  0a 0a 21 20 2d 2d 2d 2d  2d 2d 2d 2d 2d 2d 2d 2d  |..! ------------|
00003940  2d 2d 2d 2d 2d 2d 2d 2d  2d 2d 2d 2d 2d 2d 2d 2d  |----------------|
*
00003980  0a 21 20 20 54 68 65 20  63 6f 6d 6d 61 5f 77 6f  |.!  The comma_wo|
00003990  72 64 20 69 73 20 61 20  73 70 65 63 69 61 6c 20  |rd is a special |
000039a0  77 6f 72 64 2c 20 75 73  65 64 20 74 6f 20 73 75  |word, used to su|
000039b0  62 73 74 69 74 75 74 65  20 63 6f 6d 6d 61 73 20  |bstitute commas |
000039c0  69 6e 20 74 68 65 20 69  6e 70 75 74 0a 21 20 2d  |in the input.! -|
000039d0  2d 2d 2d 2d 2d 2d 2d 2d  2d 2d 2d 2d 2d 2d 2d 2d  |----------------|
*
00003a10  2d 2d 2d 2d 2d 2d 2d 2d  2d 2d 2d 0a 0a 44 69 63  |-----------..Dic|
00003a20  74 69 6f 6e 61 72 79 20  63 6f 6d 6d 61 5f 77 6f  |tionary comma_wo|
00003a30  72 64 20 20 20 22 78 63  6f 6d 6d 61 22 3b 0a 0a  |rd   "xcomma";..|
00003a40  21 20 2d 2d 2d 2d 2d 2d  2d 2d 2d 2d 2d 2d 2d 2d  |! --------------|
00003a50  2d 2d 2d 2d 2d 2d 2d 2d  2d 2d 2d 2d 2d 2d 2d 2d  |----------------|
*
00003a80  2d 2d 2d 2d 2d 2d 2d 2d  2d 2d 2d 2d 2d 2d 0a 21  |--------------.!|
00003a90  20 20 49 6e 20 41 64 76  61 6e 63 65 64 20 67 61  |  In Advanced ga|
00003aa0  6d 65 73 20 6f 6e 6c 79  2c 20 74 68 65 20 44 72  |mes only, the Dr|
00003ab0  61 77 53 74 61 74 75 73  4c 69 6e 65 20 72 6f 75  |awStatusLine rou|
00003ac0  74 69 6e 65 20 64 6f 65  73 20 6a 75 73 74 20 74  |tine does just t|
00003ad0  68 61 74 3a 20 74 68 69  73 20 69 73 0a 21 20 20  |hat: this is.!  |
00003ae0  70 72 6f 76 69 64 65 64  20 65 78 70 6c 69 63 69  |provided explici|
00003af0  74 6c 79 20 73 6f 20 74  68 61 74 20 69 74 20 63  |tly so that it c|
00003b00  61 6e 20 62 65 20 52 65  70 6c 61 63 65 27 64 20  |an be Replace'd |
00003b10  74 6f 20 63 68 61 6e 67  65 20 74 68 65 20 73 74  |to change the st|
00003b20  79 6c 65 2c 20 61 6e 64  0a 21 20 20 61 73 20 77  |yle, and.!  as w|
00003b30  72 69 74 74 65 6e 20 69  74 20 65 6d 75 6c 61 74  |ritten it emulat|
00003b40  65 73 20 74 68 65 20 6f  72 64 69 6e 61 72 79 20  |es the ordinary |
00003b50  53 74 61 6e 64 61 72 64  20 67 61 6d 65 20 73 74  |Standard game st|
00003b60  61 74 75 73 20 6c 69 6e  65 2c 20 77 68 69 63 68  |atus line, which|
00003b70  20 69 73 0a 21 20 20 64  72 61 77 6e 20 69 6e 20  | is.!  drawn in |
00003b80  68 61 72 64 77 61 72 65  0a 21 20 2d 2d 2d 2d 2d  |hardware.! -----|
00003b90  2d 2d 2d 2d 2d 2d 2d 2d  2d 2d 2d 2d 2d 2d 2d 2d  |----------------|
*
00003bd0  2d 2d 2d 2d 2d 2d 2d 0a  23 49 46 56 35 3b 0a 5b  |-------.#IFV5;.[|
00003be0  20 44 72 61 77 53 74 61  74 75 73 4c 69 6e 65 20  | DrawStatusLine |
00003bf0  69 3b 0a 20 20 20 40 73  70 6c 69 74 5f 77 69 6e  |i;.   @split_win|
00003c00  64 6f 77 20 31 3b 20 40  73 65 74 5f 77 69 6e 64  |dow 1; @set_wind|
00003c10  6f 77 20 31 3b 20 40 73  65 74 5f 63 75 72 73 6f  |ow 1; @set_curso|
00003c20  72 20 31 20 31 3b 20 73  74 79 6c 65 20 72 65 76  |r 1 1; style rev|
00003c30  65 72 73 65 3b 0a 20 20  20 73 70 61 63 65 73 20  |erse;.   spaces |
00003c40  28 30 2d 3e 33 33 29 2d  31 3b 0a 20 20 20 40 73  |(0->33)-1;.   @s|
00003c50  65 74 5f 63 75 72 73 6f  72 20 31 20 32 3b 20 20  |et_cursor 1 2;  |
00003c60  50 72 69 6e 74 53 68 6f  72 74 4e 61 6d 65 28 6c  |PrintShortName(l|
00003c70  6f 63 61 74 69 6f 6e 29  3b 0a 20 20 20 69 66 20  |ocation);.   if |
00003c80  28 28 30 2d 3e 31 29 26  32 20 3d 3d 20 30 29 0a  |((0->1)&2 == 0).|
00003c90  20 20 20 7b 20 20 20 40  73 65 74 5f 63 75 72 73  |   {   @set_curs|
00003ca0  6f 72 20 31 20 35 31 3b  20 70 72 69 6e 74 20 22  |or 1 51; print "|
00003cb0  53 63 6f 72 65 3a 20 22  2c 20 73 6c 69 6e 65 31  |Score: ", sline1|
00003cc0  3b 0a 20 20 20 20 20 20  20 40 73 65 74 5f 63 75  |;.       @set_cu|
00003cd0  72 73 6f 72 20 31 20 36  34 3b 20 70 72 69 6e 74  |rsor 1 64; print|
00003ce0  20 22 4d 6f 76 65 73 3a  20 22 2c 20 73 6c 69 6e  | "Moves: ", slin|
00003cf0  65 32 3b 0a 20 20 20 7d  0a 20 20 20 65 6c 73 65  |e2;.   }.   else|
00003d00  0a 20 20 20 7b 20 20 20  40 73 65 74 5f 63 75 72  |.   {   @set_cur|
00003d10  73 6f 72 20 31 20 35 31  3b 20 70 72 69 6e 74 20  |sor 1 51; print |
00003d20  22 54 69 6d 65 3a 20 22  3b 0a 20 20 20 20 20 20  |"Time: ";.      |
00003d30  20 69 3d 73 6c 69 6e 65  31 25 31 32 3b 20 69 66  | i=sline1%12; if|
00003d40  20 28 69 3c 31 30 29 20  70 72 69 6e 74 20 22 20  | (i<10) print " |
00003d50  22 3b 0a 20 20 20 20 20  20 20 69 66 20 28 69 3d  |";.       if (i=|
00003d60  3d 30 29 20 69 3d 31 32  3b 0a 20 20 20 20 20 20  |=0) i=12;.      |
00003d70  20 70 72 69 6e 74 20 69  2c 20 22 3a 22 3b 0a 20  | print i, ":";. |
00003d80  20 20 20 20 20 20 69 66  20 28 73 6c 69 6e 65 32  |      if (sline2|
00003d90  3c 31 30 29 20 70 72 69  6e 74 20 22 30 22 3b 0a  |<10) print "0";.|
00003da0  20 20 20 20 20 20 20 70  72 69 6e 74 20 73 6c 69  |       print sli|
00003db0  6e 65 32 3b 0a 20 20 20  20 20 20 20 69 66 20 28  |ne2;.       if (|
00003dc0  28 73 6c 69 6e 65 31 2f  31 32 29 20 3e 20 30 29  |(sline1/12) > 0)|
00003dd0  20 70 72 69 6e 74 20 22  20 70 6d 22 3b 20 65 6c  | print " pm"; el|
00003de0  73 65 20 70 72 69 6e 74  20 22 20 61 6d 22 3b 0a  |se print " am";.|
00003df0  20 20 20 7d 0a 20 20 20  40 73 65 74 5f 63 75 72  |   }.   @set_cur|
00003e00  73 6f 72 20 31 20 31 3b  20 73 74 79 6c 65 20 72  |sor 1 1; style r|
00003e10  6f 6d 61 6e 3b 20 40 73  65 74 5f 77 69 6e 64 6f  |oman; @set_windo|
00003e20  77 20 30 3b 0a 5d 3b 0a  23 45 4e 44 49 46 3b 0a  |w 0;.];.#ENDIF;.|
00003e30  0a 21 20 2d 2d 2d 2d 2d  2d 2d 2d 2d 2d 2d 2d 2d  |.! -------------|
00003e40  2d 2d 2d 2d 2d 2d 2d 2d  2d 2d 2d 2d 2d 2d 2d 2d  |----------------|
*
00003e70  2d 2d 2d 2d 2d 2d 2d 2d  2d 2d 2d 2d 2d 2d 2d 0a  |---------------.|
00003e80  21 20 20 54 68 65 20 4b  65 79 62 6f 61 72 64 20  |!  The Keyboard |
00003e90  72 6f 75 74 69 6e 65 20  61 63 74 75 61 6c 6c 79  |routine actually|
00003ea0  20 72 65 63 65 69 76 65  73 20 74 68 65 20 70 6c  | receives the pl|
00003eb0  61 79 65 72 27 73 20 77  6f 72 64 73 2c 0a 21 20  |ayer's words,.! |
00003ec0  20 70 75 74 74 69 6e 67  20 74 68 65 20 77 6f 72  | putting the wor|
00003ed0  64 73 20 69 6e 20 22 61  5f 62 75 66 66 65 72 22  |ds in "a_buffer"|
00003ee0  20 61 6e 64 20 74 68 65  69 72 20 64 69 63 74 69  | and their dicti|
00003ef0  6f 6e 61 72 79 20 61 64  64 72 65 73 73 65 73 20  |onary addresses |
00003f00  69 6e 0a 21 20 20 22 61  5f 74 61 62 6c 65 22 2e  |in.!  "a_table".|
00003f10  20 20 49 74 20 69 73 20  61 73 73 75 6d 65 64 20  |  It is assumed |
00003f20  74 68 61 74 20 74 68 65  20 74 61 62 6c 65 20 69  |that the table i|
00003f30  73 20 74 68 65 20 73 61  6d 65 20 6f 6e 65 20 6f  |s the same one o|
00003f40  6e 20 65 61 63 68 0a 21  20 20 28 73 74 61 6e 64  |n each.!  (stand|
00003f50  61 72 64 29 20 63 61 6c  6c 2e 0a 21 0a 21 20 20  |ard) call..!.!  |
00003f60  49 74 20 63 61 6e 20 61  6c 73 6f 20 62 65 20 75  |It can also be u|
00003f70  73 65 64 20 62 79 20 6d  69 73 63 65 6c 6c 61 6e  |sed by miscellan|
00003f80  65 6f 75 73 20 72 6f 75  74 69 6e 65 73 20 69 6e  |eous routines in|
00003f90  20 74 68 65 20 67 61 6d  65 20 74 6f 20 61 73 6b  | the game to ask|
00003fa0  0a 21 20 20 79 65 73 2d  6e 6f 20 71 75 65 73 74  |.!  yes-no quest|
00003fb0  69 6f 6e 73 20 61 6e 64  20 74 68 65 20 6c 69 6b  |ions and the lik|
00003fc0  65 2c 20 77 69 74 68 6f  75 74 20 69 6e 76 6f 6b  |e, without invok|
00003fd0  69 6e 67 20 74 68 65 20  72 65 73 74 20 6f 66 20  |ing the rest of |
00003fe0  74 68 65 20 70 61 72 73  65 72 2e 0a 21 0a 21 20  |the parser..!.! |
00003ff0  20 52 65 74 75 72 6e 20  74 68 65 20 6e 75 6d 62  | Return the numb|
00004000  65 72 20 6f 66 20 77 6f  72 64 73 20 74 79 70 65  |er of words type|
00004010  64 0a 21 20 2d 2d 2d 2d  2d 2d 2d 2d 2d 2d 2d 2d  |d.! ------------|
00004020  2d 2d 2d 2d 2d 2d 2d 2d  2d 2d 2d 2d 2d 2d 2d 2d  |----------------|
*
00004060  0a 0a 5b 20 4b 65 79 62  6f 61 72 64 20 20 61 5f  |..[ Keyboard  a_|
00004070  62 75 66 66 65 72 20 61  5f 74 61 62 6c 65 20 20  |buffer a_table  |
00004080  6e 77 20 69 20 77 20 78  31 20 78 32 3b 0a 0a 20  |nw i w x1 x2;.. |
00004090  20 20 20 44 69 73 70 6c  61 79 53 74 61 74 75 73  |   DisplayStatus|
000040a0  28 29 3b 0a 20 20 20 20  2e 46 72 65 73 68 49 6e  |();.    .FreshIn|
000040b0  70 75 74 3b 0a 0a 21 20  20 53 61 76 65 20 74 68  |put;..!  Save th|
000040c0  65 20 73 74 61 72 74 20  6f 66 20 74 68 65 20 74  |e start of the t|
000040d0  61 62 6c 65 2c 20 69 6e  20 63 61 73 65 20 22 6f  |able, in case "o|
000040e0  6f 70 73 22 20 6e 65 65  64 73 20 74 6f 20 72 65  |ops" needs to re|
000040f0  73 74 6f 72 65 20 69 74  0a 21 20 20 74 6f 20 74  |store it.!  to t|
00004100  68 65 20 70 72 65 76 69  6f 75 73 20 74 69 6d 65  |he previous time|
00004110  27 73 20 74 61 62 6c 65  0a 0a 20 20 20 20 66 6f  |'s table..    fo|
00004120  72 20 69 20 30 20 74 6f  20 39 20 7b 20 70 75 74  |r i 0 to 9 { put|
00004130  20 6f 6f 70 73 5f 68 65  61 70 20 62 79 74 65 20  | oops_heap byte |
00004140  69 20 61 5f 74 61 62 6c  65 2d 3e 69 3b 20 7d 0a  |i a_table->i; }.|
00004150  0a 21 20 20 50 72 69 6e  74 20 74 68 65 20 70 72  |.!  Print the pr|
00004160  6f 6d 70 74 2c 20 61 6e  64 20 72 65 61 64 20 69  |ompt, and read i|
00004170  6e 20 74 68 65 20 77 6f  72 64 73 20 61 6e 64 20  |n the words and |
00004180  64 69 63 74 69 6f 6e 61  72 79 20 61 64 64 72 65  |dictionary addre|
00004190  73 73 65 73 0a 0a 20 20  20 20 70 72 69 6e 74 20  |sses..    print |
000041a0  22 5e 3e 22 3b 0a 20 20  20 20 23 49 46 56 33 3b  |"^>";.    #IFV3;|
000041b0  20 72 65 61 64 20 61 5f  62 75 66 66 65 72 20 61  | read a_buffer a|
000041c0  5f 74 61 62 6c 65 3b 20  23 45 4e 44 49 46 3b 0a  |_table; #ENDIF;.|
000041d0  20 20 20 20 23 49 46 56  35 3b 20 72 65 61 64 20  |    #IFV5; read |
000041e0  61 5f 62 75 66 66 65 72  20 61 5f 74 61 62 6c 65  |a_buffer a_table|
000041f0  20 44 72 61 77 53 74 61  74 75 73 4c 69 6e 65 3b  | DrawStatusLine;|
00004200  20 23 45 4e 44 49 46 3b  0a 20 20 20 20 6e 77 3d  | #ENDIF;.    nw=|
00004210  61 5f 74 61 62 6c 65 2d  3e 31 3b 0a 0a 21 20 20  |a_table->1;..!  |
00004220  49 66 20 74 68 65 20 6c  69 6e 65 20 77 61 73 20  |If the line was |
00004230  62 6c 61 6e 6b 2c 20 67  65 74 20 61 20 66 72 65  |blank, get a fre|
00004240  73 68 20 6c 69 6e 65 0a  20 20 20 20 69 66 20 28  |sh line.    if (|
00004250  6e 77 20 3d 3d 20 30 29  0a 20 20 20 20 7b 20 70  |nw == 0).    { p|
00004260  72 69 6e 74 20 22 49 20  62 65 67 20 79 6f 75 72  |rint "I beg your|
00004270  20 70 61 72 64 6f 6e 3f  5e 22 3b 20 6a 75 6d 70  | pardon?^"; jump|
00004280  20 46 72 65 73 68 49 6e  70 75 74 3b 20 7d 0a 0a  | FreshInput; }..|
00004290  21 20 20 55 6e 6c 65 73  73 20 74 68 65 20 6f 70  |!  Unless the op|
000042a0  65 6e 69 6e 67 20 77 6f  72 64 20 77 61 73 20 22  |ening word was "|
000042b0  6f 6f 70 73 22 20 6f 72  20 69 74 73 20 61 62 62  |oops" or its abb|
000042c0  72 65 76 69 61 74 69 6f  6e 20 22 6f 22 2c 20 72  |reviation "o", r|
000042d0  65 74 75 72 6e 0a 0a 20  20 20 20 77 3d 61 5f 74  |eturn..    w=a_t|
000042e0  61 62 6c 65 2d 2d 3e 31  3b 0a 20 20 20 20 69 66  |able-->1;.    if|
000042f0  20 28 77 20 3d 3d 20 23  6e 24 6f 20 6f 72 20 27  | (w == #n$o or '|
00004300  6f 6f 70 73 27 29 20 6a  75 6d 70 20 44 6f 4f 6f  |oops') jump DoOo|
00004310  70 73 3b 0a 0a 23 49 46  56 35 3b 0a 21 20 20 55  |ps;..#IFV5;.!  U|
00004320  6e 64 6f 20 68 61 6e 64  6c 69 6e 67 0a 0a 20 20  |ndo handling..  |
00004330  20 20 69 66 20 28 77 20  3d 3d 20 27 75 6e 64 6f  |  if (w == 'undo|
00004340  27 29 0a 20 20 20 20 7b  20 20 20 69 66 20 28 75  |').    {   if (u|
00004350  6e 64 6f 5f 66 6c 61 67  3d 3d 30 29 0a 20 20 20  |ndo_flag==0).   |
00004360  20 20 20 20 20 7b 20 20  20 70 72 69 6e 74 20 22  |     {   print "|
00004370  5b 59 6f 75 72 20 69 6e  74 65 72 70 72 65 74 65  |[Your interprete|
00004380  72 20 64 6f 65 73 20 6e  6f 74 20 70 72 6f 76 69  |r does not provi|
00004390  64 65 20 7e 75 6e 64 6f  7e 2e 20 20 53 6f 72 72  |de ~undo~.  Sorr|
000043a0  79 21 5d 5e 22 3b 0a 20  20 20 20 20 20 20 20 20  |y!]^";.         |
000043b0  20 20 20 6a 75 6d 70 20  46 72 65 73 68 49 6e 70  |   jump FreshInp|
000043c0  75 74 3b 0a 20 20 20 20  20 20 20 20 7d 0a 20 20  |ut;.        }.  |
000043d0  20 20 20 20 20 20 69 66  20 28 75 6e 64 6f 5f 66  |      if (undo_f|
000043e0  6c 61 67 3d 3d 31 29 20  6a 75 6d 70 20 55 6e 64  |lag==1) jump Und|
000043f0  6f 46 61 69 6c 65 64 3b  0a 20 20 20 20 20 20 20  |oFailed;.       |
00004400  20 69 66 20 28 6a 75 73  74 5f 75 6e 64 6f 6e 65  | if (just_undone|
00004410  3d 3d 31 29 0a 20 20 20  20 20 20 20 20 7b 20 20  |==1).        {  |
00004420  20 70 72 69 6e 74 20 22  5b 43 61 6e 27 74 20 7e  | print "[Can't ~|
00004430  75 6e 64 6f 7e 20 74 77  69 63 65 20 69 6e 20 73  |undo~ twice in s|
00004440  75 63 63 65 73 73 69 6f  6e 2e 20 20 53 6f 72 72  |uccession.  Sorr|
00004450  79 21 5d 5e 22 3b 0a 20  20 20 20 20 20 20 20 20  |y!]^";.         |
00004460  20 20 20 6a 75 6d 70 20  46 72 65 73 68 49 6e 70  |   jump FreshInp|
00004470  75 74 3b 0a 20 20 20 20  20 20 20 20 7d 0a 20 20  |ut;.        }.  |
00004480  20 20 20 20 20 20 72 65  73 74 6f 72 65 5f 75 6e  |      restore_un|
00004490  64 6f 20 69 3b 0a 20 20  20 20 20 20 20 20 69 66  |do i;.        if|
000044a0  20 28 69 3d 3d 30 29 0a  20 20 20 20 20 20 20 20  | (i==0).        |
000044b0  7b 20 20 20 2e 55 6e 64  6f 46 61 69 6c 65 64 3b  |{   .UndoFailed;|
000044c0  0a 20 20 20 20 20 20 20  20 20 20 20 20 70 72 69  |.            pri|
000044d0  6e 74 20 22 7e 55 6e 64  6f 7e 20 66 61 69 6c 65  |nt "~Undo~ faile|
000044e0  64 2e 20 20 5b 4e 6f 74  20 65 76 65 72 79 20 69  |d.  [Not every i|
000044f0  6e 74 65 72 70 72 65 74  65 72 20 70 72 6f 76 69  |nterpreter provi|
00004500  64 65 73 20 69 74 2e 5d  5e 22 3b 0a 20 20 20 20  |des it.]^";.    |
00004510  20 20 20 20 7d 0a 20 20  20 20 20 20 20 20 6a 75  |    }.        ju|
00004520  6d 70 20 46 72 65 73 68  49 6e 70 75 74 3b 0a 20  |mp FreshInput;. |
00004530  20 20 20 7d 0a 20 20 20  20 73 61 76 65 5f 75 6e  |   }.    save_un|
00004540  64 6f 20 69 3b 0a 20 20  20 20 6a 75 73 74 5f 75  |do i;.    just_u|
00004550  6e 64 6f 6e 65 3d 30 3b  0a 20 20 20 20 75 6e 64  |ndone=0;.    und|
00004560  6f 5f 66 6c 61 67 3d 32  3b 0a 20 20 20 20 69 66  |o_flag=2;.    if|
00004570  20 28 69 3d 3d 2d 31 29  20 75 6e 64 6f 5f 66 6c  | (i==-1) undo_fl|
00004580  61 67 3d 30 3b 0a 20 20  20 20 69 66 20 28 69 3d  |ag=0;.    if (i=|
00004590  3d 30 29 20 75 6e 64 6f  5f 66 6c 61 67 3d 31 3b  |=0) undo_flag=1;|
000045a0  0a 20 20 20 20 69 66 20  28 69 3d 3d 32 29 0a 20  |.    if (i==2). |
000045b0  20 20 20 7b 20 20 20 70  72 69 6e 74 20 22 5e 22  |   {   print "^"|
000045c0  2c 20 6f 62 6a 65 63 74  20 6c 6f 63 61 74 69 6f  |, object locatio|
000045d0  6e 2c 20 22 5e 5b 50 72  65 76 69 6f 75 73 20 74  |n, "^[Previous t|
000045e0  75 72 6e 20 75 6e 64 6f  6e 65 5d 5e 22 3b 0a 20  |urn undone]^";. |
000045f0  20 20 20 20 20 20 20 6a  75 73 74 5f 75 6e 64 6f  |       just_undo|
00004600  6e 65 3d 31 3b 0a 20 20  20 20 20 20 20 20 6a 75  |ne=1;.        ju|
00004610  6d 70 20 46 72 65 73 68  49 6e 70 75 74 3b 0a 20  |mp FreshInput;. |
00004620  20 20 20 7d 0a 23 45 4e  44 49 46 3b 0a 0a 20 20  |   }.#ENDIF;..  |
00004630  20 20 72 65 74 75 72 6e  20 6e 77 3b 0a 0a 20 20  |  return nw;..  |
00004640  20 20 2e 44 6f 4f 6f 70  73 3b 0a 20 20 20 20 69  |  .DoOops;.    i|
00004650  66 20 28 6f 6f 70 73 5f  66 72 6f 6d 20 3d 3d 20  |f (oops_from == |
00004660  30 29 0a 20 20 20 20 7b  20 20 20 70 72 69 6e 74  |0).    {   print|
00004670  20 22 53 6f 72 72 79 2c  20 74 68 61 74 20 63 61  | "Sorry, that ca|
00004680  6e 27 74 20 62 65 20 63  6f 72 72 65 63 74 65 64  |n't be corrected|
00004690  2e 5e 22 3b 20 6a 75 6d  70 20 46 72 65 73 68 49  |.^"; jump FreshI|
000046a0  6e 70 75 74 3b 20 7d 0a  20 20 20 20 69 66 20 28  |nput; }.    if (|
000046b0  6e 77 20 3d 3d 20 31 29  0a 20 20 20 20 7b 20 20  |nw == 1).    {  |
000046c0  20 70 72 69 6e 74 20 22  54 68 69 6e 6b 20 6e 6f  | print "Think no|
000046d0  74 68 69 6e 67 20 6f 66  20 69 74 2e 5e 22 3b 20  |thing of it.^"; |
000046e0  6a 75 6d 70 20 46 72 65  73 68 49 6e 70 75 74 3b  |jump FreshInput;|
000046f0  20 7d 0a 20 20 20 20 69  66 20 28 6e 77 20 3e 20  | }.    if (nw > |
00004700  32 29 0a 20 20 20 20 7b  20 20 20 70 72 69 6e 74  |2).    {   print|
00004710  20 22 7e 4f 6f 70 73 7e  20 63 61 6e 20 6f 6e 6c  | "~Oops~ can onl|
00004720  79 20 63 6f 72 72 65 63  74 20 61 20 73 69 6e 67  |y correct a sing|
00004730  6c 65 20 77 6f 72 64 2e  5e 22 3b 20 6a 75 6d 70  |le word.^"; jump|
00004740  20 46 72 65 73 68 49 6e  70 75 74 3b 20 7d 0a 0a  | FreshInput; }..|
00004750  21 20 20 53 6f 20 6e 6f  77 20 77 65 20 6b 6e 6f  |!  So now we kno|
00004760  77 3a 20 74 68 65 72 65  20 77 61 73 20 61 20 70  |w: there was a p|
00004770  72 65 76 69 6f 75 73 20  6d 69 73 74 61 6b 65 2c  |revious mistake,|
00004780  20 61 6e 64 20 74 68 65  20 70 6c 61 79 65 72 20  | and the player |
00004790  68 61 73 0a 21 20 20 61  74 74 65 6d 70 74 65 64  |has.!  attempted|
000047a0  20 74 6f 20 63 6f 72 72  65 63 74 20 61 20 73 69  | to correct a si|
000047b0  6e 67 6c 65 20 77 6f 72  64 20 6f 66 20 69 74 2e  |ngle word of it.|
000047c0  0a 21 0a 21 20 20 4f 6f  70 73 20 69 73 20 76 65  |.!.!  Oops is ve|
000047d0  72 79 20 70 72 69 6d 69  74 69 76 65 3a 20 69 74  |ry primitive: it|
000047e0  20 67 65 74 73 20 74 68  65 20 74 65 78 74 20 62  | gets the text b|
000047f0  75 66 66 65 72 20 77 72  6f 6e 67 2c 20 66 6f 72  |uffer wrong, for|
00004800  20 69 6e 73 74 61 6e 63  65 2e 0a 21 0a 21 20 20  | instance..!.!  |
00004810  54 61 6b 65 20 6f 75 74  20 74 68 65 20 34 2d 62  |Take out the 4-b|
00004820  79 74 65 20 74 61 62 6c  65 20 65 6e 74 72 79 20  |yte table entry |
00004830  66 6f 72 20 74 68 65 20  73 75 70 70 6c 69 65 64  |for the supplied|
00004840  20 63 6f 72 72 65 63 74  69 6f 6e 3a 0a 21 20 20  | correction:.!  |
00004850  72 65 73 74 6f 72 65 20  74 68 65 20 31 30 20 62  |restore the 10 b|
00004860  79 74 65 73 20 61 74 20  74 68 65 20 66 72 6f 6e  |ytes at the fron|
00004870  74 20 6f 66 20 74 68 65  20 74 61 62 6c 65 2c 20  |t of the table, |
00004880  77 68 69 63 68 20 77 65  72 65 20 6f 76 65 72 2d  |which were over-|
00004890  77 72 69 74 74 65 6e 0a  21 20 20 62 79 20 77 68  |written.!  by wh|
000048a0  61 74 20 74 68 65 20 75  73 65 72 20 6a 75 73 74  |at the user just|
000048b0  20 74 79 70 65 64 3a 20  61 6e 64 20 74 68 65 6e  | typed: and then|
000048c0  20 72 65 70 6c 61 63 65  20 74 68 65 20 6f 6f 70  | replace the oop|
000048d0  73 5f 66 72 6f 6d 20 77  6f 72 64 20 65 6e 74 72  |s_from word entr|
000048e0  79 0a 21 20 20 77 69 74  68 20 74 68 65 20 63 6f  |y.!  with the co|
000048f0  72 72 65 63 74 69 6f 6e  20 6f 6e 65 2e 0a 21 0a  |rrection one..!.|
00004900  20 20 20 20 78 31 3d 61  5f 74 61 62 6c 65 2d 2d  |    x1=a_table--|
00004910  3e 33 3b 20 78 32 3d 61  5f 74 61 62 6c 65 2d 2d  |>3; x2=a_table--|
00004920  3e 34 3b 0a 20 20 20 20  66 6f 72 20 69 20 30 20  |>4;.    for i 0 |
00004930  74 6f 20 39 20 7b 20 70  75 74 20 61 5f 74 61 62  |to 9 { put a_tab|
00004940  6c 65 20 62 79 74 65 20  69 20 6f 6f 70 73 5f 68  |le byte i oops_h|
00004950  65 61 70 2d 3e 69 3b 20  7d 0a 20 20 20 20 77 3d  |eap->i; }.    w=|
00004960  32 2a 6f 6f 70 73 5f 66  72 6f 6d 20 2d 20 31 3b  |2*oops_from - 1;|
00004970  0a 20 20 20 20 70 75 74  20 61 5f 74 61 62 6c 65  |.    put a_table|
00004980  20 77 6f 72 64 20 77 20  78 31 3b 0a 20 20 20 20  | word w x1;.    |
00004990  69 6e 63 20 77 3b 0a 20  20 20 20 70 75 74 20 61  |inc w;.    put a|
000049a0  5f 74 61 62 6c 65 20 77  6f 72 64 20 77 20 78 31  |_table word w x1|
000049b0  3b 0a 0a 20 20 20 20 72  65 74 75 72 6e 20 6e 77  |;..    return nw|
000049c0  3b 0a 5d 3b 0a 0a 43 6f  6e 73 74 61 6e 74 20 53  |;.];..Constant S|
000049d0  54 55 43 4b 5f 50 45 20  20 20 20 20 31 3b 0a 43  |TUCK_PE     1;.C|
000049e0  6f 6e 73 74 61 6e 74 20  55 50 54 4f 5f 50 45 20  |onstant UPTO_PE |
000049f0  20 20 20 20 20 32 3b 0a  43 6f 6e 73 74 61 6e 74  |     2;.Constant|
00004a00  20 43 41 4e 54 53 45 45  5f 50 45 20 20 20 33 3b  | CANTSEE_PE   3;|
00004a10  0a 43 6f 6e 73 74 61 6e  74 20 54 4f 4f 4c 49 54  |.Constant TOOLIT|
00004a20  5f 50 45 20 20 20 20 34  3b 0a 43 6f 6e 73 74 61  |_PE    4;.Consta|
00004a30  6e 74 20 4e 4f 54 48 45  4c 44 5f 50 45 20 20 20  |nt NOTHELD_PE   |
00004a40  35 3b 0a 43 6f 6e 73 74  61 6e 74 20 4d 55 4c 54  |5;.Constant MULT|
00004a50  49 5f 50 45 20 20 20 20  20 36 3b 0a 43 6f 6e 73  |I_PE     6;.Cons|
00004a60  74 61 6e 74 20 4d 4d 55  4c 54 49 5f 50 45 20 20  |tant MMULTI_PE  |
00004a70  20 20 37 3b 0a 43 6f 6e  73 74 61 6e 74 20 56 41  |  7;.Constant VA|
00004a80  47 55 45 5f 50 45 20 20  20 20 20 38 3b 0a 43 6f  |GUE_PE     8;.Co|
00004a90  6e 73 74 61 6e 74 20 45  58 43 45 50 54 5f 50 45  |nstant EXCEPT_PE|
00004aa0  20 20 20 20 39 3b 0a 43  6f 6e 73 74 61 6e 74 20  |    9;.Constant |
00004ab0  41 4e 49 4d 41 5f 50 45  20 20 20 20 20 31 30 3b  |ANIMA_PE     10;|
00004ac0  0a 43 6f 6e 73 74 61 6e  74 20 56 45 52 42 5f 50  |.Constant VERB_P|
00004ad0  45 20 20 20 20 20 20 31  31 3b 0a 43 6f 6e 73 74  |E      11;.Const|
00004ae0  61 6e 74 20 53 43 45 4e  45 52 59 5f 50 45 20 20  |ant SCENERY_PE  |
00004af0  20 31 32 3b 0a 43 6f 6e  73 74 61 6e 74 20 49 54  | 12;.Constant IT|
00004b00  47 4f 4e 45 5f 50 45 20  20 20 20 31 33 3b 0a 43  |GONE_PE    13;.C|
00004b10  6f 6e 73 74 61 6e 74 20  4a 55 4e 4b 41 46 54 45  |onstant JUNKAFTE|
00004b20  52 5f 50 45 20 31 34 3b  0a 43 6f 6e 73 74 61 6e  |R_PE 14;.Constan|
00004b30  74 20 54 4f 4f 46 45 57  5f 50 45 20 20 20 20 31  |t TOOFEW_PE    1|
00004b40  35 3b 0a 43 6f 6e 73 74  61 6e 74 20 4e 4f 54 48  |5;.Constant NOTH|
00004b50  49 4e 47 5f 50 45 20 20  20 31 36 3b 0a 43 6f 6e  |ING_PE   16;.Con|
00004b60  73 74 61 6e 74 20 4e 55  4d 42 45 52 5f 50 45 20  |stant NUMBER_PE |
00004b70  20 20 20 31 37 3b 0a 43  6f 6e 73 74 61 6e 74 20  |   17;.Constant |
00004b80  41 53 4b 53 43 4f 50 45  5f 50 45 20 20 31 38 3b  |ASKSCOPE_PE  18;|
00004b90  0a 0a 21 20 2d 2d 2d 2d  2d 2d 2d 2d 2d 2d 2d 2d  |..! ------------|
00004ba0  2d 2d 2d 2d 2d 2d 2d 2d  2d 2d 2d 2d 2d 2d 2d 2d  |----------------|
*
00004be0  0a 21 20 20 54 68 65 20  50 61 72 73 65 72 20 72  |.!  The Parser r|
00004bf0  6f 75 74 69 6e 65 20 69  73 20 74 68 65 20 68 65  |outine is the he|
00004c00  61 72 74 20 6f 66 20 74  68 65 20 70 61 72 73 65  |art of the parse|
00004c10  72 2e 0a 21 0a 21 20 20  49 74 20 72 65 74 75 72  |r..!.!  It retur|
00004c20  6e 73 20 6f 6e 6c 79 20  77 68 65 6e 20 61 20 73  |ns only when a s|
00004c30  65 6e 73 69 62 6c 65 20  72 65 71 75 65 73 74 20  |ensible request |
00004c40  68 61 73 20 62 65 65 6e  20 6d 61 64 65 2c 20 61  |has been made, a|
00004c50  6e 64 20 70 75 74 73 20  69 6e 74 6f 20 74 68 65  |nd puts into the|
00004c60  0a 21 20 20 22 72 65 73  75 6c 74 73 22 20 62 75  |.!  "results" bu|
00004c70  66 66 65 72 3a 0a 21 0a  21 20 20 57 6f 72 64 20  |ffer:.!.!  Word |
00004c80  30 20 3d 20 54 68 65 20  61 63 74 69 6f 6e 20 6e  |0 = The action n|
00004c90  75 6d 62 65 72 0a 21 20  20 57 6f 72 64 20 31 20  |umber.!  Word 1 |
00004ca0  3d 20 4e 75 6d 62 65 72  20 6f 66 20 70 61 72 61  |= Number of para|
00004cb0  6d 65 74 65 72 73 0a 21  20 20 57 6f 72 64 73 20  |meters.!  Words |
00004cc0  32 2c 20 33 2c 20 2e 2e  2e 20 3d 20 54 68 65 20  |2, 3, ... = The |
00004cd0  70 61 72 61 6d 65 74 65  72 73 20 28 6f 62 6a 65  |parameters (obje|
00004ce0  63 74 20 6e 75 6d 62 65  72 73 29 2c 20 62 75 74  |ct numbers), but|
00004cf0  0a 21 20 20 20 20 20 20  20 20 20 20 20 20 20 20  |.!              |
00004d00  20 20 20 20 20 20 30 30  20 6d 65 61 6e 73 20 22  |      00 means "|
00004d10  6d 75 6c 74 69 70 6c 65  20 6f 62 6a 65 63 74 20  |multiple object |
00004d20  6c 69 73 74 20 67 6f 65  73 20 68 65 72 65 22 0a  |list goes here".|
00004d30  21 20 20 20 20 20 20 20  20 20 20 20 20 20 20 20  |!               |
00004d40  20 20 20 20 20 30 31 20  6d 65 61 6e 73 20 22 73  |     01 means "s|
00004d50  70 65 63 69 61 6c 20 77  6f 72 64 20 67 6f 65 73  |pecial word goes|
00004d60  20 68 65 72 65 22 0a 21  0a 21 20 20 28 53 6f 6d  | here".!.!  (Som|
00004d70  65 20 6f 66 20 74 68 65  20 67 6c 6f 62 61 6c 20  |e of the global |
00004d80  76 61 72 69 61 62 6c 65  73 20 61 62 6f 76 65 20  |variables above |
00004d90  61 72 65 20 72 65 61 6c  6c 79 20 6c 6f 63 61 6c  |are really local|
00004da0  20 76 61 72 69 61 62 6c  65 73 20 66 6f 72 20 74  | variables for t|
00004db0  68 69 73 0a 21 20 20 72  6f 75 74 69 6e 65 2c 20  |his.!  routine, |
00004dc0  62 65 63 61 75 73 65 20  74 68 65 20 5a 2d 6d 61  |because the Z-ma|
00004dd0  63 68 69 6e 65 20 6f 6e  6c 79 20 61 6c 6c 6f 77  |chine only allow|
00004de0  73 20 75 70 20 74 6f 20  31 35 20 6c 6f 63 61 6c  |s up to 15 local|
00004df0  20 76 61 72 69 61 62 6c  65 73 20 70 65 72 0a 21  | variables per.!|
00004e00  20 20 72 6f 75 74 69 6e  65 2c 20 61 6e 64 20 50  |  routine, and P|
00004e10  61 72 73 65 72 20 72 75  6e 73 20 6f 75 74 2e 29  |arser runs out.)|
00004e20  0a 21 0a 21 20 20 54 6f  20 73 69 6d 70 6c 69 66  |.!.!  To simplif|
00004e30  79 20 74 68 65 20 70 69  63 74 75 72 65 20 61 20  |y the picture a |
00004e40  6c 69 74 74 6c 65 2c 20  61 20 72 6f 75 67 68 20  |little, a rough |
00004e50  6d 61 70 20 6f 66 20 74  68 69 73 20 72 6f 75 74  |map of this rout|
00004e60  69 6e 65 20 69 73 3a 0a  21 0a 21 20 20 28 41 29  |ine is:.!.!  (A)|
00004e70  20 20 20 20 47 65 74 20  74 68 65 20 69 6e 70 75  |    Get the inpu|
00004e80  74 2c 20 64 6f 20 22 6f  6f 70 73 22 20 61 6e 64  |t, do "oops" and|
00004e90  20 22 61 67 61 69 6e 22  0a 21 20 20 28 42 29 20  | "again".!  (B) |
00004ea0  20 20 20 49 73 20 69 74  20 61 20 64 69 72 65 63  |   Is it a direc|
00004eb0  74 69 6f 6e 2c 20 61 6e  64 20 73 6f 20 61 6e 20  |tion, and so an |
00004ec0  69 6d 70 6c 69 63 69 74  20 22 67 6f 22 3f 20 20  |implicit "go"?  |
00004ed0  49 66 20 73 6f 20 67 6f  20 74 6f 20 28 4b 29 0a  |If so go to (K).|
00004ee0  21 20 20 28 43 29 20 20  20 20 49 73 20 61 6e 79  |!  (C)    Is any|
00004ef0  6f 6e 65 20 62 65 69 6e  67 20 61 64 64 72 65 73  |one being addres|
00004f00  73 65 64 3f 0a 21 20 20  28 44 29 20 20 20 20 47  |sed?.!  (D)    G|
00004f10  65 74 20 74 68 65 20 76  65 72 62 3a 20 74 72 79  |et the verb: try|
00004f20  20 61 6c 6c 20 74 68 65  20 73 79 6e 74 61 78 20  | all the syntax |
00004f30  6c 69 6e 65 73 20 66 6f  72 20 74 68 61 74 20 76  |lines for that v|
00004f40  65 72 62 0a 21 20 20 28  45 29 20 20 20 20 20 20  |erb.!  (E)      |
00004f50  20 20 47 6f 20 74 68 72  6f 75 67 68 20 65 61 63  |  Go through eac|
00004f60  68 20 74 6f 6b 65 6e 20  69 6e 20 74 68 65 20 73  |h token in the s|
00004f70  79 6e 74 61 78 20 6c 69  6e 65 0a 21 20 20 28 46  |yntax line.!  (F|
00004f80  29 20 20 20 20 20 20 20  20 20 20 20 43 68 65 63  |)           Chec|
00004f90  6b 20 28 6f 72 20 69 6e  66 65 72 29 20 61 6e 20  |k (or infer) an |
00004fa0  61 64 6a 65 63 74 69 76  65 0a 21 20 20 28 47 29  |adjective.!  (G)|
00004fb0  20 20 20 20 20 20 20 20  20 20 20 20 43 68 65 63  |            Chec|
00004fc0  6b 20 74 6f 20 73 65 65  20 69 66 20 74 68 65 20  |k to see if the |
00004fd0  73 79 6e 74 61 78 20 69  73 20 66 69 6e 69 73 68  |syntax is finish|
00004fe0  65 64 2c 20 61 6e 64 20  69 66 20 73 6f 20 72 65  |ed, and if so re|
00004ff0  74 75 72 6e 0a 21 20 20  28 48 29 20 20 20 20 43  |turn.!  (H)    C|
00005000  68 65 61 70 6c 79 20 70  61 72 73 65 20 6f 74 68  |heaply parse oth|
00005010  65 72 77 69 73 65 20 75  6e 72 65 63 6f 67 6e 69  |erwise unrecogni|
00005020  73 65 64 20 63 6f 6e 76  65 72 73 61 74 69 6f 6e  |sed conversation|
00005030  20 61 6e 64 20 72 65 74  75 72 6e 0a 21 20 20 28  | and return.!  (|
00005040  49 29 20 20 20 20 50 72  69 6e 74 20 62 65 73 74  |I)    Print best|
00005050  20 70 6f 73 73 69 62 6c  65 20 65 72 72 6f 72 20  | possible error |
00005060  6d 65 73 73 61 67 65 0a  21 20 20 28 4a 29 20 20  |message.!  (J)  |
00005070  20 20 52 65 74 72 79 20  74 68 65 20 77 68 6f 6c  |  Retry the whol|
00005080  65 20 6c 6f 74 0a 21 20  20 28 4b 29 20 20 20 20  |e lot.!  (K)    |
00005090  4c 61 73 74 20 74 68 69  6e 67 3a 20 63 68 65 63  |Last thing: chec|
000050a0  6b 20 66 6f 72 20 22 74  68 65 6e 22 20 61 6e 64  |k for "then" and|
000050b0  20 66 75 72 74 68 65 72  20 69 6e 73 74 72 75 63  | further instruc|
000050c0  74 69 6f 6e 73 28 73 29  2c 20 72 65 74 75 72 6e  |tions(s), return|
000050d0  2e 0a 21 0a 21 20 20 54  68 65 20 73 74 72 61 74  |..!.!  The strat|
000050e0  65 67 69 63 20 70 6f 69  6e 74 73 20 28 41 29 20  |egic points (A) |
000050f0  74 6f 20 28 4b 29 20 61  72 65 20 6d 61 72 6b 65  |to (K) are marke|
00005100  64 20 69 6e 20 74 68 65  20 63 6f 6d 6d 65 6e 74  |d in the comment|
00005110  61 72 79 2e 0a 21 0a 21  20 20 4e 6f 74 65 20 74  |ary..!.!  Note t|
00005120  68 61 74 20 74 68 65 72  65 20 61 72 65 20 74 68  |hat there are th|
00005130  72 65 65 20 64 69 66 66  65 72 65 6e 74 20 70 6c  |ree different pl|
00005140  61 63 65 73 20 77 68 65  72 65 20 61 20 72 65 74  |aces where a ret|
00005150  75 72 6e 20 63 61 6e 20  68 61 70 70 65 6e 2e 0a  |urn can happen..|
00005160  21 0a 21 20 2d 2d 2d 2d  2d 2d 2d 2d 2d 2d 2d 2d  |!.! ------------|
00005170  2d 2d 2d 2d 2d 2d 2d 2d  2d 2d 2d 2d 2d 2d 2d 2d  |----------------|
*
000051b0  0a 0a 5b 20 50 61 72 73  65 72 20 20 72 65 73 75  |..[ Parser  resu|
000051c0  6c 74 73 20 20 20 73 79  6e 74 61 78 20 6c 69 6e  |lts   syntax lin|
000051d0  65 20 6e 75 6d 5f 6c 69  6e 65 73 20 6c 69 6e 65  |e num_lines line|
000051e0  5f 61 64 64 72 65 73 73  20 69 20 6a 0a 20 20 20  |_address i j.   |
000051f0  20 20 20 20 20 20 20 20  20 20 20 20 20 20 20 20  |                |
00005200  20 74 6f 6b 65 6e 20 6c  20 6d 3b 0a 0a 21 20 20  | token l m;..!  |
00005210  2a 2a 2a 2a 20 28 41 29  20 2a 2a 2a 2a 0a 0a 21  |**** (A) ****..!|
00005220  20 20 46 69 72 73 74 6c  79 2c 20 69 6e 20 22 6e  |  Firstly, in "n|
00005230  6f 74 20 68 65 6c 64 22  20 6d 6f 64 65 2c 20 77  |ot held" mode, w|
00005240  65 20 73 74 69 6c 6c 20  68 61 76 65 20 61 20 63  |e still have a c|
00005250  6f 6d 6d 61 6e 64 20 6c  65 66 74 20 6f 76 65 72  |ommand left over|
00005260  20 66 72 6f 6d 20 6c 61  73 74 0a 21 20 20 74 69  | from last.!  ti|
00005270  6d 65 20 28 65 67 2c 20  74 68 65 20 75 73 65 72  |me (eg, the user|
00005280  20 74 79 70 65 64 20 22  65 61 74 20 62 69 73 63  | typed "eat bisc|
00005290  75 69 74 22 2c 20 77 68  69 63 68 20 77 61 73 20  |uit", which was |
000052a0  70 61 72 73 65 64 20 61  73 20 22 74 61 6b 65 20  |parsed as "take |
000052b0  62 69 73 63 75 69 74 22  0a 21 20 20 6c 61 73 74  |biscuit".!  last|
000052c0  20 74 69 6d 65 2c 20 77  69 74 68 20 22 65 61 74  | time, with "eat|
000052d0  20 62 69 73 63 75 69 74  22 20 74 75 63 6b 65 64  | biscuit" tucked|
000052e0  20 61 77 61 79 20 75 6e  74 69 6c 20 6e 6f 77 29  | away until now)|
000052f0  2e 20 20 53 6f 20 77 65  20 72 65 74 75 72 6e 20  |.  So we return |
00005300  74 68 61 74 2e 0a 0a 20  20 20 20 69 66 20 28 6e  |that...    if (n|
00005310  6f 74 68 65 6c 64 5f 6d  6f 64 65 3d 3d 31 29 0a  |otheld_mode==1).|
00005320  20 20 20 20 7b 20 20 20  66 6f 72 20 28 69 3d 30  |    {   for (i=0|
00005330  3a 69 3c 38 3a 69 2b 2b  29 20 72 65 73 75 6c 74  |:i<8:i++) result|
00005340  73 2d 2d 3e 69 3d 6b 65  70 74 5f 72 65 73 75 6c  |s-->i=kept_resul|
00005350  74 73 2d 2d 3e 69 3b 0a  20 20 20 20 20 20 20 20  |ts-->i;.        |
00005360  6e 6f 74 68 65 6c 64 5f  6d 6f 64 65 3d 30 3b 20  |notheld_mode=0; |
00005370  72 74 72 75 65 3b 0a 20  20 20 20 7d 0a 0a 20 20  |rtrue;.    }..  |
00005380  20 20 69 66 20 28 68 65  6c 64 5f 62 61 63 6b 5f  |  if (held_back_|
00005390  6d 6f 64 65 3d 3d 31 29  0a 20 20 20 20 7b 20 20  |mode==1).    {  |
000053a0  20 68 65 6c 64 5f 62 61  63 6b 5f 6d 6f 64 65 3d  | held_back_mode=|
000053b0  30 3b 0a 20 20 20 20 20  20 20 20 66 6f 72 20 28  |0;.        for (|
000053c0  69 3d 30 3a 69 3c 36 34  3a 69 2b 2b 29 20 70 61  |i=0:i<64:i++) pa|
000053d0  72 73 65 2d 3e 69 3d 70  61 72 73 65 32 2d 3e 69  |rse->i=parse2->i|
000053e0  3b 0a 20 20 20 20 20 20  20 20 6e 65 77 5f 6c 69  |;.        new_li|
000053f0  6e 65 3b 0a 20 20 20 20  20 20 20 20 6a 75 6d 70  |ne;.        jump|
00005400  20 52 65 50 61 72 73 65  3b 0a 20 20 20 20 7d 0a  | ReParse;.    }.|
00005410  0a 20 20 2e 52 65 54 79  70 65 3b 0a 0a 20 20 20  |.  .ReType;..   |
00005420  20 4b 65 79 62 6f 61 72  64 28 62 75 66 66 65 72  | Keyboard(buffer|
00005430  2c 70 61 72 73 65 29 3b  0a 0a 20 20 2e 52 65 50  |,parse);..  .ReP|
00005440  61 72 73 65 3b 0a 0a 21  20 20 49 6e 69 74 69 61  |arse;..!  Initia|
00005450  6c 6c 79 20 61 73 73 75  6d 65 20 74 68 65 20 63  |lly assume the c|
00005460  6f 6d 6d 61 6e 64 20 69  73 20 61 69 6d 65 64 20  |ommand is aimed |
00005470  61 74 20 74 68 65 20 70  6c 61 79 65 72 2c 20 61  |at the player, a|
00005480  6e 64 20 74 68 65 20 76  65 72 62 0a 21 20 20 69  |nd the verb.!  i|
00005490  73 20 74 68 65 20 66 69  72 73 74 20 77 6f 72 64  |s the first word|
000054a0  0a 0a 20 20 20 20 6e 75  6d 5f 77 6f 72 64 73 3d  |..    num_words=|
000054b0  70 61 72 73 65 2d 3e 31  3b 0a 20 20 20 20 76 65  |parse->1;.    ve|
000054c0  72 62 5f 77 6f 72 64 6e  75 6d 3d 31 3b 0a 20 20  |rb_wordnum=1;.  |
000054d0  20 20 61 63 74 6f 72 3d  70 6c 61 79 65 72 3b 0a  |  actor=player;.|
000054e0  20 20 20 20 74 6f 6b 65  6e 5f 77 61 73 20 3d 20  |    token_was = |
000054f0  30 3b 20 21 20 49 6e 20  63 61 73 65 20 77 65 27  |0; ! In case we'|
00005500  72 65 20 73 74 69 6c 6c  20 69 6e 20 22 75 73 65  |re still in "use|
00005510  72 2d 66 69 6c 74 65 72  22 20 6d 6f 64 65 20 66  |r-filter" mode f|
00005520  72 6f 6d 20 6c 61 73 74  20 72 6f 75 6e 64 0a 20  |rom last round. |
00005530  20 20 20 73 63 6f 70 65  5f 74 6f 6b 65 6e 20 3d  |   scope_token =|
00005540  20 30 3b 0a 0a 21 20 20  42 65 67 69 6e 20 66 72  | 0;..!  Begin fr|
00005550  6f 6d 20 77 68 61 74 20  77 65 20 63 75 72 72 65  |om what we curre|
00005560  6e 74 6c 79 20 74 68 69  6e 6b 20 69 73 20 74 68  |ntly think is th|
00005570  65 20 76 65 72 62 20 77  6f 72 64 0a 0a 20 20 2e  |e verb word..  .|
00005580  42 65 67 69 6e 43 6f 6d  6d 61 6e 64 3b 0a 20 20  |BeginCommand;.  |
00005590  20 20 77 6e 3d 76 65 72  62 5f 77 6f 72 64 6e 75  |  wn=verb_wordnu|
000055a0  6d 3b 0a 20 20 20 20 76  65 72 62 5f 77 6f 72 64  |m;.    verb_word|
000055b0  20 3d 20 4e 65 78 74 57  6f 72 64 28 29 3b 0a 0a  | = NextWord();..|
000055c0  21 20 20 4e 6f 77 20 74  72 79 20 66 6f 72 20 22  |!  Now try for "|
000055d0  61 67 61 69 6e 22 20 6f  72 20 22 67 22 2c 20 77  |again" or "g", w|
000055e0  68 69 63 68 20 61 72 65  20 73 70 65 63 69 61 6c  |hich are special|
000055f0  20 63 61 73 65 73 3a 0a  21 20 20 64 6f 6e 27 74  | cases:.!  don't|
00005600  20 61 6c 6c 6f 77 20 22  61 67 61 69 6e 22 20 69  | allow "again" i|
00005610  66 20 6e 6f 74 68 69 6e  67 20 68 61 73 20 70 72  |f nothing has pr|
00005620  65 76 69 6f 75 73 6c 79  20 62 65 65 6e 20 74 79  |eviously been ty|
00005630  70 65 64 3b 0a 21 20 20  73 69 6d 70 6c 79 20 63  |ped;.!  simply c|
00005640  6f 70 79 20 74 68 65 20  70 72 65 76 69 6f 75 73  |opy the previous|
00005650  20 70 61 72 73 65 20 74  61 62 6c 65 20 61 6e 64  | parse table and|
00005660  20 52 65 50 61 72 73 65  20 77 69 74 68 20 74 68  | ReParse with th|
00005670  61 74 0a 0a 20 20 20 20  69 66 20 28 76 65 72 62  |at..    if (verb|
00005680  5f 77 6f 72 64 3d 3d 23  6e 24 67 29 20 76 65 72  |_word==#n$g) ver|
00005690  62 5f 77 6f 72 64 3d 27  61 67 61 69 6e 27 3b 0a  |b_word='again';.|
000056a0  20 20 20 20 69 66 20 28  76 65 72 62 5f 77 6f 72  |    if (verb_wor|
000056b0  64 3d 3d 27 61 67 61 69  6e 27 29 0a 20 20 20 20  |d=='again').    |
000056c0  7b 20 20 20 69 66 20 28  70 61 72 73 65 33 2d 3e  |{   if (parse3->|
000056d0  31 3d 3d 30 29 0a 20 20  20 20 20 20 20 20 7b 20  |1==0).        { |
000056e0  20 20 70 72 69 6e 74 20  22 59 6f 75 20 63 61 6e  |  print "You can|
000056f0  20 68 61 72 64 6c 79 20  72 65 70 65 61 74 20 74  | hardly repeat t|
00005700  68 61 74 2e 5e 22 3b 20  6a 75 6d 70 20 52 65 54  |hat.^"; jump ReT|
00005710  79 70 65 3b 20 7d 0a 20  20 20 20 20 20 20 20 66  |ype; }.        f|
00005720  6f 72 20 28 69 3d 30 3a  69 3c 36 34 3a 69 2b 2b  |or (i=0:i<64:i++|
00005730  29 20 70 61 72 73 65 2d  3e 69 3d 70 61 72 73 65  |) parse->i=parse|
00005740  33 2d 3e 69 3b 0a 20 20  20 20 20 20 20 20 6a 75  |3->i;.        ju|
00005750  6d 70 20 52 65 50 61 72  73 65 3b 0a 20 20 20 20  |mp ReParse;.    |
00005760  7d 0a 0a 21 20 20 53 61  76 65 20 74 68 65 20 70  |}..!  Save the p|
00005770  72 65 73 65 6e 74 20 70  61 72 73 65 20 74 61 62  |resent parse tab|
00005780  6c 65 20 69 6e 20 63 61  73 65 20 6f 66 20 61 6e  |le in case of an|
00005790  20 22 61 67 61 69 6e 22  20 6e 65 78 74 20 74 69  | "again" next ti|
000057a0  6d 65 0a 0a 20 20 20 20  69 66 20 28 76 65 72 62  |me..    if (verb|
000057b0  5f 77 6f 72 64 7e 3d 27  61 67 61 69 6e 27 29 0a  |_word~='again').|
000057c0  20 20 20 20 20 20 20 20  66 6f 72 20 28 69 3d 30  |        for (i=0|
000057d0  3a 69 3c 36 34 3a 69 2b  2b 29 0a 20 20 20 20 20  |:i<64:i++).     |
000057e0  20 20 20 20 20 20 20 70  61 72 73 65 33 2d 3e 69  |       parse3->i|
000057f0  3d 70 61 72 73 65 2d 3e  69 3b 0a 0a 21 20 20 49  |=parse->i;..!  I|
00005800  66 20 74 68 65 20 66 69  72 73 74 20 77 6f 72 64  |f the first word|
00005810  20 69 73 20 6e 6f 74 20  72 65 63 6f 67 6e 69 73  | is not recognis|
00005820  65 64 2c 20 67 69 76 65  20 61 20 75 73 65 72 2d  |ed, give a user-|
00005830  73 75 70 70 6c 69 65 64  20 72 6f 75 74 69 6e 65  |supplied routine|
00005840  0a 21 20 20 74 68 65 20  63 68 61 6e 63 65 20 74  |.!  the chance t|
00005850  6f 20 77 6f 72 6b 20 6f  75 74 20 77 68 61 74 20  |o work out what |
00005860  69 74 20 69 73 3a 0a 0a  20 20 20 20 69 66 20 28  |it is:..    if (|
00005870  76 65 72 62 5f 77 6f 72  64 3d 3d 30 20 26 26 20  |verb_word==0 && |
00005880  61 63 74 6f 72 3d 3d 70  6c 61 79 65 72 29 20 76  |actor==player) v|
00005890  65 72 62 5f 77 6f 72 64  3d 55 6e 6b 6e 6f 77 6e  |erb_word=Unknown|
000058a0  56 65 72 62 28 76 65 72  62 5f 77 6f 72 64 29 3b  |Verb(verb_word);|
000058b0  0a 0a 21 20 20 42 75 74  20 69 66 20 69 74 20 73  |..!  But if it s|
000058c0  74 69 6c 6c 20 69 73 6e  27 74 2c 20 74 68 65 6e  |till isn't, then|
000058d0  20 69 74 20 63 61 6e 27  74 20 62 65 20 65 69 74  | it can't be eit|
000058e0  68 65 72 20 74 68 65 20  6e 61 6d 65 20 6f 66 0a  |her the name of.|
000058f0  21 20 20 61 6e 20 61 6e  69 6d 61 74 65 20 63 72  |!  an animate cr|
00005900  65 61 74 75 72 65 20 6f  72 20 61 20 76 65 72 62  |eature or a verb|
00005910  2c 20 73 6f 20 67 69 76  65 20 61 6e 20 65 72 72  |, so give an err|
00005920  6f 72 20 61 74 20 6f 6e  63 65 2e 0a 0a 20 20 20  |or at once...   |
00005930  20 69 66 20 28 76 65 72  62 5f 77 6f 72 64 3d 3d  | if (verb_word==|
00005940  30 29 0a 20 20 20 20 7b  20 20 20 62 65 73 74 5f  |0).    {   best_|
00005950  65 74 79 70 65 3d 56 45  52 42 5f 50 45 3b 0a 20  |etype=VERB_PE;. |
00005960  20 20 20 20 20 20 20 6a  75 6d 70 20 47 69 76 65  |       jump Give|
00005970  45 72 72 6f 72 3b 0a 20  20 20 20 7d 0a 0a 21 20  |Error;.    }..! |
00005980  20 2a 2a 2a 2a 20 28 42  29 20 2a 2a 2a 2a 0a 0a  | **** (B) ****..|
00005990  21 20 20 49 66 20 74 68  65 20 66 69 72 73 74 20  |!  If the first |
000059a0  77 6f 72 64 20 69 73 20  6e 6f 74 20 6c 69 73 74  |word is not list|
000059b0  65 64 20 61 73 20 61 20  76 65 72 62 2c 20 69 74  |ed as a verb, it|
000059c0  20 6d 75 73 74 20 62 65  20 61 20 64 69 72 65 63  | must be a direc|
000059d0  74 69 6f 6e 0a 21 20 20  6f 72 20 74 68 65 20 6e  |tion.!  or the n|
000059e0  61 6d 65 20 6f 66 20 73  6f 6d 65 6f 6e 65 20 74  |ame of someone t|
000059f0  6f 20 74 61 6c 6b 20 74  6f 0a 21 20 20 28 4e 42  |o talk to.!  (NB|
00005a00  3a 20 62 65 74 74 65 72  20 61 76 6f 69 64 20 68  |: better avoid h|
00005a10  61 76 69 6e 67 20 61 20  4d 72 20 54 61 6b 65 20  |aving a Mr Take |
00005a20  6f 72 20 4d 72 73 20 49  6e 76 65 6e 74 6f 72 79  |or Mrs Inventory|
00005a30  20 61 72 6f 75 6e 64 2e  2e 2e 29 0a 0a 20 20 20  | around...)..   |
00005a40  20 69 66 20 28 28 28 76  65 72 62 5f 77 6f 72 64  | if (((verb_word|
00005a50  2d 3e 23 64 69 63 74 5f  70 61 72 31 29 20 26 20  |->#dict_par1) & |
00005a60  31 29 20 3d 3d 20 30 29  0a 20 20 20 20 7b 20 20  |1) == 0).    {  |
00005a70  20 0a 0a 21 20 20 53 6f  20 69 73 20 74 68 65 20  | ..!  So is the |
00005a80  66 69 72 73 74 20 77 6f  72 64 20 61 6e 20 6f 62  |first word an ob|
00005a90  6a 65 63 74 20 63 6f 6e  74 61 69 6e 65 64 20 69  |ject contained i|
00005aa0  6e 20 74 68 65 20 73 70  65 63 69 61 6c 20 6f 62  |n the special ob|
00005ab0  6a 65 63 74 20 22 63 6f  6d 70 61 73 73 22 0a 21  |ject "compass".!|
00005ac0  20 20 28 69 2e 65 2e 2c  20 61 20 64 69 72 65 63  |  (i.e., a direc|
00005ad0  74 69 6f 6e 29 3f 20 20  54 68 69 73 20 6e 65 65  |tion)?  This nee|
00005ae0  64 73 20 75 73 65 20 6f  66 20 4e 6f 75 6e 44 6f  |ds use of NounDo|
00005af0  6d 61 69 6e 2c 20 61 20  72 6f 75 74 69 6e 65 20  |main, a routine |
00005b00  77 68 69 63 68 0a 21 20  20 64 6f 65 73 20 74 68  |which.!  does th|
00005b10  65 20 6f 62 6a 65 63 74  20 6d 61 74 63 68 69 6e  |e object matchin|
00005b20  67 2c 20 72 65 74 75 72  6e 69 6e 67 20 74 68 65  |g, returning the|
00005b30  20 6f 62 6a 65 63 74 20  6e 75 6d 62 65 72 2c 20  | object number, |
00005b40  6f 72 20 30 20 69 66 20  6e 6f 6e 65 20 66 6f 75  |or 0 if none fou|
00005b50  6e 64 2c 0a 21 20 20 6f  72 20 31 30 30 30 20 69  |nd,.!  or 1000 i|
00005b60  66 20 69 74 20 68 61 73  20 72 65 73 74 72 75 63  |f it has restruc|
00005b70  74 75 72 65 64 20 74 68  65 20 70 61 72 73 65 20  |tured the parse |
00005b80  74 61 62 6c 65 20 73 6f  20 74 68 61 74 20 74 68  |table so that th|
00005b90  65 20 77 68 6f 6c 65 20  70 61 72 73 65 0a 21 20  |e whole parse.! |
00005ba0  20 6d 75 73 74 20 62 65  20 62 65 67 75 6e 20 61  | must be begun a|
00005bb0  67 61 69 6e 2e 2e 2e 0a  0a 20 20 20 20 20 20 20  |gain.....       |
00005bc0  20 77 6e 3d 76 65 72 62  5f 77 6f 72 64 6e 75 6d  | wn=verb_wordnum|
00005bd0  3b 0a 20 20 20 20 20 20  20 20 6c 3d 4e 6f 75 6e  |;.        l=Noun|
00005be0  44 6f 6d 61 69 6e 28 63  6f 6d 70 61 73 73 2c 30  |Domain(compass,0|
00005bf0  2c 30 29 3b 20 69 66 20  28 6c 3d 3d 31 30 30 30  |,0); if (l==1000|
00005c00  29 20 6a 75 6d 70 20 52  65 50 61 72 73 65 3b 0a  |) jump ReParse;.|
00005c10  0a 21 20 20 49 66 20 69  74 20 69 73 20 61 20 64  |.!  If it is a d|
00005c20  69 72 65 63 74 69 6f 6e  2c 20 73 65 6e 64 20 62  |irection, send b|
00005c30  61 63 6b 20 74 68 65 20  72 65 73 75 6c 74 73 3a  |ack the results:|
00005c40  0a 21 20 20 61 63 74 69  6f 6e 3d 47 6f 53 75 62  |.!  action=GoSub|
00005c50  2c 20 6e 6f 20 6f 66 20  61 72 67 75 6d 65 6e 74  |, no of argument|
00005c60  73 3d 31 2c 20 61 72 67  75 6d 65 6e 74 20 31 3d  |s=1, argument 1=|
00005c70  74 68 65 20 64 69 72 65  63 74 69 6f 6e 2e 0a 0a  |the direction...|
00005c80  20 20 20 20 20 20 20 20  69 66 20 28 6c 7e 3d 30  |        if (l~=0|
00005c90  29 0a 20 20 20 20 20 20  20 20 7b 20 20 20 72 65  |).        {   re|
00005ca0  73 75 6c 74 73 2d 2d 3e  30 20 3d 20 23 23 47 6f  |sults-->0 = ##Go|
00005cb0  3b 0a 20 20 20 20 20 20  20 20 20 20 20 20 72 65  |;.            re|
00005cc0  73 75 6c 74 73 2d 2d 3e  31 20 3d 20 31 3b 0a 20  |sults-->1 = 1;. |
00005cd0  20 20 20 20 20 20 20 20  20 20 20 72 65 73 75 6c  |           resul|
00005ce0  74 73 2d 2d 3e 32 20 3d  20 6c 3b 0a 20 20 20 20  |ts-->2 = l;.    |
00005cf0  20 20 20 20 20 20 20 20  6a 75 6d 70 20 4c 6f 6f  |        jump Loo|
00005d00  6b 46 6f 72 4d 6f 72 65  3b 0a 20 20 20 20 20 20  |kForMore;.      |
00005d10  20 20 7d 0a 0a 21 20 20  2a 2a 2a 2a 20 28 43 29  |  }..!  **** (C)|
00005d20  20 2a 2a 2a 2a 0a 0a 21  20 20 4f 6e 6c 79 20 63  | ****..!  Only c|
00005d30  68 65 63 6b 20 66 6f 72  20 61 20 63 6f 6d 6d 61  |heck for a comma|
00005d40  20 28 61 20 22 73 6f 6d  65 6f 6e 65 2c 20 64 6f  | (a "someone, do|
00005d50  20 73 6f 6d 65 74 68 69  6e 67 22 20 63 6f 6d 6d  | something" comm|
00005d60  61 6e 64 29 20 69 66 20  77 65 20 61 72 65 0a 21  |and) if we are.!|
00005d70  20 20 6e 6f 74 20 61 6c  72 65 61 64 79 20 69 6e  |  not already in|
00005d80  20 74 68 65 20 6d 69 64  64 6c 65 20 6f 66 20 6f  | the middle of o|
00005d90  6e 65 2e 20 20 28 54 68  69 73 20 73 69 6d 70 6c  |ne.  (This simpl|
00005da0  69 66 69 63 61 74 69 6f  6e 20 73 74 6f 70 73 20  |ification stops |
00005db0  75 73 20 66 72 6f 6d 0a  21 20 20 77 6f 72 72 79  |us from.!  worry|
00005dc0  69 6e 67 20 61 62 6f 75  74 20 22 72 6f 62 6f 74  |ing about "robot|
00005dd0  2c 20 77 69 7a 61 72 64  2c 20 79 6f 75 20 61 72  |, wizard, you ar|
00005de0  65 20 61 6e 20 69 64 69  6f 74 22 2c 20 74 65 6c  |e an idiot", tel|
00005df0  6c 69 6e 67 20 74 68 65  20 72 6f 62 6f 74 20 74  |ling the robot t|
00005e00  6f 0a 21 20 20 74 65 6c  6c 20 74 68 65 20 77 69  |o.!  tell the wi|
00005e10  7a 61 72 64 20 74 68 61  74 20 73 68 65 20 69 73  |zard that she is|
00005e20  20 61 6e 20 69 64 69 6f  74 2e 29 0a 0a 20 20 20  | an idiot.)..   |
00005e30  20 20 20 20 20 69 66 20  28 61 63 74 6f 72 3d 3d  |     if (actor==|
00005e40  70 6c 61 79 65 72 29 0a  20 20 20 20 20 20 20 20  |player).        |
00005e50  20 20 20 20 66 6f 72 20  28 6a 3d 32 3a 6a 3c 3d  |    for (j=2:j<=|
00005e60  6e 75 6d 5f 77 6f 72 64  73 3a 6a 2b 2b 29 0a 20  |num_words:j++). |
00005e70  20 20 20 20 20 20 20 20  20 20 20 7b 20 20 20 69  |           {   i|
00005e80  3d 4e 65 78 74 57 6f 72  64 28 29 3b 20 69 66 20  |=NextWord(); if |
00005e90  28 69 3d 3d 63 6f 6d 6d  61 5f 77 6f 72 64 29 20  |(i==comma_word) |
00005ea0  6a 75 6d 70 20 43 6f 6e  76 65 72 73 61 74 69 6f  |jump Conversatio|
00005eb0  6e 3b 0a 20 20 20 20 20  20 20 20 20 20 20 20 7d  |n;.            }|
00005ec0  0a 0a 21 20 20 54 68 65  20 69 6e 69 74 69 61 6c  |..!  The initial|
00005ed0  20 77 6f 72 64 20 77 61  73 20 73 6f 6d 65 74 68  | word was someth|
00005ee0  69 6e 67 2c 20 62 75 74  20 6e 6f 74 20 61 20 76  |ing, but not a v|
00005ef0  65 72 62 20 2d 20 67 69  76 65 20 55 6e 6b 6e 6f  |erb - give Unkno|
00005f00  77 6e 56 65 72 62 0a 21  20 20 61 20 63 68 61 6e  |wnVerb.!  a chan|
00005f10  63 65 20 74 6f 20 72 65  73 74 6f 72 65 20 69 74  |ce to restore it|
00005f20  20 74 6f 20 68 65 61 6c  74 68 2e 0a 20 20 20 20  | to health..    |
00005f30  20 20 20 20 20 0a 20 20  20 20 20 20 20 20 69 66  |     .        if|
00005f40  20 28 61 63 74 6f 72 3d  3d 70 6c 61 79 65 72 29  | (actor==player)|
00005f50  0a 20 20 20 20 20 20 20  20 7b 20 20 20 76 65 72  |.        {   ver|
00005f60  62 5f 77 6f 72 64 3d 55  6e 6b 6e 6f 77 6e 56 65  |b_word=UnknownVe|
00005f70  72 62 28 76 65 72 62 5f  77 6f 72 64 29 3b 0a 20  |rb(verb_word);. |
00005f80  20 20 20 20 20 20 20 20  20 20 20 69 66 20 28 76  |           if (v|
00005f90  65 72 62 5f 77 6f 72 64  7e 3d 30 29 20 6a 75 6d  |erb_word~=0) jum|
00005fa0  70 20 56 65 72 62 41 63  63 65 70 74 65 64 3b 0a  |p VerbAccepted;.|
00005fb0  20 20 20 20 20 20 20 20  7d 0a 0a 20 20 20 20 20  |        }..     |
00005fc0  20 20 20 62 65 73 74 5f  65 74 79 70 65 3d 56 45  |   best_etype=VE|
00005fd0  52 42 5f 50 45 3b 20 6a  75 6d 70 20 47 69 76 65  |RB_PE; jump Give|
00005fe0  45 72 72 6f 72 3b 0a 0a  21 20 20 4e 65 78 74 57  |Error;..!  NextW|
00005ff0  6f 72 64 20 6e 75 64 67  65 73 20 74 68 65 20 77  |ord nudges the w|
00006000  6f 72 64 20 6e 75 6d 62  65 72 20 77 6e 20 6f 6e  |ord number wn on|
00006010  20 62 79 20 6f 6e 65 20  65 61 63 68 20 74 69 6d  | by one each tim|
00006020  65 2c 20 73 6f 20 77 65  27 76 65 20 6e 6f 77 0a  |e, so we've now.|
00006030  21 20 20 61 64 76 61 6e  63 65 64 20 70 61 73 74  |!  advanced past|
00006040  20 61 20 63 6f 6d 6d 61  2e 20 20 28 41 20 63 6f  | a comma.  (A co|
00006050  6d 6d 61 20 69 73 20 61  20 77 6f 72 64 20 61 6c  |mma is a word al|
00006060  6c 20 6f 6e 20 69 74 73  20 6f 77 6e 20 69 6e 20  |l on its own in |
00006070  74 68 65 20 74 61 62 6c  65 2e 29 0a 0a 20 20 20  |the table.)..   |
00006080  20 20 20 2e 43 6f 6e 76  65 72 73 61 74 69 6f 6e  |   .Conversation|
00006090  3b 0a 20 20 20 20 20 20  20 20 6a 3d 77 6e 2d 31  |;.        j=wn-1|
000060a0  3b 0a 20 20 20 20 20 20  20 20 69 66 20 28 6a 3d  |;.        if (j=|
000060b0  3d 31 29 20 7b 20 70 72  69 6e 74 20 22 59 6f 75  |=1) { print "You|
000060c0  20 63 61 6e 27 74 20 62  65 67 69 6e 20 77 69 74  | can't begin wit|
000060d0  68 20 61 20 63 6f 6d 6d  61 2e 5e 22 3b 20 6a 75  |h a comma.^"; ju|
000060e0  6d 70 20 52 65 54 79 70  65 3b 20 7d 0a 0a 21 20  |mp ReType; }..! |
000060f0  20 55 73 65 20 4e 6f 75  6e 44 6f 6d 61 69 6e 20  | Use NounDomain |
00006100  28 69 6e 20 74 68 65 20  63 6f 6e 74 65 78 74 20  |(in the context |
00006110  6f 66 20 22 61 6e 69 6d  61 74 65 20 63 72 65 61  |of "animate crea|
00006120  74 75 72 65 22 29 20 74  6f 20 73 65 65 20 69 66  |ture") to see if|
00006130  20 74 68 65 0a 21 20 20  77 6f 72 64 73 20 6d 61  | the.!  words ma|
00006140  6b 65 20 73 65 6e 73 65  20 61 73 20 74 68 65 20  |ke sense as the |
00006150  6e 61 6d 65 20 6f 66 20  73 6f 6d 65 6f 6e 65 20  |name of someone |
00006160  68 65 6c 64 20 6f 72 20  6e 65 61 72 62 79 0a 0a  |held or nearby..|
00006170  20 20 20 20 20 20 20 20  77 6e 3d 31 3b 20 6c 6f  |        wn=1; lo|
00006180  6f 6b 61 68 65 61 64 3d  31 3b 0a 20 20 20 20 20  |okahead=1;.     |
00006190  20 20 20 6c 3d 4e 6f 75  6e 44 6f 6d 61 69 6e 28  |   l=NounDomain(|
000061a0  70 6c 61 79 65 72 2c 6c  6f 63 61 74 69 6f 6e 2c  |player,location,|
000061b0  36 29 3b 20 69 66 20 28  6c 3d 3d 31 30 30 30 29  |6); if (l==1000)|
000061c0  20 6a 75 6d 70 20 52 65  50 61 72 73 65 3b 0a 0a  | jump ReParse;..|
000061d0  20 20 20 20 20 20 20 20  69 66 20 28 6c 3d 3d 30  |        if (l==0|
000061e0  29 20 7b 20 70 72 69 6e  74 20 22 59 6f 75 20 73  |) { print "You s|
000061f0  65 65 6d 20 74 6f 20 77  61 6e 74 20 74 6f 20 74  |eem to want to t|
00006200  61 6c 6b 20 74 6f 20 73  6f 6d 65 6f 6e 65 2c 20  |alk to someone, |
00006210  5c 0a 20 20 20 20 20 20  20 20 20 20 20 20 20 20  |\.              |
00006220  20 20 20 20 20 20 20 20  20 20 20 62 75 74 20 49  |           but I|
00006230  20 63 61 6e 27 74 20 73  65 65 20 77 68 6f 6d 2e  | can't see whom.|
00006240  5e 22 3b 20 6a 75 6d 70  20 52 65 54 79 70 65 3b  |^"; jump ReType;|
00006250  20 7d 0a 0a 21 20 20 54  68 65 20 6f 62 6a 65 63  | }..!  The objec|
00006260  74 20 61 64 64 72 65 73  73 65 64 20 6d 75 73 74  |t addressed must|
00006270  20 61 74 20 6c 65 61 73  74 20 62 65 20 22 74 61  | at least be "ta|
00006280  6c 6b 61 62 6c 65 22 20  69 66 20 6e 6f 74 20 61  |lkable" if not a|
00006290  63 74 75 61 6c 6c 79 20  22 61 6e 69 6d 61 74 65  |ctually "animate|
000062a0  22 0a 21 20 20 28 74 68  65 20 64 69 73 74 69 6e  |".!  (the distin|
000062b0  63 74 69 6f 6e 20 61 6c  6c 6f 77 73 2c 20 66 6f  |ction allows, fo|
000062c0  72 20 69 6e 73 74 61 6e  63 65 2c 20 61 20 6d 69  |r instance, a mi|
000062d0  63 72 6f 70 68 6f 6e 65  20 74 6f 20 62 65 20 73  |crophone to be s|
000062e0  70 6f 6b 65 6e 20 74 6f  2c 0a 21 20 20 77 69 74  |poken to,.!  wit|
000062f0  68 6f 75 74 20 74 68 65  20 70 61 72 73 65 72 20  |hout the parser |
00006300  74 68 69 6e 6b 69 6e 67  20 74 68 61 74 20 74 68  |thinking that th|
00006310  65 20 6d 69 63 72 6f 70  68 6f 6e 65 20 69 73 20  |e microphone is |
00006320  68 75 6d 61 6e 29 2e 0a  0a 20 20 20 20 20 20 20  |human)...       |
00006330  20 69 66 20 28 6c 20 68  61 73 6e 74 20 61 6e 69  | if (l hasnt ani|
00006340  6d 61 74 65 20 26 26 20  6c 20 68 61 73 6e 74 20  |mate && l hasnt |
00006350  74 61 6c 6b 61 62 6c 65  29 0a 20 20 20 20 20 20  |talkable).      |
00006360  20 20 7b 20 20 20 70 72  69 6e 74 20 22 59 6f 75  |  {   print "You|
00006370  20 63 61 6e 27 74 20 74  61 6c 6b 20 74 6f 20 22  | can't talk to "|
00006380  3b 20 44 65 66 41 72 74  28 6c 29 3b 20 70 72 69  |; DefArt(l); pri|
00006390  6e 74 20 22 2e 5e 22 3b  20 6a 75 6d 70 20 52 65  |nt ".^"; jump Re|
000063a0  54 79 70 65 3b 20 7d 0a  0a 21 20 20 43 68 65 63  |Type; }..!  Chec|
000063b0  6b 20 74 68 61 74 20 74  68 65 72 65 20 61 72 65  |k that there are|
000063c0  6e 27 74 20 61 6e 79 20  6d 79 73 74 65 72 79 20  |n't any mystery |
000063d0  77 6f 72 64 73 20 62 65  74 77 65 65 6e 20 74 68  |words between th|
000063e0  65 20 65 6e 64 20 6f 66  20 74 68 65 20 70 65 72  |e end of the per|
000063f0  73 6f 6e 27 73 0a 21 20  20 6e 61 6d 65 20 61 6e  |son's.!  name an|
00006400  64 20 74 68 65 20 63 6f  6d 6d 61 20 28 65 67 2c  |d the comma (eg,|
00006410  20 74 68 72 6f 77 20 6f  75 74 20 22 64 77 61 72  | throw out "dwar|
00006420  66 20 73 64 66 67 73 64  67 73 2c 20 67 6f 20 6e  |f sdfgsdgs, go n|
00006430  6f 72 74 68 22 29 2e 0a  0a 20 20 20 20 20 20 20  |orth")...       |
00006440  20 69 66 20 28 77 6e 7e  3d 6a 29 0a 20 20 20 20  | if (wn~=j).    |
00006450  20 20 20 20 7b 20 20 20  70 72 69 6e 74 20 22 54  |    {   print "T|
00006460  6f 20 74 61 6c 6b 20 74  6f 20 73 6f 6d 65 6f 6e  |o talk to someon|
00006470  65 2c 20 74 72 79 20 7e  73 6f 6d 65 6f 6e 65 2c  |e, try ~someone,|
00006480  20 68 65 6c 6c 6f 7e 20  6f 72 20 73 6f 6d 65 20  | hello~ or some |
00006490  73 75 63 68 2e 5e 22 3b  0a 20 20 20 20 20 20 20  |such.^";.       |
000064a0  20 20 20 20 20 6a 75 6d  70 20 52 65 54 79 70 65  |     jump ReType|
000064b0  3b 0a 20 20 20 20 20 20  20 20 7d 0a 0a 21 20 20  |;.        }..!  |
000064c0  54 68 65 20 70 6c 61 79  65 72 20 68 61 73 20 6e  |The player has n|
000064d0  6f 77 20 73 75 63 63 65  73 73 66 75 6c 6c 79 20  |ow successfully |
000064e0  6e 61 6d 65 64 20 73 6f  6d 65 6f 6e 65 2e 20 20  |named someone.  |
000064f0  41 64 6a 75 73 74 20 22  68 69 6d 22 2c 20 22 68  |Adjust "him", "h|
00006500  65 72 22 2c 20 22 69 74  22 3a 0a 0a 20 20 20 20  |er", "it":..    |
00006510  20 20 20 20 52 65 73 65  74 56 61 67 75 65 57 6f  |    ResetVagueWo|
00006520  72 64 73 28 6c 29 3b 0a  0a 21 20 20 53 65 74 20  |rds(l);..!  Set |
00006530  74 68 65 20 67 6c 6f 62  61 6c 20 76 61 72 69 61  |the global varia|
00006540  62 6c 65 20 22 61 63 74  6f 72 22 2c 20 61 64 6a  |ble "actor", adj|
00006550  75 73 74 20 74 68 65 20  6e 75 6d 62 65 72 20 6f  |ust the number o|
00006560  66 20 74 68 65 20 66 69  72 73 74 20 77 6f 72 64  |f the first word|
00006570  2c 0a 21 20 20 61 6e 64  20 62 65 67 69 6e 20 70  |,.!  and begin p|
00006580  61 72 73 69 6e 67 20 61  67 61 69 6e 20 66 72 6f  |arsing again fro|
00006590  6d 20 74 68 65 72 65 2e  0a 0a 20 20 20 20 20 20  |m there...      |
000065a0  20 20 76 65 72 62 5f 77  6f 72 64 6e 75 6d 3d 6a  |  verb_wordnum=j|
000065b0  2b 31 3b 20 61 63 74 6f  72 3d 6c 3b 0a 20 20 20  |+1; actor=l;.   |
000065c0  20 20 20 20 20 6a 75 6d  70 20 42 65 67 69 6e 43  |     jump BeginC|
000065d0  6f 6d 6d 61 6e 64 3b 0a  20 20 20 20 7d 0a 0a 21  |ommand;.    }..!|
000065e0  20 20 2a 2a 2a 2a 20 28  44 29 20 2a 2a 2a 2a 0a  |  **** (D) ****.|
000065f0  0a 20 20 20 2e 56 65 72  62 41 63 63 65 70 74 65  |.   .VerbAccepte|
00006600  64 3b 0a 0a 21 20 20 57  65 20 6e 6f 77 20 64 65  |d;..!  We now de|
00006610  66 69 6e 69 74 65 6c 79  20 68 61 76 65 20 61 20  |finitely have a |
00006620  76 65 72 62 2c 20 6e 6f  74 20 61 20 64 69 72 65  |verb, not a dire|
00006630  63 74 69 6f 6e 2c 20 77  68 65 74 68 65 72 20 77  |ction, whether w|
00006640  65 20 67 6f 74 20 68 65  72 65 20 62 79 20 74 68  |e got here by th|
00006650  65 0a 21 20 20 22 74 61  6b 65 20 2e 2e 2e 22 20  |e.!  "take ..." |
00006660  6f 72 20 22 70 65 72 73  6f 6e 2c 20 74 61 6b 65  |or "person, take|
00006670  20 2e 2e 2e 22 20 6d 65  74 68 6f 64 2e 20 20 47  | ..." method.  G|
00006680  65 74 20 74 68 65 20 6d  65 74 61 20 66 6c 61 67  |et the meta flag|
00006690  20 66 6f 72 20 74 68 69  73 20 76 65 72 62 3a 0a  | for this verb:.|
000066a0  0a 20 20 20 20 6d 65 74  61 3d 28 28 76 65 72 62  |.    meta=((verb|
000066b0  5f 77 6f 72 64 2d 3e 23  64 69 63 74 5f 70 61 72  |_word->#dict_par|
000066c0  31 29 20 26 20 32 29 2f  32 3b 0a 0a 21 20 20 4e  |1) & 2)/2;..!  N|
000066d0  6f 77 20 6c 65 74 20 69  20 62 65 20 74 68 65 20  |ow let i be the |
000066e0  63 6f 72 72 65 73 70 6f  6e 64 69 6e 67 20 76 65  |corresponding ve|
000066f0  72 62 20 6e 75 6d 62 65  72 2c 20 73 74 6f 72 65  |rb number, store|
00006700  64 20 69 6e 20 74 68 65  20 64 69 63 74 69 6f 6e  |d in the diction|
00006710  61 72 79 20 65 6e 74 72  79 0a 21 20 20 28 69 6e  |ary entry.!  (in|
00006720  20 61 20 70 65 63 75 6c  69 61 72 20 32 35 35 2d  | a peculiar 255-|
00006730  6e 20 66 61 73 68 69 6f  6e 20 66 6f 72 20 74 72  |n fashion for tr|
00006740  61 64 69 74 69 6f 6e 61  6c 20 49 6e 66 6f 63 6f  |aditional Infoco|
00006750  6d 20 72 65 61 73 6f 6e  73 29 2e 2e 2e 0a 0a 20  |m reasons)..... |
00006760  20 20 20 69 3d 24 66 66  2d 28 76 65 72 62 5f 77  |   i=$ff-(verb_w|
00006770  6f 72 64 2d 3e 23 64 69  63 74 5f 70 61 72 32 29  |ord->#dict_par2)|
00006780  3b 0a 0a 21 20 20 2e 2e  2e 74 68 65 6e 20 6c 6f  |;..!  ...then lo|
00006790  6f 6b 20 75 70 20 74 68  65 20 69 2d 74 68 20 65  |ok up the i-th e|
000067a0  6e 74 72 79 20 69 6e 20  74 68 65 20 76 65 72 62  |ntry in the verb|
000067b0  20 74 61 62 6c 65 2c 20  77 68 6f 73 65 20 61 64  | table, whose ad|
000067c0  64 72 65 73 73 20 69 73  20 61 74 20 77 6f 72 64  |dress is at word|
000067d0  0a 21 20 20 37 20 69 6e  20 74 68 65 20 5a 2d 6d  |.!  7 in the Z-m|
000067e0  61 63 68 69 6e 65 20 28  69 6e 20 74 68 65 20 68  |achine (in the h|
000067f0  65 61 64 65 72 29 2c 20  73 6f 20 61 73 20 74 6f  |eader), so as to|
00006800  20 67 65 74 20 74 68 65  20 61 64 64 72 65 73 73  | get the address|
00006810  20 6f 66 20 74 68 65 20  73 79 6e 74 61 78 0a 21  | of the syntax.!|
00006820  20 20 74 61 62 6c 65 20  66 6f 72 20 74 68 65 20  |  table for the |
00006830  67 69 76 65 6e 20 76 65  72 62 2e 2e 2e 0a 0a 20  |given verb..... |
00006840  20 20 20 73 79 6e 74 61  78 3d 28 30 2d 2d 3e 37  |   syntax=(0-->7|
00006850  29 2d 2d 3e 69 3b 0a 0a  21 20 20 2e 2e 2e 61 6e  |)-->i;..!  ...an|
00006860  64 20 74 68 65 6e 20 73  65 65 20 68 6f 77 20 6d  |d then see how m|
00006870  61 6e 79 20 6c 69 6e 65  73 20 28 69 65 2c 20 64  |any lines (ie, d|
00006880  69 66 66 65 72 65 6e 74  20 70 61 74 74 65 72 6e  |ifferent pattern|
00006890  73 20 63 6f 72 72 65 73  70 6f 6e 64 69 6e 67 20  |s corresponding |
000068a0  74 6f 20 74 68 65 0a 21  20 20 73 61 6d 65 20 76  |to the.!  same v|
000068b0  65 72 62 29 20 61 72 65  20 73 74 6f 72 65 64 20  |erb) are stored |
000068c0  69 6e 20 74 68 65 20 70  61 72 73 65 20 74 61 62  |in the parse tab|
000068d0  6c 65 2e 2e 2e 0a 0a 20  20 20 20 6e 75 6d 5f 6c  |le.....    num_l|
000068e0  69 6e 65 73 3d 28 73 79  6e 74 61 78 2d 3e 30 29  |ines=(syntax->0)|
000068f0  2d 31 3b 0a 0a 21 20 20  2e 2e 2e 61 6e 64 20 6e  |-1;..!  ...and n|
00006900  6f 77 20 67 6f 20 74 68  72 6f 75 67 68 20 74 68  |ow go through th|
00006910  65 6d 20 61 6c 6c 2c 20  6f 6e 65 20 62 79 20 6f  |em all, one by o|
00006920  6e 65 2e 0a 21 20 20 54  6f 20 70 72 65 76 65 6e  |ne..!  To preven|
00006930  74 20 76 61 67 75 65 5f  77 6f 72 64 20 30 20 62  |t vague_word 0 b|
00006940  65 69 6e 67 20 6d 69 73  75 6e 64 65 72 73 74 6f  |eing misundersto|
00006950  6f 64 2c 0a 0a 20 20 20  76 61 67 75 65 5f 77 6f  |od,..   vague_wo|
00006960  72 64 3d 27 69 74 27 3b  20 76 61 67 75 65 5f 6f  |rd='it'; vague_o|
00006970  62 6a 3d 69 74 6f 62 6a  3b 0a 0a 20 20 20 69 66  |bj=itobj;..   if|
00006980  20 28 70 61 72 73 65 72  5f 74 72 61 63 65 3e 3d  | (parser_trace>=|
00006990  31 29 0a 20 20 20 7b 20  20 20 20 70 72 69 6e 74  |1).   {    print|
000069a0  20 22 5b 50 61 72 73 69  6e 67 20 66 6f 72 20 74  | "[Parsing for t|
000069b0  68 65 20 76 65 72 62 20  27 22 3b 20 70 72 69 6e  |he verb '"; prin|
000069c0  74 5f 61 64 64 72 20 76  65 72 62 5f 77 6f 72 64  |t_addr verb_word|
000069d0  3b 0a 20 20 20 20 20 20  20 20 70 72 69 6e 74 20  |;.        print |
000069e0  22 27 20 28 22 2c 20 6e  75 6d 5f 6c 69 6e 65 73  |"' (", num_lines|
000069f0  2b 31 2c 20 22 20 6c 69  6e 65 73 29 5d 5e 22 3b  |+1, " lines)]^";|
00006a00  0a 20 20 20 7d 0a 0a 20  20 20 62 65 73 74 5f 65  |.   }..   best_e|
00006a10  74 79 70 65 3d 53 54 55  43 4b 5f 50 45 3b 0a 21  |type=STUCK_PE;.!|
00006a20  20 20 22 62 65 73 74 5f  65 74 79 70 65 22 20 69  |  "best_etype" i|
00006a30  73 20 74 68 65 20 63 75  72 72 65 6e 74 20 66 61  |s the current fa|
00006a40  69 6c 75 72 65 2d 74 6f  2d 6d 61 74 63 68 20 65  |ilure-to-match e|
00006a50  72 72 6f 72 20 2d 20 69  74 20 69 73 20 62 79 20  |rror - it is by |
00006a60  64 65 66 61 75 6c 74 0a  21 20 20 74 68 65 20 6c  |default.!  the l|
00006a70  65 61 73 74 20 69 6e 66  6f 72 6d 61 74 69 76 65  |east informative|
00006a80  20 6f 6e 65 2c 20 22 64  6f 6e 27 74 20 75 6e 64  | one, "don't und|
00006a90  65 72 73 74 61 6e 64 20  74 68 61 74 20 73 65 6e  |erstand that sen|
00006aa0  74 65 6e 63 65 22 0a 0a  0a 21 20 20 2a 2a 2a 2a  |tence"...!  ****|
00006ab0  20 28 45 29 20 2a 2a 2a  2a 0a 0a 20 20 20 20 66  | (E) ****..    f|
00006ac0  6f 72 20 28 6c 69 6e 65  3d 30 3a 6c 69 6e 65 3c  |or (line=0:line<|
00006ad0  3d 6e 75 6d 5f 6c 69 6e  65 73 3a 6c 69 6e 65 2b  |=num_lines:line+|
00006ae0  2b 29 0a 20 20 20 20 7b  20 20 20 6c 69 6e 65 5f  |+).    {   line_|
00006af0  61 64 64 72 65 73 73 20  3d 20 73 79 6e 74 61 78  |address = syntax|
00006b00  2b 31 2b 6c 69 6e 65 2a  38 3b 0a 0a 20 20 20 20  |+1+line*8;..    |
00006b10  20 20 20 20 69 66 20 28  70 61 72 73 65 72 5f 74  |    if (parser_t|
00006b20  72 61 63 65 3e 3d 31 29  0a 20 20 20 20 20 20 20  |race>=1).       |
00006b30  20 7b 20 20 20 70 72 69  6e 74 20 22 5b 4c 69 6e  | {   print "[Lin|
00006b40  65 20 22 2c 20 6c 69 6e  65 2c 20 22 3a 20 22 2c  |e ", line, ": ",|
00006b50  20 6c 69 6e 65 5f 61 64  64 72 65 73 73 2d 3e 30  | line_address->0|
00006b60  2c 20 22 20 70 61 72 61  6d 65 74 65 72 73 3a 20  |, " parameters: |
00006b70  22 3b 0a 20 20 20 20 20  20 20 20 20 20 20 20 66  |";.            f|
00006b80  6f 72 20 28 70 63 6f 75  6e 74 3d 31 3a 70 63 6f  |or (pcount=1:pco|
00006b90  75 6e 74 3c 3d 36 3a 70  63 6f 75 6e 74 2b 2b 29  |unt<=6:pcount++)|
00006ba0  0a 20 20 20 20 20 20 20  20 20 20 20 20 7b 20 20  |.            {  |
00006bb0  20 74 6f 6b 65 6e 3d 6c  69 6e 65 5f 61 64 64 72  | token=line_addr|
00006bc0  65 73 73 2d 3e 70 63 6f  75 6e 74 3b 0a 20 20 20  |ess->pcount;.   |
00006bd0  20 20 20 20 20 20 20 20  20 20 20 20 20 70 72 69  |             pri|
00006be0  6e 74 20 74 6f 6b 65 6e  2c 20 22 20 22 3b 0a 20  |nt token, " ";. |
00006bf0  20 20 20 20 20 20 20 20  20 20 20 7d 0a 20 20 20  |           }.   |
00006c00  20 20 20 20 20 20 20 20  20 70 72 69 6e 74 20 22  |         print "|
00006c10  20 2d 3e 20 61 63 74 69  6f 6e 20 22 2c 20 6c 69  | -> action ", li|
00006c20  6e 65 5f 61 64 64 72 65  73 73 2d 3e 37 2c 20 22  |ne_address->7, "|
00006c30  5d 5e 22 3b 0a 20 20 20  20 20 20 20 20 7d 0a 0a  |]^";.        }..|
00006c40  21 20 20 57 65 20 61 72  65 6e 27 74 20 69 6e 20  |!  We aren't in |
00006c50  22 6e 6f 74 20 68 6f 6c  64 69 6e 67 22 20 6f 72  |"not holding" or|
00006c60  20 69 6e 66 65 72 72 69  6e 67 20 6d 6f 64 65 73  | inferring modes|
00006c70  2c 20 61 6e 64 20 68 61  76 65 6e 27 74 20 65 6e  |, and haven't en|
00006c80  74 65 72 65 64 0a 21 20  20 61 6e 79 20 70 61 72  |tered.!  any par|
00006c90  61 6d 65 74 65 72 73 20  6f 6e 20 74 68 65 20 6c  |ameters on the l|
00006ca0  69 6e 65 20 79 65 74 2c  20 6f 72 20 61 6e 79 20  |ine yet, or any |
00006cb0  73 70 65 63 69 61 6c 20  6e 75 6d 62 65 72 73 3b  |special numbers;|
00006cc0  20 74 68 65 20 6d 75 6c  74 69 70 6c 65 0a 21 20  | the multiple.! |
00006cd0  20 6f 62 6a 65 63 74 20  69 73 20 73 74 69 6c 6c  | object is still|
00006ce0  20 65 6d 70 74 79 2e 0a  0a 20 20 20 20 20 20 20  | empty...       |
00006cf0  20 6e 6f 74 5f 68 6f 6c  64 69 6e 67 3d 30 3b 0a  | not_holding=0;.|
00006d00  20 20 20 20 20 20 20 20  69 6e 66 65 72 66 72 6f  |        inferfro|
00006d10  6d 3d 30 3b 0a 20 20 20  20 20 20 20 20 70 61 72  |m=0;.        par|
00006d20  61 6d 65 74 65 72 73 3d  30 3b 0a 20 20 20 20 20  |ameters=0;.     |
00006d30  20 20 20 6e 73 6e 73 3d  30 3b 0a 20 20 20 20 20  |   nsns=0;.     |
00006d40  20 20 20 6d 75 6c 74 69  70 6c 65 5f 6f 62 6a 65  |   multiple_obje|
00006d50  63 74 2d 2d 3e 30 20 3d  20 30 3b 0a 20 20 20 20  |ct-->0 = 0;.    |
00006d60  20 20 20 20 65 74 79 70  65 3d 53 54 55 43 4b 5f  |    etype=STUCK_|
00006d70  50 45 3b 0a 20 20 20 20  20 20 20 20 61 63 74 69  |PE;.        acti|
00006d80  6f 6e 5f 74 6f 5f 62 65  20 3d 20 6c 69 6e 65 5f  |on_to_be = line_|
00006d90  61 64 64 72 65 73 73 2d  3e 37 3b 0a 0a 21 20 20  |address->7;..!  |
00006da0  50 75 74 20 74 68 65 20  77 6f 72 64 20 6d 61 72  |Put the word mar|
00006db0  6b 65 72 20 62 61 63 6b  20 74 6f 20 6a 75 73 74  |ker back to just|
00006dc0  20 61 66 74 65 72 20 74  68 65 20 76 65 72 62 0a  | after the verb.|
00006dd0  0a 20 20 20 20 20 20 20  20 77 6e 3d 76 65 72 62  |.        wn=verb|
00006de0  5f 77 6f 72 64 6e 75 6d  2b 31 3b 0a 0a 21 20 20  |_wordnum+1;..!  |
00006df0  41 6e 20 69 6e 64 69 76  69 64 75 61 6c 20 22 6c  |An individual "l|
00006e00  69 6e 65 22 20 63 6f 6e  74 61 69 6e 73 20 73 69  |ine" contains si|
00006e10  78 20 74 6f 6b 65 6e 73  2e 2e 2e 20 20 54 68 65  |x tokens...  The|
00006e20  72 65 27 73 20 61 20 70  72 65 6c 69 6d 69 6e 61  |re's a prelimina|
00006e30  72 79 20 70 61 73 73 0a  21 20 20 66 69 72 73 74  |ry pass.!  first|
00006e40  2c 20 74 6f 20 70 61 72  73 65 20 6c 61 74 65 20  |, to parse late |
00006e50  74 6f 6b 65 6e 73 20 65  61 72 6c 79 20 69 66 20  |tokens early if |
00006e60  6e 65 63 65 73 73 61 72  79 20 28 62 65 63 61 75  |necessary (becau|
00006e70  73 65 20 6f 66 20 6d 69  20 6f 72 20 6d 65 29 0a  |se of mi or me).|
00006e80  0a 20 20 20 20 20 20 20  20 61 64 76 61 6e 63 65  |.        advance|
00006e90  5f 77 61 72 6e 69 6e 67  3d 2d 31 3b 0a 20 20 20  |_warning=-1;.   |
00006ea0  20 20 20 20 20 66 6f 72  20 28 69 3d 30 2c 70 63  |     for (i=0,pc|
00006eb0  6f 75 6e 74 3d 31 3a 70  63 6f 75 6e 74 3c 3d 36  |ount=1:pcount<=6|
00006ec0  3a 70 63 6f 75 6e 74 2b  2b 29 0a 20 20 20 20 20  |:pcount++).     |
00006ed0  20 20 20 7b 20 20 20 73  63 6f 70 65 5f 74 6f 6b  |   {   scope_tok|
00006ee0  65 6e 3d 30 3b 0a 20 20  20 20 20 20 20 20 20 20  |en=0;.          |
00006ef0  20 20 74 6f 6b 65 6e 3d  6c 69 6e 65 5f 61 64 64  |  token=line_add|
00006f00  72 65 73 73 2d 3e 70 63  6f 75 6e 74 3b 0a 20 20  |ress->pcount;.  |
00006f10  20 20 20 20 20 20 20 20  20 20 69 66 20 28 74 6f  |          if (to|
00006f20  6b 65 6e 3c 31 38 30 29  20 69 2b 2b 3b 0a 20 20  |ken<180) i++;.  |
00006f30  20 20 20 20 20 20 20 20  20 20 69 66 20 28 74 6f  |          if (to|
00006f40  6b 65 6e 3d 3d 34 20 6f  72 20 35 20 26 26 20 69  |ken==4 or 5 && i|
00006f50  3d 3d 31 29 0a 20 20 20  20 20 20 20 20 20 20 20  |==1).           |
00006f60  20 7b 20 20 20 69 66 20  28 70 61 72 73 65 72 5f  | {   if (parser_|
00006f70  74 72 61 63 65 3e 3d 32  29 20 70 72 69 6e 74 20  |trace>=2) print |
00006f80  22 20 5b 54 72 79 69 6e  67 20 6c 6f 6f 6b 2d 61  |" [Trying look-a|
00006f90  68 65 61 64 5d 5e 22 3b  0a 20 20 20 20 20 20 20  |head]^";.       |
00006fa0  20 20 20 20 20 20 20 20  20 70 63 6f 75 6e 74 2b  |         pcount+|
00006fb0  2b 3b 0a 20 20 20 20 20  20 20 20 20 20 20 20 20  |+;.             |
00006fc0  20 20 20 77 68 69 6c 65  20 28 70 63 6f 75 6e 74  |   while (pcount|
00006fd0  3c 3d 36 20 26 26 20 6c  69 6e 65 5f 61 64 64 72  |<=6 && line_addr|
00006fe0  65 73 73 2d 3e 70 63 6f  75 6e 74 3e 3d 31 38 30  |ess->pcount>=180|
00006ff0  29 20 70 63 6f 75 6e 74  2b 2b 3b 0a 20 20 20 20  |) pcount++;.    |
00007000  20 20 20 20 20 20 20 20  20 20 20 20 74 6f 6b 65  |            toke|
00007010  6e 3d 6c 69 6e 65 5f 61  64 64 72 65 73 73 2d 3e  |n=line_address->|
00007020  28 70 63 6f 75 6e 74 2d  31 29 3b 0a 20 20 20 20  |(pcount-1);.    |
00007030  20 20 20 20 20 20 20 20  20 20 20 20 69 66 20 28  |            if (|
00007040  74 6f 6b 65 6e 3e 3d 31  38 30 29 0a 20 20 20 20  |token>=180).    |
00007050  20 20 20 20 20 20 20 20  20 20 20 20 7b 20 20 20  |            {   |
00007060  6a 3d 41 64 6a 65 63 74  69 76 65 41 64 64 72 65  |j=AdjectiveAddre|
00007070  73 73 28 74 6f 6b 65 6e  29 3b 0a 0a 20 20 20 20  |ss(token);..    |
00007080  20 20 20 20 20 20 20 20  20 20 20 20 20 20 20 20  |                |
00007090  21 20 20 4e 6f 77 20 6c  6f 6f 6b 20 66 6f 72 20  |!  Now look for |
000070a0  77 6f 72 64 20 77 69 74  68 20 6a 2c 20 6d 6f 76  |word with j, mov|
000070b0  65 20 77 6e 2c 20 70 61  72 73 65 20 6e 65 78 74  |e wn, parse next|
000070c0  0a 20 20 20 20 20 20 20  20 20 20 20 20 20 20 20  |.               |
000070d0  20 20 20 20 20 21 20 20  74 6f 6b 65 6e 2e 2e 2e  |     !  token...|
000070e0  0a 20 20 20 20 20 20 20  20 20 20 20 20 20 20 20  |.               |
000070f0  20 20 20 20 20 77 68 69  6c 65 20 28 77 6e 20 3c  |     while (wn <|
00007100  3d 20 6e 75 6d 5f 77 6f  72 64 73 29 0a 20 20 20  |= num_words).   |
00007110  20 20 20 20 20 20 20 20  20 20 20 20 20 20 20 20  |                |
00007120  20 7b 20 20 20 69 66 20  28 4e 65 78 74 57 6f 72  | {   if (NextWor|
00007130  64 28 29 3d 3d 6a 29 0a  20 20 20 20 20 20 20 20  |d()==j).        |
00007140  20 20 20 20 20 20 20 20  20 20 20 20 20 20 20 20  |                |
00007150  7b 20 20 20 6c 20 3d 20  4e 6f 75 6e 44 6f 6d 61  |{   l = NounDoma|
00007160  69 6e 28 6c 6f 63 61 74  69 6f 6e 2c 61 63 74 6f  |in(location,acto|
00007170  72 2c 74 6f 6b 65 6e 29  3b 0a 20 20 20 20 20 20  |r,token);.      |
00007180  20 20 20 20 20 20 20 20  20 20 20 20 20 20 20 20  |                |
00007190  20 20 20 20 20 20 69 66  20 28 70 61 72 73 65 72  |      if (parser|
000071a0  5f 74 72 61 63 65 3e 3d  32 29 0a 20 20 20 20 20  |_trace>=2).     |
000071b0  20 20 20 20 20 20 20 20  20 20 20 20 20 20 20 20  |                |
000071c0  20 20 20 20 20 20 20 7b  20 20 20 70 72 69 6e 74  |       {   print|
000071d0  20 22 20 5b 46 6f 72 77  61 72 64 20 74 6f 6b 65  | " [Forward toke|
000071e0  6e 20 70 61 72 73 65 64  3a 20 22 3b 0a 20 20 20  |n parsed: ";.   |
000071f0  20 20 20 20 20 20 20 20  20 20 20 20 20 20 20 20  |                |
00007200  20 20 20 20 20 20 20 20  20 20 20 20 20 69 66 20  |             if |
00007210  28 6c 3d 3d 31 30 30 30  29 20 70 72 69 6e 74 20  |(l==1000) print |
00007220  22 72 65 2d 70 61 72 73  65 20 72 65 71 75 65 73  |"re-parse reques|
00007230  74 5d 5e 22 3b 0a 20 20  20 20 20 20 20 20 20 20  |t]^";.          |
00007240  20 20 20 20 20 20 20 20  20 20 20 20 20 20 20 20  |                |
00007250  20 20 20 20 20 20 69 66  20 28 6c 3d 3d 31 29 20  |      if (l==1) |
00007260  70 72 69 6e 74 20 22 62  75 74 20 6d 75 6c 74 69  |print "but multi|
00007270  70 6c 65 20 66 6f 75 6e  64 5d 5e 22 3b 0a 20 20  |ple found]^";.  |
00007280  20 20 20 20 20 20 20 20  20 20 20 20 20 20 20 20  |                |
00007290  20 20 20 20 20 20 20 20  20 20 20 20 20 20 69 66  |              if|
000072a0  20 28 6c 3d 3d 30 29 20  70 72 69 6e 74 20 22 68  | (l==0) print "h|
000072b0  69 74 20 65 72 72 6f 72  20 22 2c 20 65 74 79 70  |it error ", etyp|
000072c0  65 2c 20 22 5d 5e 22 3b  0a 20 20 20 20 20 20 20  |e, "]^";.       |
000072d0  20 20 20 20 20 20 20 20  20 20 20 20 20 20 20 20  |                |
000072e0  20 20 20 20 20 7d 0a 20  20 20 20 20 20 20 20 20  |     }.         |
000072f0  20 20 20 20 20 20 20 20  20 20 20 20 20 20 20 20  |                |
00007300  20 20 20 69 66 20 28 6c  3d 3d 31 30 30 30 29 20  |   if (l==1000) |
00007310  6a 75 6d 70 20 52 65 50  61 72 73 65 3b 0a 20 20  |jump ReParse;.  |
00007320  20 20 20 20 20 20 20 20  20 20 20 20 20 20 20 20  |                |
00007330  20 20 20 20 20 20 20 20  20 20 69 66 20 28 6c 3e  |          if (l>|
00007340  3d 32 29 0a 20 20 20 20  20 20 20 20 20 20 20 20  |=2).            |
00007350  20 20 20 20 20 20 20 20  20 20 20 20 20 20 20 20  |                |
00007360  7b 20 20 20 61 64 76 61  6e 63 65 5f 77 61 72 6e  |{   advance_warn|
00007370  69 6e 67 20 3d 20 6c 3b  0a 20 20 20 20 20 20 20  |ing = l;.       |
00007380  20 20 20 20 20 20 20 20  20 20 20 20 20 20 20 20  |                |
00007390  20 20 20 20 20 20 20 20  20 69 66 20 28 70 61 72  |         if (par|
000073a0  73 65 72 5f 74 72 61 63  65 3e 3d 33 29 0a 20 20  |ser_trace>=3).  |
000073b0  20 20 20 20 20 20 20 20  20 20 20 20 20 20 20 20  |                |
000073c0  20 20 20 20 20 20 20 20  20 20 20 20 20 20 7b 20  |              { |
000073d0  20 20 44 65 66 41 72 74  28 6c 29 3b 20 70 72 69  |  DefArt(l); pri|
000073e0  6e 74 20 22 5d 5e 22 3b  0a 20 20 20 20 20 20 20  |nt "]^";.       |
000073f0  20 20 20 20 20 20 20 20  20 20 20 20 20 20 20 20  |                |
00007400  20 20 20 20 20 20 20 20  20 7d 0a 20 20 20 20 20  |         }.     |
00007410  20 20 20 20 20 20 20 20  20 20 20 20 20 20 20 20  |                |
00007420  20 20 20 20 20 20 20 7d  0a 20 20 20 20 20 20 20  |       }.       |
00007430  20 20 20 20 20 20 20 20  20 20 20 20 20 20 20 20  |                |
00007440  20 7d 0a 20 20 20 20 20  20 20 20 20 20 20 20 20  | }.             |
00007450  20 20 20 20 20 20 20 7d  0a 20 20 20 20 20 20 20  |       }.       |
00007460  20 20 20 20 20 20 20 20  20 7d 0a 20 20 20 20 20  |         }.     |
00007470  20 20 20 20 20 20 20 7d  0a 20 20 20 20 20 20 20  |       }.       |
00007480  20 7d 0a 0a 21 20 20 41  6e 64 20 6e 6f 77 20 73  | }..!  And now s|
00007490  74 61 72 74 20 61 67 61  69 6e 2c 20 70 72 6f 70  |tart again, prop|
000074a0  65 72 6c 79 2c 20 66 6f  72 65 61 72 6d 65 64 20  |erly, forearmed |
000074b0  6f 72 20 6e 6f 74 20 61  73 20 74 68 65 20 63 61  |or not as the ca|
000074c0  73 65 20 6d 61 79 20 62  65 2e 0a 0a 20 20 20 20  |se may be...    |
000074d0  20 20 20 20 6e 6f 74 5f  68 6f 6c 64 69 6e 67 3d  |    not_holding=|
000074e0  30 3b 0a 20 20 20 20 20  20 20 20 69 6e 66 65 72  |0;.        infer|
000074f0  66 72 6f 6d 3d 30 3b 0a  20 20 20 20 20 20 20 20  |from=0;.        |
00007500  70 61 72 61 6d 65 74 65  72 73 3d 30 3b 0a 20 20  |parameters=0;.  |
00007510  20 20 20 20 20 20 6e 73  6e 73 3d 30 3b 0a 20 20  |      nsns=0;.  |
00007520  20 20 20 20 20 20 6d 75  6c 74 69 70 6c 65 5f 6f  |      multiple_o|
00007530  62 6a 65 63 74 2d 2d 3e  30 20 3d 20 30 3b 0a 20  |bject-->0 = 0;. |
00007540  20 20 20 20 20 20 20 65  74 79 70 65 3d 53 54 55  |       etype=STU|
00007550  43 4b 5f 50 45 3b 0a 20  20 20 20 20 20 20 20 61  |CK_PE;.        a|
00007560  63 74 69 6f 6e 5f 74 6f  5f 62 65 20 3d 20 6c 69  |ction_to_be = li|
00007570  6e 65 5f 61 64 64 72 65  73 73 2d 3e 37 3b 0a 20  |ne_address->7;. |
00007580  20 20 20 20 20 20 20 77  6e 3d 76 65 72 62 5f 77  |       wn=verb_w|
00007590  6f 72 64 6e 75 6d 2b 31  3b 0a 0a 21 20 20 22 50  |ordnum+1;..!  "P|
000075a0  61 74 74 65 72 6e 22 20  67 72 61 64 75 61 6c 6c  |attern" graduall|
000075b0  79 20 61 63 63 75 6d 75  6c 61 74 65 73 20 77 68  |y accumulates wh|
000075c0  61 74 20 68 61 73 20 62  65 65 6e 20 72 65 63 6f  |at has been reco|
000075d0  67 6e 69 73 65 64 20 73  6f 20 66 61 72 2c 0a 21  |gnised so far,.!|
000075e0  20 20 73 6f 20 74 68 61  74 20 69 74 20 6d 61 79  |  so that it may|
000075f0  20 62 65 20 72 65 70 72  69 6e 74 65 64 20 62 79  | be reprinted by|
00007600  20 74 68 65 20 70 61 72  73 65 72 20 6c 61 74 65  | the parser late|
00007610  72 20 6f 6e 0a 0a 20 20  20 20 20 20 20 20 66 6f  |r on..        fo|
00007620  72 20 28 70 63 6f 75 6e  74 3d 31 3a 70 63 6f 75  |r (pcount=1:pcou|
00007630  6e 74 3c 3d 36 3a 70 63  6f 75 6e 74 2b 2b 29 0a  |nt<=6:pcount++).|
00007640  20 20 20 20 20 20 20 20  7b 20 20 20 70 61 74 74  |        {   patt|
00007650  65 72 6e 2d 2d 3e 70 63  6f 75 6e 74 3d 30 3b 0a  |ern-->pcount=0;.|
00007660  0a 20 20 20 20 20 20 20  20 20 20 20 20 74 6f 6b  |.            tok|
00007670  65 6e 3d 6c 69 6e 65 5f  61 64 64 72 65 73 73 2d  |en=line_address-|
00007680  3e 70 63 6f 75 6e 74 3b  0a 0a 20 20 20 20 20 20  |>pcount;..      |
00007690  20 20 20 20 20 20 69 66  20 28 70 61 72 73 65 72  |      if (parser|
000076a0  5f 74 72 61 63 65 3e 3d  32 29 0a 20 20 20 20 20  |_trace>=2).     |
000076b0  20 20 20 20 20 20 20 7b  20 20 20 70 72 69 6e 74  |       {   print|
000076c0  20 22 20 5b 54 6f 6b 65  6e 20 22 2c 70 63 6f 75  | " [Token ",pcou|
000076d0  6e 74 2c 20 22 20 69 73  20 22 2c 20 74 6f 6b 65  |nt, " is ", toke|
000076e0  6e 2c 20 22 3a 20 22 3b  0a 20 20 20 20 20 20 20  |n, ": ";.       |
000076f0  20 20 20 20 20 20 20 20  20 69 66 20 28 74 6f 6b  |         if (tok|
00007700  65 6e 3c 31 36 29 0a 20  20 20 20 20 20 20 20 20  |en<16).         |
00007710  20 20 20 20 20 20 20 7b  20 20 20 69 66 20 28 74  |       {   if (t|
00007720  6f 6b 65 6e 3d 3d 30 29  20 70 72 69 6e 74 20 22  |oken==0) print "|
00007730  3c 6e 6f 75 6e 3e 20 6f  72 20 6e 75 6c 6c 22 3b  |<noun> or null";|
00007740  0a 20 20 20 20 20 20 20  20 20 20 20 20 20 20 20  |.               |
00007750  20 20 20 20 20 69 66 20  28 74 6f 6b 65 6e 3d 3d  |     if (token==|
00007760  31 29 20 70 72 69 6e 74  20 22 3c 68 65 6c 64 3e  |1) print "<held>|
00007770  22 3b 0a 20 20 20 20 20  20 20 20 20 20 20 20 20  |";.             |
00007780  20 20 20 20 20 20 20 69  66 20 28 74 6f 6b 65 6e  |       if (token|
00007790  3d 3d 32 29 20 70 72 69  6e 74 20 22 3c 6d 75 6c  |==2) print "<mul|
000077a0  74 69 3e 22 3b 0a 20 20  20 20 20 20 20 20 20 20  |ti>";.          |
000077b0  20 20 20 20 20 20 20 20  20 20 69 66 20 28 74 6f  |          if (to|
000077c0  6b 65 6e 3d 3d 33 29 20  70 72 69 6e 74 20 22 3c  |ken==3) print "<|
000077d0  6d 75 6c 74 69 68 65 6c  64 3e 22 3b 0a 20 20 20  |multiheld>";.   |
000077e0  20 20 20 20 20 20 20 20  20 20 20 20 20 20 20 20  |                |
000077f0  20 69 66 20 28 74 6f 6b  65 6e 3d 3d 34 29 20 70  | if (token==4) p|
00007800  72 69 6e 74 20 22 3c 6d  75 6c 74 69 65 78 63 65  |rint "<multiexce|
00007810  70 74 3e 22 3b 0a 20 20  20 20 20 20 20 20 20 20  |pt>";.          |
00007820  20 20 20 20 20 20 20 20  20 20 69 66 20 28 74 6f  |          if (to|
00007830  6b 65 6e 3d 3d 35 29 20  70 72 69 6e 74 20 22 3c  |ken==5) print "<|
00007840  6d 75 6c 74 69 69 6e 73  69 64 65 3e 22 3b 0a 20  |multiinside>";. |
00007850  20 20 20 20 20 20 20 20  20 20 20 20 20 20 20 20  |                |
00007860  20 20 20 69 66 20 28 74  6f 6b 65 6e 3d 3d 36 29  |   if (token==6)|
00007870  20 70 72 69 6e 74 20 22  3c 63 72 65 61 74 75 72  | print "<creatur|
00007880  65 3e 22 3b 0a 20 20 20  20 20 20 20 20 20 20 20  |e>";.           |
00007890  20 20 20 20 20 20 20 20  20 69 66 20 28 74 6f 6b  |         if (tok|
000078a0  65 6e 3d 3d 37 29 20 70  72 69 6e 74 20 22 3c 73  |en==7) print "<s|
000078b0  70 65 63 69 61 6c 3e 22  3b 0a 20 20 20 20 20 20  |pecial>";.      |
000078c0  20 20 20 20 20 20 20 20  20 20 20 20 20 20 69 66  |              if|
000078d0  20 28 74 6f 6b 65 6e 3d  3d 38 29 20 70 72 69 6e  | (token==8) prin|
000078e0  74 20 22 3c 6e 75 6d 62  65 72 3e 22 3b 0a 20 20  |t "<number>";.  |
000078f0  20 20 20 20 20 20 20 20  20 20 20 20 20 20 7d 0a  |              }.|
00007900  20 20 20 20 20 20 20 20  20 20 20 20 20 20 20 20  |                |
00007910  69 66 20 28 74 6f 6b 65  6e 3e 3d 31 36 20 26 26  |if (token>=16 &&|
00007920  20 74 6f 6b 65 6e 3c 34  38 29 0a 20 20 20 20 20  | token<48).     |
00007930  20 20 20 20 20 20 20 20  20 20 20 20 20 20 20 70  |               p|
00007940  72 69 6e 74 20 22 3c 6e  6f 75 6e 20 66 69 6c 74  |rint "<noun filt|
00007950  65 72 20 62 79 20 72 6f  75 74 69 6e 65 20 22 2c  |er by routine ",|
00007960  74 6f 6b 65 6e 2d 31 36  2c 20 22 3e 22 3b 0a 20  |token-16, ">";. |
00007970  20 20 20 20 20 20 20 20  20 20 20 20 20 20 20 69  |               i|
00007980  66 20 28 74 6f 6b 65 6e  3e 3d 34 38 20 26 26 20  |f (token>=48 && |
00007990  74 6f 6b 65 6e 3c 38 30  29 0a 20 20 20 20 20 20  |token<80).      |
000079a0  20 20 20 20 20 20 20 20  20 20 20 20 20 20 70 72  |              pr|
000079b0  69 6e 74 20 22 3c 67 65  6e 65 72 61 6c 20 70 61  |int "<general pa|
000079c0  72 73 65 20 62 79 20 72  6f 75 74 69 6e 65 20 22  |rse by routine "|
000079d0  2c 74 6f 6b 65 6e 2d 34  38 2c 20 22 3e 22 3b 0a  |,token-48, ">";.|
000079e0  20 20 20 20 20 20 20 20  20 20 20 20 20 20 20 20  |                |
000079f0  69 66 20 28 74 6f 6b 65  6e 3e 3d 38 30 20 26 26  |if (token>=80 &&|
00007a00  20 74 6f 6b 65 6e 3c 31  32 38 29 0a 20 20 20 20  | token<128).    |
00007a10  20 20 20 20 20 20 20 20  20 20 20 20 20 20 20 20  |                |
00007a20  70 72 69 6e 74 20 22 3c  73 63 6f 70 65 20 70 61  |print "<scope pa|
00007a30  72 73 65 20 62 79 20 72  6f 75 74 69 6e 65 20 22  |rse by routine "|
00007a40  2c 74 6f 6b 65 6e 2d 38  30 2c 20 22 3e 22 3b 0a  |,token-80, ">";.|
00007a50  20 20 20 20 20 20 20 20  20 20 20 20 20 20 20 20  |                |
00007a60  69 66 20 28 74 6f 6b 65  6e 3e 3d 31 32 38 20 26  |if (token>=128 &|
00007a70  26 20 74 6f 6b 65 6e 3c  31 38 30 29 0a 20 20 20  |& token<180).   |
00007a80  20 20 20 20 20 20 20 20  20 20 20 20 20 20 20 20  |                |
00007a90  20 70 72 69 6e 74 20 22  3c 6e 6f 75 6e 20 66 69  | print "<noun fi|
00007aa0  6c 74 65 72 20 62 79 20  61 74 74 72 69 62 75 74  |lter by attribut|
00007ab0  65 20 22 2c 74 6f 6b 65  6e 2d 31 32 38 2c 20 22  |e ",token-128, "|
00007ac0  3e 22 3b 0a 20 20 20 20  20 20 20 20 20 20 20 20  |>";.            |
00007ad0  20 20 20 20 69 66 20 28  74 6f 6b 65 6e 3e 31 38  |    if (token>18|
00007ae0  30 29 0a 20 20 20 20 20  20 20 20 20 20 20 20 20  |0).             |
00007af0  20 20 20 7b 20 20 20 70  72 69 6e 74 20 22 3c 61  |   {   print "<a|
00007b00  64 6a 65 63 74 69 76 65  20 22 2c 32 35 35 2d 74  |djective ",255-t|
00007b10  6f 6b 65 6e 2c 20 22 20  27 22 3b 0a 20 20 20 20  |oken, " '";.    |
00007b20  20 20 20 20 20 20 20 20  20 20 20 20 20 20 20 20  |                |
00007b30  70 72 69 6e 74 5f 61 64  64 72 20 41 64 6a 65 63  |print_addr Adjec|
00007b40  74 69 76 65 41 64 64 72  65 73 73 28 74 6f 6b 65  |tiveAddress(toke|
00007b50  6e 29 3b 20 70 72 69 6e  74 20 22 27 3e 22 3b 0a  |n); print "'>";.|
00007b60  20 20 20 20 20 20 20 20  20 20 20 20 20 20 20 20  |                |
00007b70  7d 0a 20 20 20 20 20 20  20 20 20 20 20 20 20 20  |}.              |
00007b80  20 20 70 72 69 6e 74 20  22 20 61 74 20 77 6f 72  |  print " at wor|
00007b90  64 20 6e 75 6d 62 65 72  20 22 2c 20 77 6e 2c 20  |d number ", wn, |
00007ba0  22 5d 5e 22 3b 0a 20 20  20 20 20 20 20 20 20 20  |"]^";.          |
00007bb0  20 20 7d 0a 0a 21 20 20  4c 6f 6f 6b 61 68 65 61  |  }..!  Lookahea|
00007bc0  64 20 69 73 20 73 65 74  20 74 6f 20 74 68 65 20  |d is set to the |
00007bd0  74 6f 6b 65 6e 20 61 66  74 65 72 20 74 68 69 73  |token after this|
00007be0  20 6f 6e 65 2c 20 6f 72  20 38 20 69 66 20 74 68  | one, or 8 if th|
00007bf0  65 72 65 20 69 73 6e 27  74 20 6f 6e 65 2e 0a 21  |ere isn't one..!|
00007c00  20 20 28 43 6f 6d 70 6c  69 63 61 74 65 64 20 62  |  (Complicated b|
00007c10  65 63 61 75 73 65 20 74  68 65 20 6c 69 6e 65 20  |ecause the line |
00007c20  69 73 20 70 61 64 64 65  64 20 77 69 74 68 20 30  |is padded with 0|
00007c30  27 73 2e 29 0a 0a 20 20  20 20 20 20 20 20 20 20  |'s.)..          |
00007c40  20 20 6d 3d 70 63 6f 75  6e 74 2b 31 3b 20 6c 6f  |  m=pcount+1; lo|
00007c50  6f 6b 61 68 65 61 64 3d  38 3b 0a 20 20 20 20 20  |okahead=8;.     |
00007c60  20 20 20 20 20 20 20 69  66 20 28 6d 3c 3d 36 29  |       if (m<=6)|
00007c70  20 6c 6f 6f 6b 61 68 65  61 64 3d 6c 69 6e 65 5f  | lookahead=line_|
00007c80  61 64 64 72 65 73 73 2d  3e 6d 3b 0a 20 20 20 20  |address->m;.    |
00007c90  20 20 20 20 20 20 20 20  69 66 20 28 6c 6f 6f 6b  |        if (look|
00007ca0  61 68 65 61 64 3d 3d 30  29 0a 20 20 20 20 20 20  |ahead==0).      |
00007cb0  20 20 20 20 20 20 7b 20  20 20 6d 3d 70 61 72 61  |      {   m=para|
00007cc0  6d 65 74 65 72 73 3b 20  69 66 20 28 74 6f 6b 65  |meters; if (toke|
00007cd0  6e 3c 3d 37 29 20 6d 2b  2b 3b 0a 20 20 20 20 20  |n<=7) m++;.     |
00007ce0  20 20 20 20 20 20 20 20  20 20 20 69 66 20 28 6d  |           if (m|
00007cf0  3e 3d 6c 69 6e 65 5f 61  64 64 72 65 73 73 2d 3e  |>=line_address->|
00007d00  30 29 20 6c 6f 6f 6b 61  68 65 61 64 3d 38 3b 0a  |0) lookahead=8;.|
00007d10  20 20 20 20 20 20 20 20  20 20 20 20 7d 0a 0a 21  |            }..!|
00007d20  20 20 2a 2a 2a 2a 20 28  46 29 20 2a 2a 2a 2a 0a  |  **** (F) ****.|
00007d30  0a 21 20 20 57 68 65 6e  20 74 68 65 20 74 6f 6b  |.!  When the tok|
00007d40  65 6e 20 69 73 20 61 20  6c 61 72 67 65 20 6e 75  |en is a large nu|
00007d50  6d 62 65 72 2c 20 69 74  20 6d 75 73 74 20 62 65  |mber, it must be|
00007d60  20 61 6e 20 61 64 6a 65  63 74 69 76 65 3a 0a 21  | an adjective:.!|
00007d70  20 20 72 65 6d 65 6d 62  65 72 20 74 68 65 20 61  |  remember the a|
00007d80  64 6a 65 63 74 69 76 65  20 6e 75 6d 62 65 72 20  |djective number |
00007d90  69 6e 20 74 68 65 20 22  70 61 74 74 65 72 6e 22  |in the "pattern"|
00007da0  2e 0a 0a 20 20 20 20 20  20 20 20 20 20 20 20 69  |...            i|
00007db0  66 20 28 74 6f 6b 65 6e  3e 31 38 30 29 0a 20 20  |f (token>180).  |
00007dc0  20 20 20 20 20 20 20 20  20 20 7b 20 20 20 70 61  |          {   pa|
00007dd0  74 74 65 72 6e 2d 2d 3e  70 63 6f 75 6e 74 20 3d  |ttern-->pcount =|
00007de0  20 31 30 30 30 2b 74 6f  6b 65 6e 3b 0a 0a 21 20  | 1000+token;..! |
00007df0  20 49 66 20 77 65 27 76  65 20 72 75 6e 20 6f 75  | If we've run ou|
00007e00  74 20 6f 66 20 74 68 65  20 70 6c 61 79 65 72 27  |t of the player'|
00007e10  73 20 69 6e 70 75 74 2c  20 62 75 74 20 73 74 69  |s input, but sti|
00007e20  6c 6c 20 68 61 76 65 20  70 61 72 61 6d 65 74 65  |ll have paramete|
00007e30  72 73 20 74 6f 0a 21 20  20 73 70 65 63 69 66 79  |rs to.!  specify|
00007e40  2c 20 77 65 20 67 6f 20  69 6e 74 6f 20 22 69 6e  |, we go into "in|
00007e50  66 65 72 22 20 6d 6f 64  65 2c 20 72 65 6d 65 6d  |fer" mode, remem|
00007e60  62 65 72 69 6e 67 20 77  68 65 72 65 20 77 65 20  |bering where we |
00007e70  61 72 65 20 61 6e 64 20  74 68 65 0a 21 20 20 61  |are and the.!  a|
00007e80  64 6a 65 63 74 69 76 65  20 77 65 20 61 72 65 20  |djective we are |
00007e90  69 6e 66 65 72 72 69 6e  67 2e 2e 2e 0a 0a 20 20  |inferring.....  |
00007ea0  20 20 20 20 20 20 20 20  20 20 20 20 20 20 69 66  |              if|
00007eb0  20 28 77 6e 20 3e 20 6e  75 6d 5f 77 6f 72 64 73  | (wn > num_words|
00007ec0  29 0a 20 20 20 20 20 20  20 20 20 20 20 20 20 20  |).              |
00007ed0  20 20 7b 20 20 20 69 66  20 28 69 6e 66 65 72 66  |  {   if (inferf|
00007ee0  72 6f 6d 3d 3d 30 20 26  26 20 70 61 72 61 6d 65  |rom==0 && parame|
00007ef0  74 65 72 73 3c 6c 69 6e  65 5f 61 64 64 72 65 73  |ters<line_addres|
00007f00  73 2d 3e 30 29 0a 20 20  20 20 20 20 20 20 20 20  |s->0).          |
00007f10  20 20 20 20 20 20 20 20  20 20 7b 20 69 6e 66 65  |          { infe|
00007f20  72 66 72 6f 6d 3d 70 63  6f 75 6e 74 3b 20 69 6e  |rfrom=pcount; in|
00007f30  66 65 72 77 6f 72 64 3d  74 6f 6b 65 6e 3b 20 7d  |ferword=token; }|
00007f40  0a 0a 21 20 20 4f 74 68  65 72 77 69 73 65 2c 20  |..!  Otherwise, |
00007f50  74 68 69 73 20 6c 69 6e  65 20 6d 75 73 74 20 62  |this line must b|
00007f60  65 20 77 72 6f 6e 67 2e  0a 0a 20 20 20 20 20 20  |e wrong...      |
00007f70  20 20 20 20 20 20 20 20  20 20 20 20 20 20 69 66  |              if|
00007f80  20 28 69 6e 66 65 72 66  72 6f 6d 3d 3d 30 29 20  | (inferfrom==0) |
00007f90  62 72 65 61 6b 3b 0a 20  20 20 20 20 20 20 20 20  |break;.         |
00007fa0  20 20 20 20 20 20 20 7d  0a 0a 21 20 20 57 68 65  |       }..!  Whe|
00007fb0  72 65 61 73 2c 20 69 66  20 74 68 65 20 70 6c 61  |reas, if the pla|
00007fc0  79 65 72 20 68 61 73 20  74 79 70 65 64 20 73 6f  |yer has typed so|
00007fd0  6d 65 74 68 69 6e 67 20  68 65 72 65 2c 20 73 65  |mething here, se|
00007fe0  65 20 69 66 20 69 74 20  69 73 20 74 68 65 0a 21  |e if it is the.!|
00007ff0  20 20 72 65 71 75 69 72  65 64 20 61 64 6a 65 63  |  required adjec|
00008000  74 69 76 65 2e 2e 2e 20  69 66 20 69 74 27 73 20  |tive... if it's |
00008010  77 72 6f 6e 67 2c 20 74  68 65 20 6c 69 6e 65 20  |wrong, the line |
00008020  6d 75 73 74 20 62 65 20  77 72 6f 6e 67 2c 0a 21  |must be wrong,.!|
00008030  20 20 62 75 74 20 69 66  20 69 74 27 73 20 72 69  |  but if it's ri|
00008040  67 68 74 2c 20 74 68 65  20 74 6f 6b 65 6e 20 69  |ght, the token i|
00008050  73 20 70 61 73 73 65 64  20 28 6a 75 6d 70 20 74  |s passed (jump t|
00008060  6f 20 66 69 6e 69 73 68  20 74 68 69 73 20 74 6f  |o finish this to|
00008070  6b 65 6e 29 2e 0a 0a 20  20 20 20 20 20 20 20 20  |ken)...         |
00008080  20 20 20 20 20 20 20 69  66 20 28 77 6e 20 3c 3d  |       if (wn <=|
00008090  20 6e 75 6d 5f 77 6f 72  64 73 20 26 26 20 74 6f  | num_words && to|
000080a0  6b 65 6e 7e 3d 41 64 6a  65 63 74 69 76 65 28 29  |ken~=Adjective()|
000080b0  29 20 62 72 65 61 6b 3b  0a 20 20 20 20 20 20 20  |) break;.       |
000080c0  20 20 20 20 20 20 20 20  20 6a 75 6d 70 20 54 6f  |         jump To|
000080d0  6b 65 6e 50 61 73 73 65  64 3b 0a 20 20 20 20 20  |kenPassed;.     |
000080e0  20 20 20 20 20 20 20 7d  0a 0a 21 20 20 2a 2a 2a  |       }..!  ***|
000080f0  2a 20 28 47 29 20 2a 2a  2a 2a 0a 21 20 20 43 68  |* (G) ****.!  Ch|
00008100  65 63 6b 20 6e 6f 77 20  74 6f 20 73 65 65 20 69  |eck now to see i|
00008110  66 20 74 68 65 20 70 6c  61 79 65 72 20 68 61 73  |f the player has|
00008120  20 65 6e 74 65 72 65 64  20 65 6e 6f 75 67 68 20  | entered enough |
00008130  70 61 72 61 6d 65 74 65  72 73 2e 2e 2e 0a 21 20  |parameters....! |
00008140  20 28 73 69 6e 63 65 20  6c 69 6e 65 5f 61 64 64  | (since line_add|
00008150  72 65 73 73 2d 3e 30 20  69 73 20 74 68 65 20 6e  |ress->0 is the n|
00008160  75 6d 62 65 72 20 6f 66  20 74 68 65 6d 29 0a 0a  |umber of them)..|
00008170  20 20 20 20 20 20 20 20  20 20 20 20 69 66 20 28  |            if (|
00008180  70 61 72 61 6d 65 74 65  72 73 20 3d 3d 20 6c 69  |parameters == li|
00008190  6e 65 5f 61 64 64 72 65  73 73 2d 3e 30 29 0a 20  |ne_address->0). |
000081a0  20 20 20 20 20 20 20 20  20 20 20 7b 20 20 0a 0a  |           {  ..|
000081b0  21 20 20 49 66 20 74 68  65 20 70 6c 61 79 65 72  |!  If the player|
000081c0  20 68 61 73 20 65 6e 74  65 72 65 64 20 65 6e 6f  | has entered eno|
000081d0  75 67 68 20 70 61 72 61  6d 65 74 65 72 73 20 61  |ugh parameters a|
000081e0  6c 72 65 61 64 79 20 62  75 74 20 74 68 65 72 65  |lready but there|
000081f0  27 73 20 73 74 69 6c 6c  0a 21 20 20 74 65 78 74  |'s still.!  text|
00008200  20 74 6f 20 77 61 64 65  20 74 68 72 6f 75 67 68  | to wade through|
00008210  3a 20 73 74 6f 72 65 20  74 68 65 20 70 61 74 74  |: store the patt|
00008220  65 72 6e 20 61 77 61 79  20 73 6f 20 61 73 20 74  |ern away so as t|
00008230  6f 20 62 65 20 61 62 6c  65 20 74 6f 20 70 72 6f  |o be able to pro|
00008240  64 75 63 65 0a 21 20 20  61 20 64 65 63 65 6e 74  |duce.!  a decent|
00008250  20 65 72 72 6f 72 20 6d  65 73 73 61 67 65 20 69  | error message i|
00008260  66 20 74 68 69 73 20 74  75 72 6e 73 20 6f 75 74  |f this turns out|
00008270  20 74 6f 20 62 65 20 74  68 65 20 62 65 73 74 20  | to be the best |
00008280  77 65 20 65 76 65 72 20  6d 61 6e 61 67 65 2c 0a  |we ever manage,.|
00008290  21 20 20 61 6e 64 20 69  6e 20 74 68 65 20 6d 65  |!  and in the me|
000082a0  61 6e 20 74 69 6d 65 20  67 69 76 65 20 75 70 20  |an time give up |
000082b0  6f 6e 20 74 68 69 73 20  6c 69 6e 65 0a 0a 21 20  |on this line..! |
000082c0  20 48 6f 77 65 76 65 72  2c 20 69 66 20 74 68 65  | However, if the|
000082d0  20 73 75 70 65 72 66 6c  75 6f 75 73 20 74 65 78  | superfluous tex|
000082e0  74 20 62 65 67 69 6e 73  20 77 69 74 68 20 61 20  |t begins with a |
000082f0  63 6f 6d 6d 61 2c 20 22  61 6e 64 22 20 6f 72 20  |comma, "and" or |
00008300  22 74 68 65 6e 22 20 74  68 65 6e 0a 21 20 20 74  |"then" then.!  t|
00008310  61 6b 65 20 74 68 61 74  20 74 6f 20 62 65 20 74  |ake that to be t|
00008320  68 65 20 73 74 61 72 74  20 6f 66 20 61 6e 6f 74  |he start of anot|
00008330  68 65 72 20 69 6e 73 74  72 75 63 74 69 6f 6e 0a  |her instruction.|
00008340  0a 20 20 20 20 20 20 20  20 20 20 20 20 20 20 20  |.               |
00008350  20 69 66 20 28 77 6e 20  3c 3d 20 6e 75 6d 5f 77  | if (wn <= num_w|
00008360  6f 72 64 73 29 0a 20 20  20 20 20 20 20 20 20 20  |ords).          |
00008370  20 20 20 20 20 20 7b 20  20 20 6c 3d 4e 65 78 74  |      {   l=Next|
00008380  57 6f 72 64 28 29 3b 0a  20 20 20 20 20 20 20 20  |Word();.        |
00008390  20 20 20 20 20 20 20 20  20 20 20 20 69 66 20 28  |            if (|
000083a0  6c 3d 3d 27 74 68 65 6e  27 20 6f 72 20 63 6f 6d  |l=='then' or com|
000083b0  6d 61 5f 77 6f 72 64 29  0a 20 20 20 20 20 20 20  |ma_word).       |
000083c0  20 20 20 20 20 20 20 20  20 20 20 20 20 7b 20 20  |             {  |
000083d0  20 68 65 6c 64 5f 62 61  63 6b 5f 6d 6f 64 65 3d  | held_back_mode=|
000083e0  31 3b 20 68 62 5f 77 6e  3d 77 6e 2d 31 3b 20 7d  |1; hb_wn=wn-1; }|
000083f0  0a 20 20 20 20 20 20 20  20 20 20 20 20 20 20 20  |.               |
00008400  20 20 20 20 20 65 6c 73  65 0a 20 20 20 20 20 20  |     else.      |
00008410  20 20 20 20 20 20 20 20  20 20 20 20 20 20 7b 20  |              { |
00008420  20 20 66 6f 72 20 28 6d  3d 30 3a 6d 3c 38 3a 6d  |  for (m=0:m<8:m|
00008430  2b 2b 29 20 70 61 74 74  65 72 6e 32 2d 2d 3e 6d  |++) pattern2-->m|
00008440  3d 70 61 74 74 65 72 6e  2d 2d 3e 6d 3b 0a 20 20  |=pattern-->m;.  |
00008450  20 20 20 20 20 20 20 20  20 20 20 20 20 20 20 20  |                |
00008460  20 20 20 20 20 20 70 63  6f 75 6e 74 32 3d 70 63  |      pcount2=pc|
00008470  6f 75 6e 74 3b 0a 20 20  20 20 20 20 20 20 20 20  |ount;.          |
00008480  20 20 20 20 20 20 20 20  20 20 20 20 20 20 65 74  |              et|
00008490  79 70 65 3d 55 50 54 4f  5f 50 45 3b 20 62 72 65  |ype=UPTO_PE; bre|
000084a0  61 6b 3b 0a 20 20 20 20  20 20 20 20 20 20 20 20  |ak;.            |
000084b0  20 20 20 20 20 20 20 20  7d 0a 20 20 20 20 20 20  |        }.      |
000084c0  20 20 20 20 20 20 20 20  20 20 7d 0a 0a 21 20 20  |          }..!  |
000084d0  4e 6f 77 2c 20 77 65 20  6d 61 79 20 6e 65 65 64  |Now, we may need|
000084e0  20 74 6f 20 72 65 76 69  73 65 20 74 68 65 20 6d  | to revise the m|
000084f0  75 6c 74 69 70 6c 65 20  6f 62 6a 65 63 74 20 62  |ultiple object b|
00008500  65 63 61 75 73 65 20 6f  66 20 74 68 65 20 73 69  |ecause of the si|
00008510  6e 67 6c 65 20 6f 6e 65  0a 21 20 20 77 65 20 6e  |ngle one.!  we n|
00008520  6f 77 20 6b 6e 6f 77 20  28 62 75 74 20 64 69 64  |ow know (but did|
00008530  6e 27 74 20 77 68 65 6e  20 74 68 65 20 6c 69 73  |n't when the lis|
00008540  74 20 77 61 73 20 64 72  61 77 6e 20 75 70 29 2e  |t was drawn up).|
00008550  0a 0a 20 20 20 20 20 20  20 20 20 20 20 20 20 20  |..              |
00008560  20 20 69 66 20 28 70 61  72 61 6d 65 74 65 72 73  |  if (parameters|
00008570  3e 3d 31 20 26 26 20 72  65 73 75 6c 74 73 2d 2d  |>=1 && results--|
00008580  3e 32 20 3d 3d 20 30 29  0a 20 20 20 20 20 20 20  |>2 == 0).       |
00008590  20 20 20 20 20 20 20 20  20 7b 20 20 20 6c 3d 52  |         {   l=R|
000085a0  65 76 69 73 65 4d 75 6c  74 69 28 72 65 73 75 6c  |eviseMulti(resul|
000085b0  74 73 2d 2d 3e 33 29 3b  0a 20 20 20 20 20 20 20  |ts-->3);.       |
000085c0  20 20 20 20 20 20 20 20  20 20 20 20 20 69 66 20  |             if |
000085d0  28 6c 7e 3d 30 29 20 7b  20 65 74 79 70 65 3d 6c  |(l~=0) { etype=l|
000085e0  3b 20 62 72 65 61 6b 3b  20 7d 0a 20 20 20 20 20  |; break; }.     |
000085f0  20 20 20 20 20 20 20 20  20 20 20 7d 0a 20 20 20  |           }.   |
00008600  20 20 20 20 20 20 20 20  20 20 20 20 20 69 66 20  |             if |
00008610  28 70 61 72 61 6d 65 74  65 72 73 3e 3d 32 20 26  |(parameters>=2 &|
00008620  26 20 72 65 73 75 6c 74  73 2d 2d 3e 33 20 3d 3d  |& results-->3 ==|
00008630  20 30 29 0a 20 20 20 20  20 20 20 20 20 20 20 20  | 0).            |
00008640  20 20 20 20 7b 20 20 20  6c 3d 52 65 76 69 73 65  |    {   l=Revise|
00008650  4d 75 6c 74 69 28 72 65  73 75 6c 74 73 2d 2d 3e  |Multi(results-->|
00008660  32 29 3b 0a 20 20 20 20  20 20 20 20 20 20 20 20  |2);.            |
00008670  20 20 20 20 20 20 20 20  69 66 20 28 6c 7e 3d 30  |        if (l~=0|
00008680  29 20 7b 20 65 74 79 70  65 3d 6c 3b 20 62 72 65  |) { etype=l; bre|
00008690  61 6b 3b 20 7d 0a 20 20  20 20 20 20 20 20 20 20  |ak; }.          |
000086a0  20 20 20 20 20 20 7d 0a  0a 20 20 20 20 20 20 20  |      }..       |
000086b0  20 20 20 20 20 20 20 20  20 69 66 20 28 70 61 72  |         if (par|
000086c0  73 65 72 5f 74 72 61 63  65 3e 3d 31 29 0a 20 20  |ser_trace>=1).  |
000086d0  20 20 20 20 20 20 20 20  20 20 20 20 20 20 20 20  |                |
000086e0  20 20 70 72 69 6e 74 20  22 5b 4c 69 6e 65 20 73  |  print "[Line s|
000086f0  75 63 63 65 73 73 66 75  6c 6c 79 20 70 61 72 73  |uccessfully pars|
00008700  65 64 5d 5e 22 3b 0a 0a  21 20 20 41 74 20 74 68  |ed]^";..!  At th|
00008710  69 73 20 70 6f 69 6e 74  20 74 68 65 20 6c 69 6e  |is point the lin|
00008720  65 20 68 61 73 20 77 6f  72 6b 65 64 20 6f 75 74  |e has worked out|
00008730  20 70 65 72 66 65 63 74  6c 79 2c 20 61 6e 64 20  | perfectly, and |
00008740  69 74 27 73 20 61 20 6d  61 74 74 65 72 20 6f 66  |it's a matter of|
00008750  0a 21 20 20 73 65 6e 64  69 6e 67 20 74 68 65 20  |.!  sending the |
00008760  72 65 73 75 6c 74 73 20  62 61 63 6b 2e 2e 2e 0a  |results back....|
00008770  21 20 20 2e 2e 2e 70 61  75 73 69 6e 67 20 74 6f  |!  ...pausing to|
00008780  20 65 78 70 6c 61 69 6e  20 61 6e 79 20 69 6e 66  | explain any inf|
00008790  65 72 65 6e 63 65 73 20  6d 61 64 65 20 28 75 73  |erences made (us|
000087a0  69 6e 67 20 74 68 65 20  70 61 74 74 65 72 6e 29  |ing the pattern)|
000087b0  2e 2e 2e 0a 0a 20 20 20  20 20 20 20 20 20 20 20  |.....           |
000087c0  20 20 20 20 20 69 66 20  28 69 6e 66 65 72 66 72  |     if (inferfr|
000087d0  6f 6d 7e 3d 30 29 0a 20  20 20 20 20 20 20 20 20  |om~=0).         |
000087e0  20 20 20 20 20 20 20 7b  20 20 20 70 72 69 6e 74  |       {   print|
000087f0  20 22 28 22 3b 20 50 72  69 6e 74 43 6f 6d 6d 61  | "("; PrintComma|
00008800  6e 64 28 69 6e 66 65 72  66 72 6f 6d 2c 31 29 3b  |nd(inferfrom,1);|
00008810  20 70 72 69 6e 74 20 22  29 5e 22 3b 0a 20 20 20  | print ")^";.   |
00008820  20 20 20 20 20 20 20 20  20 20 20 20 20 7d 0a 0a  |             }..|
00008830  21 20 20 2e 2e 2e 61 6e  64 20 74 6f 20 63 6f 70  |!  ...and to cop|
00008840  79 20 74 68 65 20 61 63  74 69 6f 6e 20 6e 75 6d  |y the action num|
00008850  62 65 72 2c 20 61 6e 64  20 74 68 65 20 6e 75 6d  |ber, and the num|
00008860  62 65 72 20 6f 66 20 70  61 72 61 6d 65 74 65 72  |ber of parameter|
00008870  73 2e 2e 2e 0a 0a 20 20  20 20 20 20 20 20 20 20  |s.....          |
00008880  20 20 20 20 20 20 72 65  73 75 6c 74 73 2d 2d 3e  |      results-->|
00008890  31 20 3d 20 6c 69 6e 65  5f 61 64 64 72 65 73 73  |1 = line_address|
000088a0  2d 3e 30 3b 0a 20 20 20  20 20 20 20 20 20 20 20  |->0;.           |
000088b0  20 20 20 20 20 72 65 73  75 6c 74 73 2d 2d 3e 30  |     results-->0|
000088c0  20 3d 20 6c 69 6e 65 5f  61 64 64 72 65 73 73 2d  | = line_address-|
000088d0  3e 37 3b 0a 0a 21 20 20  2e 2e 2e 61 6e 64 20 74  |>7;..!  ...and t|
000088e0  6f 20 72 65 73 65 74 20  22 69 74 22 2d 73 74 79  |o reset "it"-sty|
000088f0  6c 65 20 6f 62 6a 65 63  74 73 20 74 6f 20 74 68  |le objects to th|
00008900  65 20 66 69 72 73 74 20  6f 66 20 74 68 65 73 65  |e first of these|
00008910  20 70 61 72 61 6d 65 74  65 72 73 2c 20 69 66 0a  | parameters, if.|
00008920  21 20 20 74 68 65 72 65  20 69 73 20 6f 6e 65 20  |!  there is one |
00008930  28 61 6e 64 20 69 74 20  72 65 61 6c 6c 79 20 69  |(and it really i|
00008940  73 20 61 6e 20 6f 62 6a  65 63 74 29 2e 2e 2e 0a  |s an object)....|
00008950  0a 20 20 20 20 20 20 20  20 20 20 20 20 20 20 20  |.               |
00008960  20 69 66 20 28 70 61 72  61 6d 65 74 65 72 73 20  | if (parameters |
00008970  3e 20 30 20 26 26 20 72  65 73 75 6c 74 73 2d 2d  |> 0 && results--|
00008980  3e 32 20 3e 3d 20 32 29  0a 20 20 20 20 20 20 20  |>2 >= 2).       |
00008990  20 20 20 20 20 20 20 20  20 20 20 20 20 52 65 73  |             Res|
000089a0  65 74 56 61 67 75 65 57  6f 72 64 73 28 72 65 73  |etVagueWords(res|
000089b0  75 6c 74 73 2d 2d 3e 32  29 3b 0a 0a 21 20 20 2e  |ults-->2);..!  .|
000089c0  2e 2e 61 6e 64 20 64 65  63 6c 61 72 65 20 74 68  |..and declare th|
000089d0  65 20 75 73 65 72 27 73  20 69 6e 70 75 74 20 74  |e user's input t|
000089e0  6f 20 62 65 20 65 72 72  6f 72 20 66 72 65 65 2e  |o be error free.|
000089f0  2e 2e 0a 0a 20 20 20 20  20 20 20 20 20 20 20 20  |....            |
00008a00  20 20 20 20 6f 6f 70 73  5f 66 72 6f 6d 20 3d 20  |    oops_from = |
00008a10  30 3b 0a 0a 21 20 20 2e  2e 2e 61 6e 64 20 77 6f  |0;..!  ...and wo|
00008a20  72 72 79 20 61 62 6f 75  74 20 74 68 65 20 63 61  |rry about the ca|
00008a30  73 65 20 77 68 65 72 65  20 61 6e 20 6f 62 6a 65  |se where an obje|
00008a40  63 74 20 77 61 73 20 61  6c 6c 6f 77 65 64 20 61  |ct was allowed a|
00008a50  73 20 61 20 70 61 72 61  6d 65 74 65 72 0a 21 20  |s a parameter.! |
00008a60  20 65 76 65 6e 20 74 68  6f 75 67 68 20 74 68 65  | even though the|
00008a70  20 70 6c 61 79 65 72 20  77 61 73 6e 27 74 20 68  | player wasn't h|
00008a80  6f 6c 64 69 6e 67 20 69  74 20 61 6e 64 20 73 68  |olding it and sh|
00008a90  6f 75 6c 64 20 68 61 76  65 20 62 65 65 6e 3a 20  |ould have been: |
00008aa0  69 6e 20 74 68 69 73 0a  21 20 20 65 76 65 6e 74  |in this.!  event|
00008ab0  2c 20 6b 65 65 70 20 74  68 65 20 72 65 73 75 6c  |, keep the resul|
00008ac0  74 73 20 66 6f 72 20 6e  65 78 74 20 74 69 6d 65  |ts for next time|
00008ad0  20 72 6f 75 6e 64 2c 20  67 6f 20 69 6e 74 6f 20  | round, go into |
00008ae0  22 6e 6f 74 20 68 6f 6c  64 69 6e 67 22 20 6d 6f  |"not holding" mo|
00008af0  64 65 2c 0a 21 20 20 61  6e 64 20 66 6f 72 20 6e  |de,.!  and for n|
00008b00  6f 77 20 74 65 6c 6c 20  74 68 65 20 70 6c 61 79  |ow tell the play|
00008b10  65 72 20 77 68 61 74 27  73 20 68 61 70 70 65 6e  |er what's happen|
00008b20  69 6e 67 20 61 6e 64 20  72 65 74 75 72 6e 20 61  |ing and return a|
00008b30  20 22 74 61 6b 65 22 20  72 65 71 75 65 73 74 0a  | "take" request.|
00008b40  21 20 20 69 6e 73 74 65  61 64 2e 2e 2e 0a 0a 20  |!  instead..... |
00008b50  20 20 20 20 20 20 20 20  20 20 20 20 20 20 20 69  |               i|
00008b60  66 20 28 6e 6f 74 5f 68  6f 6c 64 69 6e 67 7e 3d  |f (not_holding~=|
00008b70  30 20 26 26 20 61 63 74  6f 72 3d 3d 70 6c 61 79  |0 && actor==play|
00008b80  65 72 29 0a 20 20 20 20  20 20 20 20 20 20 20 20  |er).            |
00008b90  20 20 20 20 7b 20 20 20  6e 6f 74 68 65 6c 64 5f  |    {   notheld_|
00008ba0  6d 6f 64 65 3d 31 3b 0a  20 20 20 20 20 20 20 20  |mode=1;.        |
00008bb0  20 20 20 20 20 20 20 20  20 20 20 20 66 6f 72 20  |            for |
00008bc0  28 69 3d 30 3a 69 3c 38  3a 69 2b 2b 29 20 6b 65  |(i=0:i<8:i++) ke|
00008bd0  70 74 5f 72 65 73 75 6c  74 73 2d 2d 3e 69 20 3d  |pt_results-->i =|
00008be0  20 72 65 73 75 6c 74 73  2d 2d 3e 69 3b 0a 20 20  | results-->i;.  |
00008bf0  20 20 20 20 20 20 20 20  20 20 20 20 20 20 20 20  |                |
00008c00  20 20 72 65 73 75 6c 74  73 2d 2d 3e 30 20 3d 20  |  results-->0 = |
00008c10  23 23 54 61 6b 65 3b 0a  20 20 20 20 20 20 20 20  |##Take;.        |
00008c20  20 20 20 20 20 20 20 20  20 20 20 20 72 65 73 75  |            resu|
00008c30  6c 74 73 2d 2d 3e 31 20  3d 20 31 3b 0a 20 20 20  |lts-->1 = 1;.   |
00008c40  20 20 20 20 20 20 20 20  20 20 20 20 20 20 20 20  |                |
00008c50  20 72 65 73 75 6c 74 73  2d 2d 3e 32 20 3d 20 6e  | results-->2 = n|
00008c60  6f 74 5f 68 6f 6c 64 69  6e 67 3b 0a 20 20 20 20  |ot_holding;.    |
00008c70  20 20 20 20 20 20 20 20  20 20 20 20 20 20 20 20  |                |
00008c80  70 72 69 6e 74 20 22 28  66 69 72 73 74 20 74 61  |print "(first ta|
00008c90  6b 69 6e 67 20 22 3b 20  44 65 66 41 72 74 28 6e  |king "; DefArt(n|
00008ca0  6f 74 5f 68 6f 6c 64 69  6e 67 29 3b 20 70 72 69  |ot_holding); pri|
00008cb0  6e 74 20 22 29 5e 22 3b  0a 20 20 20 20 20 20 20  |nt ")^";.       |
00008cc0  20 20 20 20 20 20 20 20  20 7d 0a 0a 21 20 20 28  |         }..!  (|
00008cd0  4e 6f 74 69 63 65 20 74  68 61 74 20 69 6d 70 6c  |Notice that impl|
00008ce0  69 63 69 74 20 74 61 6b  65 73 20 61 72 65 20 6f  |icit takes are o|
00008cf0  6e 6c 79 20 67 65 6e 65  72 61 74 65 64 20 66 6f  |nly generated fo|
00008d00  72 20 74 68 65 20 70 6c  61 79 65 72 2c 20 61 6e  |r the player, an|
00008d10  64 20 6e 6f 74 0a 21 20  20 66 6f 72 20 6f 74 68  |d not.!  for oth|
00008d20  65 72 20 61 63 74 6f 72  73 2e 20 20 54 68 69 73  |er actors.  This|
00008d30  20 61 76 6f 69 64 73 20  65 6e 74 69 72 65 6c 79  | avoids entirely|
00008d40  20 6c 6f 67 69 63 61 6c  2c 20 62 75 74 20 6d 69  | logical, but mi|
00008d50  73 6c 65 61 64 69 6e 67  2c 20 74 65 78 74 0a 21  |sleading, text.!|
00008d60  20 20 62 65 69 6e 67 20  70 72 69 6e 74 65 64 2e  |  being printed.|
00008d70  29 0a 0a 21 20 20 2e 2e  2e 61 6e 64 20 66 69 6e  |)..!  ...and fin|
00008d80  69 73 68 2e 0a 0a 20 20  20 20 20 20 20 20 20 20  |ish...          |
00008d90  20 20 20 20 20 20 69 66  20 28 68 65 6c 64 5f 62  |      if (held_b|
00008da0  61 63 6b 5f 6d 6f 64 65  3d 3d 31 29 20 7b 20 77  |ack_mode==1) { w|
00008db0  6e 3d 68 62 5f 77 6e 3b  20 6a 75 6d 70 20 4c 6f  |n=hb_wn; jump Lo|
00008dc0  6f 6b 46 6f 72 4d 6f 72  65 3b 20 7d 0a 20 20 20  |okForMore; }.   |
00008dd0  20 20 20 20 20 20 20 20  20 20 20 20 20 72 74 72  |             rtr|
00008de0  75 65 3b 0a 20 20 20 20  20 20 20 20 20 20 20 20  |ue;.            |
00008df0  7d 0a 0a 21 20 20 4f 74  68 65 72 77 69 73 65 2c  |}..!  Otherwise,|
00008e00  20 74 68 65 20 70 6c 61  79 65 72 20 73 74 69 6c  | the player stil|
00008e10  6c 20 68 61 73 20 61 74  20 6c 65 61 73 74 20 6f  |l has at least o|
00008e20  6e 65 20 70 61 72 61 6d  65 74 65 72 20 74 6f 20  |ne parameter to |
00008e30  73 70 65 63 69 66 79 3a  20 61 6e 0a 21 20 20 6f  |specify: an.!  o|
00008e40  62 6a 65 63 74 20 6f 66  20 73 6f 6d 65 20 6b 69  |bject of some ki|
00008e50  6e 64 20 69 73 20 65 78  70 65 63 74 65 64 2c 20  |nd is expected, |
00008e60  61 6e 64 20 74 68 69 73  20 77 65 20 68 61 6e 64  |and this we hand|
00008e70  20 6f 76 65 72 20 74 6f  3a 0a 0a 20 20 20 20 20  | over to:..     |
00008e80  20 20 20 20 20 20 20 6c  3d 50 61 72 73 65 4f 62  |       l=ParseOb|
00008e90  6a 65 63 74 4c 69 73 74  28 72 65 73 75 6c 74 73  |jectList(results|
00008ea0  2c 74 6f 6b 65 6e 29 3b  0a 20 20 20 20 20 20 20  |,token);.       |
00008eb0  20 20 20 20 20 69 66 20  28 70 61 72 73 65 72 5f  |     if (parser_|
00008ec0  74 72 61 63 65 3e 3d 33  29 0a 20 20 20 20 20 20  |trace>=3).      |
00008ed0  20 20 20 20 20 20 7b 20  20 20 70 72 69 6e 74 20  |      {   print |
00008ee0  22 20 20 5b 50 61 72 73  65 20 6f 62 6a 65 63 74  |"  [Parse object|
00008ef0  20 6c 69 73 74 20 72 65  70 6c 69 65 64 20 77 69  | list replied wi|
00008f00  74 68 22 3b 0a 20 20 20  20 20 20 20 20 20 20 20  |th";.           |
00008f10  20 20 20 20 20 69 66 20  28 6c 3d 3d 31 30 30 30  |     if (l==1000|
00008f20  29 20 70 72 69 6e 74 20  22 20 72 65 2d 70 61 72  |) print " re-par|
00008f30  73 65 20 72 65 71 75 65  73 74 5d 5e 22 3b 0a 20  |se request]^";. |
00008f40  20 20 20 20 20 20 20 20  20 20 20 20 20 20 20 69  |               i|
00008f50  66 20 28 6c 3d 3d 30 29  20 70 72 69 6e 74 20 22  |f (l==0) print "|
00008f60  20 74 6f 6b 65 6e 20 66  61 69 6c 65 64 2c 20 65  | token failed, e|
00008f70  72 72 6f 72 20 74 79 70  65 20 22 2c 20 65 74 79  |rror type ", ety|
00008f80  70 65 2c 20 22 5d 5e 22  3b 0a 20 20 20 20 20 20  |pe, "]^";.      |
00008f90  20 20 20 20 20 20 20 20  20 20 69 66 20 28 6c 3d  |          if (l=|
00008fa0  3d 31 29 20 70 72 69 6e  74 20 22 20 74 6f 6b 65  |=1) print " toke|
00008fb0  6e 20 61 63 63 65 70 74  65 64 5d 5e 22 3b 0a 20  |n accepted]^";. |
00008fc0  20 20 20 20 20 20 20 20  20 20 20 7d 0a 20 20 20  |           }.   |
00008fd0  20 20 20 20 20 20 20 20  20 69 66 20 28 6c 3d 3d  |         if (l==|
00008fe0  31 30 30 30 29 20 6a 75  6d 70 20 52 65 50 61 72  |1000) jump RePar|
00008ff0  73 65 3b 0a 20 20 20 20  20 20 20 20 20 20 20 20  |se;.            |
00009000  69 66 20 28 6c 3d 3d 30  29 20 20 20 20 62 72 65  |if (l==0)    bre|
00009010  61 6b 3b 0a 0a 21 20 20  54 68 65 20 74 6f 6b 65  |ak;..!  The toke|
00009020  6e 20 68 61 73 20 62 65  65 6e 20 73 75 63 63 65  |n has been succe|
00009030  73 73 66 75 6c 6c 79 20  70 61 73 73 65 64 3b 20  |ssfully passed; |
00009040  77 65 20 61 72 65 20 72  65 61 64 79 20 66 6f 72  |we are ready for|
00009050  20 74 68 65 20 6e 65 78  74 2e 0a 0a 20 20 20 20  | the next...    |
00009060  20 20 20 20 20 20 20 20  2e 54 6f 6b 65 6e 50 61  |        .TokenPa|
00009070  73 73 65 64 3b 0a 20 20  20 20 20 20 20 20 7d 0a  |ssed;.        }.|
00009080  0a 21 20 20 42 75 74 20  69 66 20 77 65 20 67 65  |.!  But if we ge|
00009090  74 20 68 65 72 65 20 69  74 20 6d 65 61 6e 73 20  |t here it means |
000090a0  74 68 61 74 20 74 68 65  20 6c 69 6e 65 20 66 61  |that the line fa|
000090b0  69 6c 65 64 20 73 6f 6d  65 77 68 65 72 65 2c 20  |iled somewhere, |
000090c0  73 6f 20 77 65 20 63 6f  6e 74 69 6e 75 65 0a 21  |so we continue.!|
000090d0  20 20 74 68 65 20 6f 75  74 65 72 20 66 6f 72 20  |  the outer for |
000090e0  6c 6f 6f 70 20 61 6e 64  20 74 72 79 20 74 68 65  |loop and try the|
000090f0  20 6e 65 78 74 20 6c 69  6e 65 2e 2e 2e 0a 0a 20  | next line..... |
00009100  20 20 20 20 20 20 20 69  66 20 28 65 74 79 70 65  |       if (etype|
00009110  3e 62 65 73 74 5f 65 74  79 70 65 29 20 62 65 73  |>best_etype) bes|
00009120  74 5f 65 74 79 70 65 3d  65 74 79 70 65 3b 0a 20  |t_etype=etype;. |
00009130  20 20 7d 0a 0a 21 20 20  53 6f 20 74 68 61 74 20  |  }..!  So that |
00009140  69 66 20 77 65 20 67 65  74 20 68 65 72 65 2c 20  |if we get here, |
00009150  65 61 63 68 20 6c 69 6e  65 20 66 6f 72 20 74 68  |each line for th|
00009160  65 20 73 70 65 63 69 66  69 65 64 20 76 65 72 62  |e specified verb|
00009170  20 68 61 73 20 66 61 69  6c 65 64 2e 0a 0a 21 20  | has failed...! |
00009180  20 2a 2a 2a 2a 20 28 48  29 20 2a 2a 2a 2a 0a 0a  | **** (H) ****..|
00009190  20 20 2e 47 69 76 65 45  72 72 6f 72 3b 0a 20 20  |  .GiveError;.  |
000091a0  20 20 20 20 20 20 65 74  79 70 65 3d 62 65 73 74  |      etype=best|
000091b0  5f 65 74 79 70 65 3b 0a  0a 21 20 20 45 72 72 6f  |_etype;..!  Erro|
000091c0  72 73 20 61 72 65 20 68  61 6e 64 6c 65 64 20 64  |rs are handled d|
000091d0  69 66 66 65 72 65 6e 74  6c 79 20 64 65 70 65 6e  |ifferently depen|
000091e0  64 69 6e 67 20 6f 6e 20  77 68 6f 20 77 61 73 20  |ding on who was |
000091f0  74 61 6c 6b 69 6e 67 2e  0a 0a 21 20 20 49 66 20  |talking...!  If |
00009200  74 68 65 20 63 6f 6d 6d  61 6e 64 20 77 61 73 20  |the command was |
00009210  61 64 64 72 65 73 73 65  64 20 74 6f 20 73 6f 6d  |addressed to som|
00009220  65 62 6f 64 79 20 65 6c  73 65 20 28 65 67 2c 20  |ebody else (eg, |
00009230  22 64 77 61 72 66 2c 20  73 66 67 68 22 29 20 74  |"dwarf, sfgh") t|
00009240  68 65 6e 0a 21 20 20 69  74 20 69 73 20 74 61 6b  |hen.!  it is tak|
00009250  65 6e 20 61 73 20 63 6f  6e 76 65 72 73 61 74 69  |en as conversati|
00009260  6f 6e 20 77 68 69 63 68  20 74 68 65 20 70 61 72  |on which the par|
00009270  73 65 72 20 68 61 73 20  6e 6f 20 62 75 73 69 6e  |ser has no busin|
00009280  65 73 73 20 69 6e 20 64  69 73 61 6c 6c 6f 77 69  |ess in disallowi|
00009290  6e 67 2e 0a 21 20 20 49  6e 20 6f 72 64 65 72 20  |ng..!  In order |
000092a0  74 6f 20 6d 61 6b 65 20  69 74 20 65 61 73 69 65  |to make it easie|
000092b0  72 20 66 6f 72 20 74 68  65 20 68 6f 73 74 20 67  |r for the host g|
000092c0  61 6d 65 20 74 6f 20 77  6f 72 6b 20 6f 75 74 20  |ame to work out |
000092d0  77 68 61 74 20 77 61 73  20 73 61 69 64 2c 20 74  |what was said, t|
000092e0  68 65 0a 21 20 20 22 76  65 72 62 22 20 77 6f 72  |he.!  "verb" wor|
000092f0  64 20 28 65 67 2c 20 22  73 66 67 68 22 29 20 69  |d (eg, "sfgh") i|
00009300  73 20 70 61 72 73 65 64  20 61 73 20 61 20 6e 75  |s parsed as a nu|
00009310  6d 62 65 72 20 61 6e 64  20 61 73 20 61 20 64 69  |mber and as a di|
00009320  63 74 69 6f 6e 61 72 79  20 65 6e 74 72 79 2c 0a  |ctionary entry,.|
00009330  21 20 20 61 6e 64 20 74  68 65 20 70 61 72 73 65  |!  and the parse|
00009340  72 20 72 65 74 75 72 6e  73 20 61 73 20 69 66 20  |r returns as if |
00009350  74 68 65 20 70 6c 61 79  65 72 20 68 61 64 20 74  |the player had t|
00009360  79 70 65 64 0a 21 0a 21  20 20 20 20 20 61 6e 73  |yped.!.!     ans|
00009370  77 65 72 20 73 66 67 68  20 74 6f 20 64 77 61 72  |wer sfgh to dwar|
00009380  66 20 20 20 0a 21 0a 21  20 20 77 69 74 68 20 74  |f   .!.!  with t|
00009390  68 65 20 67 6c 6f 62 61  6c 73 20 73 70 65 63 69  |he globals speci|
000093a0  61 6c 5f 77 6f 72 64 20  61 6e 64 20 73 70 65 63  |al_word and spec|
000093b0  69 61 6c 5f 6e 75 6d 62  65 72 20 73 65 74 20 61  |ial_number set a|
000093c0  63 63 6f 72 64 69 6e 67  6c 79 2e 0a 0a 21 20 20  |ccordingly...!  |
000093d0  28 54 68 69 73 20 69 73  20 63 6f 6e 76 65 6e 69  |(This is conveni|
000093e0  65 6e 74 20 66 6f 72 2c  20 73 61 79 2c 20 22 63  |ent for, say, "c|
000093f0  6f 6d 70 75 74 65 72 2c  20 32 34 35 31 22 20 6f  |omputer, 2451" o|
00009400  72 20 22 67 75 61 72 64  2c 20 62 6c 75 65 22 29  |r "guard, blue")|
00009410  2e 0a 0a 20 20 20 20 69  66 20 28 61 63 74 6f 72  |...    if (actor|
00009420  7e 3d 70 6c 61 79 65 72  29 0a 20 20 20 20 7b 20  |~=player).    { |
00009430  20 20 73 70 65 63 69 61  6c 5f 6e 75 6d 62 65 72  |  special_number|
00009440  3d 54 72 79 4e 75 6d 62  65 72 28 76 65 72 62 5f  |=TryNumber(verb_|
00009450  77 6f 72 64 6e 75 6d 29  3b 0a 20 20 20 20 20 20  |wordnum);.      |
00009460  20 20 77 6e 3d 76 65 72  62 5f 77 6f 72 64 6e 75  |  wn=verb_wordnu|
00009470  6d 3b 0a 20 20 20 20 20  20 20 20 73 70 65 63 69  |m;.        speci|
00009480  61 6c 5f 77 6f 72 64 3d  4e 65 78 74 57 6f 72 64  |al_word=NextWord|
00009490  28 29 3b 0a 20 20 20 20  20 20 20 20 61 63 74 69  |();.        acti|
000094a0  6f 6e 3d 23 23 41 6e 73  77 65 72 3b 0a 20 20 20  |on=##Answer;.   |
000094b0  20 20 20 20 20 69 6e 70  31 3d 31 3b 20 69 6e 70  |     inp1=1; inp|
000094c0  32 3d 61 63 74 6f 72 3b  20 61 63 74 6f 72 3d 70  |2=actor; actor=p|
000094d0  6c 61 79 65 72 3b 0a 20  20 20 20 20 20 20 20 72  |layer;.        r|
000094e0  74 72 75 65 3b 0a 20 20  20 20 7d 0a 0a 21 20 20  |true;.    }..!  |
000094f0  2a 2a 2a 2a 20 28 49 29  20 2a 2a 2a 2a 0a 0a 21  |**** (I) ****..!|
00009500  20 20 49 66 20 74 68 65  20 70 6c 61 79 65 72 20  |  If the player |
00009510  77 61 73 20 74 68 65 20  61 63 74 6f 72 20 28 65  |was the actor (e|
00009520  67 2c 20 69 6e 20 22 74  61 6b 65 20 64 66 67 68  |g, in "take dfgh|
00009530  68 22 29 20 74 68 65 20  65 72 72 6f 72 20 6d 75  |h") the error mu|
00009540  73 74 20 62 65 20 70 72  69 6e 74 65 64 2c 0a 21  |st be printed,.!|
00009550  20 20 61 6e 64 20 66 72  65 73 68 20 69 6e 70 75  |  and fresh inpu|
00009560  74 20 63 61 6c 6c 65 64  20 66 6f 72 2e 20 20 49  |t called for.  I|
00009570  6e 20 74 68 72 65 65 20  63 61 73 65 73 20 74 68  |n three cases th|
00009580  65 20 6f 6f 70 73 20 77  6f 72 64 20 6d 75 73 74  |e oops word must|
00009590  20 62 65 20 6a 69 67 67  6c 65 64 2e 0a 0a 20 20  | be jiggled...  |
000095a0  20 20 69 66 20 28 50 61  72 73 65 72 45 72 72 6f  |  if (ParserErro|
000095b0  72 28 65 74 79 70 65 29  7e 3d 30 29 20 6a 75 6d  |r(etype)~=0) jum|
000095c0  70 20 52 65 54 79 70 65  3b 0a 0a 20 20 20 20 69  |p ReType;..    i|
000095d0  66 20 28 65 74 79 70 65  3d 3d 53 54 55 43 4b 5f  |f (etype==STUCK_|
000095e0  50 45 29 0a 20 20 20 20  20 20 20 20 20 20 20 20  |PE).            |
000095f0  20 7b 20 20 20 70 72 69  6e 74 20 22 49 20 64 69  | {   print "I di|
00009600  64 6e 27 74 20 75 6e 64  65 72 73 74 61 6e 64 20  |dn't understand |
00009610  74 68 61 74 20 73 65 6e  74 65 6e 63 65 2e 5e 22  |that sentence.^"|
00009620  3b 20 6f 6f 70 73 5f 66  72 6f 6d 3d 31 3b 20 7d  |; oops_from=1; }|
00009630  0a 20 20 20 20 69 66 20  28 65 74 79 70 65 3d 3d  |.    if (etype==|
00009640  55 50 54 4f 5f 50 45 29  0a 20 20 20 20 20 20 20  |UPTO_PE).       |
00009650  20 20 20 20 20 20 7b 20  20 20 70 72 69 6e 74 20  |      {   print |
00009660  22 49 20 6f 6e 6c 79 20  75 6e 64 65 72 73 74 6f  |"I only understo|
00009670  6f 64 20 79 6f 75 20 61  73 20 66 61 72 20 61 73  |od you as far as|
00009680  20 77 61 6e 74 69 6e 67  20 74 6f 20 22 3b 0a 20  | wanting to ";. |
00009690  20 20 20 20 20 20 20 20  20 20 20 20 20 20 20 20  |                |
000096a0  66 6f 72 20 28 6d 3d 30  3a 6d 3c 38 3a 6d 2b 2b  |for (m=0:m<8:m++|
000096b0  29 20 70 61 74 74 65 72  6e 2d 2d 3e 6d 20 3d 20  |) pattern-->m = |
000096c0  70 61 74 74 65 72 6e 32  2d 2d 3e 6d 3b 0a 20 20  |pattern2-->m;.  |
000096d0  20 20 20 20 20 20 20 20  20 20 20 20 20 20 20 70  |               p|
000096e0  63 6f 75 6e 74 3d 70 63  6f 75 6e 74 32 3b 20 50  |count=pcount2; P|
000096f0  72 69 6e 74 43 6f 6d 6d  61 6e 64 28 30 2c 31 29  |rintCommand(0,1)|
00009700  3b 20 70 72 69 6e 74 20  22 2e 5e 22 3b 0a 20 20  |; print ".^";.  |
00009710  20 20 20 20 20 20 20 20  20 20 20 7d 0a 20 20 20  |           }.   |
00009720  20 69 66 20 28 65 74 79  70 65 3d 3d 43 41 4e 54  | if (etype==CANT|
00009730  53 45 45 5f 50 45 29 0a  20 20 20 20 20 20 20 20  |SEE_PE).        |
00009740  20 20 20 20 20 7b 20 20  20 70 72 69 6e 74 20 22  |     {   print "|
00009750  59 6f 75 20 63 61 6e 27  74 20 73 65 65 20 61 6e  |You can't see an|
00009760  79 20 73 75 63 68 20 74  68 69 6e 67 2e 5e 22 3b  |y such thing.^";|
00009770  0a 20 20 20 20 20 20 20  20 20 20 20 20 20 20 20  |.               |
00009780  20 20 6f 6f 70 73 5f 66  72 6f 6d 3d 73 61 76 65  |  oops_from=save|
00009790  64 5f 6f 6f 70 73 3b 20  7d 0a 20 20 20 20 69 66  |d_oops; }.    if|
000097a0  20 28 65 74 79 70 65 3d  3d 54 4f 4f 4c 49 54 5f  | (etype==TOOLIT_|
000097b0  50 45 29 0a 20 20 20 20  20 20 20 20 20 20 20 20  |PE).            |
000097c0  20 20 20 20 20 70 72 69  6e 74 20 22 59 6f 75 20  |     print "You |
000097d0  73 65 65 6d 20 74 6f 20  68 61 76 65 20 73 61 69  |seem to have sai|
000097e0  64 20 74 6f 6f 20 6c 69  74 74 6c 65 21 5e 22 3b  |d too little!^";|
000097f0  0a 20 20 20 20 69 66 20  28 65 74 79 70 65 3d 3d  |.    if (etype==|
00009800  4e 4f 54 48 45 4c 44 5f  50 45 29 0a 20 20 20 20  |NOTHELD_PE).    |
00009810  20 20 20 20 20 20 20 20  20 7b 20 20 20 70 72 69  |         {   pri|
00009820  6e 74 20 22 59 6f 75 20  61 72 65 6e 27 74 20 68  |nt "You aren't h|
00009830  6f 6c 64 69 6e 67 20 74  68 61 74 21 5e 22 3b 0a  |olding that!^";.|
00009840  20 20 20 20 20 20 20 20  20 20 20 20 20 20 20 20  |                |
00009850  20 6f 6f 70 73 5f 66 72  6f 6d 3d 73 61 76 65 64  | oops_from=saved|
00009860  5f 6f 6f 70 73 3b 20 7d  0a 20 20 20 20 69 66 20  |_oops; }.    if |
00009870  28 65 74 79 70 65 3d 3d  4d 55 4c 54 49 5f 50 45  |(etype==MULTI_PE|
00009880  29 0a 20 20 20 20 20 20  20 20 20 20 20 20 20 20  |).              |
00009890  20 20 20 70 72 69 6e 74  20 22 59 6f 75 20 63 61  |   print "You ca|
000098a0  6e 27 74 20 75 73 65 20  6d 75 6c 74 69 70 6c 65  |n't use multiple|
000098b0  20 6f 62 6a 65 63 74 73  20 77 69 74 68 20 74 68  | objects with th|
000098c0  61 74 20 76 65 72 62 2e  5e 22 3b 0a 20 20 20 20  |at verb.^";.    |
000098d0  69 66 20 28 65 74 79 70  65 3d 3d 4d 4d 55 4c 54  |if (etype==MMULT|
000098e0  49 5f 50 45 29 0a 20 20  20 20 20 20 20 20 20 20  |I_PE).          |
000098f0  20 20 20 20 20 20 20 70  72 69 6e 74 20 22 59 6f  |       print "Yo|
00009900  75 20 63 61 6e 20 6f 6e  6c 79 20 75 73 65 20 6d  |u can only use m|
00009910  75 6c 74 69 70 6c 65 20  6f 62 6a 65 63 74 73 20  |ultiple objects |
00009920  6f 6e 63 65 20 6f 6e 20  61 20 6c 69 6e 65 2e 5e  |once on a line.^|
00009930  22 3b 0a 20 20 20 20 69  66 20 28 65 74 79 70 65  |";.    if (etype|
00009940  3d 3d 56 41 47 55 45 5f  50 45 29 0a 20 20 20 20  |==VAGUE_PE).    |
00009950  20 20 20 20 20 20 20 20  20 7b 20 20 20 70 72 69  |         {   pri|
00009960  6e 74 20 22 49 27 6d 20  6e 6f 74 20 73 75 72 65  |nt "I'm not sure|
00009970  20 77 68 61 74 20 7e 22  3b 20 70 72 69 6e 74 5f  | what ~"; print_|
00009980  61 64 64 72 20 76 61 67  75 65 5f 77 6f 72 64 3b  |addr vague_word;|
00009990  0a 20 20 20 20 20 20 20  20 20 20 20 20 20 20 20  |.               |
000099a0  20 20 70 72 69 6e 74 20  22 7e 20 72 65 66 65 72  |  print "~ refer|
000099b0  73 20 74 6f 2e 5e 22 3b  20 7d 0a 20 20 20 20 69  |s to.^"; }.    i|
000099c0  66 20 28 65 74 79 70 65  3d 3d 45 58 43 45 50 54  |f (etype==EXCEPT|
000099d0  5f 50 45 29 0a 20 20 20  20 20 20 20 20 20 20 20  |_PE).           |
000099e0  20 20 20 20 20 20 70 72  69 6e 74 20 22 59 6f 75  |      print "You|
000099f0  20 65 78 63 65 70 74 65  64 20 73 6f 6d 65 74 68  | excepted someth|
00009a00  69 6e 67 20 6e 6f 74 20  69 6e 63 6c 75 64 65 64  |ing not included|
00009a10  20 61 6e 79 77 61 79 21  5e 22 3b 0a 20 20 20 20  | anyway!^";.    |
00009a20  69 66 20 28 65 74 79 70  65 3d 3d 41 4e 49 4d 41  |if (etype==ANIMA|
00009a30  5f 50 45 29 0a 20 20 20  20 20 20 20 20 20 20 20  |_PE).           |
00009a40  20 20 20 20 20 20 70 72  69 6e 74 20 22 59 6f 75  |      print "You|
00009a50  20 63 61 6e 20 6f 6e 6c  79 20 64 6f 20 74 68 61  | can only do tha|
00009a60  74 20 74 6f 20 73 6f 6d  65 74 68 69 6e 67 20 61  |t to something a|
00009a70  6e 69 6d 61 74 65 2e 5e  22 3b 0a 20 20 20 20 69  |nimate.^";.    i|
00009a80  66 20 28 65 74 79 70 65  3d 3d 56 45 52 42 5f 50  |f (etype==VERB_P|
00009a90  45 29 0a 20 20 20 20 20  20 20 20 20 20 20 20 20  |E).             |
00009aa0  20 20 20 20 70 72 69 6e  74 20 22 54 68 61 74 27  |    print "That'|
00009ab0  73 20 6e 6f 74 20 61 20  76 65 72 62 20 49 20 72  |s not a verb I r|
00009ac0  65 63 6f 67 6e 69 73 65  2e 5e 22 3b 0a 20 20 20  |ecognise.^";.   |
00009ad0  20 69 66 20 28 65 74 79  70 65 3d 3d 53 43 45 4e  | if (etype==SCEN|
00009ae0  45 52 59 5f 50 45 29 0a  20 20 20 20 20 20 20 20  |ERY_PE).        |
00009af0  20 20 20 20 20 20 20 20  20 70 72 69 6e 74 20 22  |         print "|
00009b00  54 68 61 74 27 73 20 6e  6f 74 20 73 6f 6d 65 74  |That's not somet|
00009b10  68 69 6e 67 20 79 6f 75  20 6e 65 65 64 20 74 6f  |hing you need to|
00009b20  20 72 65 66 65 72 20 74  6f 20 5c 0a 20 20 20 20  | refer to \.    |
00009b30  20 20 20 20 20 20 20 20  20 20 20 20 20 20 20 20  |                |
00009b40  20 20 20 20 69 6e 20 74  68 65 20 63 6f 75 72 73  |    in the cours|
00009b50  65 20 6f 66 20 74 68 69  73 20 67 61 6d 65 2e 5e  |e of this game.^|
00009b60  22 3b 0a 20 20 20 20 69  66 20 28 65 74 79 70 65  |";.    if (etype|
00009b70  3d 3d 49 54 47 4f 4e 45  5f 50 45 29 0a 20 20 20  |==ITGONE_PE).   |
00009b80  20 20 20 20 20 20 20 20  20 20 7b 20 20 20 70 72  |          {   pr|
00009b90  69 6e 74 20 22 59 6f 75  20 63 61 6e 27 74 20 73  |int "You can't s|
00009ba0  65 65 20 7e 22 3b 20 70  72 69 6e 74 5f 61 64 64  |ee ~"; print_add|
00009bb0  72 20 76 61 67 75 65 5f  77 6f 72 64 3b 0a 20 20  |r vague_word;.  |
00009bc0  20 20 20 20 20 20 20 20  20 20 20 20 20 20 20 70  |               p|
00009bd0  72 69 6e 74 20 22 7e 20  28 22 3b 20 44 65 66 41  |rint "~ ("; DefA|
00009be0  72 74 28 76 61 67 75 65  5f 6f 62 6a 29 3b 20 70  |rt(vague_obj); p|
00009bf0  72 69 6e 74 20 22 29 20  61 74 20 74 68 65 20 6d  |rint ") at the m|
00009c00  6f 6d 65 6e 74 2e 5e 22  3b 20 7d 0a 20 20 20 20  |oment.^"; }.    |
00009c10  69 66 20 28 65 74 79 70  65 3d 3d 4a 55 4e 4b 41  |if (etype==JUNKA|
00009c20  46 54 45 52 5f 50 45 29  0a 20 20 20 20 20 20 20  |FTER_PE).       |
00009c30  20 20 20 20 20 20 20 20  20 20 70 72 69 6e 74 20  |          print |
00009c40  22 49 20 64 69 64 6e 27  74 20 75 6e 64 65 72 73  |"I didn't unders|
00009c50  74 61 6e 64 20 74 68 65  20 77 61 79 20 74 68 61  |tand the way tha|
00009c60  74 20 66 69 6e 69 73 68  65 64 2e 5e 22 3b 0a 20  |t finished.^";. |
00009c70  20 20 20 69 66 20 28 65  74 79 70 65 3d 3d 54 4f  |   if (etype==TO|
00009c80  4f 46 45 57 5f 50 45 29  0a 20 20 20 20 20 20 20  |OFEW_PE).       |
00009c90  20 20 20 20 20 20 7b 20  20 20 69 66 20 28 6d 75  |      {   if (mu|
00009ca0  6c 74 69 5f 68 61 64 3d  3d 30 29 20 70 72 69 6e  |lti_had==0) prin|
00009cb0  74 20 22 4e 6f 6e 65 22  3b 0a 20 20 20 20 20 20  |t "None";.      |
00009cc0  20 20 20 20 20 20 20 20  20 20 20 65 6c 73 65 20  |           else |
00009cd0  7b 20 70 72 69 6e 74 20  22 4f 6e 6c 79 20 22 3b  |{ print "Only ";|
00009ce0  20 45 6e 67 6c 69 73 68  4e 75 6d 62 65 72 28 6d  | EnglishNumber(m|
00009cf0  75 6c 74 69 5f 68 61 64  29 3b 20 7d 0a 20 20 20  |ulti_had); }.   |
00009d00  20 20 20 20 20 20 20 20  20 20 20 20 20 20 70 72  |              pr|
00009d10  69 6e 74 20 22 20 6f 66  20 74 68 6f 73 65 20 22  |int " of those "|
00009d20  3b 0a 20 20 20 20 20 20  20 20 20 20 20 20 20 20  |;.              |
00009d30  20 20 20 69 66 20 28 6d  75 6c 74 69 5f 68 61 64  |   if (multi_had|
00009d40  3d 3d 31 29 20 70 72 69  6e 74 20 22 69 73 22 3b  |==1) print "is";|
00009d50  20 65 6c 73 65 20 70 72  69 6e 74 20 22 61 72 65  | else print "are|
00009d60  22 3b 0a 20 20 20 20 20  20 20 20 20 20 20 20 20  |";.             |
00009d70  20 20 20 20 70 72 69 6e  74 20 22 20 61 76 61 69  |    print " avai|
00009d80  6c 61 62 6c 65 2e 5e 22  3b 20 7d 0a 20 20 20 20  |lable.^"; }.    |
00009d90  69 66 20 28 65 74 79 70  65 3d 3d 4e 4f 54 48 49  |if (etype==NOTHI|
00009da0  4e 47 5f 50 45 29 0a 20  20 20 20 20 20 20 20 20  |NG_PE).         |
00009db0  20 20 20 20 7b 20 20 20  69 66 20 28 6d 75 6c 74  |    {   if (mult|
00009dc0  69 5f 77 61 6e 74 65 64  3d 3d 31 30 30 29 20 70  |i_wanted==100) p|
00009dd0  72 69 6e 74 20 22 4e 6f  74 68 69 6e 67 20 74 6f  |rint "Nothing to|
00009de0  20 64 6f 21 5e 22 3b 0a  20 20 20 20 20 20 20 20  | do!^";.        |
00009df0  20 20 20 20 20 20 20 20  20 65 6c 73 65 20 70 72  |         else pr|
00009e00  69 6e 74 20 22 54 68 65  72 65 20 61 72 65 20 6e  |int "There are n|
00009e10  6f 6e 65 20 61 74 20 61  6c 6c 20 61 76 61 69 6c  |one at all avail|
00009e20  61 62 6c 65 21 5e 22 3b  20 20 7d 0a 20 20 20 20  |able!^";  }.    |
00009e30  69 66 20 28 65 74 79 70  65 3d 3d 4e 55 4d 42 45  |if (etype==NUMBE|
00009e40  52 5f 50 45 29 0a 20 20  20 20 20 20 20 20 20 20  |R_PE).          |
00009e50  20 20 20 20 20 20 20 70  72 69 6e 74 20 22 49 20  |       print "I |
00009e60  64 69 64 6e 27 74 20 75  6e 64 65 72 73 74 61 6e  |didn't understan|
00009e70  64 20 74 68 61 74 20 6e  75 6d 62 65 72 2e 5e 22  |d that number.^"|
00009e80  3b 0a 20 20 20 20 69 66  20 28 65 74 79 70 65 3d  |;.    if (etype=|
00009e90  3d 41 53 4b 53 43 4f 50  45 5f 50 45 29 0a 20 20  |=ASKSCOPE_PE).  |
00009ea0  20 20 7b 20 20 20 20 20  20 20 20 20 20 20 20 73  |  {            s|
00009eb0  63 6f 70 65 5f 73 74 61  67 65 3d 33 3b 20 69 6e  |cope_stage=3; in|
00009ec0  64 69 72 65 63 74 28 73  63 6f 70 65 5f 65 72 72  |direct(scope_err|
00009ed0  6f 72 29 3b 20 7d 0a 0a  21 20 20 2a 2a 2a 2a 20  |or); }..!  **** |
00009ee0  28 4a 29 20 2a 2a 2a 2a  0a 0a 21 20 20 41 6e 64  |(J) ****..!  And|
00009ef0  20 67 6f 20 28 61 6c 6d  6f 73 74 29 20 72 69 67  | go (almost) rig|
00009f00  68 74 20 62 61 63 6b 20  74 6f 20 73 71 75 61 72  |ht back to squar|
00009f10  65 20 6f 6e 65 2e 2e 2e  0a 0a 20 20 20 20 6a 75  |e one.....    ju|
00009f20  6d 70 20 52 65 54 79 70  65 3b 0a 0a 21 20 20 2e  |mp ReType;..!  .|
00009f30  2e 2e 62 65 69 6e 67 20  63 61 72 65 66 75 6c 20  |..being careful |
00009f40  6e 6f 74 20 74 6f 20 67  6f 20 61 6c 6c 20 74 68  |not to go all th|
00009f50  65 20 77 61 79 20 62 61  63 6b 2c 20 74 6f 20 61  |e way back, to a|
00009f60  76 6f 69 64 20 69 6e 66  69 6e 69 74 65 20 72 65  |void infinite re|
00009f70  70 65 74 69 74 69 6f 6e  0a 21 20 20 6f 66 20 61  |petition.!  of a|
00009f80  20 64 65 66 65 72 72 65  64 20 63 6f 6d 6d 61 6e  | deferred comman|
00009f90  64 20 63 61 75 73 69 6e  67 20 61 6e 20 65 72 72  |d causing an err|
00009fa0  6f 72 2e 0a 0a 0a 21 20  20 2a 2a 2a 2a 20 28 4b  |or....!  **** (K|
00009fb0  29 20 2a 2a 2a 2a 0a 0a  21 20 20 41 74 20 74 68  |) ****..!  At th|
00009fc0  69 73 20 70 6f 69 6e 74  2c 20 74 68 65 20 72 65  |is point, the re|
00009fd0  74 75 72 6e 20 76 61 6c  75 65 20 69 73 20 61 6c  |turn value is al|
00009fe0  6c 20 70 72 65 70 61 72  65 64 2c 20 61 6e 64 20  |l prepared, and |
00009ff0  77 65 20 61 72 65 20 6f  6e 6c 79 20 6c 6f 6f 6b  |we are only look|
0000a000  69 6e 67 0a 21 20 20 74  6f 20 73 65 65 20 69 66  |ing.!  to see if|
0000a010  20 74 68 65 72 65 20 69  73 20 61 20 22 74 68 65  | there is a "the|
0000a020  6e 22 20 66 6f 6c 6c 6f  77 65 64 20 62 79 20 73  |n" followed by s|
0000a030  75 62 73 65 71 75 65 6e  74 20 69 6e 73 74 72 75  |ubsequent instru|
0000a040  63 74 69 6f 6e 28 73 29  2e 0a 20 20 20 20 0a 20  |ction(s)..    . |
0000a050  20 20 2e 4c 6f 6f 6b 46  6f 72 4d 6f 72 65 3b 0a  |  .LookForMore;.|
0000a060  0a 20 20 20 69 66 20 28  77 6e 3e 6e 75 6d 5f 77  |.   if (wn>num_w|
0000a070  6f 72 64 73 29 20 72 74  72 75 65 3b 0a 0a 20 20  |ords) rtrue;..  |
0000a080  20 69 3d 4e 65 78 74 57  6f 72 64 28 29 3b 0a 20  | i=NextWord();. |
0000a090  20 20 69 66 20 28 69 3d  3d 27 74 68 65 6e 27 20  |  if (i=='then' |
0000a0a0  7c 7c 20 69 3d 3d 63 6f  6d 6d 61 5f 77 6f 72 64  ||| i==comma_word|
0000a0b0  29 0a 20 20 20 7b 20 20  20 69 66 20 28 77 6e 3e  |).   {   if (wn>|
0000a0c0  6e 75 6d 5f 77 6f 72 64  73 29 0a 20 20 20 20 20  |num_words).     |
0000a0d0  20 20 7b 20 70 61 72 73  65 32 2d 3e 31 3d 28 70  |  { parse2->1=(p|
0000a0e0  61 72 73 65 32 2d 3e 31  29 2d 31 3b 20 68 65 6c  |arse2->1)-1; hel|
0000a0f0  64 5f 62 61 63 6b 5f 6d  6f 64 65 20 3d 20 30 3b  |d_back_mode = 0;|
0000a100  20 72 74 72 75 65 3b 20  7d 0a 20 20 20 20 20 20  | rtrue; }.      |
0000a110  20 69 66 20 28 61 63 74  6f 72 3d 3d 70 6c 61 79  | if (actor==play|
0000a120  65 72 29 20 6a 3d 30 3b  20 65 6c 73 65 20 6a 3d  |er) j=0; else j=|
0000a130  76 65 72 62 5f 77 6f 72  64 6e 75 6d 2d 31 3b 0a  |verb_wordnum-1;.|
0000a140  20 20 20 20 20 20 20 6c  61 73 74 5f 63 6f 6d 6d  |       last_comm|
0000a150  61 6e 64 5f 66 72 6f 6d  20 3d 20 6a 2b 31 3b 20  |and_from = j+1; |
0000a160  6c 61 73 74 5f 63 6f 6d  6d 61 6e 64 5f 74 6f 20  |last_command_to |
0000a170  3d 20 77 6e 2d 32 3b 0a  20 20 20 20 20 20 20 69  |= wn-2;.       i|
0000a180  3d 4e 65 78 74 57 6f 72  64 28 29 3b 0a 20 20 20  |=NextWord();.   |
0000a190  20 20 20 20 69 66 20 28  69 3d 3d 27 61 67 61 69  |    if (i=='agai|
0000a1a0  6e 27 20 6f 72 20 23 6e  24 67 29 0a 20 20 20 20  |n' or #n$g).    |
0000a1b0  20 20 20 7b 20 20 20 66  6f 72 20 28 69 3d 30 3a  |   {   for (i=0:|
0000a1c0  20 69 3c 6a 3a 20 69 2b  2b 29 0a 20 20 20 20 20  | i<j: i++).     |
0000a1d0  20 20 20 20 20 20 7b 20  20 20 70 61 72 73 65 32  |      {   parse2|
0000a1e0  2d 2d 3e 28 32 2a 69 2b  31 29 20 3d 20 70 61 72  |-->(2*i+1) = par|
0000a1f0  73 65 2d 2d 3e 28 32 2a  69 2b 31 29 3b 0a 20 20  |se-->(2*i+1);.  |
0000a200  20 20 20 20 20 20 20 20  20 20 20 20 20 70 61 72  |             par|
0000a210  73 65 32 2d 2d 3e 28 32  2a 69 2b 32 29 20 3d 20  |se2-->(2*i+2) = |
0000a220  70 61 72 73 65 2d 2d 3e  28 32 2a 69 2b 32 29 3b  |parse-->(2*i+2);|
0000a230  0a 20 20 20 20 20 20 20  20 20 20 20 7d 0a 20 20  |.           }.  |
0000a240  20 20 20 20 20 20 20 20  20 66 6f 72 20 28 69 3d  |         for (i=|
0000a250  6c 61 73 74 5f 63 6f 6d  6d 61 6e 64 5f 66 72 6f  |last_command_fro|
0000a260  6d 3a 69 3c 3d 6c 61 73  74 5f 63 6f 6d 6d 61 6e  |m:i<=last_comman|
0000a270  64 5f 74 6f 3a 69 2b 2b  2c 20 6a 2b 2b 29 0a 20  |d_to:i++, j++). |
0000a280  20 20 20 20 20 20 20 20  20 20 7b 20 20 20 70 61  |          {   pa|
0000a290  72 73 65 32 2d 2d 3e 28  32 2b 32 2a 6a 29 20 3d  |rse2-->(2+2*j) =|
0000a2a0  20 70 61 72 73 65 2d 2d  3e 28 32 2a 69 29 3b 0a  | parse-->(2*i);.|
0000a2b0  20 20 20 20 20 20 20 20  20 20 20 20 20 20 20 70  |               p|
0000a2c0  61 72 73 65 32 2d 2d 3e  28 31 2b 32 2a 6a 29 20  |arse2-->(1+2*j) |
0000a2d0  3d 20 70 61 72 73 65 2d  2d 3e 28 32 2a 69 2d 31  |= parse-->(2*i-1|
0000a2e0  29 3b 0a 20 20 20 20 20  20 20 20 20 20 20 7d 0a  |);.           }.|
0000a2f0  20 20 20 20 20 20 20 20  20 20 20 66 6f 72 20 28  |           for (|
0000a300  69 3d 77 6e 3a 69 3c 3d  6e 75 6d 5f 77 6f 72 64  |i=wn:i<=num_word|
0000a310  73 3a 69 2b 2b 2c 20 6a  2b 2b 29 0a 20 20 20 20  |s:i++, j++).    |
0000a320  20 20 20 20 20 20 20 7b  20 20 20 70 61 72 73 65  |       {   parse|
0000a330  32 2d 2d 3e 28 32 2b 32  2a 6a 29 20 3d 20 70 61  |2-->(2+2*j) = pa|
0000a340  72 73 65 2d 2d 3e 28 32  2a 69 29 3b 0a 20 20 20  |rse-->(2*i);.   |
0000a350  20 20 20 20 20 20 20 20  20 20 20 20 70 61 72 73  |            pars|
0000a360  65 32 2d 2d 3e 28 31 2b  32 2a 6a 29 20 3d 20 70  |e2-->(1+2*j) = p|
0000a370  61 72 73 65 2d 2d 3e 28  32 2a 69 2d 31 29 3b 0a  |arse-->(2*i-1);.|
0000a380  20 20 20 20 20 20 20 20  20 20 20 7d 0a 20 20 20  |           }.   |
0000a390  20 20 20 20 20 20 20 20  70 61 72 73 65 32 2d 3e  |        parse2->|
0000a3a0  31 3d 6a 3b 20 68 65 6c  64 5f 62 61 63 6b 5f 6d  |1=j; held_back_m|
0000a3b0  6f 64 65 20 3d 20 31 3b  20 72 74 72 75 65 3b 0a  |ode = 1; rtrue;.|
0000a3c0  20 20 20 20 20 20 20 7d  0a 20 20 20 20 20 20 20  |       }.       |
0000a3d0  65 6c 73 65 20 77 6e 2d  2d 3b 0a 20 20 20 20 20  |else wn--;.     |
0000a3e0  20 20 66 6f 72 20 28 69  3d 30 3a 20 69 3c 6a 3a  |  for (i=0: i<j:|
0000a3f0  20 69 2b 2b 29 0a 20 20  20 20 20 20 20 7b 20 20  | i++).       {  |
0000a400  20 70 61 72 73 65 32 2d  2d 3e 28 32 2a 69 2b 31  | parse2-->(2*i+1|
0000a410  29 20 3d 20 70 61 72 73  65 2d 2d 3e 28 32 2a 69  |) = parse-->(2*i|
0000a420  2b 31 29 3b 0a 20 20 20  20 20 20 20 20 20 20 20  |+1);.           |
0000a430  70 61 72 73 65 32 2d 2d  3e 28 32 2a 69 2b 32 29  |parse2-->(2*i+2)|
0000a440  20 3d 20 70 61 72 73 65  2d 2d 3e 28 32 2a 69 2b  | = parse-->(2*i+|
0000a450  32 29 3b 0a 20 20 20 20  20 20 20 7d 0a 20 20 20  |2);.       }.   |
0000a460  20 20 20 20 66 6f 72 20  28 69 3d 77 6e 3a 69 3c  |    for (i=wn:i<|
0000a470  3d 6e 75 6d 5f 77 6f 72  64 73 3a 69 2b 2b 2c 20  |=num_words:i++, |
0000a480  6a 2b 2b 29 0a 20 20 20  20 20 20 20 7b 20 20 20  |j++).       {   |
0000a490  70 61 72 73 65 32 2d 2d  3e 28 32 2b 32 2a 6a 29  |parse2-->(2+2*j)|
0000a4a0  20 3d 20 70 61 72 73 65  2d 2d 3e 28 32 2a 69 29  | = parse-->(2*i)|
0000a4b0  3b 0a 20 20 20 20 20 20  20 20 20 20 20 70 61 72  |;.           par|
0000a4c0  73 65 32 2d 2d 3e 28 31  2b 32 2a 6a 29 20 3d 20  |se2-->(1+2*j) = |
0000a4d0  70 61 72 73 65 2d 2d 3e  28 32 2a 69 2d 31 29 3b  |parse-->(2*i-1);|
0000a4e0  0a 20 20 20 20 20 20 20  7d 0a 20 20 20 20 20 20  |.       }.      |
0000a4f0  20 70 61 72 73 65 32 2d  3e 31 3d 6a 3b 20 68 65  | parse2->1=j; he|
0000a500  6c 64 5f 62 61 63 6b 5f  6d 6f 64 65 20 3d 20 31  |ld_back_mode = 1|
0000a510  3b 20 72 74 72 75 65 3b  0a 20 20 20 7d 0a 20 20  |; rtrue;.   }.  |
0000a520  20 62 65 73 74 5f 65 74  79 70 65 3d 55 50 54 4f  | best_etype=UPTO|
0000a530  5f 50 45 3b 20 6a 75 6d  70 20 47 69 76 65 45 72  |_PE; jump GiveEr|
0000a540  72 6f 72 3b 0a 5d 3b 0a  0a 21 20 2d 2d 2d 2d 2d  |ror;.];..! -----|
0000a550  2d 2d 2d 2d 2d 2d 2d 2d  2d 2d 2d 2d 2d 2d 2d 2d  |----------------|
*
0000a590  2d 2d 2d 2d 2d 2d 2d 0a  21 20 20 4e 75 6d 62 65  |-------.!  Numbe|
0000a5a0  72 57 6f 72 64 20 2d 20  66 61 69 72 6c 79 20 73  |rWord - fairly s|
0000a5b0  65 6c 66 2d 65 78 70 6c  61 6e 61 74 6f 72 79 0a  |elf-explanatory.|
0000a5c0  21 20 2d 2d 2d 2d 2d 2d  2d 2d 2d 2d 2d 2d 2d 2d  |! --------------|
0000a5d0  2d 2d 2d 2d 2d 2d 2d 2d  2d 2d 2d 2d 2d 2d 2d 2d  |----------------|
*
0000a600  2d 2d 2d 2d 2d 2d 2d 2d  2d 2d 2d 2d 2d 2d 0a 0a  |--------------..|
0000a610  5b 20 4e 75 6d 62 65 72  57 6f 72 64 20 6f 3b 0a  |[ NumberWord o;.|
0000a620  20 20 69 66 20 28 6f 3d  3d 27 6f 6e 65 27 29 20  |  if (o=='one') |
0000a630  72 65 74 75 72 6e 20 31  3b 0a 20 20 69 66 20 28  |return 1;.  if (|
0000a640  6f 3d 3d 27 74 77 6f 27  29 20 72 65 74 75 72 6e  |o=='two') return|
0000a650  20 32 3b 0a 20 20 69 66  20 28 6f 3d 3d 27 74 68  | 2;.  if (o=='th|
0000a660  72 65 65 27 29 20 72 65  74 75 72 6e 20 33 3b 0a  |ree') return 3;.|
0000a670  20 20 69 66 20 28 6f 3d  3d 27 66 6f 75 72 27 29  |  if (o=='four')|
0000a680  20 72 65 74 75 72 6e 20  34 3b 0a 20 20 69 66 20  | return 4;.  if |
0000a690  28 6f 3d 3d 27 66 69 76  65 27 29 20 72 65 74 75  |(o=='five') retu|
0000a6a0  72 6e 20 35 3b 0a 20 20  69 66 20 28 6f 3d 3d 27  |rn 5;.  if (o=='|
0000a6b0  73 69 78 27 29 20 72 65  74 75 72 6e 20 36 3b 0a  |six') return 6;.|
0000a6c0  20 20 69 66 20 28 6f 3d  3d 27 73 65 76 65 6e 27  |  if (o=='seven'|
0000a6d0  29 20 72 65 74 75 72 6e  20 37 3b 0a 20 20 69 66  |) return 7;.  if|
0000a6e0  20 28 6f 3d 3d 27 65 69  67 68 74 27 29 20 72 65  | (o=='eight') re|
0000a6f0  74 75 72 6e 20 38 3b 0a  20 20 69 66 20 28 6f 3d  |turn 8;.  if (o=|
0000a700  3d 27 6e 69 6e 65 27 29  20 72 65 74 75 72 6e 20  |='nine') return |
0000a710  39 3b 0a 20 20 69 66 20  28 6f 3d 3d 27 74 65 6e  |9;.  if (o=='ten|
0000a720  27 29 20 72 65 74 75 72  6e 20 31 30 3b 0a 20 20  |') return 10;.  |
0000a730  69 66 20 28 6f 3d 3d 27  65 6c 65 76 65 6e 27 29  |if (o=='eleven')|
0000a740  20 72 65 74 75 72 6e 20  31 31 3b 0a 20 20 69 66  | return 11;.  if|
0000a750  20 28 6f 3d 3d 27 74 77  65 6c 76 65 27 29 20 72  | (o=='twelve') r|
0000a760  65 74 75 72 6e 20 31 32  3b 0a 20 20 69 66 20 28  |eturn 12;.  if (|
0000a770  6f 3d 3d 27 74 68 69 72  74 65 65 6e 27 29 20 72  |o=='thirteen') r|
0000a780  65 74 75 72 6e 20 31 33  3b 0a 20 20 69 66 20 28  |eturn 13;.  if (|
0000a790  6f 3d 3d 27 66 6f 75 72  74 65 65 6e 27 29 20 72  |o=='fourteen') r|
0000a7a0  65 74 75 72 6e 20 31 34  3b 0a 20 20 69 66 20 28  |eturn 14;.  if (|
0000a7b0  6f 3d 3d 27 66 69 66 74  65 65 6e 27 29 20 72 65  |o=='fifteen') re|
0000a7c0  74 75 72 6e 20 31 35 3b  0a 20 20 69 66 20 28 6f  |turn 15;.  if (o|
0000a7d0  3d 3d 27 73 69 78 74 65  65 6e 27 29 20 72 65 74  |=='sixteen') ret|
0000a7e0  75 72 6e 20 31 36 3b 0a  20 20 69 66 20 28 6f 3d  |urn 16;.  if (o=|
0000a7f0  3d 27 73 65 76 65 6e 74  65 65 6e 27 29 20 72 65  |='seventeen') re|
0000a800  74 75 72 6e 20 31 37 3b  0a 20 20 69 66 20 28 6f  |turn 17;.  if (o|
0000a810  3d 3d 27 65 69 67 68 74  65 65 6e 27 29 20 72 65  |=='eighteen') re|
0000a820  74 75 72 6e 20 31 38 3b  0a 20 20 69 66 20 28 6f  |turn 18;.  if (o|
0000a830  3d 3d 27 6e 69 6e 65 74  65 65 6e 27 29 20 72 65  |=='nineteen') re|
0000a840  74 75 72 6e 20 31 39 3b  0a 20 20 69 66 20 28 6f  |turn 19;.  if (o|
0000a850  3d 3d 27 74 77 65 6e 74  79 27 29 20 72 65 74 75  |=='twenty') retu|
0000a860  72 6e 20 32 30 3b 0a 20  20 72 65 74 75 72 6e 20  |rn 20;.  return |
0000a870  30 3b 0a 5d 3b 0a 0a 21  20 2d 2d 2d 2d 2d 2d 2d  |0;.];..! -------|
0000a880  2d 2d 2d 2d 2d 2d 2d 2d  2d 2d 2d 2d 2d 2d 2d 2d  |----------------|
*
0000a8c0  2d 2d 2d 2d 2d 0a 21 20  20 44 65 73 63 72 69 70  |-----.!  Descrip|
0000a8d0  74 6f 72 73 28 29 0a 21  0a 21 20 20 48 61 6e 64  |tors().!.!  Hand|
0000a8e0  6c 65 73 20 64 65 73 63  72 69 70 74 69 76 65 20  |les descriptive |
0000a8f0  77 6f 72 64 73 20 6c 69  6b 65 20 22 6d 79 22 2c  |words like "my",|
0000a900  20 22 68 69 73 22 2c 20  22 61 6e 6f 74 68 65 72  | "his", "another|
0000a910  22 20 61 6e 64 20 73 6f  20 6f 6e 2e 0a 21 20 20  |" and so on..!  |
0000a920  53 6b 69 70 73 20 22 74  68 65 22 2c 20 61 6e 64  |Skips "the", and|
0000a930  20 6c 65 61 76 65 73 20  77 6e 20 70 6f 69 6e 74  | leaves wn point|
0000a940  69 6e 67 20 74 6f 20 74  68 65 20 66 69 72 73 74  |ing to the first|
0000a950  20 6d 69 73 75 6e 64 65  72 73 74 6f 6f 64 20 77  | misunderstood w|
0000a960  6f 72 64 2e 0a 21 0a 21  20 20 41 6c 6c 6f 77 65  |ord..!.!  Allowe|
0000a970  64 20 74 6f 20 73 65 74  20 75 70 20 66 6f 72 20  |d to set up for |
0000a980  61 20 70 6c 75 72 61 6c  20 6f 6e 6c 79 20 69 66  |a plural only if|
0000a990  20 61 6c 6c 6f 77 5f 70  20 69 73 20 73 65 74 0a  | allow_p is set.|
0000a9a0  21 0a 21 20 20 52 65 74  75 72 6e 73 20 65 72 72  |!.!  Returns err|
0000a9b0  6f 72 20 6e 75 6d 62 65  72 2c 20 6f 72 20 30 20  |or number, or 0 |
0000a9c0  69 66 20 6e 6f 20 65 72  72 6f 72 20 6f 63 63 75  |if no error occu|
0000a9d0  72 72 65 64 0a 21 20 2d  2d 2d 2d 2d 2d 2d 2d 2d  |rred.! ---------|
0000a9e0  2d 2d 2d 2d 2d 2d 2d 2d  2d 2d 2d 2d 2d 2d 2d 2d  |----------------|
*
0000aa20  2d 2d 2d 0a 0a 43 6f 6e  73 74 61 6e 74 20 4f 54  |---..Constant OT|
0000aa30  48 45 52 5f 42 49 54 20  20 20 20 31 3b 20 20 20  |HER_BIT    1;   |
0000aa40  20 20 21 20 20 54 68 65  73 65 20 77 69 6c 6c 20  |  !  These will |
0000aa50  62 65 20 75 73 65 64 20  69 6e 20 41 64 6a 75 64  |be used in Adjud|
0000aa60  69 63 61 74 65 28 29 0a  43 6f 6e 73 74 61 6e 74  |icate().Constant|
0000aa70  20 4d 59 5f 42 49 54 20  20 20 20 20 20 20 32 3b  | MY_BIT       2;|
0000aa80  20 20 20 20 20 21 20 20  74 6f 20 64 69 73 61 6d  |     !  to disam|
0000aa90  62 69 67 75 61 74 65 20  63 68 6f 69 63 65 73 0a  |biguate choices.|
0000aaa0  43 6f 6e 73 74 61 6e 74  20 54 48 41 54 5f 42 49  |Constant THAT_BI|
0000aab0  54 20 20 20 20 20 34 3b  0a 43 6f 6e 73 74 61 6e  |T     4;.Constan|
0000aac0  74 20 50 4c 55 52 41 4c  5f 42 49 54 20 20 20 38  |t PLURAL_BIT   8|
0000aad0  3b 0a 43 6f 6e 73 74 61  6e 74 20 49 54 53 5f 42  |;.Constant ITS_B|
0000aae0  49 54 20 20 20 20 20 31  36 3b 0a 43 6f 6e 73 74  |IT     16;.Const|
0000aaf0  61 6e 74 20 48 49 53 5f  42 49 54 20 20 20 20 20  |ant HIS_BIT     |
0000ab00  33 32 3b 0a 43 6f 6e 73  74 61 6e 74 20 4c 49 54  |32;.Constant LIT|
0000ab10  5f 42 49 54 20 20 20 20  20 36 34 3b 0a 43 6f 6e  |_BIT     64;.Con|
0000ab20  73 74 61 6e 74 20 55 4e  4c 49 54 5f 42 49 54 20  |stant UNLIT_BIT |
0000ab30  20 31 32 38 3b 0a 0a 5b  20 44 65 73 63 72 69 70  | 128;..[ Descrip|
0000ab40  74 6f 72 73 20 63 6f 6e  74 65 78 74 20 20 6f 20  |tors context  o |
0000ab50  66 6c 61 67 20 6e 3b 0a  0a 20 20 20 69 6e 64 65  |flag n;..   inde|
0000ab60  66 5f 6d 6f 64 65 3d 30  3b 20 69 6e 64 65 66 5f  |f_mode=0; indef_|
0000ab70  74 79 70 65 3d 30 3b 20  69 6e 64 65 66 5f 77 61  |type=0; indef_wa|
0000ab80  6e 74 65 64 3d 30 3b 20  69 6e 64 65 66 5f 67 75  |nted=0; indef_gu|
0000ab90  65 73 73 5f 70 3d 30 3b  0a 0a 20 20 20 66 6f 72  |ess_p=0;..   for|
0000aba0  20 28 66 6c 61 67 3d 31  3a 66 6c 61 67 3d 3d 31  | (flag=1:flag==1|
0000abb0  3a 29 0a 20 20 20 7b 20  20 20 6f 3d 4e 65 78 74  |:).   {   o=Next|
0000abc0  57 6f 72 64 28 29 3b 20  66 6c 61 67 3d 30 3b 0a  |Word(); flag=0;.|
0000abd0  20 20 20 20 20 20 20 69  66 20 28 6f 3d 3d 27 74  |       if (o=='t|
0000abe0  68 65 27 29 20 66 6c 61  67 3d 31 3b 0a 20 20 20  |he') flag=1;.   |
0000abf0  20 20 20 20 69 66 20 28  6f 3d 3d 23 6e 24 61 20  |    if (o==#n$a |
0000ac00  6f 72 20 27 61 6e 27 20  6f 72 20 27 61 6e 79 27  |or 'an' or 'any'|
0000ac10  20 7c 7c 20 6f 3d 3d 27  65 69 74 68 65 72 27 20  | || o=='either' |
0000ac20  6f 72 20 27 61 6e 79 74  68 69 6e 67 27 29 0a 20  |or 'anything'). |
0000ac30  20 20 20 20 20 20 20 20  20 20 20 20 20 20 20 20  |                |
0000ac40  20 20 20 20 20 20 20 20  20 20 20 7b 20 69 6e 64  |           { ind|
0000ac50  65 66 5f 6d 6f 64 65 3d  31 3b 20 66 6c 61 67 3d  |ef_mode=1; flag=|
0000ac60  31 3b 20 7d 0a 20 20 20  20 20 20 20 69 66 20 28  |1; }.       if (|
0000ac70  6f 3d 3d 27 61 6e 6f 74  68 65 72 27 20 6f 72 20  |o=='another' or |
0000ac80  27 6f 74 68 65 72 27 29  0a 20 20 20 20 20 20 20  |'other').       |
0000ac90  20 20 20 20 20 20 20 20  20 20 20 20 20 20 20 20  |                |
0000aca0  20 20 20 20 20 7b 20 69  6e 64 65 66 5f 6d 6f 64  |     { indef_mod|
0000acb0  65 3d 31 3b 20 66 6c 61  67 3d 31 3b 0a 20 20 20  |e=1; flag=1;.   |
0000acc0  20 20 20 20 20 20 20 20  20 20 20 20 20 20 20 20  |                |
0000acd0  20 20 20 20 20 20 20 20  20 20 20 69 6e 64 65 66  |           indef|
0000ace0  5f 74 79 70 65 20 3d 20  69 6e 64 65 66 5f 74 79  |_type = indef_ty|
0000acf0  70 65 20 7c 20 4f 54 48  45 52 5f 42 49 54 3b 20  |pe | OTHER_BIT; |
0000ad00  7d 0a 20 20 20 20 20 20  20 69 66 20 28 6f 3d 3d  |}.       if (o==|
0000ad10  27 6d 79 27 20 6f 72 20  27 74 68 69 73 27 20 6f  |'my' or 'this' o|
0000ad20  72 20 27 74 68 65 73 65  27 29 0a 20 20 20 20 20  |r 'these').     |
0000ad30  20 20 20 20 20 20 20 20  20 20 20 20 20 20 20 20  |                |
0000ad40  20 20 20 20 20 20 20 7b  20 69 6e 64 65 66 5f 6d  |       { indef_m|
0000ad50  6f 64 65 3d 31 3b 20 66  6c 61 67 3d 31 3b 0a 20  |ode=1; flag=1;. |
0000ad60  20 20 20 20 20 20 20 20  20 20 20 20 20 20 20 20  |                |
0000ad70  20 20 20 20 20 20 20 20  20 20 20 20 20 69 6e 64  |             ind|
0000ad80  65 66 5f 74 79 70 65 20  3d 20 69 6e 64 65 66 5f  |ef_type = indef_|
0000ad90  74 79 70 65 20 7c 20 4d  59 5f 42 49 54 3b 20 7d  |type | MY_BIT; }|
0000ada0  0a 20 20 20 20 20 20 20  69 66 20 28 6f 3d 3d 27  |.       if (o=='|
0000adb0  74 68 61 74 27 20 6f 72  20 27 74 68 6f 73 65 27  |that' or 'those'|
0000adc0  29 0a 20 20 20 20 20 20  20 20 20 20 20 20 20 20  |).              |
0000add0  20 20 20 20 20 20 20 20  20 20 20 20 20 20 7b 20  |              { |
0000ade0  69 6e 64 65 66 5f 6d 6f  64 65 3d 31 3b 20 66 6c  |indef_mode=1; fl|
0000adf0  61 67 3d 31 3b 0a 20 20  20 20 20 20 20 20 20 20  |ag=1;.          |
0000ae00  20 20 20 20 20 20 20 20  20 20 20 20 20 20 20 20  |                |
0000ae10  20 20 20 20 69 6e 64 65  66 5f 74 79 70 65 20 3d  |    indef_type =|
0000ae20  20 69 6e 64 65 66 5f 74  79 70 65 20 7c 20 54 48  | indef_type | TH|
0000ae30  41 54 5f 42 49 54 3b 20  7d 0a 20 20 20 20 20 20  |AT_BIT; }.      |
0000ae40  20 69 66 20 28 6f 3d 3d  27 69 74 73 27 29 0a 20  | if (o=='its'). |
0000ae50  20 20 20 20 20 20 20 20  20 20 20 20 20 20 20 20  |                |
0000ae60  20 20 20 20 20 20 20 20  20 20 20 7b 20 69 6e 64  |           { ind|
0000ae70  65 66 5f 6d 6f 64 65 3d  31 3b 20 66 6c 61 67 3d  |ef_mode=1; flag=|
0000ae80  31 3b 0a 20 20 20 20 20  20 20 20 20 20 20 20 20  |1;.             |
0000ae90  20 20 20 20 20 20 20 20  20 20 20 20 20 20 20 20  |                |
0000aea0  20 69 6e 64 65 66 5f 74  79 70 65 20 3d 20 69 6e  | indef_type = in|
0000aeb0  64 65 66 5f 74 79 70 65  20 7c 20 49 54 53 5f 42  |def_type | ITS_B|
0000aec0  49 54 3b 20 7d 0a 20 20  20 20 20 20 20 69 66 20  |IT; }.       if |
0000aed0  28 6f 3d 3d 27 68 69 73  27 29 0a 20 20 20 20 20  |(o=='his').     |
0000aee0  20 20 20 20 20 20 20 20  20 20 20 20 20 20 20 20  |                |
0000aef0  20 20 20 20 20 20 20 7b  20 69 6e 64 65 66 5f 6d  |       { indef_m|
0000af00  6f 64 65 3d 31 3b 20 66  6c 61 67 3d 31 3b 0a 20  |ode=1; flag=1;. |
0000af10  20 20 20 20 20 20 20 20  20 20 20 20 20 20 20 20  |                |
0000af20  20 20 20 20 20 20 20 20  20 20 20 20 20 69 6e 64  |             ind|
0000af30  65 66 5f 74 79 70 65 20  3d 20 69 6e 64 65 66 5f  |ef_type = indef_|
0000af40  74 79 70 65 20 7c 20 48  49 53 5f 42 49 54 3b 20  |type | HIS_BIT; |
0000af50  7d 0a 20 20 20 20 20 20  20 69 66 20 28 6f 3d 3d  |}.       if (o==|
0000af60  27 6c 69 74 27 20 6f 72  20 27 6c 69 67 68 74 65  |'lit' or 'lighte|
0000af70  64 27 29 0a 20 20 20 20  20 20 20 20 20 20 20 20  |d').            |
0000af80  20 20 20 20 20 20 20 20  20 20 20 20 20 20 20 20  |                |
0000af90  7b 20 69 6e 64 65 66 5f  6d 6f 64 65 3d 31 3b 20  |{ indef_mode=1; |
0000afa0  66 6c 61 67 3d 31 3b 0a  20 20 20 20 20 20 20 20  |flag=1;.        |
0000afb0  20 20 20 20 20 20 20 20  20 20 20 20 20 20 20 20  |                |
0000afc0  20 20 20 20 20 20 69 6e  64 65 66 5f 74 79 70 65  |      indef_type|
0000afd0  20 3d 20 69 6e 64 65 66  5f 74 79 70 65 20 7c 20  | = indef_type | |
0000afe0  4c 49 54 5f 42 49 54 3b  20 7d 0a 20 20 20 20 20  |LIT_BIT; }.     |
0000aff0  20 20 69 66 20 28 6f 3d  3d 27 75 6e 6c 69 74 27  |  if (o=='unlit'|
0000b000  29 0a 20 20 20 20 20 20  20 20 20 20 20 20 20 20  |).              |
0000b010  20 20 20 20 20 20 20 20  20 20 20 20 20 20 7b 20  |              { |
0000b020  69 6e 64 65 66 5f 6d 6f  64 65 3d 31 3b 20 66 6c  |indef_mode=1; fl|
0000b030  61 67 3d 31 3b 0a 20 20  20 20 20 20 20 20 20 20  |ag=1;.          |
0000b040  20 20 20 20 20 20 20 20  20 20 20 20 20 20 20 20  |                |
0000b050  20 20 20 20 69 6e 64 65  66 5f 74 79 70 65 20 3d  |    indef_type =|
0000b060  20 69 6e 64 65 66 5f 74  79 70 65 20 7c 20 55 4e  | indef_type | UN|
0000b070  4c 49 54 5f 42 49 54 3b  20 7d 0a 20 20 20 20 20  |LIT_BIT; }.     |
0000b080  20 20 69 66 20 28 6f 3d  3d 27 61 6c 6c 27 20 6f  |  if (o=='all' o|
0000b090  72 20 27 65 61 63 68 27  20 6f 72 20 27 65 76 65  |r 'each' or 'eve|
0000b0a0  72 79 27 20 7c 7c 20 6f  3d 3d 27 65 76 65 72 79  |ry' || o=='every|
0000b0b0  74 68 69 6e 67 27 29 0a  20 20 20 20 20 20 20 20  |thing').        |
0000b0c0  20 20 20 20 20 20 20 20  20 20 20 20 20 20 20 20  |                |
0000b0d0  20 20 20 20 7b 20 69 6e  64 65 66 5f 6d 6f 64 65  |    { indef_mode|
0000b0e0  3d 31 3b 20 66 6c 61 67  3d 31 3b 20 69 6e 64 65  |=1; flag=1; inde|
0000b0f0  66 5f 77 61 6e 74 65 64  3d 31 30 30 3b 0a 20 20  |f_wanted=100;.  |
0000b100  20 20 20 20 20 20 20 20  20 20 20 20 20 20 20 20  |                |
0000b110  20 20 20 20 20 20 20 20  20 20 20 20 69 6e 64 65  |            inde|
0000b120  66 5f 74 79 70 65 20 3d  20 69 6e 64 65 66 5f 74  |f_type = indef_t|
0000b130  79 70 65 20 7c 20 50 4c  55 52 41 4c 5f 42 49 54  |ype | PLURAL_BIT|
0000b140  3b 20 7d 0a 20 20 20 20  20 20 20 69 66 20 28 61  |; }.       if (a|
0000b150  6c 6c 6f 77 5f 70 6c 75  72 61 6c 73 3d 3d 31 29  |llow_plurals==1)|
0000b160  0a 20 20 20 20 20 20 20  7b 20 20 20 6e 3d 4e 75  |.       {   n=Nu|
0000b170  6d 62 65 72 57 6f 72 64  28 6f 29 3b 0a 20 20 20  |mberWord(o);.   |
0000b180  20 20 20 20 20 20 20 20  69 66 20 28 6e 3e 31 29  |        if (n>1)|
0000b190  20 20 20 20 20 20 20 20  20 7b 20 69 6e 64 65 66  |         { indef|
0000b1a0  5f 67 75 65 73 73 5f 70  3d 31 3b 0a 20 20 20 20  |_guess_p=1;.    |
0000b1b0  20 20 20 20 20 20 20 20  20 20 20 20 20 20 20 20  |                |
0000b1c0  20 20 20 20 20 20 20 20  20 20 69 6e 64 65 66 5f  |          indef_|
0000b1d0  6d 6f 64 65 3d 31 3b 20  66 6c 61 67 3d 31 3b 20  |mode=1; flag=1; |
0000b1e0  69 6e 64 65 66 5f 77 61  6e 74 65 64 3d 6e 3b 0a  |indef_wanted=n;.|
0000b1f0  20 20 20 20 20 20 20 20  20 20 20 20 20 20 20 20  |                |
0000b200  20 20 20 20 20 20 20 20  20 20 20 20 20 20 69 6e  |              in|
0000b210  64 65 66 5f 74 79 70 65  20 3d 20 69 6e 64 65 66  |def_type = indef|
0000b220  5f 74 79 70 65 20 7c 20  50 4c 55 52 41 4c 5f 42  |_type | PLURAL_B|
0000b230  49 54 3b 20 7d 0a 20 20  20 20 20 20 20 7d 0a 20  |IT; }.       }. |
0000b240  20 20 20 20 20 20 69 66  20 28 66 6c 61 67 3d 3d  |      if (flag==|
0000b250  31 20 26 26 20 4e 65 78  74 57 6f 72 64 28 29 20  |1 && NextWord() |
0000b260  7e 3d 20 27 6f 66 27 29  20 77 6e 2d 2d 3b 20 20  |~= 'of') wn--;  |
0000b270  21 20 53 6b 69 70 20 27  6f 66 27 20 61 66 74 65  |! Skip 'of' afte|
0000b280  72 20 74 68 65 73 65 0a  20 20 20 7d 0a 20 20 20  |r these.   }.   |
0000b290  77 6e 2d 2d 3b 0a 20 20  20 69 66 20 28 28 69 6e  |wn--;.   if ((in|
0000b2a0  64 65 66 5f 77 61 6e 74  65 64 20 3e 20 30 29 20  |def_wanted > 0) |
0000b2b0  26 26 20 28 63 6f 6e 74  65 78 74 3c 32 20 7c 7c  |&& (context<2 |||
0000b2c0  20 63 6f 6e 74 65 78 74  3e 35 29 29 20 72 65 74  | context>5)) ret|
0000b2d0  75 72 6e 20 4d 55 4c 54  49 5f 50 45 3b 0a 20 20  |urn MULTI_PE;.  |
0000b2e0  20 72 65 74 75 72 6e 20  30 3b 0a 5d 3b 0a 0a 21  | return 0;.];..!|
0000b2f0  20 2d 2d 2d 2d 2d 2d 2d  2d 2d 2d 2d 2d 2d 2d 2d  | ---------------|
0000b300  2d 2d 2d 2d 2d 2d 2d 2d  2d 2d 2d 2d 2d 2d 2d 2d  |----------------|
*
0000b330  2d 2d 2d 2d 2d 2d 2d 2d  2d 2d 2d 2d 2d 0a 21 20  |-------------.! |
0000b340  20 50 61 72 73 65 4f 62  6a 65 63 74 4c 69 73 74  | ParseObjectList|
0000b350  3a 20 50 61 72 73 65 73  20 74 6f 6b 65 6e 73 20  |: Parses tokens |
0000b360  30 20 74 6f 20 38 2c 20  66 72 6f 6d 20 74 68 65  |0 to 8, from the|
0000b370  20 63 75 72 72 65 6e 74  20 77 6f 72 64 20 6e 75  | current word nu|
0000b380  6d 62 65 72 20 77 6e 0a  21 0a 21 20 20 52 65 74  |mber wn.!.!  Ret|
0000b390  75 72 6e 73 3a 0a 21 20  20 20 20 31 30 30 30 20  |urns:.!    1000 |
0000b3a0  66 6f 72 20 22 72 65 63  6f 6e 73 74 72 75 63 74  |for "reconstruct|
0000b3b0  65 64 20 69 6e 70 75 74  2c 20 70 6c 65 61 73 65  |ed input, please|
0000b3c0  20 72 65 2d 70 61 72 73  65 20 66 72 6f 6d 20 73  | re-parse from s|
0000b3d0  63 72 61 74 63 68 22 0a  21 20 20 20 20 31 20 20  |cratch".!    1  |
0000b3e0  20 20 66 6f 72 20 22 74  6f 6b 65 6e 20 61 63 63  |  for "token acc|
0000b3f0  65 70 74 65 64 22 0a 21  20 20 20 20 30 20 20 20  |epted".!    0   |
0000b400  20 66 6f 72 20 22 74 6f  6b 65 6e 20 66 61 69 6c  | for "token fail|
0000b410  65 64 22 0a 21 0a 21 20  20 28 41 29 20 20 20 20  |ed".!.!  (A)    |
0000b420  20 20 20 20 20 20 20 20  50 72 65 6c 69 6d 69 6e  |        Prelimin|
0000b430  61 72 69 65 73 20 61 6e  64 20 73 70 65 63 69 61  |aries and specia|
0000b440  6c 2f 6e 75 6d 62 65 72  20 74 6f 6b 65 6e 73 0a  |l/number tokens.|
0000b450  21 20 20 28 42 29 20 20  20 20 20 20 20 20 20 20  |!  (B)          |
0000b460  20 20 41 63 74 75 61 6c  20 6f 62 6a 65 63 74 20  |  Actual object |
0000b470  6e 61 6d 65 73 20 28 6d  6f 73 74 6c 79 20 73 75  |names (mostly su|
0000b480  62 63 6f 6e 74 72 61 63  74 65 64 21 29 0a 21 20  |bcontracted!).! |
0000b490  20 28 43 29 20 20 20 20  20 20 20 20 20 20 20 20  | (C)            |
0000b4a0  61 6e 64 2f 62 75 74 20  61 6e 64 20 73 6f 20 6f  |and/but and so o|
0000b4b0  6e 0a 21 20 20 28 44 29  20 20 20 20 20 20 20 20  |n.!  (D)        |
0000b4c0  20 20 20 20 52 65 74 75  72 6e 69 6e 67 20 61 6e  |    Returning an|
0000b4d0  20 61 63 63 65 70 74 65  64 20 74 6f 6b 65 6e 0a  | accepted token.|
0000b4e0  21 0a 21 20 2d 2d 2d 2d  2d 2d 2d 2d 2d 2d 2d 2d  |!.! ------------|
0000b4f0  2d 2d 2d 2d 2d 2d 2d 2d  2d 2d 2d 2d 2d 2d 2d 2d  |----------------|
*
0000b530  0a 0a 5b 20 50 61 72 73  65 4f 62 6a 65 63 74 4c  |..[ ParseObjectL|
0000b540  69 73 74 20 72 65 73 75  6c 74 73 20 74 6f 6b 65  |ist results toke|
0000b550  6e 20 20 6c 20 6f 20 69  20 6a 20 6b 0a 20 20 20  |n  l o i j k.   |
0000b560  20 20 20 20 20 20 20 20  20 20 20 20 20 20 20 20  |                |
0000b570  20 20 20 20 20 20 20 20  20 20 20 20 20 20 61 6e  |              an|
0000b580  64 5f 70 61 72 69 74 79  20 73 69 6e 67 6c 65 5f  |d_parity single_|
0000b590  6f 62 6a 65 63 74 20 64  65 73 63 5f 77 6e 20 6d  |object desc_wn m|
0000b5a0  61 6e 79 5f 66 6c 61 67  3b 0a 0a 20 20 20 20 6d  |any_flag;..    m|
0000b5b0  61 6e 79 5f 66 6c 61 67  3d 30 3b 20 61 6e 64 5f  |any_flag=0; and_|
0000b5c0  70 61 72 69 74 79 3d 31  3b 20 6d 75 6c 74 69 70  |parity=1; multip|
0000b5d0  6c 65 5f 6f 62 6a 65 63  74 2d 3e 30 20 3d 20 30  |le_object->0 = 0|
0000b5e0  3b 20 64 6f 6e 74 5f 69  6e 66 65 72 3d 30 3b 0a  |; dont_infer=0;.|
0000b5f0  0a 21 20 20 2a 2a 2a 2a  20 28 41 29 20 2a 2a 2a  |.!  **** (A) ***|
0000b600  2a 0a 21 20 20 57 65 20  65 78 70 65 63 74 20 74  |*.!  We expect t|
0000b610  6f 20 66 69 6e 64 20 61  20 6c 69 73 74 20 6f 66  |o find a list of|
0000b620  20 6f 62 6a 65 63 74 73  20 6e 65 78 74 20 69 6e  | objects next in|
0000b630  20 77 68 61 74 20 74 68  65 20 70 6c 61 79 65 72  | what the player|
0000b640  27 73 20 74 79 70 65 64  2e 0a 0a 20 20 2e 4f 62  |'s typed...  .Ob|
0000b650  6a 65 63 74 4c 69 73 74  3b 0a 0a 20 20 20 69 66  |jectList;..   if|
0000b660  20 28 70 61 72 73 65 72  5f 74 72 61 63 65 3e 3d  | (parser_trace>=|
0000b670  33 29 20 70 72 69 6e 74  20 22 20 20 5b 4f 62 6a  |3) print "  [Obj|
0000b680  65 63 74 20 6c 69 73 74  20 66 72 6f 6d 20 77 6f  |ect list from wo|
0000b690  72 64 20 22 2c 20 77 6e  2c 20 22 5d 5e 22 3b 0a  |rd ", wn, "]^";.|
0000b6a0  0a 21 20 20 54 61 6b 65  20 61 6e 20 61 64 76 61  |.!  Take an adva|
0000b6b0  6e 63 65 20 6c 6f 6f 6b  20 61 74 20 74 68 65 20  |nce look at the |
0000b6c0  6e 65 78 74 20 77 6f 72  64 3a 20 69 66 20 69 74  |next word: if it|
0000b6d0  27 73 20 22 69 74 22 20  6f 72 20 22 74 68 65 6d  |'s "it" or "them|
0000b6e0  22 2c 20 61 6e 64 20 74  68 65 73 65 0a 21 20 20  |", and these.!  |
0000b6f0  61 72 65 20 75 6e 73 65  74 2c 20 73 65 74 20 74  |are unset, set t|
0000b700  68 65 20 61 70 70 72 6f  70 72 69 61 74 65 20 65  |he appropriate e|
0000b710  72 72 6f 72 20 6e 75 6d  62 65 72 20 61 6e 64 20  |rror number and |
0000b720  67 69 76 65 20 75 70 20  6f 6e 20 74 68 65 20 6c  |give up on the l|
0000b730  69 6e 65 0a 21 20 20 28  69 66 20 6e 6f 74 2c 20  |ine.!  (if not, |
0000b740  74 68 65 73 65 20 61 72  65 20 73 74 69 6c 6c 20  |these are still |
0000b750  70 61 72 73 65 64 20 69  6e 20 74 68 65 20 75 73  |parsed in the us|
0000b760  75 61 6c 20 77 61 79 20  2d 20 69 74 20 69 73 20  |ual way - it is |
0000b770  6e 6f 74 20 61 73 73 75  6d 65 64 0a 21 20 20 74  |not assumed.!  t|
0000b780  68 61 74 20 74 68 65 79  20 73 74 69 6c 6c 20 72  |hat they still r|
0000b790  65 66 65 72 20 74 6f 20  73 6f 6d 65 74 68 69 6e  |efer to somethin|
0000b7a0  67 20 69 6e 20 73 63 6f  70 65 29 0a 0a 20 20 20  |g in scope)..   |
0000b7b0  20 6f 3d 4e 65 78 74 57  6f 72 64 28 29 3b 20 77  | o=NextWord(); w|
0000b7c0  6e 2d 2d 3b 0a 20 20 20  20 69 66 20 28 6f 3d 3d  |n--;.    if (o==|
0000b7d0  27 69 74 27 20 6f 72 20  27 74 68 65 6d 27 29 0a  |'it' or 'them').|
0000b7e0  20 20 20 20 7b 20 20 20  76 61 67 75 65 5f 77 6f  |    {   vague_wo|
0000b7f0  72 64 3d 6f 3b 20 76 61  67 75 65 5f 6f 62 6a 3d  |rd=o; vague_obj=|
0000b800  69 74 6f 62 6a 3b 0a 20  20 20 20 20 20 20 20 69  |itobj;.        i|
0000b810  66 20 28 69 74 6f 62 6a  3d 3d 30 29 20 7b 20 65  |f (itobj==0) { e|
0000b820  74 79 70 65 3d 56 41 47  55 45 5f 50 45 3b 20 72  |type=VAGUE_PE; r|
0000b830  65 74 75 72 6e 20 30 3b  20 7d 0a 20 20 20 20 7d  |eturn 0; }.    }|
0000b840  0a 20 20 20 20 69 66 20  28 6f 3d 3d 27 68 69 6d  |.    if (o=='him|
0000b850  27 29 0a 20 20 20 20 7b  20 20 20 76 61 67 75 65  |').    {   vague|
0000b860  5f 77 6f 72 64 3d 6f 3b  20 76 61 67 75 65 5f 6f  |_word=o; vague_o|
0000b870  62 6a 3d 68 69 6d 6f 62  6a 3b 0a 20 20 20 20 20  |bj=himobj;.     |
0000b880  20 20 20 69 66 20 28 68  69 6d 6f 62 6a 3d 3d 30  |   if (himobj==0|
0000b890  29 20 7b 20 65 74 79 70  65 3d 56 41 47 55 45 5f  |) { etype=VAGUE_|
0000b8a0  50 45 3b 20 72 65 74 75  72 6e 20 30 3b 20 7d 0a  |PE; return 0; }.|
0000b8b0  20 20 20 20 7d 0a 20 20  20 20 69 66 20 28 6f 3d  |    }.    if (o=|
0000b8c0  3d 27 68 65 72 27 29 0a  20 20 20 20 7b 20 20 20  |='her').    {   |
0000b8d0  76 61 67 75 65 5f 77 6f  72 64 3d 6f 3b 20 76 61  |vague_word=o; va|
0000b8e0  67 75 65 5f 6f 62 6a 3d  68 65 72 6f 62 6a 3b 0a  |gue_obj=herobj;.|
0000b8f0  20 20 20 20 20 20 20 20  69 66 20 28 68 65 72 6f  |        if (hero|
0000b900  62 6a 3d 3d 30 29 20 7b  20 65 74 79 70 65 3d 56  |bj==0) { etype=V|
0000b910  41 47 55 45 5f 50 45 3b  20 72 65 74 75 72 6e 20  |AGUE_PE; return |
0000b920  30 3b 20 7d 0a 20 20 20  20 7d 0a 20 20 20 20 69  |0; }.    }.    i|
0000b930  66 20 28 6f 3d 3d 27 6d  65 27 20 6f 72 20 27 6d  |f (o=='me' or 'm|
0000b940  79 73 65 6c 66 27 20 6f  72 20 27 73 65 6c 66 27  |yself' or 'self'|
0000b950  29 0a 20 20 20 20 7b 20  20 20 76 61 67 75 65 5f  |).    {   vague_|
0000b960  77 6f 72 64 3d 6f 3b 20  76 61 67 75 65 5f 6f 62  |word=o; vague_ob|
0000b970  6a 3d 70 6c 61 79 65 72  3b 0a 20 20 20 20 7d 0a  |j=player;.    }.|
0000b980  0a 21 20 20 46 69 72 73  74 6c 79 2c 20 67 65 74  |.!  Firstly, get|
0000b990  20 72 69 64 20 6f 66 20  74 6f 6b 65 6e 73 20 37  | rid of tokens 7|
0000b9a0  20 61 6e 64 20 38 20 28  22 73 70 65 63 69 61 6c  | and 8 ("special|
0000b9b0  22 20 61 6e 64 20 22 6e  75 6d 62 65 72 22 29 2c  |" and "number"),|
0000b9c0  20 61 6e 64 0a 21 20 20  74 6f 6b 65 6e 73 20 77  | and.!  tokens w|
0000b9d0  68 69 63 68 20 61 72 65  20 65 6e 74 69 72 65 6c  |hich are entirel|
0000b9e0  79 20 68 61 6e 64 65 64  20 6f 75 74 20 74 6f 20  |y handed out to |
0000b9f0  6f 75 74 73 69 64 65 20  72 6f 75 74 69 6e 65 73  |outside routines|
0000ba00  0a 0a 20 20 20 20 69 66  20 28 74 6f 6b 65 6e 3d  |..    if (token=|
0000ba10  3d 37 29 0a 20 20 20 20  7b 20 20 20 6c 3d 54 72  |=7).    {   l=Tr|
0000ba20  79 4e 75 6d 62 65 72 28  77 6e 29 3b 0a 20 20 20  |yNumber(wn);.   |
0000ba30  20 20 20 20 20 69 66 20  28 6c 7e 3d 2d 31 30 30  |     if (l~=-100|
0000ba40  30 29 0a 20 20 20 20 20  20 20 20 7b 20 20 20 69  |0).        {   i|
0000ba50  66 20 28 6e 73 6e 73 3d  3d 30 29 20 73 70 65 63  |f (nsns==0) spec|
0000ba60  69 61 6c 5f 6e 75 6d 62  65 72 3d 6c 3b 20 65 6c  |ial_number=l; el|
0000ba70  73 65 20 73 70 65 63 69  61 6c 5f 6e 75 6d 62 65  |se special_numbe|
0000ba80  72 32 3d 6c 3b 0a 20 20  20 20 20 20 20 20 20 20  |r2=l;.          |
0000ba90  20 20 6e 73 6e 73 2b 2b  3b 0a 20 20 20 20 20 20  |  nsns++;.      |
0000baa0  20 20 20 20 20 20 69 66  20 28 70 61 72 73 65 72  |      if (parser|
0000bab0  5f 74 72 61 63 65 3e 3d  33 29 0a 20 20 20 20 20  |_trace>=3).     |
0000bac0  20 20 20 20 20 20 20 20  20 20 20 70 72 69 6e 74  |           print|
0000bad0  20 22 20 20 5b 52 65 61  64 20 73 70 65 63 69 61  | "  [Read specia|
0000bae0  6c 20 61 73 20 74 68 65  20 6e 75 6d 62 65 72 20  |l as the number |
0000baf0  22 2c 20 6c 2c 20 22 5d  5e 22 3b 0a 20 20 20 20  |", l, "]^";.    |
0000bb00  20 20 20 20 7d 0a 20 20  20 20 20 20 20 20 69 66  |    }.        if|
0000bb10  20 28 70 61 72 73 65 72  5f 74 72 61 63 65 3e 3d  | (parser_trace>=|
0000bb20  33 29 0a 20 20 20 20 20  20 20 20 20 20 20 20 70  |3).            p|
0000bb30  72 69 6e 74 20 22 20 20  5b 52 65 61 64 20 73 70  |rint "  [Read sp|
0000bb40  65 63 69 61 6c 20 77 6f  72 64 20 61 74 20 77 6f  |ecial word at wo|
0000bb50  72 64 20 6e 75 6d 62 65  72 20 22 2c 20 77 6e 2c  |rd number ", wn,|
0000bb60  20 22 5d 5e 22 3b 0a 20  20 20 20 20 20 20 20 73  | "]^";.        s|
0000bb70  70 65 63 69 61 6c 5f 77  6f 72 64 3d 4e 65 78 74  |pecial_word=Next|
0000bb80  57 6f 72 64 28 29 3b 20  73 69 6e 67 6c 65 5f 6f  |Word(); single_o|
0000bb90  62 6a 65 63 74 3d 31 3b  20 6a 75 6d 70 20 50 61  |bject=1; jump Pa|
0000bba0  73 73 54 6f 6b 65 6e 3b  0a 20 20 20 20 7d 0a 20  |ssToken;.    }. |
0000bbb0  20 20 20 69 66 20 28 74  6f 6b 65 6e 3d 3d 38 29  |   if (token==8)|
0000bbc0  0a 20 20 20 20 7b 20 20  20 6c 3d 54 72 79 4e 75  |.    {   l=TryNu|
0000bbd0  6d 62 65 72 28 77 6e 2b  2b 29 3b 0a 20 20 20 20  |mber(wn++);.    |
0000bbe0  20 20 20 20 69 66 20 28  6c 3d 3d 2d 31 30 30 30  |    if (l==-1000|
0000bbf0  29 20 7b 20 65 74 79 70  65 3d 4e 55 4d 42 45 52  |) { etype=NUMBER|
0000bc00  5f 50 45 3b 20 72 66 61  6c 73 65 3b 20 7d 0a 20  |_PE; rfalse; }. |
0000bc10  20 20 20 20 20 20 20 69  66 20 28 70 61 72 73 65  |       if (parse|
0000bc20  72 5f 74 72 61 63 65 3e  3d 33 29 20 70 72 69 6e  |r_trace>=3) prin|
0000bc30  74 20 22 20 20 5b 52 65  61 64 20 6e 75 6d 62 65  |t "  [Read numbe|
0000bc40  72 20 61 73 20 22 2c 20  6c 2c 20 22 5d 5e 22 3b  |r as ", l, "]^";|
0000bc50  0a 20 20 20 20 20 20 20  20 69 66 20 28 6e 73 6e  |.        if (nsn|
0000bc60  73 2b 2b 3d 3d 30 29 20  73 70 65 63 69 61 6c 5f  |s++==0) special_|
0000bc70  6e 75 6d 62 65 72 3d 6c  3b 20 65 6c 73 65 20 73  |number=l; else s|
0000bc80  70 65 63 69 61 6c 5f 6e  75 6d 62 65 72 32 3d 6c  |pecial_number2=l|
0000bc90  3b 0a 20 20 20 20 20 20  20 20 73 69 6e 67 6c 65  |;.        single|
0000bca0  5f 6f 62 6a 65 63 74 3d  31 3b 20 6a 75 6d 70 20  |_object=1; jump |
0000bcb0  50 61 73 73 54 6f 6b 65  6e 3b 0a 20 20 20 20 7d  |PassToken;.    }|
0000bcc0  0a 0a 20 20 20 20 69 66  20 28 74 6f 6b 65 6e 3e  |..    if (token>|
0000bcd0  3d 34 38 20 26 26 20 74  6f 6b 65 6e 3c 38 30 29  |=48 && token<80)|
0000bce0  0a 20 20 20 20 7b 20 20  20 6c 3d 69 6e 64 69 72  |.    {   l=indir|
0000bcf0  65 63 74 28 23 70 72 65  61 63 74 69 6f 6e 73 5f  |ect(#preactions_|
0000bd00  74 61 62 6c 65 2d 2d 3e  28 74 6f 6b 65 6e 2d 34  |table-->(token-4|
0000bd10  38 29 29 3b 0a 20 20 20  20 20 20 20 20 69 66 20  |8));.        if |
0000bd20  28 70 61 72 73 65 72 5f  74 72 61 63 65 3e 3d 33  |(parser_trace>=3|
0000bd30  29 0a 20 20 20 20 20 20  20 20 20 20 20 20 70 72  |).            pr|
0000bd40  69 6e 74 20 22 20 20 5b  4f 75 74 73 69 64 65 20  |int "  [Outside |
0000bd50  70 61 72 73 69 6e 67 20  72 6f 75 74 69 6e 65 20  |parsing routine |
0000bd60  72 65 74 75 72 6e 65 64  20 22 2c 20 6c 2c 20 22  |returned ", l, "|
0000bd70  5d 5e 22 3b 0a 20 20 20  20 20 20 20 20 69 66 20  |]^";.        if |
0000bd80  28 6c 3c 30 29 20 72 66  61 6c 73 65 3b 0a 20 20  |(l<0) rfalse;.  |
0000bd90  20 20 20 20 20 20 69 66  20 28 6c 3d 3d 31 29 0a  |      if (l==1).|
0000bda0  20 20 20 20 20 20 20 20  7b 20 20 20 69 66 20 28  |        {   if (|
0000bdb0  6e 73 6e 73 3d 3d 30 29  20 73 70 65 63 69 61 6c  |nsns==0) special|
0000bdc0  5f 6e 75 6d 62 65 72 3d  70 61 72 73 65 64 5f 6e  |_number=parsed_n|
0000bdd0  75 6d 62 65 72 3b 0a 20  20 20 20 20 20 20 20 20  |umber;.         |
0000bde0  20 20 20 65 6c 73 65 20  73 70 65 63 69 61 6c 5f  |   else special_|
0000bdf0  6e 75 6d 62 65 72 32 3d  70 61 72 73 65 64 5f 6e  |number2=parsed_n|
0000be00  75 6d 62 65 72 3b 0a 20  20 20 20 20 20 20 20 20  |umber;.         |
0000be10  20 20 20 6e 73 6e 73 2b  2b 3b 0a 20 20 20 20 20  |   nsns++;.     |
0000be20  20 20 20 7d 0a 20 20 20  20 20 20 20 20 73 69 6e  |   }.        sin|
0000be30  67 6c 65 5f 6f 62 6a 65  63 74 3d 6c 3b 20 6a 75  |gle_object=l; ju|
0000be40  6d 70 20 50 61 73 73 54  6f 6b 65 6e 3b 0a 20 20  |mp PassToken;.  |
0000be50  20 20 7d 0a 0a 20 20 20  20 69 66 20 28 74 6f 6b  |  }..    if (tok|
0000be60  65 6e 3e 3d 38 30 20 26  26 20 74 6f 6b 65 6e 3c  |en>=80 && token<|
0000be70  31 32 38 29 0a 20 20 20  20 7b 20 20 20 73 63 6f  |128).    {   sco|
0000be80  70 65 5f 74 6f 6b 65 6e  20 3d 20 23 70 72 65 61  |pe_token = #prea|
0000be90  63 74 69 6f 6e 73 5f 74  61 62 6c 65 2d 2d 3e 28  |ctions_table-->(|
0000bea0  74 6f 6b 65 6e 2d 38 30  29 3b 0a 20 20 20 20 20  |token-80);.     |
0000beb0  20 20 20 73 63 6f 70 65  5f 73 74 61 67 65 20 3d  |   scope_stage =|
0000bec0  20 31 3b 0a 20 20 20 20  20 20 20 20 6c 3d 69 6e  | 1;.        l=in|
0000bed0  64 69 72 65 63 74 28 73  63 6f 70 65 5f 74 6f 6b  |direct(scope_tok|
0000bee0  65 6e 29 3b 0a 20 20 20  20 20 20 20 20 69 66 20  |en);.        if |
0000bef0  28 70 61 72 73 65 72 5f  74 72 61 63 65 3e 3d 33  |(parser_trace>=3|
0000bf00  29 0a 20 20 20 20 20 20  20 20 20 20 20 20 70 72  |).            pr|
0000bf10  69 6e 74 20 22 20 20 5b  53 63 6f 70 65 20 72 6f  |int "  [Scope ro|
0000bf20  75 74 69 6e 65 20 72 65  74 75 72 6e 65 64 20 6d  |utine returned m|
0000bf30  75 6c 74 69 70 6c 65 2d  66 6c 61 67 20 6f 66 20  |ultiple-flag of |
0000bf40  22 2c 20 6c 2c 20 22 5d  5e 22 3b 0a 20 20 20 20  |", l, "]^";.    |
0000bf50  20 20 20 20 69 66 20 28  6c 3d 3d 31 29 20 74 6f  |    if (l==1) to|
0000bf60  6b 65 6e 3d 32 3b 20 65  6c 73 65 20 74 6f 6b 65  |ken=2; else toke|
0000bf70  6e 3d 30 3b 0a 20 20 20  20 7d 0a 0a 20 20 20 20  |n=0;.    }..    |
0000bf80  74 6f 6b 65 6e 5f 77 61  73 3d 30 3b 0a 20 20 20  |token_was=0;.   |
0000bf90  20 69 66 20 28 74 6f 6b  65 6e 3e 3d 31 36 29 0a  | if (token>=16).|
0000bfa0  20 20 20 20 7b 20 20 20  74 6f 6b 65 6e 5f 77 61  |    {   token_wa|
0000bfb0  73 20 3d 20 74 6f 6b 65  6e 3b 0a 20 20 20 20 20  |s = token;.     |
0000bfc0  20 20 20 74 6f 6b 65 6e  3d 30 3b 0a 20 20 20 20  |   token=0;.    |
0000bfd0  7d 0a 0a 21 20 20 4f 74  68 65 72 77 69 73 65 2c  |}..!  Otherwise,|
0000bfe0  20 77 65 20 68 61 76 65  20 6f 6e 65 20 6f 66 20  | we have one of |
0000bff0  74 68 65 20 74 6f 6b 65  6e 73 20 30 20 74 6f 20  |the tokens 0 to |
0000c000  36 2c 20 61 6c 6c 20 6f  66 20 77 68 69 63 68 20  |6, all of which |
0000c010  72 65 61 6c 6c 79 20 64  6f 20 6d 65 61 6e 0a 21  |really do mean.!|
0000c020  20 20 74 68 61 74 20 6f  62 6a 65 63 74 73 20 61  |  that objects a|
0000c030  72 65 20 65 78 70 65 63  74 65 64 2e 0a 0a 21 20  |re expected...! |
0000c040  20 53 6f 20 6e 6f 77 20  77 65 20 70 61 72 73 65  | So now we parse|
0000c050  20 61 6e 79 20 64 65 73  63 72 69 70 74 69 76 65  | any descriptive|
0000c060  20 77 6f 72 64 73 0a 0a  20 20 20 20 61 6c 6c 6f  | words..    allo|
0000c070  77 5f 70 6c 75 72 61 6c  73 20 3d 20 31 3b 20 64  |w_plurals = 1; d|
0000c080  65 73 63 5f 77 6e 20 3d  20 77 6e 3b 0a 20 20 20  |esc_wn = wn;.   |
0000c090  20 2e 54 72 79 41 67 61  69 6e 3b 0a 0a 20 20 20  | .TryAgain;..   |
0000c0a0  20 6c 3d 44 65 73 63 72  69 70 74 6f 72 73 28 74  | l=Descriptors(t|
0000c0b0  6f 6b 65 6e 29 3b 20 69  66 20 28 6c 7e 3d 30 29  |oken); if (l~=0)|
0000c0c0  20 7b 20 65 74 79 70 65  3d 6c 3b 20 72 65 74 75  | { etype=l; retu|
0000c0d0  72 6e 20 30 3b 20 7d 0a  0a 21 20 20 2a 2a 2a 2a  |rn 0; }..!  ****|
0000c0e0  20 28 42 29 20 2a 2a 2a  2a 0a 0a 21 20 20 54 68  | (B) ****..!  Th|
0000c0f0  69 73 20 69 73 20 61 6e  20 61 63 74 75 61 6c 20  |is is an actual |
0000c100  73 70 65 63 69 66 69 65  64 20 6f 62 6a 65 63 74  |specified object|
0000c110  2c 20 61 6e 64 20 69 73  20 74 68 65 72 65 66 6f  |, and is therefo|
0000c120  72 65 20 77 68 65 72 65  20 61 20 74 79 70 69 6e  |re where a typin|
0000c130  67 20 65 72 72 6f 72 0a  21 20 20 69 73 20 6d 6f  |g error.!  is mo|
0000c140  73 74 20 6c 69 6b 65 6c  79 20 74 6f 20 6f 63 63  |st likely to occ|
0000c150  75 72 2c 20 73 6f 20 77  65 20 73 65 74 3a 0a 0a  |ur, so we set:..|
0000c160  20 20 20 20 6f 6f 70 73  5f 66 72 6f 6d 3d 77 6e  |    oops_from=wn|
0000c170  3b 0a 0a 21 20 20 49 6e  20 65 69 74 68 65 72 20  |;..!  In either |
0000c180  63 61 73 65 20 62 65 6c  6f 77 20 77 65 20 75 73  |case below we us|
0000c190  65 20 4e 6f 75 6e 44 6f  6d 61 69 6e 2c 20 67 69  |e NounDomain, gi|
0000c1a0  76 69 6e 67 20 69 74 20  74 68 65 20 74 6f 6b 65  |ving it the toke|
0000c1b0  6e 20 6e 75 6d 62 65 72  20 61 73 0a 21 20 20 63  |n number as.!  c|
0000c1c0  6f 6e 74 65 78 74 2c 20  61 6e 64 20 74 77 6f 20  |ontext, and two |
0000c1d0  70 6c 61 63 65 73 20 74  6f 20 6c 6f 6f 6b 3a 20  |places to look: |
0000c1e0  61 6d 6f 6e 67 20 74 68  65 20 61 63 74 6f 72 27  |among the actor'|
0000c1f0  73 20 70 6f 73 73 65 73  73 69 6f 6e 73 2c 20 61  |s possessions, a|
0000c200  6e 64 20 69 6e 20 74 68  65 0a 21 20 20 70 72 65  |nd in the.!  pre|
0000c210  73 65 6e 74 20 6c 6f 63  61 74 69 6f 6e 2e 20 20  |sent location.  |
0000c220  28 4e 6f 74 65 20 74 68  61 74 20 74 68 65 20 6f  |(Note that the o|
0000c230  72 64 65 72 20 64 65 70  65 6e 64 73 20 6f 6e 20  |rder depends on |
0000c240  77 68 69 63 68 20 69 73  20 6c 69 6b 65 6c 69 65  |which is likelie|
0000c250  73 74 2e 29 0a 0a 21 20  20 53 6f 2c 20 74 77 6f  |st.)..!  So, two|
0000c260  20 63 61 73 65 73 2e 20  20 43 61 73 65 20 31 3a  | cases.  Case 1:|
0000c270  20 74 6f 6b 65 6e 20 6e  6f 74 20 65 71 75 61 6c  | token not equal|
0000c280  20 74 6f 20 22 68 65 6c  64 22 20 28 73 6f 2c 20  | to "held" (so, |
0000c290  6e 6f 20 69 6d 70 6c 69  63 69 74 20 74 61 6b 65  |no implicit take|
0000c2a0  73 29 0a 21 20 20 62 75  74 20 77 65 20 6d 61 79  |s).!  but we may|
0000c2b0  20 77 65 6c 6c 20 62 65  20 64 65 61 6c 69 6e 67  | well be dealing|
0000c2c0  20 77 69 74 68 20 6d 75  6c 74 69 70 6c 65 20 6f  | with multiple o|
0000c2d0  62 6a 65 63 74 73 0a 0a  20 20 20 20 69 66 20 28  |bjects..    if (|
0000c2e0  74 6f 6b 65 6e 7e 3d 31  29 0a 20 20 20 20 7b 20  |token~=1).    { |
0000c2f0  20 20 69 3d 6d 75 6c 74  69 70 6c 65 5f 6f 62 6a  |  i=multiple_obj|
0000c300  65 63 74 2d 2d 3e 30 3b  0a 20 20 20 20 20 20 20  |ect-->0;.       |
0000c310  20 69 66 20 28 70 61 72  73 65 72 5f 74 72 61 63  | if (parser_trac|
0000c320  65 3e 3d 33 29 0a 20 20  20 20 20 20 20 20 20 20  |e>=3).          |
0000c330  20 20 70 72 69 6e 74 20  22 20 20 5b 43 61 6c 6c  |  print "  [Call|
0000c340  69 6e 67 20 4e 6f 75 6e  44 6f 6d 61 69 6e 20 6f  |ing NounDomain o|
0000c350  6e 20 6c 6f 63 61 74 69  6f 6e 20 61 6e 64 20 61  |n location and a|
0000c360  63 74 6f 72 5d 5e 22 3b  0a 20 20 20 20 20 20 20  |ctor]^";.       |
0000c370  20 6c 3d 4e 6f 75 6e 44  6f 6d 61 69 6e 28 6c 6f  | l=NounDomain(lo|
0000c380  63 61 74 69 6f 6e 2c 20  61 63 74 6f 72 2c 20 74  |cation, actor, t|
0000c390  6f 6b 65 6e 29 3b 0a 20  20 20 20 20 20 20 20 69  |oken);.        i|
0000c3a0  66 20 28 6c 3d 3d 31 30  30 30 29 20 72 65 74 75  |f (l==1000) retu|
0000c3b0  72 6e 20 6c 3b 20 20 20  20 20 20 20 20 20 20 20  |rn l;           |
0000c3c0  20 20 20 20 20 20 20 20  20 21 20 52 65 70 61 72  |         ! Repar|
0000c3d0  73 65 20 61 66 74 65 72  20 51 26 41 0a 20 20 20  |se after Q&A.   |
0000c3e0  20 20 20 20 20 69 66 20  28 6c 3d 3d 30 29 20 7b  |     if (l==0) {|
0000c3f0  20 65 74 79 70 65 3d 43  61 6e 74 53 65 65 28 29  | etype=CantSee()|
0000c400  3b 20 6a 75 6d 70 20 46  61 69 6c 54 6f 6b 65 6e  |; jump FailToken|
0000c410  3b 20 7d 20 20 21 20 43  68 6f 6f 73 65 20 62 65  |; }  ! Choose be|
0000c420  73 74 20 65 72 72 6f 72  0a 20 20 20 20 20 20 20  |st error.       |
0000c430  20 69 66 20 28 70 61 72  73 65 72 5f 74 72 61 63  | if (parser_trac|
0000c440  65 3e 3d 33 29 0a 20 20  20 20 20 20 20 20 7b 20  |e>=3).        { |
0000c450  20 20 69 66 20 28 6c 3e  31 29 0a 20 20 20 20 20  |  if (l>1).     |
0000c460  20 20 20 20 20 20 20 7b  20 20 20 70 72 69 6e 74  |       {   print|
0000c470  20 22 20 20 5b 4e 44 20  72 65 74 75 72 6e 65 64  | "  [ND returned|
0000c480  20 22 3b 20 44 65 66 41  72 74 28 6c 29 3b 20 70  | "; DefArt(l); p|
0000c490  72 69 6e 74 20 22 5d 5e  22 3b 20 7d 0a 20 20 20  |rint "]^"; }.   |
0000c4a0  20 20 20 20 20 20 20 20  20 65 6c 73 65 0a 20 20  |         else.  |
0000c4b0  20 20 20 20 20 20 20 20  20 20 7b 20 20 20 70 72  |          {   pr|
0000c4c0  69 6e 74 20 22 20 20 5b  4e 44 20 61 70 70 65 6e  |int "  [ND appen|
0000c4d0  64 65 64 20 74 6f 20 74  68 65 20 6d 75 6c 74 69  |ded to the multi|
0000c4e0  70 6c 65 20 6f 62 6a 65  63 74 20 6c 69 73 74 3a  |ple object list:|
0000c4f0  5e 22 3b 0a 20 20 20 20  20 20 20 20 20 20 20 20  |^";.            |
0000c500  20 20 20 20 6b 3d 6d 75  6c 74 69 70 6c 65 5f 6f  |    k=multiple_o|
0000c510  62 6a 65 63 74 2d 2d 3e  30 3b 0a 20 20 20 20 20  |bject-->0;.     |
0000c520  20 20 20 20 20 20 20 20  20 20 20 66 6f 72 20 28  |           for (|
0000c530  6a 3d 69 2b 31 3a 6a 3c  3d 6b 3a 6a 2b 2b 29 0a  |j=i+1:j<=k:j++).|
0000c540  20 20 20 20 20 20 20 20  20 20 20 20 20 20 20 20  |                |
0000c550  7b 20 20 20 70 72 69 6e  74 20 22 20 20 45 6e 74  |{   print "  Ent|
0000c560  72 79 20 22 2c 20 6a 2c  20 22 3a 20 22 3b 20 43  |ry ", j, ": "; C|
0000c570  44 65 66 41 72 74 28 6d  75 6c 74 69 70 6c 65 5f  |DefArt(multiple_|
0000c580  6f 62 6a 65 63 74 2d 2d  3e 6a 29 3b 0a 20 20 20  |object-->j);.   |
0000c590  20 20 20 20 20 20 20 20  20 20 20 20 20 20 20 20  |                |
0000c5a0  20 70 72 69 6e 74 20 22  20 28 22 2c 20 6d 75 6c  | print " (", mul|
0000c5b0  74 69 70 6c 65 5f 6f 62  6a 65 63 74 2d 2d 3e 6a  |tiple_object-->j|
0000c5c0  2c 20 22 29 5e 22 3b 0a  20 20 20 20 20 20 20 20  |, ")^";.        |
0000c5d0  20 20 20 20 20 20 20 20  7d 0a 20 20 20 20 20 20  |        }.      |
0000c5e0  20 20 20 20 20 20 20 20  20 20 70 72 69 6e 74 20  |          print |
0000c5f0  22 20 20 4c 69 73 74 20  6e 6f 77 20 68 61 73 20  |"  List now has |
0000c600  73 69 7a 65 20 22 2c 20  6b 2c 20 22 5d 5e 22 3b  |size ", k, "]^";|
0000c610  0a 20 20 20 20 20 20 20  20 20 20 20 20 7d 0a 20  |.            }. |
0000c620  20 20 20 20 20 20 20 7d  0a 20 20 20 20 20 20 20  |       }.       |
0000c630  20 69 66 20 28 6c 3d 3d  31 29 0a 20 20 20 20 20  | if (l==1).     |
0000c640  20 20 20 7b 20 20 20 69  66 20 28 6d 61 6e 79 5f  |   {   if (many_|
0000c650  66 6c 61 67 3d 3d 30 29  0a 20 20 20 20 20 20 20  |flag==0).       |
0000c660  20 20 20 20 20 7b 20 20  20 6d 61 6e 79 5f 66 6c  |     {   many_fl|
0000c670  61 67 3d 31 3b 0a 20 20  20 20 20 20 20 20 20 20  |ag=1;.          |
0000c680  20 20 7d 0a 20 20 20 20  20 20 20 20 20 20 20 20  |  }.            |
0000c690  65 6c 73 65 20 20 20 20  20 20 20 20 20 20 20 20  |else            |
0000c6a0  20 20 20 20 20 20 20 20  20 20 20 20 20 20 20 20  |                |
0000c6b0  20 20 20 20 20 20 21 20  4d 65 72 67 65 20 77 69  |      ! Merge wi|
0000c6c0  74 68 20 65 61 72 6c 69  65 72 20 6f 6e 65 73 0a  |th earlier ones.|
0000c6d0  20 20 20 20 20 20 20 20  20 20 20 20 7b 20 20 20  |            {   |
0000c6e0  6b 3d 6d 75 6c 74 69 70  6c 65 5f 6f 62 6a 65 63  |k=multiple_objec|
0000c6f0  74 2d 2d 3e 30 3b 20 20  20 20 20 20 20 20 20 20  |t-->0;          |
0000c700  20 20 21 20 28 77 69 74  68 20 65 69 74 68 65 72  |  ! (with either|
0000c710  20 70 61 72 69 74 79 29  0a 20 20 20 20 20 20 20  | parity).       |
0000c720  20 20 20 20 20 20 20 20  20 6d 75 6c 74 69 70 6c  |         multipl|
0000c730  65 5f 6f 62 6a 65 63 74  2d 2d 3e 30 20 3d 20 69  |e_object-->0 = i|
0000c740  3b 0a 20 20 20 20 20 20  20 20 20 20 20 20 20 20  |;.              |
0000c750  20 20 66 6f 72 20 28 6a  3d 69 2b 31 3a 6a 3c 3d  |  for (j=i+1:j<=|
0000c760  6b 3a 6a 2b 2b 29 0a 20  20 20 20 20 20 20 20 20  |k:j++).         |
0000c770  20 20 20 20 20 20 20 7b  20 20 20 69 66 20 28 61  |       {   if (a|
0000c780  6e 64 5f 70 61 72 69 74  79 3d 3d 31 29 20 4d 75  |nd_parity==1) Mu|
0000c790  6c 74 69 41 64 64 28 6d  75 6c 74 69 70 6c 65 5f  |ltiAdd(multiple_|
0000c7a0  6f 62 6a 65 63 74 2d 2d  3e 6a 29 3b 0a 20 20 20  |object-->j);.   |
0000c7b0  20 20 20 20 20 20 20 20  20 20 20 20 20 20 20 20  |                |
0000c7c0  20 65 6c 73 65 20 4d 75  6c 74 69 53 75 62 28 6d  | else MultiSub(m|
0000c7d0  75 6c 74 69 70 6c 65 5f  6f 62 6a 65 63 74 2d 2d  |ultiple_object--|
0000c7e0  3e 6a 29 3b 0a 20 20 20  20 20 20 20 20 20 20 20  |>j);.           |
0000c7f0  20 20 20 20 20 7d 0a 20  20 20 20 20 20 20 20 69  |     }.        i|
0000c800  66 20 28 70 61 72 73 65  72 5f 74 72 61 63 65 3e  |f (parser_trace>|
0000c810  3d 33 29 0a 20 20 20 20  20 20 20 20 20 20 20 20  |=3).            |
0000c820  70 72 69 6e 74 20 22 20  20 5b 4d 65 72 67 69 6e  |print "  [Mergin|
0000c830  67 20 22 2c 20 6b 2d 69  2c 20 22 20 6e 65 77 20  |g ", k-i, " new |
0000c840  6f 62 6a 65 63 74 73 20  74 6f 20 74 68 65 20 22  |objects to the "|
0000c850  2c 20 69 2c 20 22 20 6f  6c 64 20 6f 6e 65 73 5d  |, i, " old ones]|
0000c860  5e 22 3b 0a 20 20 20 20  20 20 20 20 20 20 20 20  |^";.            |
0000c870  7d 0a 20 20 20 20 20 20  20 20 7d 0a 20 20 20 20  |}.        }.    |
0000c880  20 20 20 20 65 6c 73 65  20 0a 20 20 20 20 20 20  |    else .      |
0000c890  20 20 7b 20 20 20 69 66  20 28 74 6f 6b 65 6e 3d  |  {   if (token=|
0000c8a0  3d 36 20 26 26 20 6c 20  68 61 73 6e 74 20 61 6e  |=6 && l hasnt an|
0000c8b0  69 6d 61 74 65 29 20 20  20 20 20 20 21 20 41 6e  |imate)      ! An|
0000c8c0  69 6d 61 74 69 6f 6e 20  61 73 20 72 65 71 75 69  |imation as requi|
0000c8d0  72 65 64 0a 20 20 20 20  20 20 20 20 20 20 20 20  |red.            |
0000c8e0  7b 20 20 20 65 74 79 70  65 3d 41 4e 49 4d 41 5f  |{   etype=ANIMA_|
0000c8f0  50 45 3b 20 6a 75 6d 70  20 46 61 69 6c 54 6f 6b  |PE; jump FailTok|
0000c900  65 6e 3b 20 7d 20 21 20  66 6f 72 20 74 6f 6b 65  |en; } ! for toke|
0000c910  6e 20 36 0a 20 20 20 20  20 20 20 20 20 20 20 20  |n 6.            |
0000c920  69 66 20 28 6d 61 6e 79  5f 66 6c 61 67 3d 3d 30  |if (many_flag==0|
0000c930  29 0a 20 20 20 20 20 20  20 20 20 20 20 20 20 20  |).              |
0000c940  20 20 73 69 6e 67 6c 65  5f 6f 62 6a 65 63 74 20  |  single_object |
0000c950  3d 20 6c 3b 0a 20 20 20  20 20 20 20 20 20 20 20  |= l;.           |
0000c960  20 65 6c 73 65 0a 20 20  20 20 20 20 20 20 20 20  | else.          |
0000c970  20 20 7b 20 20 20 69 66  20 28 61 6e 64 5f 70 61  |  {   if (and_pa|
0000c980  72 69 74 79 3d 3d 31 29  20 4d 75 6c 74 69 41 64  |rity==1) MultiAd|
0000c990  64 28 6c 29 3b 20 65 6c  73 65 20 4d 75 6c 74 69  |d(l); else Multi|
0000c9a0  53 75 62 28 6c 29 3b 0a  20 20 20 20 20 20 20 20  |Sub(l);.        |
0000c9b0  20 20 20 20 20 20 20 20  69 66 20 28 70 61 72 73  |        if (pars|
0000c9c0  65 72 5f 74 72 61 63 65  3e 3d 33 29 0a 20 20 20  |er_trace>=3).   |
0000c9d0  20 20 20 20 20 20 20 20  20 20 20 20 20 7b 20 20  |             {  |
0000c9e0  20 70 72 69 6e 74 20 22  20 20 5b 43 6f 6d 62 69  | print "  [Combi|
0000c9f0  6e 69 6e 67 20 22 3b 20  44 65 66 41 72 74 28 73  |ning "; DefArt(s|
0000ca00  69 6e 67 6c 65 5f 6f 62  6a 65 63 74 29 3b 0a 20  |ingle_object);. |
0000ca10  20 20 20 20 20 20 20 20  20 20 20 20 20 20 20 20  |                |
0000ca20  20 20 20 70 72 69 6e 74  20 22 20 77 69 74 68 20  |   print " with |
0000ca30  6c 69 73 74 5d 5e 22 3b  0a 20 20 20 20 20 20 20  |list]^";.       |
0000ca40  20 20 20 20 20 20 20 20  20 7d 0a 20 20 20 20 20  |         }.     |
0000ca50  20 20 20 20 20 20 20 7d  0a 20 20 20 20 20 20 20  |       }.       |
0000ca60  20 7d 0a 20 20 20 20 7d  0a 0a 21 20 20 43 61 73  | }.    }..!  Cas|
0000ca70  65 20 32 3a 20 74 6f 6b  65 6e 20 69 73 20 22 68  |e 2: token is "h|
0000ca80  65 6c 64 22 20 28 77 68  69 63 68 20 66 6f 72 74  |eld" (which fort|
0000ca90  75 6e 61 74 65 6c 79 20  63 61 6e 27 74 20 74 61  |unately can't ta|
0000caa0  6b 65 20 6d 75 6c 74 69  70 6c 65 20 6f 62 6a 65  |ke multiple obje|
0000cab0  63 74 73 29 0a 21 20 20  61 6e 64 20 6d 61 79 20  |cts).!  and may |
0000cac0  67 65 6e 65 72 61 74 65  20 61 6e 20 69 6d 70 6c  |generate an impl|
0000cad0  69 63 69 74 20 74 61 6b  65 0a 0a 20 20 20 20 69  |icit take..    i|
0000cae0  66 20 28 74 6f 6b 65 6e  3d 3d 31 29 0a 20 20 20  |f (token==1).   |
0000caf0  20 7b 20 20 20 6c 3d 4e  6f 75 6e 44 6f 6d 61 69  | {   l=NounDomai|
0000cb00  6e 28 61 63 74 6f 72 2c  6c 6f 63 61 74 69 6f 6e  |n(actor,location|
0000cb10  2c 74 6f 6b 65 6e 29 3b  20 20 20 20 20 20 20 21  |,token);       !|
0000cb20  20 53 61 6d 65 20 61 73  20 61 62 6f 76 65 2e 2e  | Same as above..|
0000cb30  2e 0a 20 20 20 20 20 20  20 20 69 66 20 28 6c 3d  |..        if (l=|
0000cb40  3d 31 30 30 30 29 20 72  65 74 75 72 6e 20 6c 3b  |=1000) return l;|
0000cb50  0a 20 20 20 20 20 20 20  20 69 66 20 28 6c 3d 3d  |.        if (l==|
0000cb60  30 29 20 7b 20 65 74 79  70 65 3d 43 61 6e 74 53  |0) { etype=CantS|
0000cb70  65 65 28 29 3b 20 72 65  74 75 72 6e 20 6c 3b 20  |ee(); return l; |
0000cb80  7d 0a 0a 21 20 20 2e 2e  2e 75 6e 74 69 6c 20 69  |}..!  ...until i|
0000cb90  74 20 70 72 6f 64 75 63  65 73 20 73 6f 6d 65 74  |t produces somet|
0000cba0  68 69 6e 67 20 6e 6f 74  20 68 65 6c 64 20 62 79  |hing not held by|
0000cbb0  20 74 68 65 20 61 63 74  6f 72 2e 20 20 54 68 65  | the actor.  The|
0000cbc0  6e 20 61 6e 20 69 6d 70  6c 69 63 69 74 0a 21 20  |n an implicit.! |
0000cbd0  20 74 61 6b 65 20 6d 75  73 74 20 62 65 20 74 72  | take must be tr|
0000cbe0  69 65 64 2e 20 20 49 66  20 74 68 69 73 20 69 73  |ied.  If this is|
0000cbf0  20 61 6c 72 65 61 64 79  20 68 61 70 70 65 6e 69  | already happeni|
0000cc00  6e 67 20 61 6e 79 77 61  79 2c 20 74 68 69 6e 67  |ng anyway, thing|
0000cc10  73 20 61 72 65 20 74 6f  6f 0a 21 20 20 63 6f 6e  |s are too.!  con|
0000cc20  66 75 73 65 64 20 61 6e  64 20 77 65 20 68 61 76  |fused and we hav|
0000cc30  65 20 74 6f 20 67 69 76  65 20 75 70 20 28 62 75  |e to give up (bu|
0000cc40  74 20 73 61 76 69 6e 67  20 74 68 65 20 6f 6f 70  |t saving the oop|
0000cc50  73 20 6d 61 72 6b 65 72  20 73 6f 20 61 73 20 74  |s marker so as t|
0000cc60  6f 20 67 65 74 0a 21 20  20 69 74 20 6f 6e 20 74  |o get.!  it on t|
0000cc70  68 65 20 72 69 67 68 74  20 77 6f 72 64 20 61 66  |he right word af|
0000cc80  74 65 72 77 61 72 64 73  29 2e 0a 21 20 20 54 68  |terwards)..!  Th|
0000cc90  65 20 70 6f 69 6e 74 20  6f 66 20 74 68 69 73 20  |e point of this |
0000cca0  6c 61 73 74 20 72 75 6c  65 20 69 73 20 74 68 61  |last rule is tha|
0000ccb0  74 20 61 20 73 65 71 75  65 6e 63 65 20 6c 69 6b  |t a sequence lik|
0000ccc0  65 0a 21 0a 21 20 20 20  20 20 20 3e 20 72 65 61  |e.!.!      > rea|
0000ccd0  64 20 6e 65 77 73 70 61  70 65 72 0a 21 20 20 20  |d newspaper.!   |
0000cce0  20 20 20 28 74 61 6b 69  6e 67 20 74 68 65 20 6e  |   (taking the n|
0000ccf0  65 77 73 70 61 70 65 72  20 66 69 72 73 74 29 0a  |ewspaper first).|
0000cd00  21 20 20 20 20 20 20 54  68 65 20 64 77 61 72 66  |!      The dwarf|
0000cd10  20 75 6e 65 78 70 65 63  74 65 64 6c 79 20 70 72  | unexpectedly pr|
0000cd20  65 76 65 6e 74 73 20 79  6f 75 20 66 72 6f 6d 20  |events you from |
0000cd30  74 61 6b 69 6e 67 20 74  68 65 20 6e 65 77 73 70  |taking the newsp|
0000cd40  61 70 65 72 21 0a 21 0a  21 20 20 73 68 6f 75 6c  |aper!.!.!  shoul|
0000cd50  64 20 6e 6f 74 20 62 65  20 61 6c 6c 6f 77 65 64  |d not be allowed|
0000cd60  20 74 6f 20 67 6f 20 69  6e 74 6f 20 61 6e 20 69  | to go into an i|
0000cd70  6e 66 69 6e 69 74 65 20  72 65 70 65 61 74 20 2d  |nfinite repeat -|
0000cd80  20 72 65 61 64 20 62 65  63 6f 6d 65 73 0a 21 20  | read becomes.! |
0000cd90  20 74 61 6b 65 20 74 68  65 6e 20 72 65 61 64 2c  | take then read,|
0000cda0  20 62 75 74 20 74 61 6b  65 20 68 61 73 20 6e 6f  | but take has no|
0000cdb0  20 65 66 66 65 63 74 2c  20 73 6f 20 72 65 61 64  | effect, so read|
0000cdc0  20 62 65 63 6f 6d 65 73  20 74 61 6b 65 20 74 68  | becomes take th|
0000cdd0  65 6e 20 72 65 61 64 2e  2e 2e 0a 21 20 20 41 6e  |en read....!  An|
0000cde0  79 77 61 79 20 66 6f 72  20 6e 6f 77 20 61 6c 6c  |yway for now all|
0000cdf0  20 77 65 20 64 6f 20 69  73 20 72 65 63 6f 72 64  | we do is record|
0000ce00  20 74 68 65 20 6e 75 6d  62 65 72 20 6f 66 20 74  | the number of t|
0000ce10  68 65 20 6f 62 6a 65 63  74 20 74 6f 20 74 61 6b  |he object to tak|
0000ce20  65 2e 0a 0a 20 20 20 20  20 20 20 20 6f 3d 70 61  |e...        o=pa|
0000ce30  72 65 6e 74 28 6c 29 3b  0a 20 20 20 20 20 20 20  |rent(l);.       |
0000ce40  20 69 66 20 28 6f 7e 3d  61 63 74 6f 72 29 0a 20  | if (o~=actor). |
0000ce50  20 20 20 20 20 20 20 7b  20 20 20 69 66 20 28 6e  |       {   if (n|
0000ce60  6f 74 68 65 6c 64 5f 6d  6f 64 65 3d 3d 31 29 0a  |otheld_mode==1).|
0000ce70  20 20 20 20 20 20 20 20  20 20 20 20 7b 20 20 20  |            {   |
0000ce80  73 61 76 65 64 5f 6f 6f  70 73 3d 6f 6f 70 73 5f  |saved_oops=oops_|
0000ce90  66 72 6f 6d 3b 20 65 74  79 70 65 3d 4e 4f 54 48  |from; etype=NOTH|
0000cea0  45 4c 44 5f 50 45 3b 20  6a 75 6d 70 20 46 61 69  |ELD_PE; jump Fai|
0000ceb0  6c 54 6f 6b 65 6e 3b 0a  20 20 20 20 20 20 20 20  |lToken;.        |
0000cec0  20 20 20 20 7d 0a 20 20  20 20 20 20 20 20 20 20  |    }.          |
0000ced0  20 20 6e 6f 74 5f 68 6f  6c 64 69 6e 67 20 3d 20  |  not_holding = |
0000cee0  6c 3b 0a 20 20 20 20 20  20 20 20 20 20 20 20 69  |l;.            i|
0000cef0  66 20 28 70 61 72 73 65  72 5f 74 72 61 63 65 3e  |f (parser_trace>|
0000cf00  3d 33 29 0a 20 20 20 20  20 20 20 20 20 20 20 20  |=3).            |
0000cf10  7b 20 20 20 70 72 69 6e  74 20 22 20 20 5b 41 6c  |{   print "  [Al|
0000cf20  6c 6f 77 69 6e 67 20 6f  62 6a 65 63 74 20 22 3b  |lowing object ";|
0000cf30  20 44 65 66 41 72 74 28  6c 29 3b 20 70 72 69 6e  | DefArt(l); prin|
0000cf40  74 20 22 20 66 6f 72 20  6e 6f 77 5d 5e 22 3b 0a  |t " for now]^";.|
0000cf50  20 20 20 20 20 20 20 20  20 20 20 20 7d 0a 20 20  |            }.  |
0000cf60  20 20 20 20 20 20 7d 0a  20 20 20 20 20 20 20 20  |      }.        |
0000cf70  73 69 6e 67 6c 65 5f 6f  62 6a 65 63 74 20 3d 20  |single_object = |
0000cf80  6c 3b 0a 20 20 20 20 7d  0a 0a 21 20 20 54 68 65  |l;.    }..!  The|
0000cf90  20 66 6f 6c 6c 6f 77 69  6e 67 20 6d 6f 76 65 73  | following moves|
0000cfa0  20 74 68 65 20 77 6f 72  64 20 6d 61 72 6b 65 72  | the word marker|
0000cfb0  20 74 6f 20 6a 75 73 74  20 70 61 73 74 20 74 68  | to just past th|
0000cfc0  65 20 6e 61 6d 65 64 20  6f 62 6a 65 63 74 2e 2e  |e named object..|
0000cfd0  2e 0a 0a 20 20 20 20 77  6e 20 3d 20 6f 6f 70 73  |...    wn = oops|
0000cfe0  5f 66 72 6f 6d 20 2b 20  6d 61 74 63 68 5f 6c 65  |_from + match_le|
0000cff0  6e 67 74 68 3b 0a 0a 21  20 20 2a 2a 2a 2a 20 28  |ngth;..!  **** (|
0000d000  43 29 20 2a 2a 2a 2a 0a  0a 21 20 20 4f 62 6a 65  |C) ****..!  Obje|
0000d010  63 74 28 73 29 20 73 70  65 63 69 66 69 65 64 20  |ct(s) specified |
0000d020  6e 6f 77 3a 20 69 73 20  74 68 61 74 20 74 68 65  |now: is that the|
0000d030  20 65 6e 64 20 6f 66 20  74 68 65 20 6c 69 73 74  | end of the list|
0000d040  2c 20 6f 72 20 68 61 76  65 20 77 65 20 72 65 61  |, or have we rea|
0000d050  63 68 65 64 0a 21 20 20  22 61 6e 64 22 2c 20 22  |ched.!  "and", "|
0000d060  62 75 74 22 20 61 6e 64  20 73 6f 20 6f 6e 3f 20  |but" and so on? |
0000d070  20 49 66 20 73 6f 2c 20  63 72 65 61 74 65 20 61  | If so, create a|
0000d080  20 6d 75 6c 74 69 70 6c  65 2d 6f 62 6a 65 63 74  | multiple-object|
0000d090  20 6c 69 73 74 20 69 66  20 77 65 0a 21 20 20 68  | list if we.!  h|
0000d0a0  61 76 65 6e 27 74 20 61  6c 72 65 61 64 79 20 28  |aven't already (|
0000d0b0  61 6e 64 20 61 72 65 20  61 6c 6c 6f 77 65 64 20  |and are allowed |
0000d0c0  74 6f 29 2e 0a 0a 20 20  20 20 2e 4e 65 78 74 49  |to)...    .NextI|
0000d0d0  6e 4c 69 73 74 3b 0a 0a  20 20 20 20 6f 3d 4e 65  |nList;..    o=Ne|
0000d0e0  78 74 57 6f 72 64 28 29  3b 0a 0a 20 20 20 20 69  |xtWord();..    i|
0000d0f0  66 20 28 6f 3d 3d 27 61  6e 64 27 20 6f 72 20 27  |f (o=='and' or '|
0000d100  62 75 74 27 20 6f 72 20  27 65 78 63 65 70 74 27  |but' or 'except'|
0000d110  20 7c 7c 20 6f 3d 3d 63  6f 6d 6d 61 5f 77 6f 72  | || o==comma_wor|
0000d120  64 29 0a 20 20 20 20 7b  0a 20 20 20 20 20 20 20  |d).    {.       |
0000d130  20 69 66 20 28 70 61 72  73 65 72 5f 74 72 61 63  | if (parser_trac|
0000d140  65 3e 3d 33 29 0a 20 20  20 20 20 20 20 20 7b 20  |e>=3).        { |
0000d150  20 20 70 72 69 6e 74 20  22 20 20 5b 52 65 61 64  |  print "  [Read|
0000d160  20 27 22 3b 20 70 72 69  6e 74 5f 61 64 64 72 20  | '"; print_addr |
0000d170  6f 3b 20 70 72 69 6e 74  20 22 27 5d 5e 22 3b 0a  |o; print "']^";.|
0000d180  20 20 20 20 20 20 20 20  7d 0a 0a 20 20 20 20 20  |        }..     |
0000d190  20 20 20 69 66 20 28 74  6f 6b 65 6e 3c 32 20 7c  |   if (token<2 ||
0000d1a0  7c 20 74 6f 6b 65 6e 3e  3d 36 29 20 7b 20 65 74  || token>=6) { et|
0000d1b0  79 70 65 3d 4d 55 4c 54  49 5f 50 45 3b 20 6a 75  |ype=MULTI_PE; ju|
0000d1c0  6d 70 20 46 61 69 6c 54  6f 6b 65 6e 3b 20 7d 0a  |mp FailToken; }.|
0000d1d0  0a 20 20 20 20 20 20 20  20 69 66 20 28 6f 3d 3d  |.        if (o==|
0000d1e0  27 62 75 74 27 20 6f 72  20 27 65 78 63 65 70 74  |'but' or 'except|
0000d1f0  27 29 20 61 6e 64 5f 70  61 72 69 74 79 20 3d 20  |') and_parity = |
0000d200  31 2d 61 6e 64 5f 70 61  72 69 74 79 3b 0a 0a 20  |1-and_parity;.. |
0000d210  20 20 20 20 20 20 20 69  66 20 28 6d 61 6e 79 5f  |       if (many_|
0000d220  66 6c 61 67 3d 3d 30 29  0a 20 20 20 20 20 20 20  |flag==0).       |
0000d230  20 7b 20 20 20 6d 75 6c  74 69 70 6c 65 5f 6f 62  | {   multiple_ob|
0000d240  6a 65 63 74 2d 2d 3e 30  20 3d 20 31 3b 0a 20 20  |ject-->0 = 1;.  |
0000d250  20 20 20 20 20 20 20 20  20 20 6d 75 6c 74 69 70  |          multip|
0000d260  6c 65 5f 6f 62 6a 65 63  74 2d 2d 3e 31 20 3d 20  |le_object-->1 = |
0000d270  73 69 6e 67 6c 65 5f 6f  62 6a 65 63 74 3b 0a 20  |single_object;. |
0000d280  20 20 20 20 20 20 20 20  20 20 20 6d 61 6e 79 5f  |           many_|
0000d290  66 6c 61 67 3d 31 3b 0a  20 20 20 20 20 20 20 20  |flag=1;.        |
0000d2a0  20 20 20 20 69 66 20 28  70 61 72 73 65 72 5f 74  |    if (parser_t|
0000d2b0  72 61 63 65 3e 3d 33 29  0a 20 20 20 20 20 20 20  |race>=3).       |
0000d2c0  20 20 20 20 20 7b 20 20  20 70 72 69 6e 74 20 22  |     {   print "|
0000d2d0  20 20 5b 4d 61 6b 69 6e  67 20 6e 65 77 20 6c 69  |  [Making new li|
0000d2e0  73 74 20 66 72 6f 6d 20  22 3b 0a 20 20 20 20 20  |st from ";.     |
0000d2f0  20 20 20 20 20 20 20 20  20 20 20 44 65 66 41 72  |           DefAr|
0000d300  74 28 73 69 6e 67 6c 65  5f 6f 62 6a 65 63 74 29  |t(single_object)|
0000d310  3b 20 70 72 69 6e 74 20  22 5d 5e 22 3b 0a 20 20  |; print "]^";.  |
0000d320  20 20 20 20 20 20 20 20  20 20 7d 0a 20 20 20 20  |          }.    |
0000d330  20 20 20 20 7d 0a 20 20  20 20 20 20 20 20 64 6f  |    }.        do|
0000d340  6e 74 5f 69 6e 66 65 72  20 3d 20 31 3b 20 69 6e  |nt_infer = 1; in|
0000d350  66 65 72 66 72 6f 6d 3d  30 3b 20 20 20 20 20 20  |ferfrom=0;      |
0000d360  20 20 20 20 20 20 20 20  21 20 44 6f 6e 27 74 20  |        ! Don't |
0000d370  70 72 69 6e 74 20 28 69  6e 66 65 72 65 6e 63 65  |print (inference|
0000d380  73 29 0a 20 20 20 20 20  20 20 20 6a 75 6d 70 20  |s).        jump |
0000d390  4f 62 6a 65 63 74 4c 69  73 74 3b 20 20 20 20 20  |ObjectList;     |
0000d3a0  20 20 20 20 20 20 20 20  20 20 20 20 20 20 20 20  |                |
0000d3b0  20 20 20 20 20 21 20 41  6e 64 20 62 61 63 6b 20  |     ! And back |
0000d3c0  61 72 6f 75 6e 64 0a 20  20 20 20 7d 0a 0a 20 20  |around.    }..  |
0000d3d0  20 20 77 6e 2d 2d 3b 20  20 20 21 20 57 6f 72 64  |  wn--;   ! Word|
0000d3e0  20 6d 61 72 6b 65 72 20  62 61 63 6b 20 74 6f 20  | marker back to |
0000d3f0  66 69 72 73 74 20 6e 6f  74 2d 75 6e 64 65 72 73  |first not-unders|
0000d400  74 6f 6f 64 20 77 6f 72  64 0a 0a 21 20 20 2a 2a  |tood word..!  **|
0000d410  2a 2a 20 28 44 29 20 2a  2a 2a 2a 0a 0a 21 20 20  |** (D) ****..!  |
0000d420  48 61 70 70 79 20 6f 72  20 75 6e 68 61 70 70 79  |Happy or unhappy|
0000d430  20 65 6e 64 69 6e 67 73  3a 0a 0a 20 20 20 20 2e  | endings:..    .|
0000d440  50 61 73 73 54 6f 6b 65  6e 3b 0a 0a 20 20 20 20  |PassToken;..    |
0000d450  69 66 20 28 6d 61 6e 79  5f 66 6c 61 67 3d 3d 31  |if (many_flag==1|
0000d460  29 20 73 69 6e 67 6c 65  5f 6f 62 6a 65 63 74 3d  |) single_object=|
0000d470  30 3b 0a 20 20 20 20 65  6c 73 65 0a 20 20 20 20  |0;.    else.    |
0000d480  7b 20 20 20 69 66 20 28  69 6e 64 65 66 5f 6d 6f  |{   if (indef_mo|
0000d490  64 65 3d 3d 31 20 26 26  20 69 6e 64 65 66 5f 74  |de==1 && indef_t|
0000d4a0  79 70 65 20 26 20 50 4c  55 52 41 4c 5f 42 49 54  |ype & PLURAL_BIT|
0000d4b0  20 7e 3d 20 30 29 0a 20  20 20 20 20 20 20 20 7b  | ~= 0).        {|
0000d4c0  20 20 20 69 66 20 28 69  6e 64 65 66 5f 77 61 6e  |   if (indef_wan|
0000d4d0  74 65 64 3c 31 30 30 20  26 26 20 69 6e 64 65 66  |ted<100 && indef|
0000d4e0  5f 77 61 6e 74 65 64 3e  31 29 0a 20 20 20 20 20  |_wanted>1).     |
0000d4f0  20 20 20 20 20 20 20 7b  20 20 20 6d 75 6c 74 69  |       {   multi|
0000d500  5f 68 61 64 3d 31 3b 20  6d 75 6c 74 69 5f 77 61  |_had=1; multi_wa|
0000d510  6e 74 65 64 3d 69 6e 64  65 66 5f 77 61 6e 74 65  |nted=indef_wante|
0000d520  64 3b 0a 20 20 20 20 20  20 20 20 20 20 20 20 20  |d;.             |
0000d530  20 20 20 65 74 79 70 65  3d 54 4f 4f 46 45 57 5f  |   etype=TOOFEW_|
0000d540  50 45 3b 0a 20 20 20 20  20 20 20 20 20 20 20 20  |PE;.            |
0000d550  20 20 20 20 6a 75 6d 70  20 46 61 69 6c 54 6f 6b  |    jump FailTok|
0000d560  65 6e 3b 0a 20 20 20 20  20 20 20 20 20 20 20 20  |en;.            |
0000d570  7d 0a 20 20 20 20 20 20  20 20 7d 0a 20 20 20 20  |}.        }.    |
0000d580  7d 0a 20 20 20 20 72 65  73 75 6c 74 73 2d 2d 3e  |}.    results-->|
0000d590  28 70 61 72 61 6d 65 74  65 72 73 2b 32 29 20 3d  |(parameters+2) =|
0000d5a0  20 73 69 6e 67 6c 65 5f  6f 62 6a 65 63 74 3b 0a  | single_object;.|
0000d5b0  20 20 20 20 70 61 72 61  6d 65 74 65 72 73 2b 2b  |    parameters++|
0000d5c0  3b 0a 20 20 20 20 70 61  74 74 65 72 6e 2d 2d 3e  |;.    pattern-->|
0000d5d0  70 63 6f 75 6e 74 20 3d  20 73 69 6e 67 6c 65 5f  |pcount = single_|
0000d5e0  6f 62 6a 65 63 74 3b 0a  20 20 20 20 72 65 74 75  |object;.    retu|
0000d5f0  72 6e 20 31 3b 0a 0a 20  20 20 20 2e 46 61 69 6c  |rn 1;..    .Fail|
0000d600  54 6f 6b 65 6e 3b 0a 0a  21 20 20 49 66 20 77 65  |Token;..!  If we|
0000d610  20 77 65 72 65 20 6f 6e  6c 79 20 67 75 65 73 73  | were only guess|
0000d620  69 6e 67 20 61 62 6f 75  74 20 69 74 20 62 65 69  |ing about it bei|
0000d630  6e 67 20 61 20 70 6c 75  72 61 6c 2c 20 74 72 79  |ng a plural, try|
0000d640  20 61 67 61 69 6e 20 62  75 74 20 6f 6e 6c 79 0a  | again but only.|
0000d650  21 20 20 61 6c 6c 6f 77  69 6e 67 20 73 69 6e 67  |!  allowing sing|
0000d660  75 6c 61 72 73 20 28 73  6f 20 74 68 61 74 20 77  |ulars (so that w|
0000d670  6f 72 64 73 20 6c 69 6b  65 20 22 73 69 78 22 20  |ords like "six" |
0000d680  61 72 65 20 6e 6f 74 20  73 77 61 6c 6c 6f 77 65  |are not swallowe|
0000d690  64 20 75 70 20 61 73 0a  21 20 20 44 65 73 63 72  |d up as.!  Descr|
0000d6a0  69 70 74 6f 72 73 29 0a  0a 20 20 20 20 69 66 20  |iptors)..    if |
0000d6b0  28 61 6c 6c 6f 77 5f 70  6c 75 72 61 6c 73 3d 3d  |(allow_plurals==|
0000d6c0  31 20 26 26 20 69 6e 64  65 66 5f 67 75 65 73 73  |1 && indef_guess|
0000d6d0  5f 70 3d 3d 31 29 0a 20  20 20 20 7b 20 20 20 61  |_p==1).    {   a|
0000d6e0  6c 6c 6f 77 5f 70 6c 75  72 61 6c 73 3d 30 3b 20  |llow_plurals=0; |
0000d6f0  77 6e 3d 64 65 73 63 5f  77 6e 3b 20 6a 75 6d 70  |wn=desc_wn; jump|
0000d700  20 54 72 79 41 67 61 69  6e 3b 0a 20 20 20 20 7d  | TryAgain;.    }|
0000d710  0a 20 20 20 20 72 65 74  75 72 6e 20 30 3b 0a 5d  |.    return 0;.]|
0000d720  3b 0a 0a 21 20 2d 2d 2d  2d 2d 2d 2d 2d 2d 2d 2d  |;..! -----------|
0000d730  2d 2d 2d 2d 2d 2d 2d 2d  2d 2d 2d 2d 2d 2d 2d 2d  |----------------|
*
0000d770  2d 0a 21 20 20 4e 6f 75  6e 44 6f 6d 61 69 6e 20  |-.!  NounDomain |
0000d780  64 6f 65 73 20 74 68 65  20 6d 6f 73 74 20 73 75  |does the most su|
0000d790  62 73 74 61 6e 74 69 61  6c 20 70 61 72 74 20 6f  |bstantial part o|
0000d7a0  66 20 70 61 72 73 69 6e  67 20 61 6e 20 6f 62 6a  |f parsing an obj|
0000d7b0  65 63 74 20 6e 61 6d 65  2e 0a 21 0a 21 20 20 49  |ect name..!.!  I|
0000d7c0  74 20 69 73 20 67 69 76  65 6e 20 74 77 6f 20 22  |t is given two "|
0000d7d0  64 6f 6d 61 69 6e 73 22  20 2d 20 75 73 75 61 6c  |domains" - usual|
0000d7e0  6c 79 20 61 20 6c 6f 63  61 74 69 6f 6e 20 61 6e  |ly a location an|
0000d7f0  64 20 74 68 65 6e 20 74  68 65 20 61 63 74 6f 72  |d then the actor|
0000d800  20 77 68 6f 20 69 73 0a  21 20 20 6c 6f 6f 6b 69  | who is.!  looki|
0000d810  6e 67 20 2d 20 61 6e 64  20 61 20 63 6f 6e 74 65  |ng - and a conte|
0000d820  78 74 20 28 69 2e 65 2e  20 74 6f 6b 65 6e 20 74  |xt (i.e. token t|
0000d830  79 70 65 29 2c 20 61 6e  64 20 72 65 74 75 72 6e  |ype), and return|
0000d840  73 3a 0a 21 0a 21 20 20  20 30 20 20 20 20 69 66  |s:.!.!   0    if|
0000d850  20 6e 6f 20 6d 61 74 63  68 20 61 74 20 61 6c 6c  | no match at all|
0000d860  20 63 6f 75 6c 64 20 62  65 20 6d 61 64 65 2c 0a  | could be made,.|
0000d870  21 20 20 20 31 20 20 20  20 69 66 20 61 20 6d 75  |!   1    if a mu|
0000d880  6c 74 69 70 6c 65 20 6f  62 6a 65 63 74 20 77 61  |ltiple object wa|
0000d890  73 20 6d 61 64 65 2c 0a  21 20 20 20 6b 20 20 20  |s made,.!   k   |
0000d8a0  20 69 66 20 6f 62 6a 65  63 74 20 6b 20 77 61 73  | if object k was|
0000d8b0  20 74 68 65 20 6f 6e 65  20 64 65 63 69 64 65 64  | the one decided|
0000d8c0  20 75 70 6f 6e 2c 0a 21  20 20 20 31 30 30 30 20  | upon,.!   1000 |
0000d8d0  69 66 20 69 74 20 61 73  6b 65 64 20 61 20 71 75  |if it asked a qu|
0000d8e0  65 73 74 69 6f 6e 20 6f  66 20 74 68 65 20 70 6c  |estion of the pl|
0000d8f0  61 79 65 72 20 61 6e 64  20 63 6f 6e 73 65 71 75  |ayer and consequ|
0000d900  65 6e 74 6c 79 20 72 65  77 72 6f 74 65 20 61 6c  |ently rewrote al|
0000d910  6c 0a 21 20 20 20 20 20  20 20 20 74 68 65 20 70  |l.!        the p|
0000d920  6c 61 79 65 72 27 73 20  69 6e 70 75 74 2c 20 73  |layer's input, s|
0000d930  6f 20 74 68 61 74 20 74  68 65 20 77 68 6f 6c 65  |o that the whole|
0000d940  20 70 61 72 73 65 72 20  73 68 6f 75 6c 64 20 73  | parser should s|
0000d950  74 61 72 74 20 61 67 61  69 6e 0a 21 20 20 20 20  |tart again.!    |
0000d960  20 20 20 20 6f 6e 20 74  68 65 20 72 65 77 72 69  |    on the rewri|
0000d970  74 74 65 6e 20 69 6e 70  75 74 2e 0a 21 0a 21 20  |tten input..!.! |
0000d980  20 20 49 6e 20 74 68 65  20 63 61 73 65 20 77 68  |  In the case wh|
0000d990  65 6e 20 69 74 20 72 65  74 75 72 6e 73 20 31 3c  |en it returns 1<|
0000d9a0  6b 3c 31 30 30 30 2c 20  69 74 20 61 6c 73 6f 20  |k<1000, it also |
0000d9b0  73 65 74 73 20 74 68 65  20 76 61 72 69 61 62 6c  |sets the variabl|
0000d9c0  65 0a 21 20 20 20 6c 65  6e 67 74 68 5f 6f 66 5f  |e.!   length_of_|
0000d9d0  6e 6f 75 6e 20 74 6f 20  74 68 65 20 6e 75 6d 62  |noun to the numb|
0000d9e0  65 72 20 6f 66 20 77 6f  72 64 73 20 69 6e 20 74  |er of words in t|
0000d9f0  68 65 20 69 6e 70 75 74  20 74 65 78 74 20 6d 61  |he input text ma|
0000da00  74 63 68 65 64 20 74 6f  20 74 68 65 0a 21 20 20  |tched to the.!  |
0000da10  20 6e 6f 75 6e 2e 0a 21  20 20 20 49 6e 20 74 68  | noun..!   In th|
0000da20  65 20 63 61 73 65 20 6b  3d 31 2c 20 74 68 65 20  |e case k=1, the |
0000da30  6d 75 6c 74 69 70 6c 65  20 6f 62 6a 65 63 74 73  |multiple objects|
0000da40  20 61 72 65 20 61 64 64  65 64 20 74 6f 20 6d 75  | are added to mu|
0000da50  6c 74 69 70 6c 65 5f 6f  62 6a 65 63 74 20 62 79  |ltiple_object by|
0000da60  0a 21 20 20 20 68 61 6e  64 20 28 6e 6f 74 20 62  |.!   hand (not b|
0000da70  79 20 4d 75 6c 74 69 41  64 64 2c 20 62 65 63 61  |y MultiAdd, beca|
0000da80  75 73 65 20 77 65 20 77  61 6e 74 20 74 6f 20 61  |use we want to a|
0000da90  6c 6c 6f 77 20 64 75 70  6c 69 63 61 74 65 73 29  |llow duplicates)|
0000daa0  2e 0a 21 20 2d 2d 2d 2d  2d 2d 2d 2d 2d 2d 2d 2d  |..! ------------|
0000dab0  2d 2d 2d 2d 2d 2d 2d 2d  2d 2d 2d 2d 2d 2d 2d 2d  |----------------|
*
0000daf0  0a 0a 5b 20 4e 6f 75 6e  44 6f 6d 61 69 6e 20 64  |..[ NounDomain d|
0000db00  6f 6d 61 69 6e 31 20 64  6f 6d 61 69 6e 32 20 63  |omain1 domain2 c|
0000db10  6f 6e 74 65 78 74 20 20  66 69 72 73 74 5f 77 6f  |ontext  first_wo|
0000db20  72 64 20 69 20 6a 20 6b  20 6c 20 6f 6c 64 77 0a  |rd i j k l oldw.|
0000db30  20 20 20 20 20 20 20 20  20 20 20 20 20 20 20 20  |                |
*
0000db50  20 20 20 20 20 20 61 6e  73 77 65 72 5f 77 6f 72  |      answer_wor|
0000db60  64 73 20 6d 61 72 6b 65  72 3b 0a 0a 20 20 69 66  |ds marker;..  if|
0000db70  20 28 70 61 72 73 65 72  5f 74 72 61 63 65 3e 3d  | (parser_trace>=|
0000db80  34 29 20 70 72 69 6e 74  20 22 20 20 20 5b 4e 6f  |4) print "   [No|
0000db90  75 6e 44 6f 6d 61 69 6e  20 63 61 6c 6c 65 64 20  |unDomain called |
0000dba0  61 74 20 77 6f 72 64 20  22 2c 20 77 6e 2c 20 22  |at word ", wn, "|
0000dbb0  5e 22 3b 0a 0a 20 20 6d  61 74 63 68 5f 6c 65 6e  |^";..  match_len|
0000dbc0  67 74 68 3d 30 3b 20 6e  75 6d 62 65 72 5f 6d 61  |gth=0; number_ma|
0000dbd0  74 63 68 65 64 3d 30 3b  20 6d 61 74 63 68 5f 66  |tched=0; match_f|
0000dbe0  72 6f 6d 3d 77 6e 3b 20  70 6c 61 63 65 64 5f 69  |rom=wn; placed_i|
0000dbf0  6e 5f 66 6c 61 67 3d 30  3b 0a 0a 20 20 53 65 61  |n_flag=0;..  Sea|
0000dc00  72 63 68 53 63 6f 70 65  28 64 6f 6d 61 69 6e 31  |rchScope(domain1|
0000dc10  2c 20 64 6f 6d 61 69 6e  32 2c 20 63 6f 6e 74 65  |, domain2, conte|
0000dc20  78 74 29 3b 0a 0a 20 20  69 66 20 28 70 61 72 73  |xt);..  if (pars|
0000dc30  65 72 5f 74 72 61 63 65  3e 3d 34 29 20 70 72 69  |er_trace>=4) pri|
0000dc40  6e 74 20 22 20 20 20 5b  4e 44 20 6d 61 64 65 20  |nt "   [ND made |
0000dc50  22 2c 20 6e 75 6d 62 65  72 5f 6d 61 74 63 68 65  |", number_matche|
0000dc60  64 2c 20 22 20 6d 61 74  63 68 65 73 5d 5e 22 3b  |d, " matches]^";|
0000dc70  0a 0a 20 20 77 6e 3d 6d  61 74 63 68 5f 66 72 6f  |..  wn=match_fro|
0000dc80  6d 2b 6d 61 74 63 68 5f  6c 65 6e 67 74 68 3b 0a  |m+match_length;.|
0000dc90  0a 21 20 20 49 66 20 6e  6f 74 68 69 6e 67 20 77  |.!  If nothing w|
0000dca0  6f 72 6b 65 64 20 61 74  20 61 6c 6c 2c 20 6c 65  |orked at all, le|
0000dcb0  61 76 65 20 77 69 74 68  20 74 68 65 20 77 6f 72  |ave with the wor|
0000dcc0  64 20 6d 61 72 6b 65 72  20 73 6b 69 70 70 65 64  |d marker skipped|
0000dcd0  20 70 61 73 74 20 74 68  65 0a 21 20 20 66 69 72  | past the.!  fir|
0000dce0  73 74 20 75 6e 6d 61 74  63 68 65 64 20 77 6f 72  |st unmatched wor|
0000dcf0  64 2e 2e 2e 0a 0a 20 20  69 66 20 28 6e 75 6d 62  |d.....  if (numb|
0000dd00  65 72 5f 6d 61 74 63 68  65 64 3d 3d 30 29 20 7b  |er_matched==0) {|
0000dd10  20 77 6e 2b 2b 3b 20 72  66 61 6c 73 65 3b 20 7d  | wn++; rfalse; }|
0000dd20  0a 0a 21 20 20 53 75 70  70 6f 73 65 20 74 68 61  |..!  Suppose tha|
0000dd30  74 20 74 68 65 72 65 20  72 65 61 6c 6c 79 20 77  |t there really w|
0000dd40  65 72 65 20 73 6f 6d 65  20 77 6f 72 64 73 20 62  |ere some words b|
0000dd50  65 69 6e 67 20 70 61 72  73 65 64 20 28 69 2e 65  |eing parsed (i.e|
0000dd60  2e 2c 20 77 65 20 64 69  64 0a 21 20 20 6e 6f 74  |., we did.!  not|
0000dd70  20 6a 75 73 74 20 69 6e  66 65 72 29 2e 20 20 49  | just infer).  I|
0000dd80  66 20 73 6f 2c 20 61 6e  64 20 69 66 20 74 68 65  |f so, and if the|
0000dd90  72 65 20 77 61 73 20 6f  6e 6c 79 20 6f 6e 65 20  |re was only one |
0000dda0  6d 61 74 63 68 2c 20 69  74 20 6d 75 73 74 20 62  |match, it must b|
0000ddb0  65 0a 21 20 20 72 69 67  68 74 20 61 6e 64 20 77  |e.!  right and w|
0000ddc0  65 20 72 65 74 75 72 6e  20 69 74 2e 2e 2e 0a 0a  |e return it.....|
0000ddd0  0a 20 20 69 66 20 28 6d  61 74 63 68 5f 66 72 6f  |.  if (match_fro|
0000dde0  6d 20 3c 3d 20 6e 75 6d  5f 77 6f 72 64 73 29 0a  |m <= num_words).|
0000ddf0  20 20 7b 20 20 20 69 66  20 28 6e 75 6d 62 65 72  |  {   if (number|
0000de00  5f 6d 61 74 63 68 65 64  3d 3d 31 29 20 7b 20 69  |_matched==1) { i|
0000de10  3d 6d 61 74 63 68 5f 6c  69 73 74 2d 2d 3e 30 3b  |=match_list-->0;|
0000de20  20 72 65 74 75 72 6e 20  69 3b 20 7d 0a 0a 21 20  | return i; }..! |
0000de30  20 2e 2e 2e 6e 6f 77 20  73 75 70 70 6f 73 65 20  | ...now suppose |
0000de40  74 68 61 74 20 74 68 65  72 65 20 77 61 73 20 6d  |that there was m|
0000de50  6f 72 65 20 74 79 70 69  6e 67 20 74 6f 20 63 6f  |ore typing to co|
0000de60  6d 65 2c 20 69 2e 65 2e  20 73 75 70 70 6f 73 65  |me, i.e. suppose|
0000de70  20 74 68 61 74 0a 21 20  20 74 68 65 20 75 73 65  | that.!  the use|
0000de80  72 20 65 6e 74 65 72 65  64 20 73 6f 6d 65 74 68  |r entered someth|
0000de90  69 6e 67 20 62 65 79 6f  6e 64 20 74 68 69 73 20  |ing beyond this |
0000dea0  6e 6f 75 6e 2e 20 20 55  73 65 20 74 68 65 20 6c  |noun.  Use the l|
0000deb0  6f 6f 6b 61 68 65 61 64  20 74 6f 6b 65 6e 0a 21  |ookahead token.!|
0000dec0  20 20 74 6f 20 63 68 65  63 6b 20 74 68 61 74 20  |  to check that |
0000ded0  69 66 20 61 6e 20 61 64  6a 65 63 74 69 76 65 20  |if an adjective |
0000dee0  63 6f 6d 65 73 20 6e 65  78 74 2c 20 69 74 20 69  |comes next, it i|
0000def0  73 20 74 68 65 20 72 69  67 68 74 20 6f 6e 65 2e  |s the right one.|
0000df00  20 20 28 49 66 0a 21 20  20 6e 6f 74 20 74 68 65  |  (If.!  not the|
0000df10  6e 20 74 68 65 72 65 20  6d 75 73 74 20 62 65 20  |n there must be |
0000df20  61 20 6d 69 73 74 61 6b  65 20 6c 69 6b 65 20 22  |a mistake like "|
0000df30  70 72 65 73 73 20 72 65  64 20 62 75 74 74 6e 6f  |press red buttno|
0000df40  22 20 77 68 65 72 65 20  22 72 65 64 22 0a 21 20  |" where "red".! |
0000df50  20 68 61 73 20 62 65 65  6e 20 74 61 6b 65 6e 20  | has been taken |
0000df60  66 6f 72 20 74 68 65 20  6e 6f 75 6e 20 69 6e 20  |for the noun in |
0000df70  74 68 65 20 6d 69 73 74  61 6b 65 6e 20 62 65 6c  |the mistaken bel|
0000df80  69 65 66 20 74 68 61 74  20 22 62 75 74 74 6e 6f  |ief that "buttno|
0000df90  22 20 69 73 0a 21 20 20  73 6f 6d 65 20 70 72 65  |" is.!  some pre|
0000dfa0  70 6f 73 69 74 69 6f 6e  20 6f 72 20 6f 74 68 65  |position or othe|
0000dfb0  72 2e 29 0a 21 0a 21 20  20 49 66 20 6e 6f 74 68  |r.).!.!  If noth|
0000dfc0  69 6e 67 20 6f 75 67 68  74 20 74 6f 20 66 6f 6c  |ing ought to fol|
0000dfd0  6c 6f 77 2c 20 74 68 65  6e 20 73 69 6d 69 6c 61  |low, then simila|
0000dfe0  72 6c 79 20 74 68 65 72  65 20 6d 75 73 74 20 62  |rly there must b|
0000dff0  65 20 61 20 6d 69 73 74  61 6b 65 2c 0a 21 20 20  |e a mistake,.!  |
0000e000  28 75 6e 6c 65 73 73 20  77 68 61 74 20 64 6f 65  |(unless what doe|
0000e010  73 20 66 6f 6c 6c 6f 77  20 69 73 20 6a 75 73 74  |s follow is just|
0000e020  20 61 20 66 75 6c 6c 20  73 74 6f 70 2c 20 61 6e  | a full stop, an|
0000e030  64 20 6f 72 20 63 6f 6d  6d 61 29 0a 0a 20 20 20  |d or comma)..   |
0000e040  20 20 20 69 66 20 28 77  6e 3c 3d 6e 75 6d 5f 77  |   if (wn<=num_w|
0000e050  6f 72 64 73 29 0a 20 20  20 20 20 20 7b 20 20 20  |ords).      {   |
0000e060  69 66 20 28 6c 6f 6f 6b  61 68 65 61 64 3d 3d 38  |if (lookahead==8|
0000e070  29 0a 20 20 20 20 20 20  20 20 20 20 7b 20 20 20  |).          {   |
0000e080  69 3d 4e 65 78 74 57 6f  72 64 28 29 3b 20 77 6e  |i=NextWord(); wn|
0000e090  2d 2d 3b 0a 20 20 20 20  20 20 20 20 20 20 20 20  |--;.            |
0000e0a0  20 20 69 66 20 28 69 7e  3d 27 61 6e 64 27 20 6f  |  if (i~='and' o|
0000e0b0  72 20 63 6f 6d 6d 61 5f  77 6f 72 64 20 6f 72 20  |r comma_word or |
0000e0c0  27 74 68 65 6e 27 29 20  72 66 61 6c 73 65 3b 0a  |'then') rfalse;.|
0000e0d0  20 20 20 20 20 20 20 20  20 20 7d 0a 20 20 20 20  |          }.    |
0000e0e0  20 20 20 20 20 20 69 66  20 28 6c 6f 6f 6b 61 68  |      if (lookah|
0000e0f0  65 61 64 3e 38 29 0a 20  20 20 20 20 20 20 20 20  |ead>8).         |
0000e100  20 7b 20 20 20 69 66 20  28 6c 6f 6f 6b 61 68 65  | {   if (lookahe|
0000e110  61 64 7e 3d 41 64 6a 65  63 74 69 76 65 28 29 29  |ad~=Adjective())|
0000e120  20 7b 20 77 6e 2d 2d 3b  20 72 66 61 6c 73 65 3b  | { wn--; rfalse;|
0000e130  20 7d 0a 20 20 20 20 20  20 20 20 20 20 20 20 20  | }.             |
0000e140  20 77 6e 2d 2d 3b 0a 20  20 20 20 20 20 20 20 20  | wn--;.         |
0000e150  20 7d 0a 20 20 20 20 20  20 7d 0a 20 20 7d 0a 0a  | }.      }.  }..|
0000e160  21 20 20 4e 6f 77 20 6c  6f 6f 6b 20 66 6f 72 20  |!  Now look for |
0000e170  61 20 67 6f 6f 64 20 63  68 6f 69 63 65 2c 20 69  |a good choice, i|
0000e180  66 20 74 68 65 72 65 27  73 20 6d 6f 72 65 20 74  |f there's more t|
0000e190  68 61 6e 20 6f 6e 65 20  63 68 6f 69 63 65 2e 2e  |han one choice..|
0000e1a0  2e 0a 0a 20 20 6e 75 6d  62 65 72 5f 6f 66 5f 63  |...  number_of_c|
0000e1b0  6c 61 73 73 65 73 3d 30  3b 0a 20 20 0a 20 20 69  |lasses=0;.  .  i|
0000e1c0  66 20 28 6e 75 6d 62 65  72 5f 6d 61 74 63 68 65  |f (number_matche|
0000e1d0  64 3d 3d 31 29 20 69 3d  6d 61 74 63 68 5f 6c 69  |d==1) i=match_li|
0000e1e0  73 74 2d 2d 3e 30 3b 0a  20 20 69 66 20 28 6e 75  |st-->0;.  if (nu|
0000e1f0  6d 62 65 72 5f 6d 61 74  63 68 65 64 3e 31 29 0a  |mber_matched>1).|
0000e200  20 20 7b 20 20 20 69 3d  41 64 6a 75 64 69 63 61  |  {   i=Adjudica|
0000e210  74 65 28 63 6f 6e 74 65  78 74 29 3b 0a 20 20 20  |te(context);.   |
0000e220  20 20 20 69 66 20 28 69  3d 3d 2d 31 29 20 72 66  |   if (i==-1) rf|
0000e230  61 6c 73 65 3b 0a 20 20  20 20 20 20 69 66 20 28  |alse;.      if (|
0000e240  69 3d 3d 31 29 20 72 74  72 75 65 3b 20 20 20 20  |i==1) rtrue;    |
0000e250  20 20 20 21 20 20 41 64  6a 75 64 69 63 61 74 65  |   !  Adjudicate|
0000e260  20 68 61 73 20 6d 61 64  65 20 61 20 6d 75 6c 74  | has made a mult|
0000e270  69 70 6c 65 0a 20 20 20  20 20 20 20 20 20 20 20  |iple.           |
0000e280  20 20 20 20 20 20 20 20  20 20 20 20 20 20 20 20  |                |
0000e290  20 20 21 20 20 6f 62 6a  65 63 74 2c 20 61 6e 64  |  !  object, and|
0000e2a0  20 77 65 20 70 61 73 73  20 69 74 20 6f 6e 0a 20  | we pass it on. |
0000e2b0  20 7d 0a 0a 21 20 20 49  66 20 69 20 69 73 20 6e  | }..!  If i is n|
0000e2c0  6f 6e 2d 7a 65 72 6f 20  68 65 72 65 2c 20 6f 6e  |on-zero here, on|
0000e2d0  65 20 6f 66 20 74 77 6f  20 74 68 69 6e 67 73 20  |e of two things |
0000e2e0  69 73 20 68 61 70 70 65  6e 69 6e 67 3a 20 65 69  |is happening: ei|
0000e2f0  74 68 65 72 0a 21 20 20  28 61 29 20 61 6e 20 69  |ther.!  (a) an i|
0000e300  6e 66 65 72 65 6e 63 65  20 68 61 73 20 62 65 65  |nference has bee|
0000e310  6e 20 73 75 63 63 65 73  73 66 75 6c 6c 79 20 6d  |n successfully m|
0000e320  61 64 65 20 74 68 61 74  20 6f 62 6a 65 63 74 20  |ade that object |
0000e330  69 20 69 73 0a 21 20 20  20 20 20 20 74 68 65 20  |i is.!      the |
0000e340  69 6e 74 65 6e 64 65 64  20 6f 6e 65 20 66 72 6f  |intended one fro|
0000e350  6d 20 74 68 65 20 75 73  65 72 27 73 20 73 70 65  |m the user's spe|
0000e360  63 69 66 69 63 61 74 69  6f 6e 2c 20 6f 72 0a 21  |cification, or.!|
0000e370  20 20 28 62 29 20 74 68  65 20 75 73 65 72 20 66  |  (b) the user f|
0000e380  69 6e 69 73 68 65 64 20  74 79 70 69 6e 67 20 73  |inished typing s|
0000e390  6f 6d 65 20 74 69 6d 65  20 61 67 6f 2c 20 62 75  |ome time ago, bu|
0000e3a0  74 20 77 65 27 76 65 20  64 65 63 69 64 65 64 0a  |t we've decided.|
0000e3b0  21 20 20 20 20 20 20 6f  6e 20 69 20 62 65 63 61  |!      on i beca|
0000e3c0  75 73 65 20 69 74 27 73  20 74 68 65 20 6f 6e 6c  |use it's the onl|
0000e3d0  79 20 70 6f 73 73 69 62  6c 65 20 63 68 6f 69 63  |y possible choic|
0000e3e0  65 2e 0a 21 20 20 49 6e  20 65 69 74 68 65 72 20  |e..!  In either |
0000e3f0  63 61 73 65 20 77 65 20  68 61 76 65 20 74 6f 20  |case we have to |
0000e400  6b 65 65 70 20 74 68 65  20 70 61 74 74 65 72 6e  |keep the pattern|
0000e410  20 75 70 20 74 6f 20 64  61 74 65 2c 0a 21 20 20  | up to date,.!  |
0000e420  6e 6f 74 65 20 74 68 61  74 20 61 6e 20 69 6e 66  |note that an inf|
0000e430  65 72 65 6e 63 65 20 68  61 73 20 62 65 65 6e 20  |erence has been |
0000e440  6d 61 64 65 20 61 6e 64  20 72 65 74 75 72 6e 2e  |made and return.|
0000e450  0a 21 20 20 28 45 78 63  65 70 74 2c 20 77 65 20  |.!  (Except, we |
0000e460  64 6f 6e 27 74 20 6e 6f  74 65 20 77 68 69 63 68  |don't note which|
0000e470  20 6f 66 20 61 20 70 69  6c 65 20 6f 66 20 69 64  | of a pile of id|
0000e480  65 6e 74 69 63 61 6c 20  6f 62 6a 65 63 74 73 2e  |entical objects.|
0000e490  29 0a 0a 20 20 69 66 20  28 69 7e 3d 30 29 0a 20  |)..  if (i~=0). |
0000e4a0  20 7b 20 20 20 69 66 20  28 64 6f 6e 74 5f 69 6e  | {   if (dont_in|
0000e4b0  66 65 72 3d 3d 31 29 20  72 65 74 75 72 6e 20 69  |fer==1) return i|
0000e4c0  3b 0a 20 20 20 20 20 20  69 66 20 28 69 6e 66 65  |;.      if (infe|
0000e4d0  72 66 72 6f 6d 3d 3d 30  29 20 69 6e 66 65 72 66  |rfrom==0) inferf|
0000e4e0  72 6f 6d 3d 70 63 6f 75  6e 74 3b 0a 20 20 20 20  |rom=pcount;.    |
0000e4f0  20 20 70 61 74 74 65 72  6e 2d 2d 3e 70 63 6f 75  |  pattern-->pcou|
0000e500  6e 74 20 3d 20 69 3b 0a  20 20 20 20 20 20 72 65  |nt = i;.      re|
0000e510  74 75 72 6e 20 69 3b 0a  20 20 7d 0a 0a 21 20 20  |turn i;.  }..!  |
0000e520  49 66 20 77 65 20 67 65  74 20 68 65 72 65 2c 20  |If we get here, |
0000e530  74 68 65 72 65 20 77 61  73 20 6e 6f 20 6f 62 76  |there was no obv|
0000e540  69 6f 75 73 20 63 68 6f  69 63 65 20 6f 66 20 6f  |ious choice of o|
0000e550  62 6a 65 63 74 20 74 6f  20 6d 61 6b 65 2e 20 20  |bject to make.  |
0000e560  49 66 20 69 6e 0a 21 20  20 66 61 63 74 20 77 65  |If in.!  fact we|
0000e570  27 76 65 20 61 6c 72 65  61 64 79 20 67 6f 6e 65  |'ve already gone|
0000e580  20 70 61 73 74 20 74 68  65 20 65 6e 64 20 6f 66  | past the end of|
0000e590  20 74 68 65 20 70 6c 61  79 65 72 27 73 20 74 79  | the player's ty|
0000e5a0  70 69 6e 67 20 28 77 68  69 63 68 0a 21 20 20 6d  |ping (which.!  m|
0000e5b0  65 61 6e 73 20 74 68 65  20 6d 61 74 63 68 20 6c  |eans the match l|
0000e5c0  69 73 74 20 6d 75 73 74  20 63 6f 6e 74 61 69 6e  |ist must contain|
0000e5d0  20 65 76 65 72 79 20 6f  62 6a 65 63 74 20 69 6e  | every object in|
0000e5e0  20 73 63 6f 70 65 2c 20  72 65 67 61 72 64 6c 65  | scope, regardle|
0000e5f0  73 73 0a 21 20 20 6f 66  20 69 74 73 20 6e 61 6d  |ss.!  of its nam|
0000e600  65 29 2c 20 74 68 65 6e  20 69 74 27 73 20 66 6f  |e), then it's fo|
0000e610  6f 6c 69 73 68 20 74 6f  20 67 69 76 65 20 61 6e  |olish to give an|
0000e620  20 65 6e 6f 72 6d 6f 75  73 20 6c 69 73 74 20 74  | enormous list t|
0000e630  6f 20 63 68 6f 6f 73 65  0a 21 20 20 66 72 6f 6d  |o choose.!  from|
0000e640  20 2d 20 69 6e 73 74 65  61 64 20 77 65 20 67 6f  | - instead we go|
0000e650  20 61 6e 64 20 61 73 6b  20 61 20 6d 6f 72 65 20  | and ask a more |
0000e660  73 75 69 74 61 62 6c 65  20 71 75 65 73 74 69 6f  |suitable questio|
0000e670  6e 2e 2e 2e 0a 0a 20 20  69 66 20 28 6d 61 74 63  |n.....  if (matc|
0000e680  68 5f 66 72 6f 6d 20 3e  20 6e 75 6d 5f 77 6f 72  |h_from > num_wor|
0000e690  64 73 29 20 6a 75 6d 70  20 49 6e 63 6f 6d 70 6c  |ds) jump Incompl|
0000e6a0  65 74 65 3b 0a 0a 21 20  20 4e 6f 77 20 77 65 20  |ete;..!  Now we |
0000e6b0  70 72 69 6e 74 20 75 70  20 74 68 65 20 71 75 65  |print up the que|
0000e6c0  73 74 69 6f 6e 2c 20 75  73 69 6e 67 20 74 68 65  |stion, using the|
0000e6d0  20 65 71 75 69 76 61 6c  65 6e 63 65 20 63 6c 61  | equivalence cla|
0000e6e0  73 73 65 73 20 61 73 20  77 6f 72 6b 65 64 0a 21  |sses as worked.!|
0000e6f0  20 20 6f 75 74 20 62 79  20 41 64 6a 75 64 69 63  |  out by Adjudic|
0000e700  61 74 65 28 29 20 73 6f  20 61 73 20 6e 6f 74 20  |ate() so as not |
0000e710  74 6f 20 72 65 70 65 61  74 20 6f 75 72 73 65 6c  |to repeat oursel|
0000e720  76 65 73 20 6f 6e 20 70  6c 75 72 61 6c 20 6f 62  |ves on plural ob|
0000e730  6a 65 63 74 73 2e 2e 2e  0a 0a 20 20 69 66 20 28  |jects.....  if (|
0000e740  63 6f 6e 74 65 78 74 3d  3d 36 29 20 70 72 69 6e  |context==6) prin|
0000e750  74 20 22 57 68 6f 22 3b  20 65 6c 73 65 20 70 72  |t "Who"; else pr|
0000e760  69 6e 74 20 22 57 68 69  63 68 22 3b 0a 20 20 70  |int "Which";.  p|
0000e770  72 69 6e 74 20 22 20 64  6f 20 79 6f 75 20 6d 65  |rint " do you me|
0000e780  61 6e 2c 20 22 3b 0a 20  20 6a 3d 6e 75 6d 62 65  |an, ";.  j=numbe|
0000e790  72 5f 6f 66 5f 63 6c 61  73 73 65 73 3b 20 6d 61  |r_of_classes; ma|
0000e7a0  72 6b 65 72 3d 30 3b 0a  20 20 66 6f 72 20 28 69  |rker=0;.  for (i|
0000e7b0  3d 31 3a 69 3c 3d 6e 75  6d 62 65 72 5f 6f 66 5f  |=1:i<=number_of_|
0000e7c0  63 6c 61 73 73 65 73 3a  69 2b 2b 29 0a 20 20 7b  |classes:i++).  {|
0000e7d0  20 20 20 0a 20 20 20 20  20 20 77 68 69 6c 65 20  |   .      while |
0000e7e0  28 28 28 6d 61 74 63 68  5f 63 6c 61 73 73 65 73  |(((match_classes|
0000e7f0  2d 2d 3e 6d 61 72 6b 65  72 29 20 7e 3d 20 69 29  |-->marker) ~= i)|
0000e800  0a 20 20 20 20 20 20 20  20 20 20 20 20 20 26 26  |.             &&|
0000e810  20 28 28 6d 61 74 63 68  5f 63 6c 61 73 73 65 73  | ((match_classes|
0000e820  2d 2d 3e 6d 61 72 6b 65  72 29 20 7e 3d 20 2d 69  |-->marker) ~= -i|
0000e830  29 29 20 6d 61 72 6b 65  72 2b 2b 3b 0a 20 20 20  |)) marker++;.   |
0000e840  20 20 20 6b 3d 6d 61 74  63 68 5f 6c 69 73 74 2d  |   k=match_list-|
0000e850  2d 3e 6d 61 72 6b 65 72  3b 0a 0a 20 20 20 20 20  |->marker;..     |
0000e860  20 69 66 20 28 6d 61 74  63 68 5f 63 6c 61 73 73  | if (match_class|
0000e870  65 73 2d 2d 3e 6d 61 72  6b 65 72 20 3e 20 30 29  |es-->marker > 0)|
0000e880  20 44 65 66 41 72 74 28  6b 29 3b 20 65 6c 73 65  | DefArt(k); else|
0000e890  20 49 6e 44 65 66 41 72  74 28 6b 29 3b 0a 0a 20  | InDefArt(k);.. |
0000e8a0  20 20 20 20 20 69 66 20  28 69 3c 6a 2d 31 29 20  |     if (i<j-1) |
0000e8b0  20 70 72 69 6e 74 20 22  2c 20 22 3b 0a 20 20 20  | print ", ";.   |
0000e8c0  20 20 20 69 66 20 28 69  3d 3d 6a 2d 31 29 20 70  |   if (i==j-1) p|
0000e8d0  72 69 6e 74 20 22 20 6f  72 20 22 3b 0a 20 20 7d  |rint " or ";.  }|
0000e8e0  0a 20 20 70 72 69 6e 74  20 22 3f 5e 22 3b 0a 0a  |.  print "?^";..|
0000e8f0  21 20 20 2e 2e 2e 61 6e  64 20 67 65 74 20 61 6e  |!  ...and get an|
0000e900  20 61 6e 73 77 65 72 3a  0a 0a 20 20 2e 57 68 69  | answer:..  .Whi|
0000e910  63 68 4f 6e 65 3b 0a 20  20 61 6e 73 77 65 72 5f  |chOne;.  answer_|
0000e920  77 6f 72 64 73 3d 4b 65  79 62 6f 61 72 64 28 62  |words=Keyboard(b|
0000e930  75 66 66 65 72 32 2c 20  70 61 72 73 65 32 29 3b  |uffer2, parse2);|
0000e940  0a 0a 20 20 66 69 72 73  74 5f 77 6f 72 64 3d 28  |..  first_word=(|
0000e950  70 61 72 73 65 32 2d 2d  3e 31 29 3b 0a 0a 21 20  |parse2-->1);..! |
0000e960  20 54 61 6b 65 20 63 61  72 65 20 6f 66 20 22 61  | Take care of "a|
0000e970  6c 6c 22 2c 20 62 65 63  61 75 73 65 20 74 68 61  |ll", because tha|
0000e980  74 20 64 6f 65 73 20 73  6f 6d 65 74 68 69 6e 67  |t does something|
0000e990  20 74 6f 6f 20 63 6c 65  76 65 72 20 68 65 72 65  | too clever here|
0000e9a0  20 74 6f 20 64 6f 0a 21  20 20 6c 61 74 65 72 20  | to do.!  later |
0000e9b0  6f 6e 3a 0a 0a 20 20 69  66 20 28 28 66 69 72 73  |on:..  if ((firs|
0000e9c0  74 5f 77 6f 72 64 3d 3d  27 61 6c 6c 27 20 6f 72  |t_word=='all' or|
0000e9d0  20 27 62 6f 74 68 27 20  6f 72 20 27 65 76 65 72  | 'both' or 'ever|
0000e9e0  79 74 68 69 6e 67 27 29  0a 20 20 20 20 20 20 7c  |ything').      ||
0000e9f0  7c 20 28 66 69 72 73 74  5f 77 6f 72 64 3d 3d 27  || (first_word=='|
0000ea00  65 76 65 72 79 27 20 6f  72 20 27 65 61 63 68 27  |every' or 'each'|
0000ea10  29 29 0a 20 20 7b 20 20  20 0a 20 20 20 20 20 20  |)).  {   .      |
0000ea20  69 66 20 28 63 6f 6e 74  65 78 74 3e 3d 32 20 26  |if (context>=2 &|
0000ea30  26 20 63 6f 6e 74 65 78  74 3c 3d 35 29 0a 20 20  |& context<=5).  |
0000ea40  20 20 20 20 7b 20 20 20  6c 3d 6d 75 6c 74 69 70  |    {   l=multip|
0000ea50  6c 65 5f 6f 62 6a 65 63  74 2d 2d 3e 30 3b 0a 20  |le_object-->0;. |
0000ea60  20 20 20 20 20 20 20 20  20 66 6f 72 20 28 69 3d  |         for (i=|
0000ea70  30 3a 69 3c 6e 75 6d 62  65 72 5f 6d 61 74 63 68  |0:i<number_match|
0000ea80  65 64 3a 69 2b 2b 29 0a  20 20 20 20 20 20 20 20  |ed:i++).        |
0000ea90  20 20 7b 20 20 20 6b 3d  6d 61 74 63 68 5f 6c 69  |  {   k=match_li|
0000eaa0  73 74 2d 2d 3e 69 3b 0a  20 20 20 20 20 20 20 20  |st-->i;.        |
0000eab0  20 20 20 20 20 20 6d 75  6c 74 69 70 6c 65 5f 6f  |      multiple_o|
0000eac0  62 6a 65 63 74 2d 2d 3e  28 69 2b 31 2b 6c 29 20  |bject-->(i+1+l) |
0000ead0  3d 20 6b 3b 0a 20 20 20  20 20 20 20 20 20 20 7d  |= k;.          }|
0000eae0  0a 20 20 20 20 20 20 20  20 20 20 6d 75 6c 74 69  |.          multi|
0000eaf0  70 6c 65 5f 6f 62 6a 65  63 74 2d 2d 3e 30 20 3d  |ple_object-->0 =|
0000eb00  20 6e 75 6d 62 65 72 5f  6d 61 74 63 68 65 64 2b  | number_matched+|
0000eb10  6c 3b 0a 20 20 20 20 20  20 20 20 20 20 72 74 72  |l;.          rtr|
0000eb20  75 65 3b 0a 20 20 20 20  20 20 7d 0a 20 20 20 20  |ue;.      }.    |
0000eb30  20 20 70 72 69 6e 74 20  22 53 6f 72 72 79 2c 20  |  print "Sorry, |
0000eb40  79 6f 75 20 63 61 6e 20  6f 6e 6c 79 20 68 61 76  |you can only hav|
0000eb50  65 20 6f 6e 65 20 69 74  65 6d 20 68 65 72 65 2e  |e one item here.|
0000eb60  20 20 57 68 69 63 68 20  6f 6e 65 20 65 78 61 63  |  Which one exac|
0000eb70  74 6c 79 3f 5e 22 3b 0a  20 20 20 20 20 20 6a 75  |tly?^";.      ju|
0000eb80  6d 70 20 57 68 69 63 68  4f 6e 65 3b 0a 20 20 7d  |mp WhichOne;.  }|
0000eb90  0a 0a 21 20 20 49 66 20  74 68 65 20 66 69 72 73  |..!  If the firs|
0000eba0  74 20 77 6f 72 64 20 6f  66 20 74 68 65 20 72 65  |t word of the re|
0000ebb0  70 6c 79 20 63 61 6e 20  62 65 20 69 6e 74 65 72  |ply can be inter|
0000ebc0  70 72 65 74 65 64 20 61  73 20 61 20 76 65 72 62  |preted as a verb|
0000ebd0  2c 20 74 68 65 6e 0a 21  20 20 61 73 73 75 6d 65  |, then.!  assume|
0000ebe0  20 74 68 61 74 20 74 68  65 20 70 6c 61 79 65 72  | that the player|
0000ebf0  20 68 61 73 20 69 67 6e  6f 72 65 64 20 74 68 65  | has ignored the|
0000ec00  20 71 75 65 73 74 69 6f  6e 20 61 6e 64 20 67 69  | question and gi|
0000ec10  76 65 6e 20 61 20 6e 65  77 0a 21 20 20 63 6f 6d  |ven a new.!  com|
0000ec20  6d 61 6e 64 20 61 6c 74  6f 67 65 74 68 65 72 2e  |mand altogether.|
0000ec30  0a 21 20 20 28 54 68 69  73 20 69 73 20 6f 6e 65  |.!  (This is one|
0000ec40  20 74 69 6d 65 20 77 68  65 6e 20 69 74 27 73 20  | time when it's |
0000ec50  63 6f 6e 76 65 6e 69 65  6e 74 20 74 68 61 74 20  |convenient that |
0000ec60  74 68 65 20 64 69 72 65  63 74 69 6f 6e 73 20 61  |the directions a|
0000ec70  72 65 0a 21 20 20 6e 6f  74 20 74 68 65 6d 73 65  |re.!  not themse|
0000ec80  6c 76 65 73 20 76 65 72  62 73 20 2d 20 74 68 75  |lves verbs - thu|
0000ec90  73 2c 20 22 6e 6f 72 74  68 22 20 61 73 20 61 20  |s, "north" as a |
0000eca0  72 65 70 6c 79 20 74 6f  20 22 57 68 69 63 68 2c  |reply to "Which,|
0000ecb0  20 74 68 65 20 6e 6f 72  74 68 0a 21 20 20 6f 72  | the north.!  or|
0000ecc0  20 73 6f 75 74 68 20 64  6f 6f 72 22 20 69 73 20  | south door" is |
0000ecd0  6e 6f 74 20 74 72 65 61  74 65 64 20 61 73 20 61  |not treated as a|
0000ece0  20 66 72 65 73 68 20 63  6f 6d 6d 61 6e 64 20 62  | fresh command b|
0000ecf0  75 74 20 61 73 20 61 6e  20 61 6e 73 77 65 72 2e  |ut as an answer.|
0000ed00  29 0a 0a 20 20 6a 3d 66  69 72 73 74 5f 77 6f 72  |)..  j=first_wor|
0000ed10  64 2d 3e 23 64 69 63 74  5f 70 61 72 31 3b 0a 20  |d->#dict_par1;. |
0000ed20  20 69 66 20 28 30 7e 3d  6a 26 31 29 0a 20 20 7b  | if (0~=j&1).  {|
0000ed30  20 20 20 43 6f 70 79 28  62 75 66 66 65 72 2c 20  |   Copy(buffer, |
0000ed40  62 75 66 66 65 72 32 29  3b 0a 20 20 20 20 20 20  |buffer2);.      |
0000ed50  43 6f 70 79 28 70 61 72  73 65 2c 20 70 61 72 73  |Copy(parse, pars|
0000ed60  65 32 29 3b 0a 20 20 20  20 20 20 72 65 74 75 72  |e2);.      retur|
0000ed70  6e 20 31 30 30 30 3b 0a  20 20 7d 0a 0a 21 20 20  |n 1000;.  }..!  |
0000ed80  4e 6f 77 20 77 65 20 69  6e 73 65 72 74 20 74 68  |Now we insert th|
0000ed90  65 20 61 6e 73 77 65 72  20 69 6e 74 6f 20 74 68  |e answer into th|
0000eda0  65 20 6f 72 69 67 69 6e  61 6c 20 74 79 70 65 64  |e original typed|
0000edb0  20 63 6f 6d 6d 61 6e 64  2c 20 61 73 0a 21 20 20  | command, as.!  |
0000edc0  77 6f 72 64 73 20 61 64  64 69 74 69 6f 6e 61 6c  |words additional|
0000edd0  6c 79 20 64 65 73 63 72  69 62 69 6e 67 20 74 68  |ly describing th|
0000ede0  65 20 73 61 6d 65 20 6f  62 6a 65 63 74 0a 21 20  |e same object.! |
0000edf0  20 28 65 67 2c 20 3e 20  74 61 6b 65 20 72 65 64  | (eg, > take red|
0000ee00  20 62 75 74 74 6f 6e 0a  21 20 20 20 20 20 20 20  | button.!       |
0000ee10  57 68 69 63 68 20 6f 6e  65 2c 20 2e 2e 2e 0a 21  |Which one, ....!|
0000ee20  20 20 20 20 20 20 20 3e  20 6d 75 73 69 63 0a 21  |       > music.!|
0000ee30  20 20 62 65 63 6f 6d 65  73 20 22 74 61 6b 65 20  |  becomes "take |
0000ee40  6d 75 73 69 63 20 72 65  64 20 62 75 74 74 6f 6e  |music red button|
0000ee50  22 2e 20 20 54 68 65 20  70 61 72 73 65 72 20 77  |".  The parser w|
0000ee60  69 6c 6c 20 74 68 75 73  20 68 61 76 65 20 74 68  |ill thus have th|
0000ee70  72 65 65 0a 21 20 20 77  6f 72 64 73 20 74 6f 20  |ree.!  words to |
0000ee80  77 6f 72 6b 20 66 72 6f  6d 20 6e 65 78 74 20 74  |work from next t|
0000ee90  69 6d 65 2c 20 6e 6f 74  20 74 77 6f 2e 29 0a 21  |ime, not two.).!|
0000eea0  0a 21 20 20 54 6f 20 64  6f 20 74 68 69 73 20 77  |.!  To do this w|
0000eeb0  65 20 75 73 65 20 4d 6f  76 65 57 6f 72 64 20 77  |e use MoveWord w|
0000eec0  68 69 63 68 20 63 6f 70  69 65 73 20 69 6e 20 61  |hich copies in a|
0000eed0  20 77 6f 72 64 2e 0a 0a  20 20 6f 6c 64 77 3d 70  | word...  oldw=p|
0000eee0  61 72 73 65 2d 3e 31 3b  0a 20 20 70 61 72 73 65  |arse->1;.  parse|
0000eef0  2d 3e 31 20 3d 20 61 6e  73 77 65 72 5f 77 6f 72  |->1 = answer_wor|
0000ef00  64 73 2b 6f 6c 64 77 3b  0a 0a 20 20 66 6f 72 20  |ds+oldw;..  for |
0000ef10  28 6b 3d 6f 6c 64 77 2b  61 6e 73 77 65 72 5f 77  |(k=oldw+answer_w|
0000ef20  6f 72 64 73 20 3a 20 6b  3e 6d 61 74 63 68 5f 66  |ords : k>match_f|
0000ef30  72 6f 6d 20 3a 20 6b 2d  2d 29 0a 20 20 20 20 20  |rom : k--).     |
0000ef40  20 4d 6f 76 65 57 6f 72  64 28 6b 2c 20 70 61 72  | MoveWord(k, par|
0000ef50  73 65 2c 20 6b 2d 61 6e  73 77 65 72 5f 77 6f 72  |se, k-answer_wor|
0000ef60  64 73 29 3b 0a 0a 20 20  66 6f 72 20 28 6b 3d 31  |ds);..  for (k=1|
0000ef70  3a 6b 3c 3d 61 6e 73 77  65 72 5f 77 6f 72 64 73  |:k<=answer_words|
0000ef80  3a 6b 2b 2b 29 0a 20 20  20 20 20 20 4d 6f 76 65  |:k++).      Move|
0000ef90  57 6f 72 64 28 6d 61 74  63 68 5f 66 72 6f 6d 2b  |Word(match_from+|
0000efa0  6b 2d 31 2c 20 70 61 72  73 65 32 2c 20 6b 29 3b  |k-1, parse2, k);|
0000efb0  0a 0a 21 20 20 48 61 76  69 6e 67 20 72 65 63 6f  |..!  Having reco|
0000efc0  6e 73 74 72 75 63 74 65  64 20 74 68 65 20 69 6e  |nstructed the in|
0000efd0  70 75 74 2c 20 77 65 20  77 61 72 6e 20 74 68 65  |put, we warn the|
0000efe0  20 70 61 72 73 65 72 20  61 63 63 6f 72 64 69 6e  | parser accordin|
0000eff0  67 6c 79 0a 21 20 20 61  6e 64 20 67 65 74 20 6f  |gly.!  and get o|
0000f000  75 74 2e 0a 0a 20 20 72  65 74 75 72 6e 20 31 30  |ut...  return 10|
0000f010  30 30 3b 0a 0a 21 20 20  4e 6f 77 20 77 65 20 63  |00;..!  Now we c|
0000f020  6f 6d 65 20 74 6f 20 74  68 65 20 71 75 65 73 74  |ome to the quest|
0000f030  69 6f 6e 20 61 73 6b 65  64 20 77 68 65 6e 20 74  |ion asked when t|
0000f040  68 65 20 69 6e 70 75 74  20 68 61 73 20 72 75 6e  |he input has run|
0000f050  20 6f 75 74 0a 21 20 20  61 6e 64 20 63 61 6e 27  | out.!  and can'|
0000f060  74 20 65 61 73 69 6c 79  20 62 65 20 67 75 65 73  |t easily be gues|
0000f070  73 65 64 20 28 65 67 2c  20 74 68 65 20 70 6c 61  |sed (eg, the pla|
0000f080  79 65 72 20 74 79 70 65  64 20 22 74 61 6b 65 22  |yer typed "take"|
0000f090  20 61 6e 64 20 74 68 65  72 65 0a 21 20 20 77 65  | and there.!  we|
0000f0a0  72 65 20 70 6c 65 6e 74  79 20 6f 66 20 74 68 69  |re plenty of thi|
0000f0b0  6e 67 73 20 77 68 69 63  68 20 6d 69 67 68 74 20  |ngs which might |
0000f0c0  68 61 76 65 20 62 65 65  6e 20 6d 65 61 6e 74 29  |have been meant)|
0000f0d0  2e 0a 0a 20 20 2e 49 6e  63 6f 6d 70 6c 65 74 65  |...  .Incomplete|
0000f0e0  3b 0a 0a 20 20 69 66 20  28 63 6f 6e 74 65 78 74  |;..  if (context|
0000f0f0  3d 3d 36 29 20 70 72 69  6e 74 20 22 57 68 6f 6d  |==6) print "Whom|
0000f100  22 3b 20 65 6c 73 65 20  70 72 69 6e 74 20 22 57  |"; else print "W|
0000f110  68 61 74 22 3b 0a 20 20  70 72 69 6e 74 20 22 20  |hat";.  print " |
0000f120  64 6f 20 79 6f 75 20 77  61 6e 74 22 3b 0a 20 20  |do you want";.  |
0000f130  69 66 20 28 61 63 74 6f  72 7e 3d 70 6c 61 79 65  |if (actor~=playe|
0000f140  72 29 20 7b 20 70 72 69  6e 74 20 22 20 22 3b 20  |r) { print " "; |
0000f150  44 65 66 41 72 74 28 61  63 74 6f 72 29 3b 20 7d  |DefArt(actor); }|
0000f160  0a 20 20 70 72 69 6e 74  20 22 20 74 6f 20 22 3b  |.  print " to ";|
0000f170  20 50 72 69 6e 74 43 6f  6d 6d 61 6e 64 28 30 2c  | PrintCommand(0,|
0000f180  31 29 3b 20 70 72 69 6e  74 20 22 3f 5e 22 3b 0a  |1); print "?^";.|
0000f190  0a 20 20 61 6e 73 77 65  72 5f 77 6f 72 64 73 3d  |.  answer_words=|
0000f1a0  4b 65 79 62 6f 61 72 64  28 62 75 66 66 65 72 32  |Keyboard(buffer2|
0000f1b0  2c 20 70 61 72 73 65 32  29 3b 0a 0a 20 20 66 69  |, parse2);..  fi|
0000f1c0  72 73 74 5f 77 6f 72 64  3d 28 70 61 72 73 65 32  |rst_word=(parse2|
0000f1d0  2d 2d 3e 31 29 3b 0a 0a  21 20 20 4f 6e 63 65 20  |-->1);..!  Once |
0000f1e0  61 67 61 69 6e 2c 20 69  66 20 74 68 65 20 72 65  |again, if the re|
0000f1f0  70 6c 79 20 6c 6f 6f 6b  73 20 6c 69 6b 65 20 61  |ply looks like a|
0000f200  20 63 6f 6d 6d 61 6e 64  2c 20 67 69 76 65 20 69  | command, give i|
0000f210  74 20 74 6f 20 74 68 65  0a 21 20 20 70 61 72 73  |t to the.!  pars|
0000f220  65 72 20 74 6f 20 67 65  74 20 6f 6e 20 77 69 74  |er to get on wit|
0000f230  68 20 61 6e 64 20 66 6f  72 67 65 74 20 61 62 6f  |h and forget abo|
0000f240  75 74 20 74 68 65 20 71  75 65 73 74 69 6f 6e 2e  |ut the question.|
0000f250  2e 2e 0a 0a 20 20 6a 3d  66 69 72 73 74 5f 77 6f  |....  j=first_wo|
0000f260  72 64 2d 3e 23 64 69 63  74 5f 70 61 72 31 3b 0a  |rd->#dict_par1;.|
0000f270  20 20 69 66 20 28 30 7e  3d 6a 26 31 29 0a 20 20  |  if (0~=j&1).  |
0000f280  7b 20 20 20 43 6f 70 79  28 62 75 66 66 65 72 2c  |{   Copy(buffer,|
0000f290  20 62 75 66 66 65 72 32  29 3b 0a 20 20 20 20 20  | buffer2);.     |
0000f2a0  20 43 6f 70 79 28 70 61  72 73 65 2c 20 70 61 72  | Copy(parse, par|
0000f2b0  73 65 32 29 3b 0a 20 20  20 20 20 20 72 65 74 75  |se2);.      retu|
0000f2c0  72 6e 20 31 30 30 30 3b  0a 20 20 7d 0a 0a 21 20  |rn 1000;.  }..! |
0000f2d0  20 2e 2e 2e 62 75 74 20  69 66 20 77 65 20 68 61  | ...but if we ha|
0000f2e0  76 65 20 61 20 67 65 6e  75 69 6e 65 20 61 6e 73  |ve a genuine ans|
0000f2f0  77 65 72 2c 20 74 68 65  6e 20 77 65 20 61 64 6a  |wer, then we adj|
0000f300  6f 69 6e 20 74 68 65 20  77 6f 72 64 73 0a 21 20  |oin the words.! |
0000f310  20 74 79 70 65 64 20 6f  6e 74 6f 20 74 68 65 20  | typed onto the |
0000f320  65 78 70 72 65 73 73 69  6f 6e 2e 20 20 42 75 74  |expression.  But|
0000f330  20 69 66 20 77 65 27 76  65 20 6a 75 73 74 20 69  | if we've just i|
0000f340  6e 66 65 72 72 65 64 20  61 0a 21 20 20 70 72 65  |nferred a.!  pre|
0000f350  70 6f 73 69 74 69 6f 6e  20 77 68 69 63 68 20 77  |position which w|
0000f360  61 73 6e 27 74 20 61 63  74 75 61 6c 6c 79 20 74  |asn't actually t|
0000f370  68 65 72 65 2c 20 74 68  65 6e 20 77 65 20 6e 65  |here, then we ne|
0000f380  65 64 20 74 6f 0a 21 20  20 61 64 6a 6f 69 6e 20  |ed to.!  adjoin |
0000f390  74 68 61 74 20 61 73 20  77 65 6c 6c 2e 20 20 28  |that as well.  (|
0000f3a0  4e 42 3a 20 74 77 6f 20  63 6f 6e 73 65 63 75 74  |NB: two consecut|
0000f3b0  69 76 65 20 70 72 65 70  6f 73 69 74 69 6f 6e 73  |ive prepositions|
0000f3c0  20 77 69 6c 6c 0a 21 20  20 63 61 75 73 65 20 74  | will.!  cause t|
0000f3d0  72 6f 75 62 6c 65 20 68  65 72 65 21 29 0a 0a 20  |rouble here!).. |
0000f3e0  20 6f 6c 64 77 3d 70 61  72 73 65 2d 3e 31 3b 0a  | oldw=parse->1;.|
0000f3f0  20 20 69 66 20 28 69 6e  66 65 72 66 72 6f 6d 3d  |  if (inferfrom=|
0000f400  3d 30 29 0a 20 20 20 20  20 20 66 6f 72 20 28 6b  |=0).      for (k|
0000f410  3d 31 3a 6b 3c 3d 61 6e  73 77 65 72 5f 77 6f 72  |=1:k<=answer_wor|
0000f420  64 73 3a 6b 2b 2b 29 0a  20 20 20 20 20 20 20 20  |ds:k++).        |
0000f430  20 20 4d 6f 76 65 57 6f  72 64 28 6d 61 74 63 68  |  MoveWord(match|
0000f440  5f 66 72 6f 6d 2b 6b 2d  31 2c 20 70 61 72 73 65  |_from+k-1, parse|
0000f450  32 2c 20 6b 29 3b 0a 20  20 65 6c 73 65 0a 20 20  |2, k);.  else.  |
0000f460  7b 20 20 20 66 6f 72 20  28 6b 3d 31 3a 6b 3c 3d  |{   for (k=1:k<=|
0000f470  61 6e 73 77 65 72 5f 77  6f 72 64 73 3a 6b 2b 2b  |answer_words:k++|
0000f480  29 0a 20 20 20 20 20 20  20 20 20 20 4d 6f 76 65  |).          Move|
0000f490  57 6f 72 64 28 6d 61 74  63 68 5f 66 72 6f 6d 2b  |Word(match_from+|
0000f4a0  6b 2c 20 70 61 72 73 65  32 2c 20 6b 29 3b 0a 20  |k, parse2, k);. |
0000f4b0  20 20 20 20 20 70 61 72  73 65 32 2d 2d 3e 31 20  |     parse2-->1 |
0000f4c0  3d 20 41 64 6a 65 63 74  69 76 65 41 64 64 72 65  |= AdjectiveAddre|
0000f4d0  73 73 28 69 6e 66 65 72  77 6f 72 64 29 3b 0a 20  |ss(inferword);. |
0000f4e0  20 20 20 20 20 4d 6f 76  65 57 6f 72 64 28 6d 61  |     MoveWord(ma|
0000f4f0  74 63 68 5f 66 72 6f 6d  2c 20 70 61 72 73 65 32  |tch_from, parse2|
0000f500  2c 20 31 29 3b 0a 20 20  20 20 20 20 61 6e 73 77  |, 1);.      answ|
0000f510  65 72 5f 77 6f 72 64 73  2b 2b 3b 0a 20 20 7d 0a  |er_words++;.  }.|
0000f520  20 20 70 61 72 73 65 2d  3e 31 20 3d 20 61 6e 73  |  parse->1 = ans|
0000f530  77 65 72 5f 77 6f 72 64  73 2b 6f 6c 64 77 3b 0a  |wer_words+oldw;.|
0000f540  0a 21 20 20 41 6e 64 20  67 6f 20 62 61 63 6b 20  |.!  And go back |
0000f550  74 6f 20 74 68 65 20 70  61 72 73 65 72 2e 0a 20  |to the parser.. |
0000f560  20 72 65 74 75 72 6e 20  31 30 30 30 3b 0a 5d 3b  | return 1000;.];|
0000f570  0a 0a 21 20 2d 2d 2d 2d  2d 2d 2d 2d 2d 2d 2d 2d  |..! ------------|
0000f580  2d 2d 2d 2d 2d 2d 2d 2d  2d 2d 2d 2d 2d 2d 2d 2d  |----------------|
*
0000f5c0  0a 21 20 20 54 68 65 20  41 64 6a 75 64 69 63 61  |.!  The Adjudica|
0000f5d0  74 65 20 72 6f 75 74 69  6e 65 20 74 72 69 65 73  |te routine tries|
0000f5e0  20 74 6f 20 73 65 65 20  69 66 20 74 68 65 72 65  | to see if there|
0000f5f0  20 69 73 20 61 6e 20 6f  62 76 69 6f 75 73 20 63  | is an obvious c|
0000f600  68 6f 69 63 65 2c 20 77  68 65 6e 0a 21 20 20 66  |hoice, when.!  f|
0000f610  61 63 65 64 20 77 69 74  68 20 61 20 6c 69 73 74  |aced with a list|
0000f620  20 6f 66 20 6f 62 6a 65  63 74 73 20 28 74 68 65  | of objects (the|
0000f630  20 6d 61 74 63 68 5f 6c  69 73 74 29 20 65 61 63  | match_list) eac|
0000f640  68 20 6f 66 20 77 68 69  63 68 20 6d 61 74 63 68  |h of which match|
0000f650  65 73 20 74 68 65 0a 21  20 20 70 6c 61 79 65 72  |es the.!  player|
0000f660  27 73 20 73 70 65 63 69  66 69 63 61 74 69 6f 6e  |'s specification|
0000f670  20 65 71 75 61 6c 6c 79  20 77 65 6c 6c 2e 0a 21  | equally well..!|
0000f680  0a 21 20 20 54 6f 20 64  6f 20 74 68 69 73 20 69  |.!  To do this i|
0000f690  74 20 6d 61 6b 65 73 20  75 73 65 20 6f 66 20 74  |t makes use of t|
0000f6a0  68 65 20 63 6f 6e 74 65  78 74 20 28 74 68 65 20  |he context (the |
0000f6b0  74 6f 6b 65 6e 20 74 79  70 65 20 62 65 69 6e 67  |token type being|
0000f6c0  20 77 6f 72 6b 65 64 20  6f 6e 29 2e 0a 21 20 20  | worked on)..!  |
0000f6d0  49 74 20 63 6f 75 6e 74  73 20 75 70 20 74 68 65  |It counts up the|
0000f6e0  20 6e 75 6d 62 65 72 20  6f 66 20 6f 62 76 69 6f  | number of obvio|
0000f6f0  75 73 20 63 68 6f 69 63  65 73 20 66 6f 72 20 74  |us choices for t|
0000f700  68 65 20 67 69 76 65 6e  20 63 6f 6e 74 65 78 74  |he given context|
0000f710  0a 21 20 20 28 61 6c 6c  20 74 6f 20 64 6f 20 77  |.!  (all to do w|
0000f720  69 74 68 20 77 68 65 72  65 20 61 20 63 61 6e 64  |ith where a cand|
0000f730  69 64 61 74 65 20 69 73  2c 20 65 78 63 65 70 74  |idate is, except|
0000f740  20 66 6f 72 20 36 20 28  61 6e 69 6d 61 74 65 29  | for 6 (animate)|
0000f750  20 77 68 69 63 68 20 69  73 20 74 6f 0a 21 20 20  | which is to.!  |
0000f760  64 6f 20 77 69 74 68 20  77 68 65 74 68 65 72 20  |do with whether |
0000f770  69 74 20 69 73 20 61 6e  69 6d 61 74 65 20 6f 72  |it is animate or|
0000f780  20 6e 6f 74 29 3b 0a 21  0a 21 20 20 69 66 20 6f  | not);.!.!  if o|
0000f790  6e 6c 79 20 6f 6e 65 20  6f 62 76 69 6f 75 73 20  |nly one obvious |
0000f7a0  63 68 6f 69 63 65 20 69  73 20 66 6f 75 6e 64 2c  |choice is found,|
0000f7b0  20 74 68 61 74 20 69 73  20 72 65 74 75 72 6e 65  | that is returne|
0000f7c0  64 3b 0a 21 0a 21 20 20  69 66 20 77 65 20 61 72  |d;.!.!  if we ar|
0000f7d0  65 20 69 6e 20 69 6e 64  65 66 69 6e 69 74 65 20  |e in indefinite |
0000f7e0  6d 6f 64 65 20 28 64 6f  6e 27 74 20 63 61 72 65  |mode (don't care|
0000f7f0  20 77 68 69 63 68 29 20  6f 6e 65 20 6f 66 20 74  | which) one of t|
0000f800  68 65 20 6f 62 76 69 6f  75 73 20 63 68 6f 69 63  |he obvious choic|
0000f810  65 73 0a 21 20 20 20 20  69 73 20 72 65 74 75 72  |es.!    is retur|
0000f820  6e 65 64 2c 20 6f 72 20  69 66 20 74 68 65 72 65  |ned, or if there|
0000f830  20 69 73 20 6e 6f 20 6f  62 76 69 6f 75 73 20 63  | is no obvious c|
0000f840  68 6f 69 63 65 20 74 68  65 6e 20 61 6e 20 75 6e  |hoice then an un|
0000f850  6f 62 76 69 6f 75 73 20  6f 6e 65 20 69 73 0a 21  |obvious one is.!|
0000f860  20 20 20 20 6d 61 64 65  3b 0a 21 0a 21 20 20 61  |    made;.!.!  a|
0000f870  74 20 74 68 69 73 20 73  74 61 67 65 2c 20 77 65  |t this stage, we|
0000f880  20 77 6f 72 6b 20 6f 75  74 20 77 68 65 74 68 65  | work out whethe|
0000f890  72 20 74 68 65 20 6f 62  6a 65 63 74 73 20 61 72  |r the objects ar|
0000f8a0  65 20 64 69 73 74 69 6e  67 75 69 73 68 61 62 6c  |e distinguishabl|
0000f8b0  65 20 66 72 6f 6d 0a 21  20 20 20 20 65 61 63 68  |e from.!    each|
0000f8c0  20 6f 74 68 65 72 20 6f  72 20 6e 6f 74 3a 20 69  | other or not: i|
0000f8d0  66 20 74 68 65 79 20 61  72 65 20 61 6c 6c 20 69  |f they are all i|
0000f8e0  6e 64 69 73 74 69 6e 67  75 69 73 68 61 62 6c 65  |ndistinguishable|
0000f8f0  20 66 72 6f 6d 20 65 61  63 68 20 6f 74 68 65 72  | from each other|
0000f900  2c 0a 21 20 20 20 20 74  68 65 6e 20 63 68 6f 6f  |,.!    then choo|
0000f910  73 65 20 6f 6e 65 2c 20  69 74 20 64 6f 65 73 6e  |se one, it doesn|
0000f920  27 74 20 6d 61 74 74 65  72 20 77 68 69 63 68 3b  |'t matter which;|
0000f930  0a 21 0a 21 20 20 6f 74  68 65 72 77 69 73 65 2c  |.!.!  otherwise,|
0000f940  20 30 20 28 6d 65 61 6e  69 6e 67 2c 20 75 6e 61  | 0 (meaning, una|
0000f950  62 6c 65 20 74 6f 20 64  65 63 69 64 65 29 20 69  |ble to decide) i|
0000f960  73 20 72 65 74 75 72 6e  65 64 20 28 62 75 74 20  |s returned (but |
0000f970  72 65 6d 65 6d 62 65 72  20 74 68 61 74 0a 21 20  |remember that.! |
0000f980  20 20 20 74 68 65 20 65  71 75 69 76 61 6c 65 6e  |   the equivalen|
0000f990  63 65 20 63 6c 61 73 73  65 73 20 77 65 27 76 65  |ce classes we've|
0000f9a0  20 6a 75 73 74 20 77 6f  72 6b 65 64 20 6f 75 74  | just worked out|
0000f9b0  20 77 69 6c 6c 20 62 65  20 6e 65 65 64 65 64 20  | will be needed |
0000f9c0  62 79 20 6f 74 68 65 72  0a 21 20 20 20 20 72 6f  |by other.!    ro|
0000f9d0  75 74 69 6e 65 73 20 74  6f 20 63 6c 65 61 72 20  |utines to clear |
0000f9e0  75 70 20 74 68 69 73 20  6d 65 73 73 2c 20 73 6f  |up this mess, so|
0000f9f0  20 77 65 20 63 61 6e 27  74 20 65 63 6f 6e 6f 6d  | we can't econom|
0000fa00  69 73 65 20 6f 6e 20 77  6f 72 6b 69 6e 67 20 74  |ise on working t|
0000fa10  68 65 6d 0a 21 20 20 20  20 6f 75 74 29 2e 0a 21  |hem.!    out)..!|
0000fa20  0a 21 20 20 52 65 74 75  72 6e 73 20 2d 31 20 69  |.!  Returns -1 i|
0000fa30  66 20 61 6e 20 65 72 72  6f 72 20 6f 63 63 75 72  |f an error occur|
0000fa40  72 65 64 0a 21 20 2d 2d  2d 2d 2d 2d 2d 2d 2d 2d  |red.! ----------|
0000fa50  2d 2d 2d 2d 2d 2d 2d 2d  2d 2d 2d 2d 2d 2d 2d 2d  |----------------|
*
0000fa90  2d 2d 0a 0a 5b 20 41 64  6a 75 64 69 63 61 74 65  |--..[ Adjudicate|
0000faa0  20 63 6f 6e 74 65 78 74  20 69 20 6a 20 67 6f 6f  | context i j goo|
0000fab0  64 5f 6f 6e 65 73 20 6c  61 73 74 20 6e 20 75 6c  |d_ones last n ul|
0000fac0  74 69 6d 61 74 65 20 66  6c 61 67 20 6f 66 66 73  |timate flag offs|
0000fad0  65 74 3b 0a 0a 20 20 69  66 20 28 70 61 72 73 65  |et;..  if (parse|
0000fae0  72 5f 74 72 61 63 65 3e  3d 34 29 0a 20 20 20 20  |r_trace>=4).    |
0000faf0  20 20 70 72 69 6e 74 20  22 20 20 20 5b 41 64 6a  |  print "   [Adj|
0000fb00  75 64 69 63 61 74 69 6e  67 20 6d 61 74 63 68 20  |udicating match |
0000fb10  6c 69 73 74 20 6f 66 20  73 69 7a 65 20 22 2c 20  |list of size ", |
0000fb20  6e 75 6d 62 65 72 5f 6d  61 74 63 68 65 64 2c 20  |number_matched, |
0000fb30  22 5e 22 3b 0a 0a 20 20  6a 3d 6e 75 6d 62 65 72  |"^";..  j=number|
0000fb40  5f 6d 61 74 63 68 65 64  2d 31 3b 20 67 6f 6f 64  |_matched-1; good|
0000fb50  5f 6f 6e 65 73 3d 30 3b  20 6c 61 73 74 3d 6d 61  |_ones=0; last=ma|
0000fb60  74 63 68 5f 6c 69 73 74  2d 2d 3e 30 3b 0a 20 20  |tch_list-->0;.  |
0000fb70  66 6f 72 20 28 69 3d 30  3a 69 3c 3d 6a 3a 69 2b  |for (i=0:i<=j:i+|
0000fb80  2b 29 0a 20 20 7b 20 20  20 6e 3d 6d 61 74 63 68  |+).  {   n=match|
0000fb90  5f 6c 69 73 74 2d 2d 3e  69 3b 0a 20 20 20 20 20  |_list-->i;.     |
0000fba0  20 69 66 20 28 6e 20 68  61 73 6e 74 20 63 6f 6e  | if (n hasnt con|
0000fbb0  63 65 61 6c 65 64 29 0a  20 20 20 20 20 20 7b 20  |cealed).      { |
0000fbc0  20 20 75 6c 74 69 6d 61  74 65 3d 6e 3b 0a 20 20  |  ultimate=n;.  |
0000fbd0  20 20 20 20 20 20 20 20  64 6f 0a 20 20 20 20 20  |        do.     |
0000fbe0  20 20 20 20 20 20 20 20  20 75 6c 74 69 6d 61 74  |         ultimat|
0000fbf0  65 3d 70 61 72 65 6e 74  28 75 6c 74 69 6d 61 74  |e=parent(ultimat|
0000fc00  65 29 3b 0a 20 20 20 20  20 20 20 20 20 20 75 6e  |e);.          un|
0000fc10  74 69 6c 20 28 75 6c 74  69 6d 61 74 65 3d 3d 6c  |til (ultimate==l|
0000fc20  6f 63 61 74 69 6f 6e 20  6f 72 20 61 63 74 6f 72  |ocation or actor|
0000fc30  20 6f 72 20 30 29 3b 0a  0a 20 20 20 20 20 20 20  | or 0);..       |
0000fc40  20 20 20 69 66 20 28 63  6f 6e 74 65 78 74 3d 3d  |   if (context==|
0000fc50  30 20 26 26 20 75 6c 74  69 6d 61 74 65 3d 3d 6c  |0 && ultimate==l|
0000fc60  6f 63 61 74 69 6f 6e 20  26 26 0a 20 20 20 20 20  |ocation &&.     |
0000fc70  20 20 20 20 20 20 20 20  20 28 74 6f 6b 65 6e 5f  |         (token_|
0000fc80  77 61 73 3d 3d 30 20 7c  7c 20 55 73 65 72 46 69  |was==0 || UserFi|
0000fc90  6c 74 65 72 28 6e 29 3d  3d 31 29 29 20 7b 20 67  |lter(n)==1)) { g|
0000fca0  6f 6f 64 5f 6f 6e 65 73  2b 2b 3b 20 6c 61 73 74  |ood_ones++; last|
0000fcb0  3d 6e 3b 20 7d 0a 20 20  20 20 20 20 20 20 20 20  |=n; }.          |
0000fcc0  69 66 20 28 63 6f 6e 74  65 78 74 3d 3d 31 20 26  |if (context==1 &|
0000fcd0  26 20 70 61 72 65 6e 74  28 6e 29 3d 3d 61 63 74  |& parent(n)==act|
0000fce0  6f 72 29 20 20 20 20 20  7b 20 67 6f 6f 64 5f 6f  |or)     { good_o|
0000fcf0  6e 65 73 2b 2b 3b 20 6c  61 73 74 3d 6e 3b 20 7d  |nes++; last=n; }|
0000fd00  0a 20 20 20 20 20 20 20  20 20 20 69 66 20 28 63  |.          if (c|
0000fd10  6f 6e 74 65 78 74 3d 3d  32 20 26 26 20 75 6c 74  |ontext==2 && ult|
0000fd20  69 6d 61 74 65 3d 3d 6c  6f 63 61 74 69 6f 6e 29  |imate==location)|
0000fd30  20 20 20 7b 20 67 6f 6f  64 5f 6f 6e 65 73 2b 2b  |   { good_ones++|
0000fd40  3b 20 6c 61 73 74 3d 6e  3b 20 7d 0a 20 20 20 20  |; last=n; }.    |
0000fd50  20 20 20 20 20 20 69 66  20 28 63 6f 6e 74 65 78  |      if (contex|
0000fd60  74 3d 3d 33 20 26 26 20  70 61 72 65 6e 74 28 6e  |t==3 && parent(n|
0000fd70  29 3d 3d 61 63 74 6f 72  29 20 20 20 20 20 7b 20  |)==actor)     { |
0000fd80  67 6f 6f 64 5f 6f 6e 65  73 2b 2b 3b 20 6c 61 73  |good_ones++; las|
0000fd90  74 3d 6e 3b 20 7d 0a 0a  20 20 20 20 20 20 20 20  |t=n; }..        |
0000fda0  20 20 69 66 20 28 63 6f  6e 74 65 78 74 3d 3d 34  |  if (context==4|
0000fdb0  20 6f 72 20 35 29 0a 20  20 20 20 20 20 20 20 20  | or 5).         |
0000fdc0  20 7b 20 20 20 69 66 20  28 61 64 76 61 6e 63 65  | {   if (advance|
0000fdd0  5f 77 61 72 6e 69 6e 67  3d 3d 2d 31 29 0a 20 20  |_warning==-1).  |
0000fde0  20 20 20 20 20 20 20 20  20 20 20 20 7b 20 20 20  |            {   |
0000fdf0  69 66 20 28 70 61 72 65  6e 74 28 6e 29 3d 3d 61  |if (parent(n)==a|
0000fe00  63 74 6f 72 29 20 7b 20  67 6f 6f 64 5f 6f 6e 65  |ctor) { good_one|
0000fe10  73 2b 2b 3b 20 6c 61 73  74 3d 6e 3b 20 7d 0a 20  |s++; last=n; }. |
0000fe20  20 20 20 20 20 20 20 20  20 20 20 20 20 7d 0a 20  |             }. |
0000fe30  20 20 20 20 20 20 20 20  20 20 20 20 20 65 6c 73  |             els|
0000fe40  65 0a 20 20 20 20 20 20  20 20 20 20 20 20 20 20  |e.              |
0000fe50  7b 20 20 20 69 66 20 28  63 6f 6e 74 65 78 74 3d  |{   if (context=|
0000fe60  3d 34 20 26 26 20 70 61  72 65 6e 74 28 6e 29 3d  |=4 && parent(n)=|
0000fe70  3d 61 63 74 6f 72 20 26  26 20 6e 7e 3d 61 64 76  |=actor && n~=adv|
0000fe80  61 6e 63 65 5f 77 61 72  6e 69 6e 67 29 0a 20 20  |ance_warning).  |
0000fe90  20 20 20 20 20 20 20 20  20 20 20 20 20 20 20 20  |                |
0000fea0  7b 20 67 6f 6f 64 5f 6f  6e 65 73 2b 2b 3b 20 6c  |{ good_ones++; l|
0000feb0  61 73 74 3d 6e 3b 20 7d  0a 20 20 20 20 20 20 20  |ast=n; }.       |
0000fec0  20 20 20 20 20 20 20 20  20 20 20 69 66 20 28 63  |           if (c|
0000fed0  6f 6e 74 65 78 74 3d 3d  35 20 26 26 20 70 61 72  |ontext==5 && par|
0000fee0  65 6e 74 28 6e 29 3d 3d  61 63 74 6f 72 20 26 26  |ent(n)==actor &&|
0000fef0  20 6e 20 69 6e 20 61 64  76 61 6e 63 65 5f 77 61  | n in advance_wa|
0000ff00  72 6e 69 6e 67 29 0a 20  20 20 20 20 20 20 20 20  |rning).         |
0000ff10  20 20 20 20 20 20 20 20  20 7b 20 67 6f 6f 64 5f  |         { good_|
0000ff20  6f 6e 65 73 2b 2b 3b 20  6c 61 73 74 3d 6e 3b 20  |ones++; last=n; |
0000ff30  7d 0a 20 20 20 20 20 20  20 20 20 20 20 20 20 20  |}.              |
0000ff40  7d 0a 20 20 20 20 20 20  20 20 20 20 7d 0a 20 20  |}.          }.  |
0000ff50  20 20 20 20 20 20 20 20  69 66 20 28 63 6f 6e 74  |        if (cont|
0000ff60  65 78 74 3d 3d 36 20 26  26 20 6e 20 68 61 73 20  |ext==6 && n has |
0000ff70  61 6e 69 6d 61 74 65 29  20 20 20 20 20 20 20 20  |animate)        |
0000ff80  7b 20 67 6f 6f 64 5f 6f  6e 65 73 2b 2b 3b 20 6c  |{ good_ones++; l|
0000ff90  61 73 74 3d 6e 3b 20 7d  0a 20 20 20 20 20 20 7d  |ast=n; }.      }|
0000ffa0  0a 20 20 7d 0a 20 20 69  66 20 28 67 6f 6f 64 5f  |.  }.  if (good_|
0000ffb0  6f 6e 65 73 3d 3d 31 29  20 72 65 74 75 72 6e 20  |ones==1) return |
0000ffc0  6c 61 73 74 3b 0a 0a 20  20 69 66 20 28 69 6e 64  |last;..  if (ind|
0000ffd0  65 66 5f 6d 6f 64 65 3d  3d 31 20 26 26 20 69 6e  |ef_mode==1 && in|
0000ffe0  64 65 66 5f 74 79 70 65  20 26 20 50 4c 55 52 41  |def_type & PLURA|
0000fff0  4c 5f 42 49 54 20 7e 3d  20 30 29 0a 20 20 7b 20  |L_BIT ~= 0).  { |
00010000  20 20 69 66 20 28 63 6f  6e 74 65 78 74 3c 32 20  |  if (context<2 |
00010010  7c 7c 20 63 6f 6e 74 65  78 74 3e 35 29 20 7b 20  ||| context>5) { |
00010020  65 74 79 70 65 3d 4d 55  4c 54 49 5f 50 45 3b 20  |etype=MULTI_PE; |
00010030  72 65 74 75 72 6e 20 2d  31 3b 20 7d 0a 20 20 20  |return -1; }.   |
00010040  20 20 20 69 3d 30 3b 20  6e 75 6d 62 65 72 5f 6f  |   i=0; number_o|
00010050  66 5f 63 6c 61 73 73 65  73 3d 31 3b 20 6f 66 66  |f_classes=1; off|
00010060  73 65 74 3d 6d 75 6c 74  69 70 6c 65 5f 6f 62 6a  |set=multiple_obj|
00010070  65 63 74 2d 2d 3e 30 3b  0a 20 20 20 20 20 20 66  |ect-->0;.      f|
00010080  6f 72 20 28 6a 3d 42 65  73 74 47 75 65 73 73 28  |or (j=BestGuess(|
00010090  29 3a 6a 7e 3d 2d 31 20  26 26 20 69 3c 69 6e 64  |):j~=-1 && i<ind|
000100a0  65 66 5f 77 61 6e 74 65  64 3a 6a 3d 42 65 73 74  |ef_wanted:j=Best|
000100b0  47 75 65 73 73 28 29 29  0a 20 20 20 20 20 20 7b  |Guess()).      {|
000100c0  20 20 20 69 66 20 28 6a  20 68 61 73 6e 74 20 63  |   if (j hasnt c|
000100d0  6f 6e 63 65 61 6c 65 64  20 26 26 20 6a 20 68 61  |oncealed && j ha|
000100e0  73 6e 74 20 77 6f 72 6e  29 0a 20 20 20 20 20 20  |snt worn).      |
000100f0  20 20 20 20 7b 20 20 20  66 6c 61 67 3d 31 3b 0a  |    {   flag=1;.|
00010100  20 20 20 20 20 20 20 20  20 20 20 20 20 20 69 66  |              if|
00010110  20 28 63 6f 6e 74 65 78  74 3d 3d 33 20 6f 72 20  | (context==3 or |
00010120  34 20 26 26 20 70 61 72  65 6e 74 28 6a 29 7e 3d  |4 && parent(j)~=|
00010130  61 63 74 6f 72 29 20 66  6c 61 67 3d 30 3b 0a 20  |actor) flag=0;. |
00010140  20 20 20 20 20 20 20 20  20 20 20 20 20 69 66 20  |             if |
00010150  28 66 6c 61 67 3d 3d 31  29 0a 20 20 20 20 20 20  |(flag==1).      |
00010160  20 20 20 20 20 20 20 20  7b 20 20 20 69 2b 2b 3b  |        {   i++;|
00010170  20 6d 75 6c 74 69 70 6c  65 5f 6f 62 6a 65 63 74  | multiple_object|
00010180  2d 2d 3e 28 69 2b 6f 66  66 73 65 74 29 20 3d 20  |-->(i+offset) = |
00010190  6a 3b 0a 20 20 20 20 20  20 20 20 20 20 20 20 20  |j;.             |
000101a0  20 20 20 20 20 69 66 20  28 70 61 72 73 65 72 5f  |     if (parser_|
000101b0  74 72 61 63 65 3e 3d 34  29 0a 20 20 20 20 20 20  |trace>=4).      |
000101c0  20 20 20 20 20 20 20 20  20 20 20 20 20 20 20 20  |                |
000101d0  70 72 69 6e 74 20 22 20  20 20 41 63 63 65 70 74  |print "   Accept|
000101e0  69 6e 67 20 69 74 5e 22  3b 0a 20 20 20 20 20 20  |ing it^";.      |
000101f0  20 20 20 20 20 20 20 20  7d 0a 20 20 20 20 20 20  |        }.      |
00010200  20 20 20 20 20 20 20 20  65 6c 73 65 0a 20 20 20  |        else.   |
00010210  20 20 20 20 20 20 20 20  20 20 20 7b 20 20 20 69  |           {   i|
00010220  66 20 28 70 61 72 73 65  72 5f 74 72 61 63 65 3e  |f (parser_trace>|
00010230  3d 34 29 0a 20 20 20 20  20 20 20 20 20 20 20 20  |=4).            |
00010240  20 20 20 20 20 20 20 20  20 20 70 72 69 6e 74 20  |          print |
00010250  22 20 20 20 52 65 6a 65  63 74 69 6e 67 20 69 74  |"   Rejecting it|
00010260  5e 22 3b 0a 20 20 20 20  20 20 20 20 20 20 20 20  |^";.            |
00010270  20 20 7d 0a 20 20 20 20  20 20 20 20 20 20 7d 0a  |  }.          }.|
00010280  20 20 20 20 20 20 7d 0a  20 20 20 20 20 20 69 66  |      }.      if|
00010290  20 28 69 3c 69 6e 64 65  66 5f 77 61 6e 74 65 64  | (i<indef_wanted|
000102a0  20 26 26 20 69 6e 64 65  66 5f 77 61 6e 74 65 64  | && indef_wanted|
000102b0  3c 31 30 30 29 0a 20 20  20 20 20 20 7b 20 20 20  |<100).      {   |
000102c0  65 74 79 70 65 3d 54 4f  4f 46 45 57 5f 50 45 3b  |etype=TOOFEW_PE;|
000102d0  20 6d 75 6c 74 69 5f 77  61 6e 74 65 64 3d 69 6e  | multi_wanted=in|
000102e0  64 65 66 5f 77 61 6e 74  65 64 3b 0a 20 20 20 20  |def_wanted;.    |
000102f0  20 20 20 20 20 20 6d 75  6c 74 69 5f 68 61 64 3d  |      multi_had=|
00010300  6d 75 6c 74 69 70 6c 65  5f 6f 62 6a 65 63 74 2d  |multiple_object-|
00010310  2d 3e 30 3b 0a 20 20 20  20 20 20 20 20 20 20 72  |->0;.          r|
00010320  65 74 75 72 6e 20 2d 31  3b 0a 20 20 20 20 20 20  |eturn -1;.      |
00010330  7d 0a 20 20 20 20 20 20  6d 75 6c 74 69 70 6c 65  |}.      multiple|
00010340  5f 6f 62 6a 65 63 74 2d  2d 3e 30 20 3d 20 69 2b  |_object-->0 = i+|
00010350  6f 66 66 73 65 74 3b 0a  20 20 20 20 20 20 6d 75  |offset;.      mu|
00010360  6c 74 69 5f 63 6f 6e 74  65 78 74 3d 63 6f 6e 74  |lti_context=cont|
00010370  65 78 74 3b 0a 20 20 20  20 20 20 69 66 20 28 70  |ext;.      if (p|
00010380  61 72 73 65 72 5f 74 72  61 63 65 3e 3d 34 29 0a  |arser_trace>=4).|
00010390  20 20 20 20 20 20 20 20  20 20 70 72 69 6e 74 20  |          print |
000103a0  22 20 20 20 4d 61 64 65  20 6d 75 6c 74 69 70 6c  |"   Made multipl|
000103b0  65 20 6f 62 6a 65 63 74  20 6f 66 20 73 69 7a 65  |e object of size|
000103c0  20 22 2c 20 69 2c 20 22  5d 5e 22 3b 0a 20 20 20  | ", i, "]^";.   |
000103d0  20 20 20 72 65 74 75 72  6e 20 31 3b 0a 20 20 7d  |   return 1;.  }|
000103e0  0a 0a 20 20 66 6f 72 20  28 69 3d 30 3a 69 3c 6e  |..  for (i=0:i<n|
000103f0  75 6d 62 65 72 5f 6d 61  74 63 68 65 64 3a 69 2b  |umber_matched:i+|
00010400  2b 29 20 6d 61 74 63 68  5f 63 6c 61 73 73 65 73  |+) match_classes|
00010410  2d 2d 3e 69 3d 30 3b 0a  0a 20 20 6e 3d 31 3b 0a  |-->i=0;..  n=1;.|
00010420  20 20 66 6f 72 20 28 69  3d 30 3a 69 3c 6e 75 6d  |  for (i=0:i<num|
00010430  62 65 72 5f 6d 61 74 63  68 65 64 3a 69 2b 2b 29  |ber_matched:i++)|
00010440  0a 20 20 20 20 20 20 69  66 20 28 6d 61 74 63 68  |.      if (match|
00010450  5f 63 6c 61 73 73 65 73  2d 2d 3e 69 3d 3d 30 29  |_classes-->i==0)|
00010460  0a 20 20 20 20 20 20 7b  20 20 20 6d 61 74 63 68  |.      {   match|
00010470  5f 63 6c 61 73 73 65 73  2d 2d 3e 69 3d 6e 2b 2b  |_classes-->i=n++|
00010480  3b 20 66 6c 61 67 3d 30  3b 0a 20 20 20 20 20 20  |; flag=0;.      |
00010490  20 20 20 20 66 6f 72 20  28 6a 3d 69 2b 31 3a 6a  |    for (j=i+1:j|
000104a0  3c 6e 75 6d 62 65 72 5f  6d 61 74 63 68 65 64 3a  |<number_matched:|
000104b0  6a 2b 2b 29 0a 20 20 20  20 20 20 20 20 20 20 20  |j++).           |
000104c0  20 20 20 69 66 20 28 6d  61 74 63 68 5f 63 6c 61  |   if (match_cla|
000104d0  73 73 65 73 2d 2d 3e 6a  3d 3d 30 0a 20 20 20 20  |sses-->j==0.    |
000104e0  20 20 20 20 20 20 20 20  20 20 20 20 20 20 26 26  |              &&|
000104f0  20 49 64 65 6e 74 69 63  61 6c 28 6d 61 74 63 68  | Identical(match|
00010500  5f 6c 69 73 74 2d 2d 3e  69 2c 20 6d 61 74 63 68  |_list-->i, match|
00010510  5f 6c 69 73 74 2d 2d 3e  6a 29 3d 3d 31 29 0a 20  |_list-->j)==1). |
00010520  20 20 20 20 20 20 20 20  20 20 20 20 20 7b 20 20  |             {  |
00010530  20 66 6c 61 67 3d 31 3b  0a 20 20 20 20 20 20 20  | flag=1;.       |
00010540  20 20 20 20 20 20 20 20  20 20 20 6d 61 74 63 68  |           match|
00010550  5f 63 6c 61 73 73 65 73  2d 2d 3e 6a 3d 6d 61 74  |_classes-->j=mat|
00010560  63 68 5f 63 6c 61 73 73  65 73 2d 2d 3e 69 3b 0a  |ch_classes-->i;.|
00010570  20 20 20 20 20 20 20 20  20 20 20 20 20 20 7d 0a  |              }.|
00010580  20 20 20 20 20 20 20 20  20 20 69 66 20 28 66 6c  |          if (fl|
00010590  61 67 3d 3d 31 29 20 6d  61 74 63 68 5f 63 6c 61  |ag==1) match_cla|
000105a0  73 73 65 73 2d 2d 3e 69  20 3d 20 31 2d 6e 3b 0a  |sses-->i = 1-n;.|
000105b0  20 20 20 20 20 20 7d 0a  20 20 6e 2d 2d 3b 0a 0a  |      }.  n--;..|
000105c0  20 20 69 66 20 28 70 61  72 73 65 72 5f 74 72 61  |  if (parser_tra|
000105d0  63 65 3e 3d 34 29 0a 20  20 7b 20 20 20 70 72 69  |ce>=4).  {   pri|
000105e0  6e 74 20 22 20 20 20 44  69 66 66 69 63 75 6c 74  |nt "   Difficult|
000105f0  20 61 64 6a 75 64 69 63  61 74 69 6f 6e 20 77 69  | adjudication wi|
00010600  74 68 20 22 2c 20 6e 2c  20 22 20 65 71 75 69 76  |th ", n, " equiv|
00010610  61 6c 65 6e 63 65 20 63  6c 61 73 73 65 73 3a 5e  |alence classes:^|
00010620  22 3b 0a 20 20 20 20 20  20 66 6f 72 20 28 69 3d  |";.      for (i=|
00010630  30 3a 69 3c 6e 75 6d 62  65 72 5f 6d 61 74 63 68  |0:i<number_match|
00010640  65 64 3a 69 2b 2b 29 0a  20 20 20 20 20 20 7b 20  |ed:i++).      { |
00010650  20 20 70 72 69 6e 74 20  22 20 20 20 22 3b 20 43  |  print "   "; C|
00010660  44 65 66 41 72 74 28 6d  61 74 63 68 5f 6c 69 73  |DefArt(match_lis|
00010670  74 2d 2d 3e 69 29 3b 0a  20 20 20 20 20 20 20 20  |t-->i);.        |
00010680  20 20 70 72 69 6e 74 20  22 20 28 22 2c 20 6d 61  |  print " (", ma|
00010690  74 63 68 5f 6c 69 73 74  2d 2d 3e 69 2c 20 22 29  |tch_list-->i, ")|
000106a0  20 20 2d 2d 2d 20 20 22  2c 6d 61 74 63 68 5f 63  |  ---  ",match_c|
000106b0  6c 61 73 73 65 73 2d 2d  3e 69 2c 20 22 5e 22 3b  |lasses-->i, "^";|
000106c0  0a 20 20 20 20 20 20 7d  0a 20 20 7d 0a 0a 20 20  |.      }.  }..  |
000106d0  6e 75 6d 62 65 72 5f 6f  66 5f 63 6c 61 73 73 65  |number_of_classe|
000106e0  73 20 3d 20 6e 3b 0a 0a  20 20 69 66 20 28 6e 3e  |s = n;..  if (n>|
000106f0  31 20 26 26 20 69 6e 64  65 66 5f 6d 6f 64 65 3d  |1 && indef_mode=|
00010700  3d 30 29 0a 20 20 7b 20  20 20 69 66 20 28 70 61  |=0).  {   if (pa|
00010710  72 73 65 72 5f 74 72 61  63 65 3e 3d 34 29 0a 20  |rser_trace>=4). |
00010720  20 20 20 20 20 20 20 20  20 70 72 69 6e 74 20 22  |         print "|
00010730  20 20 20 55 6e 61 62 6c  65 20 74 6f 20 64 65 63  |   Unable to dec|
00010740  69 64 65 3a 20 69 74 27  73 20 61 20 64 72 61 77  |ide: it's a draw|
00010750  2e 5d 5e 22 3b 0a 20 20  20 20 20 20 6a 75 6d 70  |.]^";.      jump|
00010760  20 46 61 69 6c 54 6f 6b  65 6e 3b 0a 20 20 7d 0a  | FailToken;.  }.|
00010770  0a 21 20 20 57 68 65 6e  20 74 68 65 20 70 6c 61  |.!  When the pla|
00010780  79 65 72 20 69 73 20 72  65 61 6c 6c 79 20 76 61  |yer is really va|
00010790  67 75 65 2c 20 6f 72 20  74 68 65 72 65 27 73 20  |gue, or there's |
000107a0  61 20 73 69 6e 67 6c 65  20 63 6f 6c 6c 65 63 74  |a single collect|
000107b0  69 6f 6e 20 6f 66 0a 21  20 20 69 6e 64 69 73 74  |ion of.!  indist|
000107c0  69 6e 67 75 69 73 68 61  62 6c 65 20 6f 62 6a 65  |inguishable obje|
000107d0  63 74 73 20 74 6f 20 63  68 6f 6f 73 65 20 66 72  |cts to choose fr|
000107e0  6f 6d 2c 20 63 68 6f 6f  73 65 20 74 68 65 20 6f  |om, choose the o|
000107f0  6e 65 20 74 68 65 20 70  6c 61 79 65 72 0a 21 20  |ne the player.! |
00010800  20 6d 6f 73 74 20 72 65  63 65 6e 74 6c 79 20 61  | most recently a|
00010810  63 71 75 69 72 65 64 2c  20 6f 72 20 69 66 20 74  |cquired, or if t|
00010820  68 65 20 70 6c 61 79 65  72 20 68 61 73 20 6e 6f  |he player has no|
00010830  6e 65 20 6f 66 20 74 68  65 6d 2c 20 74 68 65 6e  |ne of them, then|
00010840  0a 21 20 20 74 68 65 20  6f 6e 65 20 6d 6f 73 74  |.!  the one most|
00010850  20 72 65 63 65 6e 74 6c  79 20 70 75 74 20 77 68  | recently put wh|
00010860  65 72 65 20 69 74 20 69  73 2e 0a 0a 20 20 69 66  |ere it is...  if|
00010870  20 28 69 6e 64 65 66 5f  6d 6f 64 65 3d 3d 30 29  | (indef_mode==0)|
00010880  20 69 6e 64 65 66 5f 74  79 70 65 3d 30 3b 0a 20  | indef_type=0;. |
00010890  20 69 66 20 28 6e 3d 3d  31 29 20 64 6f 6e 74 5f  | if (n==1) dont_|
000108a0  69 6e 66 65 72 20 3d 20  31 3b 0a 0a 20 20 72 65  |infer = 1;..  re|
000108b0  74 75 72 6e 20 42 65 73  74 47 75 65 73 73 28 29  |turn BestGuess()|
000108c0  3b 0a 5d 3b 0a 0a 21 20  2d 2d 2d 2d 2d 2d 2d 2d  |;.];..! --------|
000108d0  2d 2d 2d 2d 2d 2d 2d 2d  2d 2d 2d 2d 2d 2d 2d 2d  |----------------|
*
00010910  2d 2d 2d 2d 0a 21 20 20  52 65 76 69 73 65 4d 75  |----.!  ReviseMu|
00010920  6c 74 69 20 20 72 65 76  69 73 65 73 20 74 68 65  |lti  revises the|
00010930  20 6d 75 6c 74 69 70 6c  65 20 6f 62 6a 65 63 74  | multiple object|
00010940  20 77 68 69 63 68 20 61  6c 72 65 61 64 79 20 65  | which already e|
00010950  78 69 73 74 73 2c 20 69  6e 20 74 68 65 0a 21 20  |xists, in the.! |
00010960  20 20 20 6c 69 67 68 74  20 6f 66 20 69 6e 66 6f  |   light of info|
00010970  72 6d 61 74 69 6f 6e 20  77 68 69 63 68 20 68 61  |rmation which ha|
00010980  73 20 63 6f 6d 65 20 61  6c 6f 6e 67 20 73 69 6e  |s come along sin|
00010990  63 65 20 74 68 65 6e 20  28 69 2e 65 2e 2c 20 74  |ce then (i.e., t|
000109a0  68 65 20 73 65 63 6f 6e  64 0a 21 20 20 20 20 70  |he second.!    p|
000109b0  61 72 61 6d 65 74 65 72  29 2e 20 20 49 74 20 72  |arameter).  It r|
000109c0  65 74 75 72 6e 73 20 61  20 70 61 72 73 65 72 20  |eturns a parser |
000109d0  65 72 72 6f 72 20 6e 75  6d 62 65 72 2c 20 6f 72  |error number, or|
000109e0  20 65 6c 73 65 20 31 20  69 66 20 61 6c 6c 20 69  | else 1 if all i|
000109f0  73 20 77 65 6c 6c 2e 0a  21 20 20 20 20 54 68 69  |s well..!    Thi|
00010a00  73 20 6f 6e 6c 79 20 65  76 65 72 20 74 68 72 6f  |s only ever thro|
00010a10  77 73 20 74 68 69 6e 67  73 20 6f 75 74 2c 20 6e  |ws things out, n|
00010a20  65 76 65 72 20 61 64 64  73 20 6e 65 77 20 6f 6e  |ever adds new on|
00010a30  65 73 2e 0a 21 20 2d 2d  2d 2d 2d 2d 2d 2d 2d 2d  |es..! ----------|
00010a40  2d 2d 2d 2d 2d 2d 2d 2d  2d 2d 2d 2d 2d 2d 2d 2d  |----------------|
*
00010a80  2d 2d 0a 0a 5b 20 52 65  76 69 73 65 4d 75 6c 74  |--..[ ReviseMult|
00010a90  69 20 73 65 63 6f 6e 64  5f 70 20 20 69 20 6c 6f  |i second_p  i lo|
00010aa0  77 3b 0a 0a 20 20 69 66  20 28 70 61 72 73 65 72  |w;..  if (parser|
00010ab0  5f 74 72 61 63 65 3e 3d  34 29 0a 20 20 20 20 20  |_trace>=4).     |
00010ac0  20 70 72 69 6e 74 20 22  20 20 20 52 65 76 69 73  | print "   Revis|
00010ad0  69 6e 67 20 74 68 65 20  6d 75 6c 74 69 70 6c 65  |ing the multiple|
00010ae0  20 6f 62 6a 65 63 74 20  6c 69 73 74 5e 22 3b 0a  | object list^";.|
00010af0  0a 20 20 69 66 20 28 6d  75 6c 74 69 5f 63 6f 6e  |.  if (multi_con|
00010b00  74 65 78 74 3d 3d 34 20  6f 72 20 35 29 0a 20 20  |text==4 or 5).  |
00010b10  7b 20 20 20 66 6f 72 20  28 69 3d 31 2c 20 6c 6f  |{   for (i=1, lo|
00010b20  77 3d 30 3a 69 3c 3d 6d  75 6c 74 69 70 6c 65 5f  |w=0:i<=multiple_|
00010b30  6f 62 6a 65 63 74 2d 2d  3e 30 3a 69 2b 2b 29 0a  |object-->0:i++).|
00010b40  20 20 20 20 20 20 7b 20  20 20 69 66 20 28 20 28  |      {   if ( (|
00010b50  6d 75 6c 74 69 5f 63 6f  6e 74 65 78 74 3d 3d 34  |multi_context==4|
00010b60  20 26 26 20 6d 75 6c 74  69 70 6c 65 5f 6f 62 6a  | && multiple_obj|
00010b70  65 63 74 2d 2d 3e 69 20  7e 3d 20 73 65 63 6f 6e  |ect-->i ~= secon|
00010b80  64 5f 70 29 0a 20 20 20  20 20 20 20 20 20 20 20  |d_p).           |
00010b90  20 20 20 20 7c 7c 20 28  6d 75 6c 74 69 5f 63 6f  |    || (multi_co|
00010ba0  6e 74 65 78 74 3d 3d 35  20 26 26 20 6d 75 6c 74  |ntext==5 && mult|
00010bb0  69 70 6c 65 5f 6f 62 6a  65 63 74 2d 2d 3e 69 20  |iple_object-->i |
00010bc0  69 6e 20 73 65 63 6f 6e  64 5f 70 29 29 0a 20 20  |in second_p)).  |
00010bd0  20 20 20 20 20 20 20 20  7b 20 20 20 6c 6f 77 2b  |        {   low+|
00010be0  2b 3b 20 6d 75 6c 74 69  70 6c 65 5f 6f 62 6a 65  |+; multiple_obje|
00010bf0  63 74 2d 2d 3e 6c 6f 77  20 3d 20 6d 75 6c 74 69  |ct-->low = multi|
00010c00  70 6c 65 5f 6f 62 6a 65  63 74 2d 2d 3e 69 3b 0a  |ple_object-->i;.|
00010c10  20 20 20 20 20 20 20 20  20 20 7d 0a 20 20 20 20  |          }.    |
00010c20  20 20 7d 0a 20 20 20 20  20 20 6d 75 6c 74 69 70  |  }.      multip|
00010c30  6c 65 5f 6f 62 6a 65 63  74 2d 2d 3e 30 20 3d 20  |le_object-->0 = |
00010c40  6c 6f 77 3b 0a 20 20 7d  0a 0a 20 20 69 66 20 28  |low;.  }..  if (|
00010c50  6d 75 6c 74 69 5f 63 6f  6e 74 65 78 74 3d 3d 32  |multi_context==2|
00010c60  29 0a 20 20 7b 20 20 20  66 6f 72 20 28 69 3d 31  |).  {   for (i=1|
00010c70  2c 20 6c 6f 77 3d 30 3a  69 3c 3d 6d 75 6c 74 69  |, low=0:i<=multi|
00010c80  70 6c 65 5f 6f 62 6a 65  63 74 2d 2d 3e 30 3a 69  |ple_object-->0:i|
00010c90  2b 2b 29 0a 20 20 20 20  20 20 20 20 20 20 69 66  |++).          if|
00010ca0  20 28 70 61 72 65 6e 74  28 6d 75 6c 74 69 70 6c  | (parent(multipl|
00010cb0  65 5f 6f 62 6a 65 63 74  2d 2d 3e 69 29 3d 3d 6c  |e_object-->i)==l|
00010cc0  6f 63 61 74 69 6f 6e 29  20 6c 6f 77 2b 2b 3b 0a  |ocation) low++;.|
00010cd0  20 20 20 20 20 20 69 66  20 28 70 61 72 73 65 72  |      if (parser|
00010ce0  5f 74 72 61 63 65 3e 3d  34 29 0a 20 20 20 20 20  |_trace>=4).     |
00010cf0  20 20 20 20 20 70 72 69  6e 74 20 22 20 20 20 54  |     print "   T|
00010d00  6f 6b 65 6e 20 32 20 70  6c 75 72 61 6c 20 63 61  |oken 2 plural ca|
00010d10  73 65 3a 20 6e 75 6d 62  65 72 20 6f 6e 20 66 6c  |se: number on fl|
00010d20  6f 6f 72 20 22 2c 20 6c  6f 77 2c 20 22 5e 22 3b  |oor ", low, "^";|
00010d30  0a 20 20 20 20 20 20 69  66 20 28 76 65 72 62 5f  |.      if (verb_|
00010d40  77 6f 72 64 3d 3d 27 74  61 6b 65 27 20 6f 72 20  |word=='take' or |
00010d50  27 67 65 74 27 20 7c 7c  20 6c 6f 77 3e 30 29 0a  |'get' || low>0).|
00010d60  20 20 20 20 20 20 7b 20  20 20 66 6f 72 20 28 69  |      {   for (i|
00010d70  3d 31 2c 20 6c 6f 77 3d  30 3a 69 3c 3d 6d 75 6c  |=1, low=0:i<=mul|
00010d80  74 69 70 6c 65 5f 6f 62  6a 65 63 74 2d 2d 3e 30  |tiple_object-->0|
00010d90  3a 69 2b 2b 29 0a 20 20  20 20 20 20 20 20 20 20  |:i++).          |
00010da0  7b 20 20 20 69 66 20 28  70 61 72 65 6e 74 28 6d  |{   if (parent(m|
00010db0  75 6c 74 69 70 6c 65 5f  6f 62 6a 65 63 74 2d 2d  |ultiple_object--|
00010dc0  3e 69 29 3d 3d 6c 6f 63  61 74 69 6f 6e 29 0a 20  |>i)==location). |
00010dd0  20 20 20 20 20 20 20 20  20 20 20 20 20 7b 20 20  |             {  |
00010de0  20 6c 6f 77 2b 2b 3b 20  6d 75 6c 74 69 70 6c 65  | low++; multiple|
00010df0  5f 6f 62 6a 65 63 74 2d  2d 3e 6c 6f 77 20 3d 20  |_object-->low = |
00010e00  6d 75 6c 74 69 70 6c 65  5f 6f 62 6a 65 63 74 2d  |multiple_object-|
00010e10  2d 3e 69 3b 0a 20 20 20  20 20 20 20 20 20 20 20  |->i;.           |
00010e20  20 20 20 7d 0a 20 20 20  20 20 20 20 20 20 20 7d  |   }.          }|
00010e30  0a 20 20 20 20 20 20 20  20 20 20 6d 75 6c 74 69  |.          multi|
00010e40  70 6c 65 5f 6f 62 6a 65  63 74 2d 2d 3e 30 20 3d  |ple_object-->0 =|
00010e50  20 6c 6f 77 3b 0a 20 20  20 20 20 20 7d 0a 20 20  | low;.      }.  |
00010e60  7d 0a 0a 20 20 69 3d 6d  75 6c 74 69 70 6c 65 5f  |}..  i=multiple_|
00010e70  6f 62 6a 65 63 74 2d 2d  3e 30 3b 0a 20 20 69 66  |object-->0;.  if|
00010e80  20 28 69 3d 3d 30 29 20  72 65 74 75 72 6e 20 4e  | (i==0) return N|
00010e90  4f 54 48 49 4e 47 5f 50  45 3b 0a 20 20 72 65 74  |OTHING_PE;.  ret|
00010ea0  75 72 6e 20 30 3b 0a 5d  3b 0a 0a 21 20 2d 2d 2d  |urn 0;.];..! ---|
00010eb0  2d 2d 2d 2d 2d 2d 2d 2d  2d 2d 2d 2d 2d 2d 2d 2d  |----------------|
*
00010ef0  2d 2d 2d 2d 2d 2d 2d 2d  2d 0a 21 20 20 53 63 6f  |---------.!  Sco|
00010f00  72 65 4d 61 74 63 68 4c  20 20 73 63 6f 72 65 73  |reMatchL  scores|
00010f10  20 74 68 65 20 6d 61 74  63 68 20 6c 69 73 74 20  | the match list |
00010f20  66 6f 72 20 71 75 61 6c  69 74 79 20 69 6e 20 74  |for quality in t|
00010f30  65 72 6d 73 20 6f 66 20  77 68 61 74 20 74 68 65  |erms of what the|
00010f40  0a 21 20 20 70 6c 61 79  65 72 20 68 61 73 20 76  |.!  player has v|
00010f50  61 67 75 65 6c 79 20 61  73 6b 65 64 20 66 6f 72  |aguely asked for|
00010f60  2e 20 20 50 6f 69 6e 74  73 20 61 72 65 20 61 77  |.  Points are aw|
00010f70  61 72 64 65 64 20 66 6f  72 20 63 6f 6e 66 6f 72  |arded for confor|
00010f80  6d 69 6e 67 20 77 69 74  68 0a 21 20 20 72 65 71  |ming with.!  req|
00010f90  75 69 72 65 6d 65 6e 74  73 20 6c 69 6b 65 20 22  |uirements like "|
00010fa0  6d 79 22 2c 20 61 6e 64  20 73 6f 20 6f 6e 2e 20  |my", and so on. |
00010fb0  20 49 66 20 74 68 65 20  73 63 6f 72 65 20 69 73  | If the score is|
00010fc0  20 6c 65 73 73 20 74 68  61 6e 20 74 68 65 0a 21  | less than the.!|
00010fd0  20 20 74 68 72 65 73 68  6f 6c 64 2c 20 62 6c 6f  |  threshold, blo|
00010fe0  63 6b 20 6f 75 74 20 74  68 65 20 65 6e 74 72 79  |ck out the entry|
00010ff0  20 74 6f 20 2d 31 2e 0a  21 20 20 54 68 65 20 73  | to -1..!  The s|
00011000  63 6f 72 65 73 20 61 72  65 20 70 75 74 20 69 6e  |cores are put in|
00011010  20 74 68 65 20 6d 61 74  63 68 5f 63 6c 61 73 73  | the match_class|
00011020  65 73 20 61 72 72 61 79  2c 20 77 68 69 63 68 20  |es array, which |
00011030  77 65 20 63 61 6e 20 73  61 66 65 6c 79 0a 21 20  |we can safely.! |
00011040  20 72 65 75 73 65 20 62  79 20 6e 6f 77 2e 0a 21  | reuse by now..!|
00011050  20 2d 2d 2d 2d 2d 2d 2d  2d 2d 2d 2d 2d 2d 2d 2d  | ---------------|
00011060  2d 2d 2d 2d 2d 2d 2d 2d  2d 2d 2d 2d 2d 2d 2d 2d  |----------------|
*
00011090  2d 2d 2d 2d 2d 2d 2d 2d  2d 2d 2d 2d 2d 0a 0a 5b  |-------------..[|
000110a0  20 53 63 6f 72 65 4d 61  74 63 68 4c 20 20 69 74  | ScoreMatchL  it|
000110b0  73 5f 6f 77 6e 65 72 20  69 74 73 5f 73 63 6f 72  |s_owner its_scor|
000110c0  65 20 6f 62 6a 20 69 20  74 68 72 65 73 68 6f 6c  |e obj i threshol|
000110d0  64 20 61 5f 73 20 6c 5f  73 3b 0a 0a 20 20 69 66  |d a_s l_s;..  if|
000110e0  20 28 69 6e 64 65 66 5f  74 79 70 65 20 26 20 4f  | (indef_type & O|
000110f0  54 48 45 52 5f 42 49 54  20 7e 3d 20 30 29 20 74  |THER_BIT ~= 0) t|
00011100  68 72 65 73 68 6f 6c 64  3d 34 3b 0a 20 20 69 66  |hreshold=4;.  if|
00011110  20 28 69 6e 64 65 66 5f  74 79 70 65 20 26 20 4d  | (indef_type & M|
00011120  59 5f 42 49 54 20 7e 3d  20 30 29 20 20 20 20 74  |Y_BIT ~= 0)    t|
00011130  68 72 65 73 68 6f 6c 64  3d 74 68 72 65 73 68 6f  |hreshold=thresho|
00011140  6c 64 2b 34 3b 0a 20 20  69 66 20 28 69 6e 64 65  |ld+4;.  if (inde|
00011150  66 5f 74 79 70 65 20 26  20 54 48 41 54 5f 42 49  |f_type & THAT_BI|
00011160  54 20 7e 3d 20 30 29 20  20 74 68 72 65 73 68 6f  |T ~= 0)  thresho|
00011170  6c 64 3d 74 68 72 65 73  68 6f 6c 64 2b 34 3b 0a  |ld=threshold+4;.|
00011180  20 20 69 66 20 28 69 6e  64 65 66 5f 74 79 70 65  |  if (indef_type|
00011190  20 26 20 49 54 53 5f 42  49 54 20 7e 3d 20 30 29  | & ITS_BIT ~= 0)|
000111a0  20 20 20 74 68 72 65 73  68 6f 6c 64 3d 74 68 72  |   threshold=thr|
000111b0  65 73 68 6f 6c 64 2b 34  3b 0a 20 20 69 66 20 28  |eshold+4;.  if (|
000111c0  69 6e 64 65 66 5f 74 79  70 65 20 26 20 48 49 53  |indef_type & HIS|
000111d0  5f 42 49 54 20 7e 3d 20  30 29 20 20 20 74 68 72  |_BIT ~= 0)   thr|
000111e0  65 73 68 6f 6c 64 3d 74  68 72 65 73 68 6f 6c 64  |eshold=threshold|
000111f0  2b 34 3b 0a 20 20 69 66  20 28 69 6e 64 65 66 5f  |+4;.  if (indef_|
00011200  74 79 70 65 20 26 20 4c  49 54 5f 42 49 54 20 7e  |type & LIT_BIT ~|
00011210  3d 20 30 29 20 20 20 74  68 72 65 73 68 6f 6c 64  |= 0)   threshold|
00011220  3d 74 68 72 65 73 68 6f  6c 64 2b 34 3b 0a 20 20  |=threshold+4;.  |
00011230  69 66 20 28 69 6e 64 65  66 5f 74 79 70 65 20 26  |if (indef_type &|
00011240  20 55 4e 4c 49 54 5f 42  49 54 20 7e 3d 20 30 29  | UNLIT_BIT ~= 0)|
00011250  20 74 68 72 65 73 68 6f  6c 64 3d 74 68 72 65 73  | threshold=thres|
00011260  68 6f 6c 64 2b 34 3b 0a  0a 20 20 69 66 20 28 70  |hold+4;..  if (p|
00011270  61 72 73 65 72 5f 74 72  61 63 65 3e 3d 34 29 20  |arser_trace>=4) |
00011280  70 72 69 6e 74 20 22 20  20 20 53 63 6f 72 69 6e  |print "   Scorin|
00011290  67 20 6d 61 74 63 68 20  6c 69 73 74 20 77 69 74  |g match list wit|
000112a0  68 20 74 79 70 65 20 22  2c 20 69 6e 64 65 66 5f  |h type ", indef_|
000112b0  74 79 70 65 2c 0a 20 20  20 20 20 20 22 2c 20 74  |type,.      ", t|
000112c0  68 72 65 73 68 6f 6c 64  20 22 2c 20 74 68 72 65  |hreshold ", thre|
000112d0  73 68 6f 6c 64 2c 20 22  3a 5e 22 3b 0a 0a 20 20  |shold, ":^";..  |
000112e0  61 5f 73 20 3d 20 33 3b  20 6c 5f 73 20 3d 20 32  |a_s = 3; l_s = 2|
000112f0  3b 0a 20 20 69 66 20 28  61 63 74 69 6f 6e 5f 74  |;.  if (action_t|
00011300  6f 5f 62 65 20 3d 3d 20  23 23 54 61 6b 65 20 6f  |o_be == ##Take o|
00011310  72 20 23 23 52 65 6d 6f  76 65 29 20 7b 20 61 5f  |r ##Remove) { a_|
00011320  73 3d 32 3b 20 6c 5f 73  3d 33 3b 20 7d 0a 0a 20  |s=2; l_s=3; }.. |
00011330  20 66 6f 72 20 28 69 3d  30 3a 69 3c 6e 75 6d 62  | for (i=0:i<numb|
00011340  65 72 5f 6d 61 74 63 68  65 64 3a 69 2b 2b 29 0a  |er_matched:i++).|
00011350  20 20 7b 20 20 20 6f 62  6a 20 3d 20 6d 61 74 63  |  {   obj = matc|
00011360  68 5f 6c 69 73 74 2d 2d  3e 69 3b 20 69 74 73 5f  |h_list-->i; its_|
00011370  6f 77 6e 65 72 20 3d 20  70 61 72 65 6e 74 28 6f  |owner = parent(o|
00011380  62 6a 29 3b 20 69 74 73  5f 73 63 6f 72 65 3d 30  |bj); its_score=0|
00011390  3b 0a 20 20 20 20 20 20  69 66 20 28 69 74 73 5f  |;.      if (its_|
000113a0  6f 77 6e 65 72 3d 3d 61  63 74 6f 72 29 20 20 20  |owner==actor)   |
000113b0  69 74 73 5f 73 63 6f 72  65 3d 33 3b 0a 20 20 20  |its_score=3;.   |
000113c0  20 20 20 69 66 20 28 69  74 73 5f 6f 77 6e 65 72  |   if (its_owner|
000113d0  3d 3d 6c 6f 63 61 74 69  6f 6e 29 20 69 74 73 5f  |==location) its_|
000113e0  73 63 6f 72 65 3d 32 3b  0a 20 20 20 20 20 20 69  |score=2;.      i|
000113f0  66 20 28 69 74 73 5f 73  63 6f 72 65 3d 3d 30 20  |f (its_score==0 |
00011400  26 26 20 69 74 73 5f 6f  77 6e 65 72 7e 3d 63 6f  |&& its_owner~=co|
00011410  6d 70 61 73 73 29 20 69  74 73 5f 73 63 6f 72 65  |mpass) its_score|
00011420  3d 31 3b 0a 0a 20 20 20  20 20 20 69 66 20 28 69  |=1;..      if (i|
00011430  6e 64 65 66 5f 74 79 70  65 20 26 20 4f 54 48 45  |ndef_type & OTHE|
00011440  52 5f 42 49 54 20 7e 3d  30 0a 20 20 20 20 20 20  |R_BIT ~=0.      |
00011450  20 20 20 20 26 26 20 20  6f 62 6a 7e 3d 69 74 6f  |    &&  obj~=ito|
00011460  62 6a 20 6f 72 20 68 69  6d 6f 62 6a 20 6f 72 20  |bj or himobj or |
00011470  68 65 72 6f 62 6a 29 0a  20 20 20 20 20 20 20 20  |herobj).        |
00011480  20 20 69 74 73 5f 73 63  6f 72 65 3d 69 74 73 5f  |  its_score=its_|
00011490  73 63 6f 72 65 2b 34 3b  0a 20 20 20 20 20 20 69  |score+4;.      i|
000114a0  66 20 28 69 6e 64 65 66  5f 74 79 70 65 20 26 20  |f (indef_type & |
000114b0  4d 59 5f 42 49 54 20 7e  3d 30 20 20 26 26 20 20  |MY_BIT ~=0  &&  |
000114c0  69 74 73 5f 6f 77 6e 65  72 3d 3d 61 63 74 6f 72  |its_owner==actor|
000114d0  29 0a 20 20 20 20 20 20  20 20 20 20 69 74 73 5f  |).          its_|
000114e0  73 63 6f 72 65 3d 69 74  73 5f 73 63 6f 72 65 2b  |score=its_score+|
000114f0  34 3b 0a 20 20 20 20 20  20 69 66 20 28 69 6e 64  |4;.      if (ind|
00011500  65 66 5f 74 79 70 65 20  26 20 54 48 41 54 5f 42  |ef_type & THAT_B|
00011510  49 54 20 7e 3d 30 20 20  26 26 20 20 69 74 73 5f  |IT ~=0  &&  its_|
00011520  6f 77 6e 65 72 3d 3d 6c  6f 63 61 74 69 6f 6e 29  |owner==location)|
00011530  0a 20 20 20 20 20 20 20  20 20 20 69 74 73 5f 73  |.          its_s|
00011540  63 6f 72 65 3d 69 74 73  5f 73 63 6f 72 65 2b 34  |core=its_score+4|
00011550  3b 0a 20 20 20 20 20 20  69 66 20 28 69 6e 64 65  |;.      if (inde|
00011560  66 5f 74 79 70 65 20 26  20 4c 49 54 5f 42 49 54  |f_type & LIT_BIT|
00011570  20 7e 3d 30 20 20 26 26  20 20 6f 62 6a 20 68 61  | ~=0  &&  obj ha|
00011580  73 20 6c 69 67 68 74 29  0a 20 20 20 20 20 20 20  |s light).       |
00011590  20 20 20 69 74 73 5f 73  63 6f 72 65 3d 69 74 73  |   its_score=its|
000115a0  5f 73 63 6f 72 65 2b 34  3b 0a 20 20 20 20 20 20  |_score+4;.      |
000115b0  69 66 20 28 69 6e 64 65  66 5f 74 79 70 65 20 26  |if (indef_type &|
000115c0  20 55 4e 4c 49 54 5f 42  49 54 20 7e 3d 30 20 20  | UNLIT_BIT ~=0  |
000115d0  26 26 20 20 6f 62 6a 20  68 61 73 6e 74 20 6c 69  |&&  obj hasnt li|
000115e0  67 68 74 29 0a 20 20 20  20 20 20 20 20 20 20 69  |ght).          i|
000115f0  74 73 5f 73 63 6f 72 65  3d 69 74 73 5f 73 63 6f  |ts_score=its_sco|
00011600  72 65 2b 34 3b 0a 20 20  20 20 20 20 69 66 20 28  |re+4;.      if (|
00011610  69 6e 64 65 66 5f 74 79  70 65 20 26 20 49 54 53  |indef_type & ITS|
00011620  5f 42 49 54 20 7e 3d 30  20 20 26 26 20 20 69 74  |_BIT ~=0  &&  it|
00011630  73 5f 6f 77 6e 65 72 3d  3d 69 74 6f 62 6a 29 0a  |s_owner==itobj).|
00011640  20 20 20 20 20 20 20 20  20 20 69 74 73 5f 73 63  |          its_sc|
00011650  6f 72 65 3d 69 74 73 5f  73 63 6f 72 65 2b 34 3b  |ore=its_score+4;|
00011660  0a 20 20 20 20 20 20 69  66 20 28 69 6e 64 65 66  |.      if (indef|
00011670  5f 74 79 70 65 20 26 20  48 49 53 5f 42 49 54 20  |_type & HIS_BIT |
00011680  7e 3d 30 20 20 26 26 20  20 69 74 73 5f 6f 77 6e  |~=0  &&  its_own|
00011690  65 72 20 68 61 73 20 61  6e 69 6d 61 74 65 0a 20  |er has animate. |
000116a0  20 20 20 20 20 20 20 20  20 26 26 20 47 65 74 47  |         && GetG|
000116b0  65 6e 64 65 72 28 69 74  73 5f 6f 77 6e 65 72 29  |ender(its_owner)|
000116c0  3d 3d 31 29 0a 20 20 20  20 20 20 20 20 20 20 69  |==1).          i|
000116d0  74 73 5f 73 63 6f 72 65  3d 69 74 73 5f 73 63 6f  |ts_score=its_sco|
000116e0  72 65 2b 34 3b 0a 0a 20  20 20 20 20 20 69 66 20  |re+4;..      if |
000116f0  28 69 74 73 5f 73 63 6f  72 65 20 3c 20 74 68 72  |(its_score < thr|
00011700  65 73 68 6f 6c 64 29 20  6d 61 74 63 68 5f 6c 69  |eshold) match_li|
00011710  73 74 2d 2d 3e 69 3d 2d  31 3b 0a 20 20 20 20 20  |st-->i=-1;.     |
00011720  20 65 6c 73 65 0a 20 20  20 20 20 20 7b 20 20 20  | else.      {   |
00011730  6d 61 74 63 68 5f 63 6c  61 73 73 65 73 2d 2d 3e  |match_classes-->|
00011740  69 3d 69 74 73 5f 73 63  6f 72 65 3b 0a 20 20 20  |i=its_score;.   |
00011750  20 20 20 20 20 20 20 69  66 20 28 70 61 72 73 65  |       if (parse|
00011760  72 5f 74 72 61 63 65 20  3e 3d 20 34 29 0a 20 20  |r_trace >= 4).  |
00011770  20 20 20 20 20 20 20 20  7b 20 20 20 70 72 69 6e  |        {   prin|
00011780  74 20 22 20 20 20 22 3b  20 43 44 65 66 41 72 74  |t "   "; CDefArt|
00011790  28 6d 61 74 63 68 5f 6c  69 73 74 2d 2d 3e 69 29  |(match_list-->i)|
000117a0  3b 0a 20 20 20 20 20 20  20 20 20 20 20 20 20 20  |;.              |
000117b0  70 72 69 6e 74 20 22 20  28 22 2c 20 6d 61 74 63  |print " (", matc|
000117c0  68 5f 6c 69 73 74 2d 2d  3e 69 2c 20 22 29 20 69  |h_list-->i, ") i|
000117d0  6e 20 22 3b 20 44 65 66  41 72 74 28 69 74 73 5f  |n "; DefArt(its_|
000117e0  6f 77 6e 65 72 29 3b 0a  20 20 20 20 20 20 20 20  |owner);.        |
000117f0  20 20 20 20 20 20 70 72  69 6e 74 20 22 20 73 63  |      print " sc|
00011800  6f 72 65 73 20 22 2c 69  74 73 5f 73 63 6f 72 65  |ores ",its_score|
00011810  2c 20 22 5e 22 3b 0a 20  20 20 20 20 20 20 20 20  |, "^";.         |
00011820  20 7d 0a 20 20 20 20 20  20 7d 0a 20 20 7d 0a 20  | }.      }.  }. |
00011830  20 6e 75 6d 62 65 72 5f  6f 66 5f 63 6c 61 73 73  | number_of_class|
00011840  65 73 3d 32 3b 0a 5d 3b  0a 0a 21 20 2d 2d 2d 2d  |es=2;.];..! ----|
00011850  2d 2d 2d 2d 2d 2d 2d 2d  2d 2d 2d 2d 2d 2d 2d 2d  |----------------|
*
00011890  2d 2d 2d 2d 2d 2d 2d 2d  0a 21 20 20 42 65 73 74  |--------.!  Best|
000118a0  47 75 65 73 73 20 6d 61  6b 65 73 20 74 68 65 20  |Guess makes the |
000118b0  62 65 73 74 20 67 75 65  73 73 20 69 74 20 63 61  |best guess it ca|
000118c0  6e 20 6f 75 74 20 6f 66  20 74 68 65 20 6d 61 74  |n out of the mat|
000118d0  63 68 20 6c 69 73 74 2c  20 61 73 73 75 6d 69 6e  |ch list, assumin|
000118e0  67 20 74 68 61 74 0a 21  20 20 65 76 65 72 79 74  |g that.!  everyt|
000118f0  68 69 6e 67 20 69 6e 20  74 68 65 20 6d 61 74 63  |hing in the matc|
00011900  68 20 6c 69 73 74 20 69  73 20 74 65 78 74 75 61  |h list is textua|
00011910  6c 6c 79 20 61 73 20 67  6f 6f 64 20 61 73 20 65  |lly as good as e|
00011920  76 65 72 79 74 68 69 6e  67 20 65 6c 73 65 3b 0a  |verything else;.|
00011930  21 20 20 68 6f 77 65 76  65 72 20 69 74 20 69 67  |!  however it ig|
00011940  6e 6f 72 65 73 20 69 74  65 6d 73 20 6d 61 72 6b  |nores items mark|
00011950  65 64 20 61 73 20 2d 31  2c 20 61 6e 64 20 73 6f  |ed as -1, and so|
00011960  20 6d 61 72 6b 73 20 61  6e 79 74 68 69 6e 67 20  | marks anything |
00011970  69 74 20 63 68 6f 6f 73  65 73 2e 0a 21 20 20 49  |it chooses..!  I|
00011980  74 20 72 65 74 75 72 6e  73 20 2d 31 20 69 66 20  |t returns -1 if |
00011990  74 68 65 72 65 20 61 72  65 20 6e 6f 20 70 6f 73  |there are no pos|
000119a0  73 69 62 6c 65 20 63 68  6f 69 63 65 73 2e 0a 21  |sible choices..!|
000119b0  20 2d 2d 2d 2d 2d 2d 2d  2d 2d 2d 2d 2d 2d 2d 2d  | ---------------|
000119c0  2d 2d 2d 2d 2d 2d 2d 2d  2d 2d 2d 2d 2d 2d 2d 2d  |----------------|
*
000119f0  2d 2d 2d 2d 2d 2d 2d 2d  2d 2d 2d 2d 2d 0a 0a 5b  |-------------..[|
00011a00  20 42 65 73 74 47 75 65  73 73 20 20 65 61 72 6c  | BestGuess  earl|
00011a10  69 65 73 74 20 69 74 73  5f 73 63 6f 72 65 20 62  |iest its_score b|
00011a20  65 73 74 20 69 3b 0a 0a  20 20 69 66 20 28 6e 75  |est i;..  if (nu|
00011a30  6d 62 65 72 5f 6f 66 5f  63 6c 61 73 73 65 73 3d  |mber_of_classes=|
00011a40  3d 31 29 20 53 63 6f 72  65 4d 61 74 63 68 4c 28  |=1) ScoreMatchL(|
00011a50  29 3b 0a 0a 20 20 65 61  72 6c 69 65 73 74 3d 30  |);..  earliest=0|
00011a60  3b 20 62 65 73 74 3d 2d  31 3b 0a 20 20 66 6f 72  |; best=-1;.  for|
00011a70  20 28 69 3d 30 3a 69 3c  6e 75 6d 62 65 72 5f 6d  | (i=0:i<number_m|
00011a80  61 74 63 68 65 64 3a 69  2b 2b 29 0a 20 20 7b 20  |atched:i++).  { |
00011a90  20 20 69 66 20 28 6d 61  74 63 68 5f 6c 69 73 74  |  if (match_list|
00011aa0  2d 2d 3e 69 20 3e 3d 20  30 29 0a 20 20 20 20 20  |-->i >= 0).     |
00011ab0  20 7b 20 20 20 69 74 73  5f 73 63 6f 72 65 3d 6d  | {   its_score=m|
00011ac0  61 74 63 68 5f 63 6c 61  73 73 65 73 2d 2d 3e 69  |atch_classes-->i|
00011ad0  3b 0a 20 20 20 20 20 20  20 20 20 20 69 66 20 28  |;.          if (|
00011ae0  69 74 73 5f 73 63 6f 72  65 3e 62 65 73 74 29 20  |its_score>best) |
00011af0  7b 20 62 65 73 74 3d 69  74 73 5f 73 63 6f 72 65  |{ best=its_score|
00011b00  3b 20 65 61 72 6c 69 65  73 74 3d 69 3b 20 7d 0a  |; earliest=i; }.|
00011b10  20 20 20 20 20 20 7d 0a  20 20 7d 0a 20 20 69 66  |      }.  }.  if|
00011b20  20 28 70 61 72 73 65 72  5f 74 72 61 63 65 3e 3d  | (parser_trace>=|
00011b30  34 29 0a 20 20 7b 20 20  20 69 66 20 28 62 65 73  |4).  {   if (bes|
00011b40  74 3c 30 29 0a 20 20 20  20 20 20 20 20 20 20 70  |t<0).          p|
00011b50  72 69 6e 74 20 22 20 20  20 42 65 73 74 20 67 75  |rint "   Best gu|
00011b60  65 73 73 20 72 61 6e 20  6f 75 74 20 6f 66 20 63  |ess ran out of c|
00011b70  68 6f 69 63 65 73 5e 22  3b 0a 20 20 20 20 20 20  |hoices^";.      |
00011b80  65 6c 73 65 0a 20 20 20  20 20 20 7b 20 20 20 70  |else.      {   p|
00011b90  72 69 6e 74 20 22 20 20  20 42 65 73 74 20 67 75  |rint "   Best gu|
00011ba0  65 73 73 20 22 3b 20 44  65 66 41 72 74 28 6d 61  |ess "; DefArt(ma|
00011bb0  74 63 68 5f 6c 69 73 74  2d 2d 3e 65 61 72 6c 69  |tch_list-->earli|
00011bc0  65 73 74 29 3b 0a 20 20  20 20 20 20 20 20 20 20  |est);.          |
00011bd0  70 72 69 6e 74 20 20 22  20 28 22 2c 20 6d 61 74  |print  " (", mat|
00011be0  63 68 5f 6c 69 73 74 2d  2d 3e 65 61 72 6c 69 65  |ch_list-->earlie|
00011bf0  73 74 2c 20 22 29 5e 22  3b 0a 20 20 20 20 20 20  |st, ")^";.      |
00011c00  7d 0a 20 20 7d 0a 20 20  69 66 20 28 62 65 73 74  |}.  }.  if (best|
00011c10  3c 30 29 20 72 65 74 75  72 6e 20 2d 31 3b 0a 20  |<0) return -1;. |
00011c20  20 69 3d 6d 61 74 63 68  5f 6c 69 73 74 2d 2d 3e  | i=match_list-->|
00011c30  65 61 72 6c 69 65 73 74  3b 0a 20 20 6d 61 74 63  |earliest;.  matc|
00011c40  68 5f 6c 69 73 74 2d 2d  3e 65 61 72 6c 69 65 73  |h_list-->earlies|
00011c50  74 3d 2d 31 3b 0a 20 20  72 65 74 75 72 6e 20 69  |t=-1;.  return i|
00011c60  3b 0a 5d 3b 0a 0a 21 20  2d 2d 2d 2d 2d 2d 2d 2d  |;.];..! --------|
00011c70  2d 2d 2d 2d 2d 2d 2d 2d  2d 2d 2d 2d 2d 2d 2d 2d  |----------------|
*
00011cb0  2d 2d 2d 2d 0a 21 20 20  49 64 65 6e 74 69 63 61  |----.!  Identica|
00011cc0  6c 20 64 65 63 69 64 65  73 20 77 68 65 74 68 65  |l decides whethe|
00011cd0  72 20 6f 72 20 6e 6f 74  20 74 77 6f 20 6f 62 6a  |r or not two obj|
00011ce0  65 63 74 73 20 63 61 6e  20 62 65 20 64 69 73 74  |ects can be dist|
00011cf0  69 6e 67 75 69 73 68 65  64 20 66 72 6f 6d 0a 21  |inguished from.!|
00011d00  20 20 65 61 63 68 20 6f  74 68 65 72 20 62 79 20  |  each other by |
00011d10  61 6e 79 74 68 69 6e 67  20 74 68 65 20 70 6c 61  |anything the pla|
00011d20  79 65 72 20 63 61 6e 20  74 79 70 65 2e 20 20 49  |yer can type.  I|
00011d30  66 20 6e 6f 74 2c 20 69  74 20 72 65 74 75 72 6e  |f not, it return|
00011d40  73 20 74 72 75 65 2e 0a  21 20 2d 2d 2d 2d 2d 2d  |s true..! ------|
00011d50  2d 2d 2d 2d 2d 2d 2d 2d  2d 2d 2d 2d 2d 2d 2d 2d  |----------------|
*
00011d90  2d 2d 2d 2d 2d 2d 0a 0a  5b 20 49 64 65 6e 74 69  |------..[ Identi|
00011da0  63 61 6c 20 6f 31 20 6f  32 20 70 31 20 70 32 20  |cal o1 o2 p1 p2 |
00011db0  6e 31 20 6e 32 20 69 20  6a 20 66 6c 61 67 3b 0a  |n1 n2 i j flag;.|
00011dc0  0a 21 20 20 70 72 69 6e  74 20 22 49 64 20 6f 6e  |.!  print "Id on|
00011dd0  20 22 2c 20 6f 31 2c 20  22 20 28 22 2c 20 6f 62  | ", o1, " (", ob|
00011de0  6a 65 63 74 20 6f 31 2c  20 22 29 20 61 6e 64 20  |ject o1, ") and |
00011df0  22 2c 20 6f 32 2c 20 22  20 28 22 2c 20 6f 62 6a  |", o2, " (", obj|
00011e00  65 63 74 20 6f 32 2c 20  22 29 5e 22 3b 0a 0a 20  |ect o2, ")^";.. |
00011e10  20 69 66 20 28 6f 31 3d  3d 6f 32 29 20 72 74 72  | if (o1==o2) rtr|
00011e20  75 65 3b 20 20 21 20 54  68 69 73 20 73 68 6f 75  |ue;  ! This shou|
00011e30  6c 64 20 6e 65 76 65 72  20 68 61 70 70 65 6e 2c  |ld never happen,|
00011e40  20 62 75 74 20 74 6f 20  62 65 20 6f 6e 20 74 68  | but to be on th|
00011e50  65 20 73 61 66 65 20 73  69 64 65 0a 20 20 69 66  |e safe side.  if|
00011e60  20 28 6f 31 3d 3d 30 20  7c 7c 20 6f 32 3d 3d 30  | (o1==0 || o2==0|
00011e70  29 20 72 66 61 6c 73 65  3b 20 20 21 20 53 69 6d  |) rfalse;  ! Sim|
00011e80  69 6c 61 72 6c 79 0a 20  20 69 66 20 28 70 61 72  |ilarly.  if (par|
00011e90  65 6e 74 28 6f 31 29 3d  3d 63 6f 6d 70 61 73 73  |ent(o1)==compass|
00011ea0  20 7c 7c 20 70 61 72 65  6e 74 28 6f 32 29 3d 3d  | || parent(o2)==|
00011eb0  63 6f 6d 70 61 73 73 29  20 72 66 61 6c 73 65 3b  |compass) rfalse;|
00011ec0  20 21 20 53 61 76 65 73  20 74 69 6d 65 0a 0a 21  | ! Saves time..!|
00011ed0  20 20 57 68 61 74 20 63  6f 6d 70 6c 69 63 61 74  |  What complicat|
00011ee0  65 73 20 74 68 69 6e 67  73 20 69 73 20 74 68 61  |es things is tha|
00011ef0  74 20 6f 31 20 6f 72 20  6f 32 20 6d 69 67 68 74  |t o1 or o2 might|
00011f00  20 68 61 76 65 20 61 20  70 61 72 73 69 6e 67 20  | have a parsing |
00011f10  72 6f 75 74 69 6e 65 2c  0a 21 20 20 73 6f 20 74  |routine,.!  so t|
00011f20  68 65 20 70 61 72 73 65  72 20 63 61 6e 27 74 20  |he parser can't |
00011f30  6b 6e 6f 77 20 66 72 6f  6d 20 68 65 72 65 20 77  |know from here w|
00011f40  68 65 74 68 65 72 20 74  68 65 79 20 61 72 65 20  |hether they are |
00011f50  6f 72 20 61 72 65 6e 27  74 20 74 68 65 20 73 61  |or aren't the sa|
00011f60  6d 65 2e 0a 21 20 20 49  66 20 74 68 65 79 20 68  |me..!  If they h|
00011f70  61 76 65 20 64 69 66 66  65 72 65 6e 74 20 70 61  |ave different pa|
00011f80  72 73 69 6e 67 20 72 6f  75 74 69 6e 65 73 2c 20  |rsing routines, |
00011f90  77 65 20 73 69 6d 70 6c  79 20 61 73 73 75 6d 65  |we simply assume|
00011fa0  20 74 68 65 79 27 72 65  0a 21 20 20 64 69 66 66  | they're.!  diff|
00011fb0  65 72 65 6e 74 2e 20 20  49 66 20 74 68 65 79 20  |erent.  If they |
00011fc0  68 61 76 65 20 74 68 65  20 73 61 6d 65 20 72 6f  |have the same ro|
00011fd0  75 74 69 6e 65 20 28 77  68 69 63 68 20 74 68 65  |utine (which the|
00011fe0  79 20 70 72 6f 62 61 62  6c 79 20 67 6f 74 20 66  |y probably got f|
00011ff0  72 6f 6d 0a 21 20 20 61  20 63 6c 61 73 73 20 64  |rom.!  a class d|
00012000  65 66 69 6e 69 74 69 6f  6e 29 20 74 68 65 6e 20  |efinition) then |
00012010  74 68 65 20 64 65 63 69  73 69 6f 6e 20 70 72 6f  |the decision pro|
00012020  63 65 73 73 20 69 73 20  61 73 20 66 6f 6c 6c 6f  |cess is as follo|
00012030  77 73 3a 0a 21 0a 21 20  20 20 20 20 74 68 65 20  |ws:.!.!     the |
00012040  72 6f 75 74 69 6e 65 20  69 73 20 63 61 6c 6c 65  |routine is calle|
00012050  64 20 28 77 69 74 68 20  73 65 6c 66 20 62 65 69  |d (with self bei|
00012060  6e 67 20 6f 31 2c 20 6e  6f 74 20 74 68 61 74 20  |ng o1, not that |
00012070  69 74 20 6d 61 74 74 65  72 73 29 0a 21 20 20 20  |it matters).!   |
00012080  20 20 20 20 77 69 74 68  20 6e 6f 75 6e 20 61 6e  |    with noun an|
00012090  64 20 73 65 63 6f 6e 64  20 62 65 69 6e 67 20 73  |d second being s|
000120a0  65 74 20 74 6f 20 6f 31  20 61 6e 64 20 6f 32 2c  |et to o1 and o2,|
000120b0  20 61 6e 64 20 61 63 74  69 6f 6e 20 62 65 69 6e  | and action bein|
000120c0  67 20 73 65 74 0a 21 20  20 20 20 20 20 20 74 6f  |g set.!       to|
000120d0  20 74 68 65 20 66 61 6b  65 20 61 63 74 69 6f 6e  | the fake action|
000120e0  20 54 68 65 53 61 6d 65  2e 20 20 49 66 20 69 74  | TheSame.  If it|
000120f0  20 72 65 74 75 72 6e 73  20 2d 31 2c 20 74 68 65  | returns -1, the|
00012100  79 20 61 72 65 20 66 6f  75 6e 64 0a 21 20 20 20  |y are found.!   |
00012110  20 20 20 20 69 64 65 6e  74 69 63 61 6c 3b 20 69  |    identical; i|
00012120  66 20 2d 32 2c 20 64 69  66 66 65 72 65 6e 74 3b  |f -2, different;|
00012130  20 61 6e 64 20 69 66 20  3e 3d 30 2c 20 74 68 65  | and if >=0, the|
00012140  6e 20 74 68 65 20 75 73  75 61 6c 20 6d 65 74 68  |n the usual meth|
00012150  6f 64 0a 21 20 20 20 20  20 20 20 69 73 20 75 73  |od.!       is us|
00012160  65 64 20 69 6e 73 74 65  61 64 2e 0a 0a 20 20 69  |ed instead...  i|
00012170  66 20 28 6f 31 2e 70 61  72 73 65 5f 6e 61 6d 65  |f (o1.parse_name|
00012180  7e 3d 30 20 7c 7c 20 6f  32 2e 70 61 72 73 65 5f  |~=0 || o2.parse_|
00012190  6e 61 6d 65 7e 3d 30 29  0a 20 20 7b 20 20 20 69  |name~=0).  {   i|
000121a0  66 20 28 6f 31 2e 70 61  72 73 65 5f 6e 61 6d 65  |f (o1.parse_name|
000121b0  20 7e 3d 20 6f 32 2e 70  61 72 73 65 5f 6e 61 6d  | ~= o2.parse_nam|
000121c0  65 29 20 72 66 61 6c 73  65 3b 0a 20 20 20 20 20  |e) rfalse;.     |
000121d0  20 70 61 72 73 65 72 5f  61 63 74 69 6f 6e 3d 23  | parser_action=#|
000121e0  23 54 68 65 53 61 6d 65  3b 20 70 61 72 73 65 72  |#TheSame; parser|
000121f0  5f 6f 6e 65 3d 6f 31 3b  20 70 61 72 73 65 72 5f  |_one=o1; parser_|
00012200  74 77 6f 3d 6f 32 3b 0a  20 20 20 20 20 20 6a 3d  |two=o2;.      j=|
00012210  77 6e 3b 20 69 3d 52 75  6e 52 6f 75 74 69 6e 65  |wn; i=RunRoutine|
00012220  73 28 6f 31 2c 70 61 72  73 65 5f 6e 61 6d 65 29  |s(o1,parse_name)|
00012230  3b 20 77 6e 3d 6a 3b 0a  20 20 20 20 20 20 69 66  |; wn=j;.      if|
00012240  20 28 69 3d 3d 2d 31 29  20 72 74 72 75 65 3b 20  | (i==-1) rtrue; |
00012250  69 66 20 28 69 3d 3d 2d  32 29 20 72 66 61 6c 73  |if (i==-2) rfals|
00012260  65 3b 0a 20 20 7d 0a 0a  21 20 20 54 68 69 73 20  |e;.  }..!  This |
00012270  69 73 20 74 68 65 20 64  65 66 61 75 6c 74 20 61  |is the default a|
00012280  6c 67 6f 72 69 74 68 6d  3a 20 64 6f 20 74 68 65  |lgorithm: do the|
00012290  79 20 68 61 76 65 20 74  68 65 20 73 61 6d 65 20  |y have the same |
000122a0  77 6f 72 64 73 20 69 6e  20 74 68 65 69 72 0a 21  |words in their.!|
000122b0  20 20 22 6e 61 6d 65 22  20 28 69 2e 65 2e 20 70  |  "name" (i.e. p|
000122c0  72 6f 70 65 72 74 79 20  6e 6f 2e 20 31 29 20 70  |roperty no. 1) p|
000122d0  72 6f 70 65 72 74 69 65  73 2e 20 20 28 4e 6f 74  |roperties.  (Not|
000122e0  65 20 74 68 61 74 20 74  68 65 20 66 6f 6c 6c 6f  |e that the follo|
000122f0  77 69 6e 67 20 61 6c 6c  6f 77 73 0a 21 20 20 66  |wing allows.!  f|
00012300  6f 72 20 72 65 70 65 61  74 65 64 20 77 6f 72 64  |or repeated word|
00012310  73 20 61 6e 64 20 77 6f  72 64 73 20 69 6e 20 64  |s and words in d|
00012320  69 66 66 65 72 65 6e 74  20 6f 72 64 65 72 73 2e  |ifferent orders.|
00012330  29 0a 0a 20 20 70 31 20  3d 20 6f 31 2e 26 31 3b  |)..  p1 = o1.&1;|
00012340  20 6e 31 20 3d 20 28 6f  31 2e 23 31 29 2f 32 3b  | n1 = (o1.#1)/2;|
00012350  0a 20 20 70 32 20 3d 20  6f 32 2e 26 31 3b 20 6e  |.  p2 = o2.&1; n|
00012360  32 20 3d 20 28 6f 32 2e  23 31 29 2f 32 3b 0a 0a  |2 = (o2.#1)/2;..|
00012370  21 20 20 66 6f 72 20 28  69 3d 30 3a 69 3c 6e 31  |!  for (i=0:i<n1|
00012380  3a 69 2b 2b 29 20 7b 20  70 72 69 6e 74 5f 61 64  |:i++) { print_ad|
00012390  64 72 20 70 31 2d 2d 3e  69 3b 20 70 72 69 6e 74  |dr p1-->i; print|
000123a0  20 22 20 22 3b 20 7d 20  6e 65 77 5f 6c 69 6e 65  | " "; } new_line|
000123b0  3b 0a 21 20 20 66 6f 72  20 28 69 3d 30 3a 69 3c  |;.!  for (i=0:i<|
000123c0  6e 32 3a 69 2b 2b 29 20  7b 20 70 72 69 6e 74 5f  |n2:i++) { print_|
000123d0  61 64 64 72 20 70 32 2d  2d 3e 69 3b 20 70 72 69  |addr p2-->i; pri|
000123e0  6e 74 20 22 20 22 3b 20  7d 20 6e 65 77 5f 6c 69  |nt " "; } new_li|
000123f0  6e 65 3b 0a 0a 20 20 66  6f 72 20 28 69 3d 30 3a  |ne;..  for (i=0:|
00012400  69 3c 6e 31 3a 69 2b 2b  29 0a 20 20 7b 20 20 20  |i<n1:i++).  {   |
00012410  66 6c 61 67 3d 30 3b 0a  20 20 20 20 20 20 66 6f  |flag=0;.      fo|
00012420  72 20 28 6a 3d 30 3a 6a  3c 6e 32 3a 6a 2b 2b 29  |r (j=0:j<n2:j++)|
00012430  0a 20 20 20 20 20 20 20  20 20 20 69 66 20 28 70  |.          if (p|
00012440  31 2d 2d 3e 69 20 3d 3d  20 70 32 2d 2d 3e 6a 29  |1-->i == p2-->j)|
00012450  20 66 6c 61 67 3d 31 3b  0a 20 20 20 20 20 20 69  | flag=1;.      i|
00012460  66 20 28 66 6c 61 67 3d  3d 30 29 20 72 66 61 6c  |f (flag==0) rfal|
00012470  73 65 3b 0a 20 20 7d 0a  0a 20 20 66 6f 72 20 28  |se;.  }..  for (|
00012480  6a 3d 30 3a 6a 3c 6e 32  3a 6a 2b 2b 29 0a 20 20  |j=0:j<n2:j++).  |
00012490  7b 20 20 20 66 6c 61 67  3d 30 3b 0a 20 20 20 20  |{   flag=0;.    |
000124a0  20 20 66 6f 72 20 28 69  3d 30 3a 69 3c 6e 31 3a  |  for (i=0:i<n1:|
000124b0  69 2b 2b 29 0a 20 20 20  20 20 20 20 20 20 20 69  |i++).          i|
000124c0  66 20 28 70 31 2d 2d 3e  69 20 3d 3d 20 70 32 2d  |f (p1-->i == p2-|
000124d0  2d 3e 6a 29 20 66 6c 61  67 3d 31 3b 0a 20 20 20  |->j) flag=1;.   |
000124e0  20 20 20 69 66 20 28 66  6c 61 67 3d 3d 30 29 20  |   if (flag==0) |
000124f0  72 66 61 6c 73 65 3b 0a  20 20 7d 0a 0a 21 20 20  |rfalse;.  }..!  |
00012500  70 72 69 6e 74 20 22 57  68 69 63 68 20 61 72 65  |print "Which are|
00012510  20 69 64 65 6e 74 69 63  61 6c 21 5e 22 3b 0a 20  | identical!^";. |
00012520  20 72 74 72 75 65 3b 0a  5d 3b 0a 0a 21 20 2d 2d  | rtrue;.];..! --|
00012530  2d 2d 2d 2d 2d 2d 2d 2d  2d 2d 2d 2d 2d 2d 2d 2d  |----------------|
*
00012570  2d 2d 2d 2d 2d 2d 2d 2d  2d 2d 0a 21 20 20 50 72  |----------.!  Pr|
00012580  69 6e 74 43 6f 6d 6d 61  6e 64 20 72 65 63 6f 6e  |intCommand recon|
00012590  73 74 72 75 63 74 73 20  74 68 65 20 63 6f 6d 6d  |structs the comm|
000125a0  61 6e 64 20 61 73 20 69  74 20 70 72 65 73 65 6e  |and as it presen|
000125b0  74 6c 79 20 72 65 61 64  73 2c 20 66 72 6f 6d 0a  |tly reads, from.|
000125c0  21 20 20 74 68 65 20 70  61 74 74 65 72 6e 20 77  |!  the pattern w|
000125d0  68 69 63 68 20 68 61 73  20 62 65 65 6e 20 62 75  |hich has been bu|
000125e0  69 6c 74 20 75 70 0a 21  0a 21 20 20 49 66 20 66  |ilt up.!.!  If f|
000125f0  72 6f 6d 20 69 73 20 30  2c 20 69 74 20 73 74 61  |rom is 0, it sta|
00012600  72 74 73 20 77 69 74 68  20 74 68 65 20 76 65 72  |rts with the ver|
00012610  62 3a 20 74 68 65 6e 20  69 74 20 67 6f 65 73 20  |b: then it goes |
00012620  74 68 72 6f 75 67 68 20  74 68 65 20 70 61 74 74  |through the patt|
00012630  65 72 6e 2e 0a 21 20 20  54 68 65 20 6f 74 68 65  |ern..!  The othe|
00012640  72 20 70 61 72 61 6d 65  74 65 72 20 69 73 20 22  |r parameter is "|
00012650  65 6d 70 74 79 66 22 20  2d 20 61 20 66 6c 61 67  |emptyf" - a flag|
00012660  3a 20 69 66 20 30 2c 20  69 74 20 67 6f 65 73 20  |: if 0, it goes |
00012670  75 70 20 74 6f 20 70 63  6f 75 6e 74 3a 0a 21 20  |up to pcount:.! |
00012680  20 69 66 20 31 2c 20 69  74 20 67 6f 65 73 20 75  | if 1, it goes u|
00012690  70 20 74 6f 20 70 63 6f  75 6e 74 2d 31 2e 0a 21  |p to pcount-1..!|
000126a0  0a 21 20 20 4e 6f 74 65  20 74 68 61 74 20 76 65  |.!  Note that ve|
000126b0  72 62 73 20 61 6e 64 20  70 72 65 70 6f 73 69 74  |rbs and preposit|
000126c0  69 6f 6e 73 20 61 72 65  20 70 72 69 6e 74 65 64  |ions are printed|
000126d0  20 6f 75 74 20 6f 66 20  74 68 65 20 64 69 63 74  | out of the dict|
000126e0  69 6f 6e 61 72 79 3a 0a  21 20 20 61 6e 64 20 74  |ionary:.!  and t|
000126f0  68 61 74 20 73 69 6e 63  65 20 74 68 65 20 64 69  |hat since the di|
00012700  63 74 69 6f 6e 61 72 79  20 6d 61 79 20 6f 6e 6c  |ctionary may onl|
00012710  79 20 70 72 65 73 65 72  76 65 20 74 68 65 20 66  |y preserve the f|
00012720  69 72 73 74 20 73 69 78  20 63 68 61 72 61 63 74  |irst six charact|
00012730  65 72 73 0a 21 20 20 6f  66 20 61 20 77 6f 72 64  |ers.!  of a word|
00012740  20 28 69 6e 20 61 20 56  33 20 67 61 6d 65 29 2c  | (in a V3 game),|
00012750  20 77 65 20 68 61 76 65  20 74 6f 20 68 61 6e 64  | we have to hand|
00012760  2d 63 6f 64 65 20 74 68  65 20 6c 6f 6e 67 65 72  |-code the longer|
00012770  20 77 6f 72 64 73 20 6e  65 65 64 65 64 2e 0a 21  | words needed..!|
00012780  0a 21 20 20 28 52 65 63  61 6c 6c 20 74 68 61 74  |.!  (Recall that|
00012790  20 70 61 74 74 65 72 6e  20 65 6e 74 72 69 65 73  | pattern entries|
000127a0  20 61 72 65 20 30 20 66  6f 72 20 22 6d 75 6c 74  | are 0 for "mult|
000127b0  69 70 6c 65 20 6f 62 6a  65 63 74 22 2c 20 31 20  |iple object", 1 |
000127c0  66 6f 72 20 22 73 70 65  63 69 61 6c 0a 21 20 20  |for "special.!  |
000127d0  77 6f 72 64 22 2c 20 32  20 74 6f 20 39 39 39 20  |word", 2 to 999 |
000127e0  61 72 65 20 6f 62 6a 65  63 74 20 6e 75 6d 62 65  |are object numbe|
000127f0  72 73 20 61 6e 64 20 31  30 30 30 2b 6e 20 6d 65  |rs and 1000+n me|
00012800  61 6e 73 20 74 68 65 20  70 72 65 70 6f 73 69 74  |ans the preposit|
00012810  69 6f 6e 20 6e 29 0a 21  20 2d 2d 2d 2d 2d 2d 2d  |ion n).! -------|
00012820  2d 2d 2d 2d 2d 2d 2d 2d  2d 2d 2d 2d 2d 2d 2d 2d  |----------------|
*
00012860  2d 2d 2d 2d 2d 0a 0a 5b  20 50 72 69 6e 74 43 6f  |-----..[ PrintCo|
00012870  6d 6d 61 6e 64 20 66 72  6f 6d 20 65 6d 70 74 79  |mmand from empty|
00012880  66 20 69 20 6a 20 6b 20  66 3b 0a 20 20 69 66 20  |f i j k f;.  if |
00012890  66 72 6f 6d 3d 3d 30 0a  20 20 7b 20 20 20 69 3d  |from==0.  {   i=|
000128a0  76 65 72 62 5f 77 6f 72  64 3b 20 66 72 6f 6d 3d  |verb_word; from=|
000128b0  31 3b 20 66 3d 31 3b 0a  23 49 46 56 33 3b 0a 20  |1; f=1;.#IFV3;. |
000128c0  20 20 20 20 20 69 66 20  28 69 3d 3d 27 69 6e 76  |     if (i=='inv|
000128d0  65 6e 74 6f 72 79 27 29  20 7b 20 70 72 69 6e 74  |entory') { print|
000128e0  20 22 74 61 6b 65 20 61  6e 20 69 6e 76 65 6e 74  | "take an invent|
000128f0  6f 72 79 22 3b 20 6a 75  6d 70 20 56 65 72 62 50  |ory"; jump VerbP|
00012900  72 69 6e 74 65 64 3b 20  7d 0a 20 20 20 20 20 20  |rinted; }.      |
00012910  69 66 20 28 69 3d 3d 27  65 78 61 6d 69 6e 65 27  |if (i=='examine'|
00012920  29 20 20 20 7b 20 70 72  69 6e 74 20 22 65 78 61  |)   { print "exa|
00012930  6d 69 6e 65 22 3b 20 20  20 20 20 20 20 20 20 20  |mine";          |
00012940  20 6a 75 6d 70 20 56 65  72 62 50 72 69 6e 74 65  | jump VerbPrinte|
00012950  64 3b 20 7d 0a 20 20 20  20 20 20 69 66 20 28 69  |d; }.      if (i|
00012960  3d 3d 27 64 69 73 63 61  72 64 27 29 20 20 20 7b  |=='discard')   {|
00012970  20 70 72 69 6e 74 20 22  64 69 73 63 61 72 64 22  | print "discard"|
00012980  3b 20 20 20 20 20 20 20  20 20 20 20 6a 75 6d 70  |;           jump|
00012990  20 56 65 72 62 50 72 69  6e 74 65 64 3b 20 7d 0a  | VerbPrinted; }.|
000129a0  20 20 20 20 20 20 69 66  20 28 69 3d 3d 27 73 77  |      if (i=='sw|
000129b0  61 6c 6c 6f 77 27 29 20  20 20 7b 20 70 72 69 6e  |allow')   { prin|
000129c0  74 20 22 73 77 61 6c 6c  6f 77 22 3b 20 20 20 20  |t "swallow";    |
000129d0  20 20 20 20 20 20 20 6a  75 6d 70 20 56 65 72 62  |       jump Verb|
000129e0  50 72 69 6e 74 65 64 3b  20 7d 0a 20 20 20 20 20  |Printed; }.     |
000129f0  20 69 66 20 28 69 3d 3d  27 65 6d 62 72 61 63 65  | if (i=='embrace|
00012a00  27 29 20 20 20 7b 20 70  72 69 6e 74 20 22 65 6d  |')   { print "em|
00012a10  62 72 61 63 65 22 3b 20  20 20 20 20 20 20 20 20  |brace";         |
00012a20  20 20 6a 75 6d 70 20 56  65 72 62 50 72 69 6e 74  |  jump VerbPrint|
00012a30  65 64 3b 20 7d 0a 20 20  20 20 20 20 69 66 20 28  |ed; }.      if (|
00012a40  69 3d 3d 27 73 71 75 65  65 7a 65 27 29 20 20 20  |i=='squeeze')   |
00012a50  7b 20 70 72 69 6e 74 20  22 73 71 75 65 65 7a 65  |{ print "squeeze|
00012a60  22 3b 20 20 20 20 20 20  20 20 20 20 20 6a 75 6d  |";           jum|
00012a70  70 20 56 65 72 62 50 72  69 6e 74 65 64 3b 20 7d  |p VerbPrinted; }|
00012a80  0a 20 20 20 20 20 20 69  66 20 28 69 3d 3d 27 70  |.      if (i=='p|
00012a90  75 72 63 68 61 73 65 27  29 20 20 7b 20 70 72 69  |urchase')  { pri|
00012aa0  6e 74 20 22 70 75 72 63  68 61 73 65 22 3b 20 20  |nt "purchase";  |
00012ab0  20 20 20 20 20 20 20 20  6a 75 6d 70 20 56 65 72  |        jump Ver|
00012ac0  62 50 72 69 6e 74 65 64  3b 20 7d 0a 20 20 20 20  |bPrinted; }.    |
00012ad0  20 20 69 66 20 28 69 3d  3d 27 75 6e 73 63 72 65  |  if (i=='unscre|
00012ae0  77 27 29 20 20 20 7b 20  70 72 69 6e 74 20 22 75  |w')   { print "u|
00012af0  6e 73 63 72 65 77 22 3b  20 20 20 20 20 20 20 20  |nscrew";        |
00012b00  20 20 20 6a 75 6d 70 20  56 65 72 62 50 72 69 6e  |   jump VerbPrin|
00012b10  74 65 64 3b 20 7d 0a 20  20 20 20 20 20 69 66 20  |ted; }.      if |
00012b20  28 69 3d 3d 27 64 65 73  63 72 69 62 65 27 29 20  |(i=='describe') |
00012b30  20 7b 20 70 72 69 6e 74  20 22 64 65 73 63 72 69  | { print "descri|
00012b40  62 65 22 3b 20 20 20 20  20 20 20 20 20 20 6a 75  |be";          ju|
00012b50  6d 70 20 56 65 72 62 50  72 69 6e 74 65 64 3b 20  |mp VerbPrinted; |
00012b60  7d 0a 20 20 20 20 20 20  69 66 20 28 69 3d 3d 27  |}.      if (i=='|
00012b70  75 6e 63 6f 76 65 72 27  29 20 20 20 7b 20 70 72  |uncover')   { pr|
00012b80  69 6e 74 20 22 75 6e 63  6f 76 65 72 22 3b 20 20  |int "uncover";  |
00012b90  20 20 20 20 20 20 20 20  20 6a 75 6d 70 20 56 65  |         jump Ve|
00012ba0  72 62 50 72 69 6e 74 65  64 3b 20 7d 0a 20 20 20  |rbPrinted; }.   |
00012bb0  20 20 20 69 66 20 28 69  3d 3d 27 64 69 73 63 61  |   if (i=='disca|
00012bc0  72 64 27 29 20 20 20 7b  20 70 72 69 6e 74 20 22  |rd')   { print "|
00012bd0  64 69 73 63 61 72 64 22  3b 20 20 20 20 20 20 20  |discard";       |
00012be0  20 20 20 20 6a 75 6d 70  20 56 65 72 62 50 72 69  |    jump VerbPri|
00012bf0  6e 74 65 64 3b 20 7d 0a  20 20 20 20 20 20 69 66  |nted; }.      if|
00012c00  20 28 69 3d 3d 27 74 72  61 6e 73 66 65 72 27 29  | (i=='transfer')|
00012c10  20 20 7b 20 70 72 69 6e  74 20 22 74 72 61 6e 73  |  { print "trans|
00012c20  66 65 72 22 3b 20 20 20  20 20 20 20 20 20 20 6a  |fer";          j|
00012c30  75 6d 70 20 56 65 72 62  50 72 69 6e 74 65 64 3b  |ump VerbPrinted;|
00012c40  20 7d 0a 23 45 4e 44 49  46 3b 0a 20 20 20 20 20  | }.#ENDIF;.     |
00012c50  20 69 66 20 28 69 3d 3d  23 6e 24 6c 29 20 20 20  | if (i==#n$l)   |
00012c60  20 20 20 20 20 20 7b 20  70 72 69 6e 74 20 22 6c  |      { print "l|
00012c70  6f 6f 6b 22 3b 20 20 20  20 20 20 20 20 20 20 20  |ook";           |
00012c80  20 20 20 6a 75 6d 70 20  56 65 72 62 50 72 69 6e  |   jump VerbPrin|
00012c90  74 65 64 3b 20 7d 0a 20  20 20 20 20 20 69 66 20  |ted; }.      if |
00012ca0  28 69 3d 3d 23 6e 24 7a  29 20 20 20 20 20 20 20  |(i==#n$z)       |
00012cb0  20 20 7b 20 70 72 69 6e  74 20 22 77 61 69 74 22  |  { print "wait"|
00012cc0  3b 20 20 20 20 20 20 20  20 20 20 20 20 20 20 6a  |;              j|
00012cd0  75 6d 70 20 56 65 72 62  50 72 69 6e 74 65 64 3b  |ump VerbPrinted;|
00012ce0  20 7d 0a 20 20 20 20 20  20 69 66 20 28 69 3d 3d  | }.      if (i==|
00012cf0  23 6e 24 78 29 20 20 20  20 20 20 20 20 20 7b 20  |#n$x)         { |
00012d00  70 72 69 6e 74 20 22 65  78 61 6d 69 6e 65 22 3b  |print "examine";|
00012d10  20 20 20 20 20 20 20 20  20 20 20 6a 75 6d 70 20  |           jump |
00012d20  56 65 72 62 50 72 69 6e  74 65 64 3b 20 7d 0a 20  |VerbPrinted; }. |
00012d30  20 20 20 20 20 69 66 20  28 69 3d 3d 23 6e 24 69  |     if (i==#n$i|
00012d40  20 6f 72 20 27 69 6e 76  27 29 20 7b 20 70 72 69  | or 'inv') { pri|
00012d50  6e 74 20 22 69 6e 76 65  6e 74 6f 72 79 22 3b 20  |nt "inventory"; |
00012d60  20 20 20 20 20 20 20 6a  75 6d 70 20 56 65 72 62  |       jump Verb|
00012d70  50 72 69 6e 74 65 64 3b  20 7d 0a 20 20 20 20 20  |Printed; }.     |
00012d80  20 69 66 20 28 50 72 69  6e 74 56 65 72 62 28 69  | if (PrintVerb(i|
00012d90  29 3d 3d 30 29 20 70 72  69 6e 74 5f 61 64 64 72  |)==0) print_addr|
00012da0  20 69 3b 0a 20 20 7d 0a  20 20 2e 56 65 72 62 50  | i;.  }.  .VerbP|
00012db0  72 69 6e 74 65 64 3b 0a  20 20 6a 3d 70 63 6f 75  |rinted;.  j=pcou|
00012dc0  6e 74 2d 65 6d 70 74 79  66 3b 0a 20 20 66 6f 72  |nt-emptyf;.  for|
00012dd0  20 28 6b 3d 66 72 6f 6d  3a 6b 3c 3d 6a 3a 6b 2b  | (k=from:k<=j:k+|
00012de0  2b 29 0a 20 20 7b 20 20  20 69 66 20 28 66 3d 3d  |+).  {   if (f==|
00012df0  31 29 20 70 72 69 6e 74  5f 63 68 61 72 20 27 20  |1) print_char ' |
00012e00  27 3b 0a 20 20 20 20 20  20 69 3d 70 61 74 74 65  |';.      i=patte|
00012e10  72 6e 2d 2d 3e 6b 3b 0a  20 20 20 20 20 20 69 66  |rn-->k;.      if|
00012e20  20 28 69 3d 3d 30 29 20  7b 20 70 72 69 6e 74 20  | (i==0) { print |
00012e30  22 74 68 6f 73 65 20 74  68 69 6e 67 73 22 3b 20  |"those things"; |
00012e40  6a 75 6d 70 20 54 6f 6b  65 6e 50 72 69 6e 74 65  |jump TokenPrinte|
00012e50  64 3b 20 7d 0a 20 20 20  20 20 20 69 66 20 28 69  |d; }.      if (i|
00012e60  3d 3d 31 29 20 7b 20 70  72 69 6e 74 20 22 74 68  |==1) { print "th|
00012e70  61 74 22 3b 20 6a 75 6d  70 20 54 6f 6b 65 6e 50  |at"; jump TokenP|
00012e80  72 69 6e 74 65 64 3b 20  7d 0a 20 20 20 20 20 20  |rinted; }.      |
00012e90  69 66 20 28 69 3e 3d 31  30 30 30 29 0a 20 20 20  |if (i>=1000).   |
00012ea0  20 20 20 7b 20 20 20 69  3d 41 64 6a 65 63 74 69  |   {   i=Adjecti|
00012eb0  76 65 41 64 64 72 65 73  73 28 69 2d 31 30 30 30  |veAddress(i-1000|
00012ec0  29 3b 0a 23 49 46 56 33  3b 0a 20 20 20 20 20 20  |);.#IFV3;.      |
00012ed0  20 20 20 20 69 66 20 28  69 3d 3d 27 61 67 61 69  |    if (i=='agai|
00012ee0  6e 73 74 27 29 20 7b 20  70 72 69 6e 74 20 22 61  |nst') { print "a|
00012ef0  67 61 69 6e 73 74 22 3b  20 20 20 20 20 20 6a 75  |gainst";      ju|
00012f00  6d 70 20 54 6f 6b 65 6e  50 72 69 6e 74 65 64 3b  |mp TokenPrinted;|
00012f10  20 7d 0a 23 45 4e 44 49  46 3b 0a 20 20 20 20 20  | }.#ENDIF;.     |
00012f20  20 20 20 20 20 70 72 69  6e 74 5f 61 64 64 72 20  |     print_addr |
00012f30  69 3b 0a 20 20 20 20 20  20 7d 0a 20 20 20 20 20  |i;.      }.     |
00012f40  20 65 6c 73 65 20 44 65  66 41 72 74 28 69 29 3b  | else DefArt(i);|
00012f50  0a 20 20 20 20 20 20 2e  54 6f 6b 65 6e 50 72 69  |.      .TokenPri|
00012f60  6e 74 65 64 3b 0a 20 20  20 20 20 20 66 3d 31 3b  |nted;.      f=1;|
00012f70  0a 20 20 7d 0a 5d 3b 0a  0a 21 20 2d 2d 2d 2d 2d  |.  }.];..! -----|
00012f80  2d 2d 2d 2d 2d 2d 2d 2d  2d 2d 2d 2d 2d 2d 2d 2d  |----------------|
*
00012fc0  2d 2d 2d 2d 2d 2d 2d 0a  21 20 20 54 68 65 20 43  |-------.!  The C|
00012fd0  61 6e 74 53 65 65 20 72  6f 75 74 69 6e 65 20 72  |antSee routine r|
00012fe0  65 74 75 72 6e 73 20 61  20 67 6f 6f 64 20 65 72  |eturns a good er|
00012ff0  72 6f 72 20 6e 75 6d 62  65 72 20 66 6f 72 20 74  |ror number for t|
00013000  68 65 20 73 69 74 75 61  74 69 6f 6e 20 77 68 65  |he situation whe|
00013010  72 65 0a 21 20 20 74 68  65 20 6c 61 73 74 20 77  |re.!  the last w|
00013020  6f 72 64 20 6c 6f 6f 6b  65 64 20 61 74 20 64 69  |ord looked at di|
00013030  64 6e 27 74 20 73 65 65  6d 20 74 6f 20 72 65 66  |dn't seem to ref|
00013040  65 72 20 74 6f 20 61 6e  79 20 6f 62 6a 65 63 74  |er to any object|
00013050  20 69 6e 20 63 6f 6e 74  65 78 74 2e 0a 21 0a 21  | in context..!.!|
00013060  20 20 54 68 65 20 69 64  65 61 20 69 73 20 74 68  |  The idea is th|
00013070  61 74 3a 20 69 66 20 74  68 65 20 61 63 74 6f 72  |at: if the actor|
00013080  20 69 73 20 69 6e 20 61  20 6c 6f 63 61 74 69 6f  | is in a locatio|
00013090  6e 20 28 62 75 74 20 6e  6f 74 20 69 6e 73 69 64  |n (but not insid|
000130a0  65 20 73 6f 6d 65 74 68  69 6e 67 0a 21 20 20 6c  |e something.!  l|
000130b0  69 6b 65 2c 20 66 6f 72  20 69 6e 73 74 61 6e 63  |ike, for instanc|
000130c0  65 2c 20 61 20 74 61 6e  6b 20 77 68 69 63 68 20  |e, a tank which |
000130d0  69 73 20 69 6e 20 74 68  61 74 20 6c 6f 63 61 74  |is in that locat|
000130e0  69 6f 6e 29 20 74 68 65  6e 20 61 6e 20 61 74 74  |ion) then an att|
000130f0  65 6d 70 74 20 74 6f 0a  21 20 20 72 65 66 65 72  |empt to.!  refer|
00013100  20 74 6f 20 6f 6e 65 20  6f 66 20 74 68 65 20 77  | to one of the w|
00013110  6f 72 64 73 20 6c 69 73  74 65 64 20 61 73 20 6d  |ords listed as m|
00013120  65 61 6e 69 6e 67 66 75  6c 2d 62 75 74 2d 69 72  |eaningful-but-ir|
00013130  72 65 6c 65 76 61 6e 74  20 74 68 65 72 65 0a 21  |relevant there.!|
00013140  20 20 77 69 6c 6c 20 63  61 75 73 65 20 22 79 6f  |  will cause "yo|
00013150  75 20 64 6f 6e 27 74 20  6e 65 65 64 20 74 6f 20  |u don't need to |
00013160  72 65 66 65 72 20 74 6f  20 74 68 61 74 20 69 6e  |refer to that in|
00013170  20 74 68 69 73 20 67 61  6d 65 22 20 72 61 74 68  | this game" rath|
00013180  65 72 20 74 68 61 6e 0a  21 20 20 22 6e 6f 20 73  |er than.!  "no s|
00013190  75 63 68 20 74 68 69 6e  67 22 20 6f 72 20 22 77  |uch thing" or "w|
000131a0  68 61 74 27 73 20 27 69  74 27 3f 22 2e 0a 21 20  |hat's 'it'?"..! |
000131b0  20 28 54 68 65 20 61 64  76 61 6e 74 61 67 65 20  | (The advantage |
000131c0  6f 66 20 6e 6f 74 20 68  61 76 69 6e 67 20 6c 6f  |of not having lo|
000131d0  6f 6b 65 64 20 61 74 20  22 69 72 72 65 6c 65 76  |oked at "irrelev|
000131e0  61 6e 74 22 20 6c 6f 63  61 6c 20 6e 6f 75 6e 73  |ant" local nouns|
000131f0  20 75 6e 74 69 6c 20 6e  6f 77 0a 21 20 20 69 73  | until now.!  is|
00013200  20 74 68 61 74 20 69 74  20 73 74 6f 70 73 20 74  | that it stops t|
00013210  68 65 6d 20 66 72 6f 6d  20 63 6c 6f 67 67 69 6e  |hem from cloggin|
00013220  67 20 75 70 20 74 68 65  20 61 6d 62 69 67 75 69  |g up the ambigui|
00013230  74 79 2d 72 65 73 6f 6c  76 69 6e 67 20 70 72 6f  |ty-resolving pro|
00013240  63 65 73 73 2e 0a 21 20  20 54 68 75 73 20 67 61  |cess..!  Thus ga|
00013250  6d 65 20 6f 62 6a 65 63  74 73 20 61 6c 77 61 79  |me objects alway|
00013260  73 20 74 72 69 75 6d 70  68 20 6f 76 65 72 20 73  |s triumph over s|
00013270  63 65 6e 65 72 79 2e 29  0a 21 20 2d 2d 2d 2d 2d  |cenery.).! -----|
00013280  2d 2d 2d 2d 2d 2d 2d 2d  2d 2d 2d 2d 2d 2d 2d 2d  |----------------|
*
000132c0  2d 2d 2d 2d 2d 2d 2d 0a  0a 5b 20 43 61 6e 74 53  |-------..[ CantS|
000132d0  65 65 20 20 69 20 77 20  65 3b 0a 20 20 20 20 73  |ee  i w e;.    s|
000132e0  61 76 65 64 5f 6f 6f 70  73 3d 6f 6f 70 73 5f 66  |aved_oops=oops_f|
000132f0  72 6f 6d 3b 0a 0a 20 20  20 20 69 66 20 28 73 63  |rom;..    if (sc|
00013300  6f 70 65 5f 74 6f 6b 65  6e 7e 3d 30 29 20 7b 20  |ope_token~=0) { |
00013310  73 63 6f 70 65 5f 65 72  72 6f 72 20 3d 20 73 63  |scope_error = sc|
00013320  6f 70 65 5f 74 6f 6b 65  6e 3b 20 72 65 74 75 72  |ope_token; retur|
00013330  6e 20 41 53 4b 53 43 4f  50 45 5f 50 45 3b 20 7d  |n ASKSCOPE_PE; }|
00013340  0a 0a 20 20 20 20 77 6e  2d 2d 3b 20 77 3d 4e 65  |..    wn--; w=Ne|
00013350  78 74 57 6f 72 64 28 29  3b 0a 20 20 20 20 65 3d  |xtWord();.    e=|
00013360  43 41 4e 54 53 45 45 5f  50 45 3b 0a 20 20 20 20  |CANTSEE_PE;.    |
00013370  69 66 20 28 77 3d 3d 76  61 67 75 65 5f 77 6f 72  |if (w==vague_wor|
00013380  64 29 20 65 3d 49 54 47  4f 4e 45 5f 50 45 3b 0a  |d) e=ITGONE_PE;.|
00013390  20 20 20 20 69 3d 70 61  72 65 6e 74 28 61 63 74  |    i=parent(act|
000133a0  6f 72 29 3b 0a 20 20 20  20 69 66 20 28 69 20 68  |or);.    if (i h|
000133b0  61 73 20 76 69 73 69 74  65 64 20 26 26 20 52 65  |as visited && Re|
000133c0  66 65 72 73 28 69 2c 77  29 3d 3d 31 29 20 65 3d  |fers(i,w)==1) e=|
000133d0  53 43 45 4e 45 52 59 5f  50 45 3b 0a 20 20 20 20  |SCENERY_PE;.    |
000133e0  69 66 20 28 65 74 79 70  65 3e 65 29 20 72 65 74  |if (etype>e) ret|
000133f0  75 72 6e 20 65 74 79 70  65 3b 0a 20 20 20 20 72  |urn etype;.    r|
00013400  65 74 75 72 6e 20 65 3b  0a 5d 3b 0a 0a 21 20 2d  |eturn e;.];..! -|
00013410  2d 2d 2d 2d 2d 2d 2d 2d  2d 2d 2d 2d 2d 2d 2d 2d  |----------------|
*
00013450  2d 2d 2d 2d 2d 2d 2d 2d  2d 2d 2d 0a 21 20 20 54  |-----------.!  T|
00013460  68 65 20 4d 75 6c 74 69  41 64 64 20 72 6f 75 74  |he MultiAdd rout|
00013470  69 6e 65 20 61 64 64 73  20 6f 62 6a 65 63 74 20  |ine adds object |
00013480  22 6f 22 20 74 6f 20 74  68 65 20 6d 75 6c 74 69  |"o" to the multi|
00013490  70 6c 65 2d 6f 62 6a 65  63 74 2d 6c 69 73 74 2e  |ple-object-list.|
000134a0  0a 21 0a 21 20 20 54 68  69 73 20 69 73 20 6f 6e  |.!.!  This is on|
000134b0  6c 79 20 61 6c 6c 6f 77  65 64 20 74 6f 20 68 6f  |ly allowed to ho|
000134c0  6c 64 20 36 33 20 6f 62  6a 65 63 74 73 20 61 74  |ld 63 objects at|
000134d0  20 6d 6f 73 74 2c 20 61  74 20 77 68 69 63 68 20  | most, at which |
000134e0  70 6f 69 6e 74 20 69 74  20 69 67 6e 6f 72 65 73  |point it ignores|
000134f0  0a 21 20 20 61 6e 79 20  6e 65 77 20 65 6e 74 72  |.!  any new entr|
00013500  69 65 73 20 28 61 6e 64  20 73 65 74 73 20 61 20  |ies (and sets a |
00013510  67 6c 6f 62 61 6c 20 66  6c 61 67 20 73 6f 20 74  |global flag so t|
00013520  68 61 74 20 61 20 77 61  72 6e 69 6e 67 20 6d 61  |hat a warning ma|
00013530  79 20 6c 61 74 65 72 20  62 65 0a 21 20 20 70 72  |y later be.!  pr|
00013540  69 6e 74 65 64 20 69 66  20 6e 65 65 64 20 62 65  |inted if need be|
00013550  29 2e 0a 21 20 2d 2d 2d  2d 2d 2d 2d 2d 2d 2d 2d  |)..! -----------|
00013560  2d 2d 2d 2d 2d 2d 2d 2d  2d 2d 2d 2d 2d 2d 2d 2d  |----------------|
*
000135a0  2d 0a 0a 5b 20 4d 75 6c  74 69 41 64 64 20 6f 20  |-..[ MultiAdd o |
000135b0  69 20 6a 3b 0a 20 20 69  3d 6d 75 6c 74 69 70 6c  |i j;.  i=multipl|
000135c0  65 5f 6f 62 6a 65 63 74  2d 2d 3e 30 3b 0a 20 20  |e_object-->0;.  |
000135d0  69 66 20 69 3d 3d 36 33  20 7b 20 74 6f 6f 6d 61  |if i==63 { tooma|
000135e0  6e 79 5f 66 6c 61 67 3d  31 3b 20 72 74 72 75 65  |ny_flag=1; rtrue|
000135f0  3b 20 7d 0a 20 20 66 6f  72 20 28 6a 3d 31 3a 6a  |; }.  for (j=1:j|
00013600  3c 3d 69 3a 6a 2b 2b 29  0a 20 20 20 20 20 20 69  |<=i:j++).      i|
00013610  66 20 28 6f 3d 3d 6d 75  6c 74 69 70 6c 65 5f 6f  |f (o==multiple_o|
00013620  62 6a 65 63 74 2d 2d 3e  6a 29 20 0a 20 20 20 20  |bject-->j) .    |
00013630  20 20 20 20 20 20 72 74  72 75 65 3b 0a 20 20 69  |      rtrue;.  i|
00013640  2b 2b 3b 0a 20 20 6d 75  6c 74 69 70 6c 65 5f 6f  |++;.  multiple_o|
00013650  62 6a 65 63 74 2d 2d 3e  69 20 3d 20 6f 3b 0a 20  |bject-->i = o;. |
00013660  20 6d 75 6c 74 69 70 6c  65 5f 6f 62 6a 65 63 74  | multiple_object|
00013670  2d 2d 3e 30 20 3d 20 69  3b 0a 5d 3b 0a 0a 21 20  |-->0 = i;.];..! |
00013680  2d 2d 2d 2d 2d 2d 2d 2d  2d 2d 2d 2d 2d 2d 2d 2d  |----------------|
*
000136c0  2d 2d 2d 2d 2d 2d 2d 2d  2d 2d 2d 2d 0a 21 20 20  |------------.!  |
000136d0  54 68 65 20 4d 75 6c 74  69 53 75 62 20 72 6f 75  |The MultiSub rou|
000136e0  74 69 6e 65 20 64 65 6c  65 74 65 73 20 6f 62 6a  |tine deletes obj|
000136f0  65 63 74 20 22 6f 22 20  66 72 6f 6d 20 74 68 65  |ect "o" from the|
00013700  20 6d 75 6c 74 69 70 6c  65 2d 6f 62 6a 65 63 74  | multiple-object|
00013710  2d 6c 69 73 74 2e 0a 21  0a 21 20 20 49 74 20 72  |-list..!.!  It r|
00013720  65 74 75 72 6e 73 20 30  20 69 66 20 74 68 65 20  |eturns 0 if the |
00013730  6f 62 6a 65 63 74 20 77  61 73 20 74 68 65 72 65  |object was there|
00013740  20 69 6e 20 74 68 65 20  66 69 72 73 74 20 70 6c  | in the first pl|
00013750  61 63 65 2c 20 61 6e 64  20 39 20 28 62 65 63 61  |ace, and 9 (beca|
00013760  75 73 65 0a 21 20 20 74  68 69 73 20 69 73 20 74  |use.!  this is t|
00013770  68 65 20 61 70 70 72 6f  70 72 69 61 74 65 20 65  |he appropriate e|
00013780  72 72 6f 72 20 6e 75 6d  62 65 72 20 69 6e 20 50  |rror number in P|
00013790  61 72 73 65 72 28 29 29  20 69 66 20 69 74 20 77  |arser()) if it w|
000137a0  61 73 6e 27 74 2e 0a 21  20 2d 2d 2d 2d 2d 2d 2d  |asn't..! -------|
000137b0  2d 2d 2d 2d 2d 2d 2d 2d  2d 2d 2d 2d 2d 2d 2d 2d  |----------------|
*
000137f0  2d 2d 2d 2d 2d 0a 0a 5b  20 4d 75 6c 74 69 53 75  |-----..[ MultiSu|
00013800  62 20 6f 20 69 20 6a 20  6b 20 65 74 3b 0a 20 20  |b o i j k et;.  |
00013810  69 3d 6d 75 6c 74 69 70  6c 65 5f 6f 62 6a 65 63  |i=multiple_objec|
00013820  74 2d 2d 3e 30 3b 20 65  74 3d 30 3b 0a 20 20 66  |t-->0; et=0;.  f|
00013830  6f 72 20 28 6a 3d 31 3a  6a 3c 3d 69 3a 6a 2b 2b  |or (j=1:j<=i:j++|
00013840  29 0a 20 20 20 20 20 20  69 66 20 28 6f 3d 3d 6d  |).      if (o==m|
00013850  75 6c 74 69 70 6c 65 5f  6f 62 6a 65 63 74 2d 2d  |ultiple_object--|
00013860  3e 6a 29 0a 20 20 20 20  20 20 7b 20 20 20 66 6f  |>j).      {   fo|
00013870  72 20 28 6b 3d 6a 3a 6b  3c 3d 69 3a 6b 2b 2b 29  |r (k=j:k<=i:k++)|
00013880  0a 20 20 20 20 20 20 20  20 20 20 20 20 20 20 6d  |.              m|
00013890  75 6c 74 69 70 6c 65 5f  6f 62 6a 65 63 74 2d 2d  |ultiple_object--|
000138a0  3e 6b 20 3d 20 6d 75 6c  74 69 70 6c 65 5f 6f 62  |>k = multiple_ob|
000138b0  6a 65 63 74 2d 2d 3e 28  6b 2b 31 29 3b 0a 20 20  |ject-->(k+1);.  |
000138c0  20 20 20 20 20 20 20 20  6d 75 6c 74 69 70 6c 65  |        multiple|
000138d0  5f 6f 62 6a 65 63 74 2d  2d 3e 30 20 3d 20 2d 2d  |_object-->0 = --|
000138e0  69 3b 0a 20 20 20 20 20  20 20 20 20 20 72 65 74  |i;.          ret|
000138f0  75 72 6e 20 65 74 3b 0a  20 20 20 20 20 20 7d 0a  |urn et;.      }.|
00013900  20 20 65 74 3d 39 3b 20  72 65 74 75 72 6e 20 65  |  et=9; return e|
00013910  74 3b 0a 5d 3b 0a 0a 21  20 2d 2d 2d 2d 2d 2d 2d  |t;.];..! -------|
00013920  2d 2d 2d 2d 2d 2d 2d 2d  2d 2d 2d 2d 2d 2d 2d 2d  |----------------|
*
00013960  2d 2d 2d 2d 2d 0a 21 20  20 54 68 65 20 4d 75 6c  |-----.!  The Mul|
00013970  74 69 46 69 6c 74 65 72  20 72 6f 75 74 69 6e 65  |tiFilter routine|
00013980  20 67 6f 65 73 20 74 68  72 6f 75 67 68 20 74 68  | goes through th|
00013990  65 20 6d 75 6c 74 69 70  6c 65 2d 6f 62 6a 65 63  |e multiple-objec|
000139a0  74 2d 6c 69 73 74 20 61  6e 64 20 74 68 72 6f 77  |t-list and throw|
000139b0  73 0a 21 20 20 6f 75 74  20 61 6e 79 74 68 69 6e  |s.!  out anythin|
000139c0  67 20 77 69 74 68 6f 75  74 20 74 68 65 20 67 69  |g without the gi|
000139d0  76 65 6e 20 61 74 74 72  69 62 75 74 65 20 22 61  |ven attribute "a|
000139e0  74 74 72 22 20 73 65 74  2e 0a 21 20 2d 2d 2d 2d  |ttr" set..! ----|
000139f0  2d 2d 2d 2d 2d 2d 2d 2d  2d 2d 2d 2d 2d 2d 2d 2d  |----------------|
*
00013a30  2d 2d 2d 2d 2d 2d 2d 2d  0a 0a 5b 20 4d 75 6c 74  |--------..[ Mult|
00013a40  69 46 69 6c 74 65 72 20  61 74 74 72 20 20 69 20  |iFilter attr  i |
00013a50  6a 20 6f 3b 0a 20 20 2e  4d 46 69 6c 74 6c 3b 0a  |j o;.  .MFiltl;.|
00013a60  20 20 69 3d 6d 75 6c 74  69 70 6c 65 5f 6f 62 6a  |  i=multiple_obj|
00013a70  65 63 74 2d 2d 3e 30 3b  0a 20 20 66 6f 72 20 28  |ect-->0;.  for (|
00013a80  6a 3d 31 3a 6a 3c 3d 69  3a 6a 2b 2b 29 0a 20 20  |j=1:j<=i:j++).  |
00013a90  7b 20 20 20 6f 3d 6d 75  6c 74 69 70 6c 65 5f 6f  |{   o=multiple_o|
00013aa0  62 6a 65 63 74 2d 2d 3e  6a 3b 0a 20 20 20 20 20  |bject-->j;.     |
00013ab0  20 69 66 20 28 6f 20 68  61 73 6e 74 20 61 74 74  | if (o hasnt att|
00013ac0  72 29 20 7b 20 4d 75 6c  74 69 53 75 62 28 6f 29  |r) { MultiSub(o)|
00013ad0  3b 20 6a 75 6d 70 20 4d  66 69 6c 74 6c 3b 20 7d  |; jump Mfiltl; }|
00013ae0  0a 20 20 7d 0a 5d 3b 0a  0a 21 20 2d 2d 2d 2d 2d  |.  }.];..! -----|
00013af0  2d 2d 2d 2d 2d 2d 2d 2d  2d 2d 2d 2d 2d 2d 2d 2d  |----------------|
*
00013b30  2d 2d 2d 2d 2d 2d 2d 0a  21 20 20 54 68 65 20 55  |-------.!  The U|
00013b40  73 65 72 46 69 6c 74 65  72 20 72 6f 75 74 69 6e  |serFilter routin|
00013b50  65 20 63 6f 6e 73 75 6c  74 73 20 74 68 65 20 75  |e consults the u|
00013b60  73 65 72 27 73 20 66 69  6c 74 65 72 20 28 6f 72  |ser's filter (or|
00013b70  20 63 68 65 63 6b 73 20  6f 6e 20 61 74 74 72 69  | checks on attri|
00013b80  62 75 74 65 29 0a 21 20  20 74 6f 20 73 65 65 20  |bute).!  to see |
00013b90  77 68 61 74 20 61 6c 72  65 61 64 79 2d 61 63 63  |what already-acc|
00013ba0  65 70 74 65 64 20 6e 6f  75 6e 73 20 61 72 65 20  |epted nouns are |
00013bb0  61 63 63 65 70 74 61 62  6c 65 0a 21 20 2d 2d 2d  |acceptable.! ---|
00013bc0  2d 2d 2d 2d 2d 2d 2d 2d  2d 2d 2d 2d 2d 2d 2d 2d  |----------------|
*
00013c00  2d 2d 2d 2d 2d 2d 2d 2d  2d 0a 0a 5b 20 55 73 65  |---------..[ Use|
00013c10  72 46 69 6c 74 65 72 20  6f 62 6a 3b 0a 0a 20 20  |rFilter obj;..  |
00013c20  69 66 20 28 74 6f 6b 65  6e 5f 77 61 73 3e 3d 31  |if (token_was>=1|
00013c30  32 38 29 0a 20 20 7b 20  20 20 69 66 20 28 6f 62  |28).  {   if (ob|
00013c40  6a 20 68 61 73 20 28 74  6f 6b 65 6e 5f 77 61 73  |j has (token_was|
00013c50  2d 31 32 38 29 29 20 72  74 72 75 65 3b 0a 20 20  |-128)) rtrue;.  |
00013c60  20 20 20 20 72 66 61 6c  73 65 3b 0a 20 20 7d 0a  |    rfalse;.  }.|
00013c70  20 20 6e 6f 75 6e 3d 6f  62 6a 3b 0a 20 20 72 65  |  noun=obj;.  re|
00013c80  74 75 72 6e 20 28 69 6e  64 69 72 65 63 74 28 23  |turn (indirect(#|
00013c90  70 72 65 61 63 74 69 6f  6e 73 5f 74 61 62 6c 65  |preactions_table|
00013ca0  2d 2d 3e 28 74 6f 6b 65  6e 5f 77 61 73 2d 31 36  |-->(token_was-16|
00013cb0  29 29 29 3b 0a 5d 3b 0a  0a 21 20 2d 2d 2d 2d 2d  |)));.];..! -----|
00013cc0  2d 2d 2d 2d 2d 2d 2d 2d  2d 2d 2d 2d 2d 2d 2d 2d  |----------------|
*
00013d00  2d 2d 2d 2d 2d 2d 2d 0a  21 20 20 4d 6f 76 65 57  |-------.!  MoveW|
00013d10  6f 72 64 20 63 6f 70 69  65 73 20 77 6f 72 64 20  |ord copies word |
00013d20  61 74 32 20 66 72 6f 6d  20 70 61 72 73 65 20 62  |at2 from parse b|
00013d30  75 66 66 65 72 20 62 32  20 74 6f 20 77 6f 72 64  |uffer b2 to word|
00013d40  20 61 74 31 20 69 6e 20  22 70 61 72 73 65 22 0a  | at1 in "parse".|
00013d50  21 20 20 28 74 68 65 20  6d 61 69 6e 20 70 61 72  |!  (the main par|
00013d60  73 65 20 62 75 66 66 65  72 29 0a 21 20 2d 2d 2d  |se buffer).! ---|
00013d70  2d 2d 2d 2d 2d 2d 2d 2d  2d 2d 2d 2d 2d 2d 2d 2d  |----------------|
*
00013db0  2d 2d 2d 2d 2d 2d 2d 2d  2d 0a 0a 5b 20 4d 6f 76  |---------..[ Mov|
00013dc0  65 57 6f 72 64 20 61 74  31 20 62 32 20 61 74 32  |eWord at1 b2 at2|
00013dd0  20 78 20 79 3b 0a 20 20  78 3d 61 74 31 2a 32 2d  | x y;.  x=at1*2-|
00013de0  31 3b 20 79 3d 61 74 32  2a 32 2d 31 3b 0a 20 20  |1; y=at2*2-1;.  |
00013df0  70 61 72 73 65 2d 2d 3e  78 2b 2b 20 3d 20 62 32  |parse-->x++ = b2|
00013e00  2d 2d 3e 79 2b 2b 3b 0a  20 20 70 61 72 73 65 2d  |-->y++;.  parse-|
00013e10  2d 3e 78 20 3d 20 62 32  2d 2d 3e 79 3b 0a 5d 3b  |->x = b2-->y;.];|
00013e20  0a 0a 21 20 2d 2d 2d 2d  2d 2d 2d 2d 2d 2d 2d 2d  |..! ------------|
00013e30  2d 2d 2d 2d 2d 2d 2d 2d  2d 2d 2d 2d 2d 2d 2d 2d  |----------------|
*
00013e70  0a 21 20 20 53 65 61 72  63 68 53 63 6f 70 65 20  |.!  SearchScope |
00013e80  20 64 6f 6d 61 69 6e 31  20 64 6f 6d 61 69 6e 32  | domain1 domain2|
00013e90  20 63 6f 6e 74 65 78 74  0a 21 0a 21 20 20 57 6f  | context.!.!  Wo|
00013ea0  72 6b 73 20 6f 75 74 20  77 68 61 74 20 6f 62 6a  |rks out what obj|
00013eb0  65 63 74 73 20 61 72 65  20 69 6e 20 73 63 6f 70  |ects are in scop|
00013ec0  65 20 28 70 6f 73 73 69  62 6c 79 20 61 73 6b 69  |e (possibly aski|
00013ed0  6e 67 20 61 6e 20 6f 75  74 73 69 64 65 20 72 6f  |ng an outside ro|
00013ee0  75 74 69 6e 65 29 2c 0a  21 20 20 62 75 74 20 64  |utine),.!  but d|
00013ef0  6f 65 73 20 6e 6f 74 20  6c 6f 6f 6b 20 61 74 20  |oes not look at |
00013f00  61 6e 79 74 68 69 6e 67  20 74 68 65 20 70 6c 61  |anything the pla|
00013f10  79 65 72 20 68 61 73 20  74 79 70 65 64 2e 0a 21  |yer has typed..!|
00013f20  20 2d 2d 2d 2d 2d 2d 2d  2d 2d 2d 2d 2d 2d 2d 2d  | ---------------|
00013f30  2d 2d 2d 2d 2d 2d 2d 2d  2d 2d 2d 2d 2d 2d 2d 2d  |----------------|
*
00013f60  2d 2d 2d 2d 2d 2d 2d 2d  2d 2d 2d 2d 2d 0a 0a 5b  |-------------..[|
00013f70  20 53 65 61 72 63 68 53  63 6f 70 65 20 64 6f 6d  | SearchScope dom|
00013f80  61 69 6e 31 20 64 6f 6d  61 69 6e 32 20 63 6f 6e  |ain1 domain2 con|
00013f90  74 65 78 74 20 69 3b 0a  0a 20 20 69 3d 30 3b 0a  |text i;..  i=0;.|
00013fa0  21 20 20 45 76 65 72 79  74 68 69 6e 67 20 69 73  |!  Everything is|
00013fb0  20 69 6e 20 73 63 6f 70  65 20 74 6f 20 74 68 65  | in scope to the|
00013fc0  20 64 65 62 75 67 67 69  6e 67 20 63 6f 6d 6d 61  | debugging comma|
00013fd0  6e 64 73 0a 0a 23 69 66  64 65 66 20 44 45 42 55  |nds..#ifdef DEBU|
00013fe0  47 3b 0a 20 20 69 66 20  28 76 65 72 62 5f 77 6f  |G;.  if (verb_wo|
00013ff0  72 64 20 3d 3d 20 27 70  75 72 6c 6f 69 6e 27 20  |rd == 'purloin' |
00014000  6f 72 20 27 74 72 65 65  27 20 6f 72 20 27 61 62  |or 'tree' or 'ab|
00014010  73 74 72 61 63 74 27 29  0a 20 20 7b 20 20 20 66  |stract').  {   f|
00014020  6f 72 20 28 69 3d 73 65  6c 66 6f 62 6a 2b 31 3a  |or (i=selfobj+1:|
00014030  69 3c 3d 74 6f 70 5f 6f  62 6a 65 63 74 3a 69 2b  |i<=top_object:i+|
00014040  2b 29 20 50 6c 61 63 65  49 6e 53 63 6f 70 65 28  |+) PlaceInScope(|
00014050  69 29 3b 0a 20 20 20 20  20 20 72 74 72 75 65 3b  |i);.      rtrue;|
00014060  0a 20 20 7d 0a 23 65 6e  64 69 66 3b 0a 0a 21 20  |.  }.#endif;..! |
00014070  20 46 69 72 73 74 2c 20  61 20 73 63 6f 70 65 20  | First, a scope |
00014080  74 6f 6b 65 6e 20 67 65  74 73 20 70 72 69 6f 72  |token gets prior|
00014090  69 74 79 20 68 65 72 65  3a 0a 0a 20 20 69 66 20  |ity here:..  if |
000140a0  28 73 63 6f 70 65 5f 74  6f 6b 65 6e 20 7e 3d 20  |(scope_token ~= |
000140b0  30 29 0a 20 20 7b 20 20  20 73 63 6f 70 65 5f 73  |0).  {   scope_s|
000140c0  74 61 67 65 3d 32 3b 0a  20 20 20 20 20 20 69 66  |tage=2;.      if|
000140d0  20 28 69 6e 64 69 72 65  63 74 28 73 63 6f 70 65  | (indirect(scope|
000140e0  5f 74 6f 6b 65 6e 29 7e  3d 30 29 20 72 74 72 75  |_token)~=0) rtru|
000140f0  65 3b 0a 20 20 7d 0a 0a  21 20 20 4e 65 78 74 2c  |e;.  }..!  Next,|
00014100  20 63 61 6c 6c 20 61 6e  79 20 75 73 65 72 2d 73  | call any user-s|
00014110  75 70 70 6c 69 65 64 20  72 6f 75 74 69 6e 65 20  |upplied routine |
00014120  61 64 64 69 6e 67 20 74  68 69 6e 67 73 20 74 6f  |adding things to|
00014130  20 74 68 65 20 73 63 6f  70 65 2c 0a 21 20 20 77  | the scope,.!  w|
00014140  68 69 63 68 20 6d 61 79  20 63 69 72 63 75 6d 76  |hich may circumv|
00014150  65 6e 74 20 74 68 65 20  75 73 75 61 6c 20 72 6f  |ent the usual ro|
00014160  75 74 69 6e 65 73 20 61  6c 74 6f 67 65 74 68 65  |utines altogethe|
00014170  72 20 69 66 20 74 68 65  79 20 72 65 74 75 72 6e  |r if they return|
00014180  20 74 72 75 65 3a 0a 0a  20 20 69 66 20 28 64 6f  | true:..  if (do|
00014190  6d 61 69 6e 31 3d 3d 61  63 74 6f 72 29 0a 20 20  |main1==actor).  |
000141a0  7b 20 20 20 69 66 20 28  49 6e 53 63 6f 70 65 28  |{   if (InScope(|
000141b0  64 6f 6d 61 69 6e 31 29  7e 3d 30 29 20 72 74 72  |domain1)~=0) rtr|
000141c0  75 65 3b 0a 20 20 7d 0a  20 20 65 6c 73 65 20 69  |ue;.  }.  else i|
000141d0  66 20 28 64 6f 6d 61 69  6e 32 3d 3d 61 63 74 6f  |f (domain2==acto|
000141e0  72 29 0a 20 20 7b 20 20  20 69 66 20 28 49 6e 53  |r).  {   if (InS|
000141f0  63 6f 70 65 28 64 6f 6d  61 69 6e 32 29 7e 3d 30  |cope(domain2)~=0|
00014200  29 20 72 74 72 75 65 3b  0a 20 20 7d 0a 0a 21 20  |) rtrue;.  }..! |
00014210  20 50 69 63 6b 20 75 70  20 65 76 65 72 79 74 68  | Pick up everyth|
00014220  69 6e 67 20 69 6e 20 74  68 65 20 6c 6f 63 61 74  |ing in the locat|
00014230  69 6f 6e 20 65 78 63 65  70 74 20 74 68 65 20 61  |ion except the a|
00014240  63 74 6f 72 27 73 20 70  6f 73 73 65 73 73 69 6f  |ctor's possessio|
00014250  6e 73 3b 0a 21 20 20 74  68 65 6e 20 67 6f 20 74  |ns;.!  then go t|
00014260  68 72 6f 75 67 68 20 74  68 6f 73 65 2e 20 20 28  |hrough those.  (|
00014270  54 68 69 73 20 65 6e 73  75 72 65 73 20 74 68 65  |This ensures the|
00014280  20 61 63 74 6f 72 27 73  20 70 6f 73 73 65 73 73  | actor's possess|
00014290  69 6f 6e 73 20 61 72 65  20 69 6e 0a 21 20 20 73  |ions are in.!  s|
000142a0  63 6f 70 65 20 65 76 65  6e 20 69 6e 20 44 61 72  |cope even in Dar|
000142b0  6b 6e 65 73 73 2e 29 0a  0a 20 20 69 66 20 28 63  |kness.)..  if (c|
000142c0  6f 6e 74 65 78 74 3d 3d  35 20 26 26 20 61 64 76  |ontext==5 && adv|
000142d0  61 6e 63 65 5f 77 61 72  6e 69 6e 67 20 7e 3d 20  |ance_warning ~= |
000142e0  2d 31 29 20 20 20 20 20  20 20 21 20 20 53 63 6f  |-1)       !  Sco|
000142f0  70 65 20 66 6f 72 20 6d  75 6c 74 69 69 6e 73 69  |pe for multiinsi|
00014300  64 65 0a 20 20 7b 20 20  20 53 63 6f 70 65 57 69  |de.  {   ScopeWi|
00014310  74 68 69 6e 28 61 64 76  61 6e 63 65 5f 77 61 72  |thin(advance_war|
00014320  6e 69 6e 67 2c 20 30 2c  20 63 6f 6e 74 65 78 74  |ning, 0, context|
00014330  29 3b 20 20 21 20 20 69  73 20 64 69 66 66 65 72  |);  !  is differ|
00014340  65 6e 74 0a 20 20 7d 0a  20 20 65 6c 73 65 0a 20  |ent.  }.  else. |
00014350  20 7b 20 20 20 53 63 6f  70 65 57 69 74 68 69 6e  | {   ScopeWithin|
00014360  28 64 6f 6d 61 69 6e 31  2c 20 64 6f 6d 61 69 6e  |(domain1, domain|
00014370  32 2c 20 63 6f 6e 74 65  78 74 29 3b 0a 20 20 20  |2, context);.   |
00014380  20 20 20 53 63 6f 70 65  57 69 74 68 69 6e 28 64  |   ScopeWithin(d|
00014390  6f 6d 61 69 6e 32 2c 30  2c 63 6f 6e 74 65 78 74  |omain2,0,context|
000143a0  29 3b 0a 20 20 7d 0a 5d  3b 0a 0a 21 20 2d 2d 2d  |);.  }.];..! ---|
000143b0  2d 2d 2d 2d 2d 2d 2d 2d  2d 2d 2d 2d 2d 2d 2d 2d  |----------------|
*
000143f0  2d 2d 2d 2d 2d 2d 2d 2d  2d 0a 21 20 20 50 6c 61  |---------.!  Pla|
00014400  63 65 49 6e 53 63 6f 70  65 20 69 73 20 70 72 6f  |ceInScope is pro|
00014410  76 69 64 65 64 20 66 6f  72 20 72 6f 75 74 69 6e  |vided for routin|
00014420  65 73 20 6f 75 74 73 69  64 65 20 74 68 65 20 6c  |es outside the l|
00014430  69 62 72 61 72 79 2c 20  61 6e 64 20 69 73 20 6e  |ibrary, and is n|
00014440  6f 74 0a 21 20 20 63 61  6c 6c 65 64 20 77 69 74  |ot.!  called wit|
00014450  68 69 6e 20 74 68 65 20  70 61 72 73 65 72 20 28  |hin the parser (|
00014460  65 78 63 65 70 74 20 66  6f 72 20 64 65 62 75 67  |except for debug|
00014470  67 69 6e 67 20 70 75 72  70 6f 73 65 73 29 2e 0a  |ging purposes)..|
00014480  21 20 2d 2d 2d 2d 2d 2d  2d 2d 2d 2d 2d 2d 2d 2d  |! --------------|
00014490  2d 2d 2d 2d 2d 2d 2d 2d  2d 2d 2d 2d 2d 2d 2d 2d  |----------------|
*
000144c0  2d 2d 2d 2d 2d 2d 2d 2d  2d 2d 2d 2d 2d 2d 0a 0a  |--------------..|
000144d0  5b 20 50 6c 61 63 65 49  6e 53 63 6f 70 65 20 74  |[ PlaceInScope t|
000144e0  68 69 6e 67 3b 0a 0a 20  20 20 69 66 20 28 65 74  |hing;..   if (et|
000144f0  5f 66 6c 61 67 3d 3d 31  29 20 7b 20 44 6f 45 61  |_flag==1) { DoEa|
00014500  63 68 54 75 72 6e 28 74  68 69 6e 67 29 3b 20 72  |chTurn(thing); r|
00014510  74 72 75 65 3b 20 7d 0a  20 20 20 77 6e 3d 6d 61  |true; }.   wn=ma|
00014520  74 63 68 5f 66 72 6f 6d  3b 20 54 72 79 47 69 76  |tch_from; TryGiv|
00014530  65 6e 4f 62 6a 65 63 74  28 74 68 69 6e 67 29 3b  |enObject(thing);|
00014540  20 70 6c 61 63 65 64 5f  69 6e 5f 66 6c 61 67 3d  | placed_in_flag=|
00014550  31 3b 0a 5d 3b 0a 0a 21  20 2d 2d 2d 2d 2d 2d 2d  |1;.];..! -------|
00014560  2d 2d 2d 2d 2d 2d 2d 2d  2d 2d 2d 2d 2d 2d 2d 2d  |----------------|
*
000145a0  2d 2d 2d 2d 2d 0a 21 20  20 44 6f 45 61 63 68 54  |-----.!  DoEachT|
000145b0  75 72 6e 0a 21 20 2d 2d  2d 2d 2d 2d 2d 2d 2d 2d  |urn.! ----------|
000145c0  2d 2d 2d 2d 2d 2d 2d 2d  2d 2d 2d 2d 2d 2d 2d 2d  |----------------|
*
00014600  2d 2d 0a 0a 5b 20 44 6f  45 61 63 68 54 75 72 6e  |--..[ DoEachTurn|
00014610  20 74 68 69 6e 67 20 6a  3b 0a 20 20 69 66 20 28  | thing j;.  if (|
00014620  70 61 72 73 65 72 5f 74  72 61 63 65 3e 3d 35 29  |parser_trace>=5)|
00014630  0a 20 20 7b 20 20 20 70  72 69 6e 74 20 22 5b 43  |.  {   print "[C|
00014640  6f 6e 73 69 64 65 72 69  6e 67 20 65 61 63 68 5f  |onsidering each_|
00014650  74 75 72 6e 20 66 6f 72  20 22 3b 20 44 65 66 41  |turn for "; DefA|
00014660  72 74 28 74 68 69 6e 67  29 3b 20 70 72 69 6e 74  |rt(thing); print|
00014670  20 22 5d 5e 22 3b 20 7d  0a 20 20 6a 3d 74 68 69  | "]^"; }.  j=thi|
00014680  6e 67 2e 65 61 63 68 5f  74 75 72 6e 3b 20 69 66  |ng.each_turn; if|
00014690  20 28 6a 3d 3d 30 29 20  72 74 72 75 65 3b 0a 20  | (j==0) rtrue;. |
000146a0  20 69 66 20 28 28 6a 2d  23 73 74 72 69 6e 67 73  | if ((j-#strings|
000146b0  5f 6f 66 66 73 65 74 29  3e 3d 30 29 20 7b 20 70  |_offset)>=0) { p|
000146c0  72 69 6e 74 5f 70 61 64  64 72 20 6a 3b 20 6e 65  |rint_paddr j; ne|
000146d0  77 5f 6c 69 6e 65 3b 20  72 74 72 75 65 3b 20 7d  |w_line; rtrue; }|
000146e0  0a 20 20 52 75 6e 52 6f  75 74 69 6e 65 73 28 74  |.  RunRoutines(t|
000146f0  68 69 6e 67 2c 65 61 63  68 5f 74 75 72 6e 29 3b  |hing,each_turn);|
00014700  0a 5d 3b 0a 0a 21 20 2d  2d 2d 2d 2d 2d 2d 2d 2d  |.];..! ---------|
00014710  2d 2d 2d 2d 2d 2d 2d 2d  2d 2d 2d 2d 2d 2d 2d 2d  |----------------|
*
00014750  2d 2d 2d 0a 21 20 20 53  63 6f 70 65 57 69 74 68  |---.!  ScopeWith|
00014760  69 6e 20 6c 6f 6f 6b 73  20 66 6f 72 20 6f 62 6a  |in looks for obj|
00014770  65 63 74 73 20 69 6e 20  74 68 65 20 64 6f 6d 61  |ects in the doma|
00014780  69 6e 20 77 68 69 63 68  20 6d 61 6b 65 20 74 65  |in which make te|
00014790  78 74 75 61 6c 20 73 65  6e 73 65 0a 21 20 20 61  |xtual sense.!  a|
000147a0  6e 64 20 70 75 74 73 20  74 68 65 6d 20 69 6e 20  |nd puts them in |
000147b0  74 68 65 20 6d 61 74 63  68 20 6c 69 73 74 2e 20  |the match list. |
000147c0  20 28 48 6f 77 65 76 65  72 2c 20 69 74 20 64 6f  | (However, it do|
000147d0  65 73 20 6e 6f 74 20 72  65 63 75 72 73 65 20 74  |es not recurse t|
000147e0  68 72 6f 75 67 68 0a 21  20 20 74 68 65 20 73 65  |hrough.!  the se|
000147f0  63 6f 6e 64 20 61 72 67  75 6d 65 6e 74 2e 29 0a  |cond argument.).|
00014800  21 20 2d 2d 2d 2d 2d 2d  2d 2d 2d 2d 2d 2d 2d 2d  |! --------------|
00014810  2d 2d 2d 2d 2d 2d 2d 2d  2d 2d 2d 2d 2d 2d 2d 2d  |----------------|
*
00014840  2d 2d 2d 2d 2d 2d 2d 2d  2d 2d 2d 2d 2d 2d 0a 0a  |--------------..|
00014850  5b 20 53 63 6f 70 65 57  69 74 68 69 6e 20 64 6f  |[ ScopeWithin do|
00014860  6d 61 69 6e 20 6e 6f 73  65 61 72 63 68 20 63 6f  |main nosearch co|
00014870  6e 74 65 78 74 20 69 3b  0a 0a 20 20 20 69 66 20  |ntext i;..   if |
00014880  28 64 6f 6d 61 69 6e 3d  3d 30 29 20 72 74 72 75  |(domain==0) rtru|
00014890  65 3b 0a 0a 21 20 20 6d  75 6c 74 69 65 78 63 65  |e;..!  multiexce|
000148a0  70 74 20 64 6f 65 73 6e  27 74 20 68 61 76 65 20  |pt doesn't have |
000148b0  73 65 63 6f 6e 64 20 70  61 72 61 6d 65 74 65 72  |second parameter|
000148c0  20 69 6e 20 73 63 6f 70  65 0a 20 20 20 69 66 20  | in scope.   if |
000148d0  28 63 6f 6e 74 65 78 74  3d 3d 34 20 26 26 20 64  |(context==4 && d|
000148e0  6f 6d 61 69 6e 3d 3d 61  64 76 61 6e 63 65 5f 77  |omain==advance_w|
000148f0  61 72 6e 69 6e 67 29 20  72 74 72 75 65 3b 0a 0a  |arning) rtrue;..|
00014900  21 20 20 53 70 65 63 69  61 6c 20 72 75 6c 65 3a  |!  Special rule:|
00014910  20 74 68 65 20 64 69 72  65 63 74 69 6f 6e 73 20  | the directions |
00014920  28 69 6e 74 65 72 70 72  65 74 65 64 20 61 73 20  |(interpreted as |
00014930  74 68 65 20 31 32 20 77  61 6c 6c 73 20 6f 66 20  |the 12 walls of |
00014940  61 20 72 6f 6f 6d 29 20  61 72 65 0a 21 20 20 61  |a room) are.!  a|
00014950  6c 77 61 79 73 20 69 6e  20 63 6f 6e 74 65 78 74  |lways in context|
00014960  2e 20 20 28 53 6f 2c 20  65 2e 67 2e 2c 20 22 65  |.  (So, e.g., "e|
00014970  78 61 6d 69 6e 65 20 6e  6f 72 74 68 20 77 61 6c  |xamine north wal|
00014980  6c 22 20 69 73 20 61 6c  77 61 79 73 20 6c 65 67  |l" is always leg|
00014990  61 6c 2e 29 0a 21 20 20  28 55 6e 6c 65 73 73 20  |al.).!  (Unless |
000149a0  77 65 27 72 65 20 70 61  72 73 69 6e 67 20 73 6f  |we're parsing so|
000149b0  6d 65 74 68 69 6e 67 20  6c 69 6b 65 20 22 61 6c  |mething like "al|
000149c0  6c 22 2c 20 62 65 63 61  75 73 65 20 69 74 20 77  |l", because it w|
000149d0  6f 75 6c 64 20 6a 75 73  74 20 73 6c 6f 77 0a 21  |ould just slow.!|
000149e0  20 20 74 68 69 6e 67 73  20 64 6f 77 6e 20 74 68  |  things down th|
000149f0  65 6e 2e 29 0a 0a 20 20  20 69 66 20 28 69 6e 64  |en.)..   if (ind|
00014a00  65 66 5f 6d 6f 64 65 3d  3d 30 20 26 26 20 64 6f  |ef_mode==0 && do|
00014a10  6d 61 69 6e 3d 3d 6c 6f  63 61 74 69 6f 6e 20 26  |main==location &|
00014a20  26 20 65 74 5f 66 6c 61  67 3d 3d 30 29 20 53 63  |& et_flag==0) Sc|
00014a30  6f 70 65 57 69 74 68 69  6e 28 63 6f 6d 70 61 73  |opeWithin(compas|
00014a40  73 29 3b 0a 0a 21 20 20  4c 6f 6f 6b 20 74 68 72  |s);..!  Look thr|
00014a50  6f 75 67 68 20 74 68 65  20 6f 62 6a 65 63 74 73  |ough the objects|
00014a60  20 69 6e 20 74 68 65 20  64 6f 6d 61 69 6e 0a 0a  | in the domain..|
00014a70  20 20 20 6f 62 6a 65 63  74 6c 6f 6f 70 20 28 64  |   objectloop (d|
00014a80  6f 6d 61 69 6e 20 69 6e  20 64 6f 6d 61 69 6e 29  |omain in domain)|
00014a90  0a 20 20 20 7b 20 0a 0a  21 20 20 49 6e 20 65 61  |.   { ..!  In ea|
00014aa0  63 68 5f 74 75 72 6e 20  6d 6f 64 65 2c 20 77 65  |ch_turn mode, we|
00014ab0  27 72 65 20 67 6f 69 6e  67 20 74 68 72 6f 75 67  |'re going throug|
00014ac0  68 20 63 61 6c 6c 69 6e  67 20 65 5f 74 20 66 6f  |h calling e_t fo|
00014ad0  72 20 65 76 65 72 79 74  68 69 6e 67 20 69 6e 0a  |r everything in.|
00014ae0  21 20 20 73 63 6f 70 65  20 61 6e 64 20 6e 6f 74  |!  scope and not|
00014af0  20 64 6f 69 6e 67 20 61  6e 79 20 70 61 72 73 69  | doing any parsi|
00014b00  6e 67 20 61 74 20 61 6c  6c 3a 0a 0a 20 20 20 20  |ng at all:..    |
00014b10  20 20 69 66 20 28 65 74  5f 66 6c 61 67 3d 3d 31  |  if (et_flag==1|
00014b20  29 20 7b 20 44 6f 45 61  63 68 54 75 72 6e 28 64  |) { DoEachTurn(d|
00014b30  6f 6d 61 69 6e 29 3b 20  6a 75 6d 70 20 44 6f 6e  |omain); jump Don|
00014b40  74 41 63 63 65 70 74 3b  20 7d 0a 0a 21 20 20 49  |tAccept; }..!  I|
00014b50  66 20 77 65 27 72 65 20  62 65 79 6f 6e 64 20 74  |f we're beyond t|
00014b60  68 65 20 65 6e 64 20 6f  66 20 74 68 65 20 75 73  |he end of the us|
00014b70  65 72 27 73 20 74 79 70  69 6e 67 2c 20 61 63 63  |er's typing, acc|
00014b80  65 70 74 20 65 76 65 72  79 74 68 69 6e 67 0a 21  |ept everything.!|
00014b90  20 20 28 4e 6f 75 6e 44  6f 6d 61 69 6e 20 77 69  |  (NounDomain wi|
00014ba0  6c 6c 20 73 6f 72 74 20  74 68 69 6e 67 73 20 6f  |ll sort things o|
00014bb0  75 74 29 0a 0a 20 20 20  20 20 20 69 66 20 28 6d  |ut)..      if (m|
00014bc0  61 74 63 68 5f 66 72 6f  6d 20 3e 20 6e 75 6d 5f  |atch_from > num_|
00014bd0  77 6f 72 64 73 29 20 7b  20 4d 61 6b 65 4d 61 74  |words) { MakeMat|
00014be0  63 68 28 64 6f 6d 61 69  6e 2c 31 29 3b 20 6a 75  |ch(domain,1); ju|
00014bf0  6d 70 20 44 6f 6e 74 41  63 63 65 70 74 3b 20 7d  |mp DontAccept; }|
00014c00  0a 0a 21 20 20 22 69 74  22 20 6f 72 20 22 74 68  |..!  "it" or "th|
00014c10  65 6d 22 20 6d 61 74 63  68 65 73 20 74 6f 20 74  |em" matches to t|
00014c20  68 65 20 69 74 2d 6f 62  6a 65 63 74 20 6f 6e 6c  |he it-object onl|
00014c30  79 2e 20 20 28 4e 6f 74  65 20 74 68 61 74 20 28  |y.  (Note that (|
00014c40  31 29 20 74 68 69 73 20  6d 65 61 6e 73 0a 21 20  |1) this means.! |
00014c50  20 74 68 61 74 20 22 69  74 22 20 77 69 6c 6c 20  | that "it" will |
00014c60  6f 6e 6c 79 20 62 65 20  75 6e 64 65 72 73 74 6f  |only be understo|
00014c70  6f 64 20 69 66 20 74 68  65 20 6f 62 6a 65 63 74  |od if the object|
00014c80  20 69 6e 20 71 75 65 73  74 69 6f 6e 20 69 73 20  | in question is |
00014c90  73 74 69 6c 6c 0a 21 20  20 69 6e 20 63 6f 6e 74  |still.!  in cont|
00014ca0  65 78 74 2c 20 61 6e 64  20 28 32 29 20 6f 6e 6c  |ext, and (2) onl|
00014cb0  79 20 6f 6e 65 20 6d 61  74 63 68 20 63 61 6e 20  |y one match can |
00014cc0  65 76 65 72 20 62 65 20  6d 61 64 65 20 69 6e 20  |ever be made in |
00014cd0  74 68 69 73 20 63 61 73  65 2e 29 0a 0a 20 20 20  |this case.)..   |
00014ce0  20 20 20 77 6e 3d 6d 61  74 63 68 5f 66 72 6f 6d  |   wn=match_from|
00014cf0  3b 0a 20 20 20 20 20 20  69 3d 4e 6f 75 6e 57 6f  |;.      i=NounWo|
00014d00  72 64 28 29 3b 0a 20 20  20 20 20 20 69 66 20 28  |rd();.      if (|
00014d10  69 3d 3d 31 20 26 26 20  69 74 6f 62 6a 3d 3d 64  |i==1 && itobj==d|
00014d20  6f 6d 61 69 6e 29 20 20  20 4d 61 6b 65 4d 61 74  |omain)   MakeMat|
00014d30  63 68 28 69 74 6f 62 6a  2c 31 29 3b 0a 20 20 20  |ch(itobj,1);.   |
00014d40  20 20 20 69 66 20 28 69  3d 3d 32 20 26 26 20 68  |   if (i==2 && h|
00014d50  69 6d 6f 62 6a 3d 3d 64  6f 6d 61 69 6e 29 20 20  |imobj==domain)  |
00014d60  4d 61 6b 65 4d 61 74 63  68 28 68 69 6d 6f 62 6a  |MakeMatch(himobj|
00014d70  2c 31 29 3b 0a 20 20 20  20 20 20 69 66 20 28 69  |,1);.      if (i|
00014d80  3d 3d 33 20 26 26 20 68  65 72 6f 62 6a 3d 3d 64  |==3 && herobj==d|
00014d90  6f 6d 61 69 6e 29 20 20  4d 61 6b 65 4d 61 74 63  |omain)  MakeMatc|
00014da0  68 28 68 65 72 6f 62 6a  2c 31 29 3b 0a 20 20 20  |h(herobj,1);.   |
00014db0  20 20 20 69 66 20 28 69  3d 3d 34 20 26 26 20 70  |   if (i==4 && p|
00014dc0  6c 61 79 65 72 3d 3d 64  6f 6d 61 69 6e 29 20 20  |layer==domain)  |
00014dd0  4d 61 6b 65 4d 61 74 63  68 28 70 6c 61 79 65 72  |MakeMatch(player|
00014de0  2c 31 29 3b 0a 0a 21 20  20 43 6f 6e 73 74 72 75  |,1);..!  Constru|
00014df0  69 6e 67 20 74 68 65 20  63 75 72 72 65 6e 74 20  |ing the current |
00014e00  77 6f 72 64 20 61 73 20  74 68 65 20 73 74 61 72  |word as the star|
00014e10  74 20 6f 66 20 61 20 6e  6f 75 6e 2c 20 63 61 6e  |t of a noun, can|
00014e20  20 69 74 20 72 65 66 65  72 20 74 6f 20 74 68 65  | it refer to the|
00014e30  0a 21 20 20 6f 62 6a 65  63 74 3f 0a 0a 20 20 20  |.!  object?..   |
00014e40  20 20 20 77 6e 2d 2d 3b  20 54 72 79 47 69 76 65  |   wn--; TryGive|
00014e50  6e 4f 62 6a 65 63 74 28  64 6f 6d 61 69 6e 29 3b  |nObject(domain);|
00014e60  0a 0a 20 20 20 20 20 20  2e 44 6f 6e 74 41 63 63  |..      .DontAcc|
00014e70  65 70 74 3b 0a 0a 21 20  20 53 68 61 6c 6c 20 77  |ept;..!  Shall w|
00014e80  65 20 63 6f 6e 73 69 64  65 72 20 74 68 65 20 70  |e consider the p|
00014e90  6f 73 73 65 73 73 69 6f  6e 73 20 6f 66 20 74 68  |ossessions of th|
00014ea0  65 20 63 75 72 72 65 6e  74 20 6f 62 6a 65 63 74  |e current object|
00014eb0  2c 20 61 73 20 77 65 6c  6c 3f 0a 21 20 20 4f 6e  |, as well?.!  On|
00014ec0  6c 79 20 69 66 20 69 74  27 73 20 61 20 63 6f 6e  |ly if it's a con|
00014ed0  74 61 69 6e 65 72 20 28  73 6f 2c 20 66 6f 72 20  |tainer (so, for |
00014ee0  69 6e 73 74 61 6e 63 65  2c 20 69 66 20 61 20 64  |instance, if a d|
00014ef0  77 61 72 66 20 63 61 72  72 69 65 73 20 61 0a 21  |warf carries a.!|
00014f00  20 20 73 77 6f 72 64 2c  20 74 68 65 6e 20 22 64  |  sword, then "d|
00014f10  72 6f 70 20 73 77 6f 72  64 22 20 77 69 6c 6c 20  |rop sword" will |
00014f20  6e 6f 74 20 62 65 20 61  63 63 65 70 74 65 64 2c  |not be accepted,|
00014f30  20 62 75 74 20 22 64 77  61 72 66 2c 20 64 72 6f  | but "dwarf, dro|
00014f40  70 20 73 77 6f 72 64 22  0a 21 20 20 77 69 6c 6c  |p sword".!  will|
00014f50  29 2e 0a 21 20 20 41 6c  73 6f 2c 20 6f 6e 6c 79  |)..!  Also, only|
00014f60  20 69 66 20 74 68 65 72  65 20 61 72 65 20 73 75  | if there are su|
00014f70  63 68 20 70 6f 73 73 65  73 73 69 6f 6e 73 2e 0a  |ch possessions..|
00014f80  21 0a 21 20 20 4e 6f 74  69 63 65 20 74 68 61 74  |!.!  Notice that|
00014f90  20 74 68 65 20 72 75 6c  65 73 20 68 61 76 65 20  | the rules have |
00014fa0  62 65 65 6e 20 63 68 61  6e 67 65 64 20 68 65 72  |been changed her|
00014fb0  65 20 72 65 63 65 6e 74  6c 79 2c 20 61 6e 64 20  |e recently, and |
00014fc0  74 68 61 74 20 74 68 69  73 20 69 73 0a 21 20 20  |that this is.!  |
00014fd0  63 72 75 63 69 61 6c 20  74 6f 20 74 68 65 20 70  |crucial to the p|
00014fe0  61 72 73 65 72 27 73 20  22 73 63 6f 70 65 20 72  |arser's "scope r|
00014ff0  75 6c 65 73 22 2e 20 20  50 72 65 76 69 6f 75 73  |ules".  Previous|
00015000  6c 79 20 6f 6e 6c 79 20  63 6f 6e 74 61 69 6e 65  |ly only containe|
00015010  72 73 20 63 6f 75 6c 64  0a 21 20 20 62 65 20 22  |rs could.!  be "|
00015020  74 72 61 6e 73 70 61 72  65 6e 74 22 20 62 75 74  |transparent" but|
00015030  20 6e 6f 77 20 74 68 65  20 70 61 72 73 65 72 20  | now the parser |
00015040  63 61 6e 20 73 65 65 20  22 69 6e 74 6f 22 20 61  |can see "into" a|
00015050  6e 79 74 68 69 6e 67 20  66 6c 61 67 67 65 64 20  |nything flagged |
00015060  61 73 0a 21 20 20 74 72  61 6e 73 70 61 72 65 6e  |as.!  transparen|
00015070  74 20 2d 20 73 75 63 68  20 61 73 20 61 20 64 77  |t - such as a dw|
00015080  61 72 66 20 77 68 6f 73  65 20 73 77 6f 72 64 20  |arf whose sword |
00015090  79 6f 75 20 63 61 6e 20  67 65 74 20 61 74 2e 0a  |you can get at..|
000150a0  0a 20 20 20 20 20 20 69  66 20 28 63 68 69 6c 64  |.      if (child|
000150b0  28 64 6f 6d 61 69 6e 29  7e 3d 30 0a 20 20 20 20  |(domain)~=0.    |
000150c0  20 20 20 20 20 20 26 26  20 64 6f 6d 61 69 6e 20  |      && domain |
000150d0  7e 3d 20 6e 6f 73 65 61  72 63 68 0a 20 20 20 20  |~= nosearch.    |
000150e0  20 20 20 20 20 20 26 26  20 28 64 6f 6d 61 69 6e  |      && (domain|
000150f0  20 68 61 73 20 73 75 70  70 6f 72 74 65 72 0a 20  | has supporter. |
00015100  20 20 20 20 20 20 20 20  20 20 20 20 20 7c 7c 20  |             || |
00015110  64 6f 6d 61 69 6e 20 68  61 73 20 74 72 61 6e 73  |domain has trans|
00015120  70 61 72 65 6e 74 0a 20  20 20 20 20 20 20 20 20  |parent.         |
00015130  20 20 20 20 20 7c 7c 20  28 64 6f 6d 61 69 6e 20  |     || (domain |
00015140  68 61 73 20 63 6f 6e 74  61 69 6e 65 72 20 26 26  |has container &&|
00015150  20 64 6f 6d 61 69 6e 20  68 61 73 20 6f 70 65 6e  | domain has open|
00015160  29 29 29 0a 20 20 20 20  20 20 20 20 20 20 53 63  |))).          Sc|
00015170  6f 70 65 57 69 74 68 69  6e 28 64 6f 6d 61 69 6e  |opeWithin(domain|
00015180  2c 30 2c 63 6f 6e 74 65  78 74 29 3b 0a 20 20 7d  |,0,context);.  }|
00015190  0a 5d 3b 0a 0a 21 20 2d  2d 2d 2d 2d 2d 2d 2d 2d  |.];..! ---------|
000151a0  2d 2d 2d 2d 2d 2d 2d 2d  2d 2d 2d 2d 2d 2d 2d 2d  |----------------|
*
000151e0  2d 2d 2d 0a 21 20 20 4d  61 6b 65 4d 61 74 63 68  |---.!  MakeMatch|
000151f0  20 6c 6f 6f 6b 73 20 61  74 20 68 6f 77 20 67 6f  | looks at how go|
00015200  6f 64 20 61 20 6d 61 74  63 68 20 69 73 2e 20 20  |od a match is.  |
00015210  49 66 20 69 74 27 73 20  74 68 65 20 62 65 73 74  |If it's the best|
00015220  20 73 6f 20 66 61 72 2c  20 74 68 65 6e 0a 21 20  | so far, then.! |
00015230  20 77 69 70 65 20 6f 75  74 20 61 6c 6c 20 74 68  | wipe out all th|
00015240  65 20 70 72 65 76 69 6f  75 73 20 6d 61 74 63 68  |e previous match|
00015250  65 73 20 61 6e 64 20 73  74 61 72 74 20 61 20 6e  |es and start a n|
00015260  65 77 20 6c 69 73 74 20  77 69 74 68 20 74 68 69  |ew list with thi|
00015270  73 20 6f 6e 65 2e 0a 21  20 20 49 66 20 69 74 27  |s one..!  If it'|
00015280  73 20 6f 6e 6c 79 20 61  73 20 67 6f 6f 64 20 61  |s only as good a|
00015290  73 20 74 68 65 20 62 65  73 74 20 73 6f 20 66 61  |s the best so fa|
000152a0  72 2c 20 61 64 64 20 69  74 20 74 6f 20 74 68 65  |r, add it to the|
000152b0  20 6c 69 73 74 2e 0a 21  20 20 49 66 20 69 74 27  | list..!  If it'|
000152c0  73 20 77 6f 72 73 65 2c  20 69 67 6e 6f 72 65 20  |s worse, ignore |
000152d0  69 74 20 61 6c 74 6f 67  65 74 68 65 72 2e 0a 21  |it altogether..!|
000152e0  0a 21 20 20 54 68 65 20  69 64 65 61 20 69 73 20  |.!  The idea is |
000152f0  74 68 61 74 20 22 72 65  64 20 70 61 6e 69 63 20  |that "red panic |
00015300  62 75 74 74 6f 6e 22 20  69 73 20 62 65 74 74 65  |button" is bette|
00015310  72 20 74 68 61 6e 20 22  72 65 64 20 62 75 74 74  |r than "red butt|
00015320  6f 6e 22 20 6f 72 20 22  70 61 6e 69 63 22 2e 0a  |on" or "panic"..|
00015330  21 0a 21 20 20 6e 75 6d  62 65 72 5f 6d 61 74 63  |!.!  number_matc|
00015340  68 65 64 20 28 74 68 65  20 6e 75 6d 62 65 72 20  |hed (the number |
00015350  6f 66 20 77 6f 72 64 73  20 6d 61 74 63 68 65 64  |of words matched|
00015360  29 20 69 73 20 73 65 74  20 74 6f 20 74 68 65 20  |) is set to the |
00015370  63 75 72 72 65 6e 74 20  6c 65 76 65 6c 0a 21 20  |current level.! |
00015380  20 6f 66 20 71 75 61 6c  69 74 79 2e 0a 21 0a 21  | of quality..!.!|
00015390  20 20 49 66 20 50 6c 61  63 65 49 6e 53 63 6f 70  |  If PlaceInScop|
000153a0  65 20 68 61 73 20 63 6f  6d 70 6c 69 63 61 74 65  |e has complicate|
000153b0  64 20 6d 61 74 74 65 72  73 2c 20 77 65 20 61 6c  |d matters, we al|
000153c0  73 6f 20 6e 65 65 64 20  6e 6f 74 20 74 6f 20 6d  |so need not to m|
000153d0  61 74 63 68 0a 21 20 20  73 6f 6d 65 74 68 69 6e  |atch.!  somethin|
000153e0  67 20 61 20 73 65 63 6f  6e 64 20 74 69 6d 65 2e  |g a second time.|
000153f0  0a 21 20 2d 2d 2d 2d 2d  2d 2d 2d 2d 2d 2d 2d 2d  |.! -------------|
00015400  2d 2d 2d 2d 2d 2d 2d 2d  2d 2d 2d 2d 2d 2d 2d 2d  |----------------|
*
00015430  2d 2d 2d 2d 2d 2d 2d 2d  2d 2d 2d 2d 2d 2d 2d 0a  |---------------.|
00015440  0a 5b 20 4d 61 6b 65 4d  61 74 63 68 20 6f 62 6a  |.[ MakeMatch obj|
00015450  20 71 75 61 6c 69 74 79  20 69 3b 0a 20 20 20 69  | quality i;.   i|
00015460  66 20 28 70 61 72 73 65  72 5f 74 72 61 63 65 3e  |f (parser_trace>|
00015470  3d 35 29 20 70 72 69 6e  74 20 22 20 20 20 20 4d  |=5) print "    M|
00015480  61 74 63 68 20 77 69 74  68 20 71 75 61 6c 69 74  |atch with qualit|
00015490  79 20 22 2c 71 75 61 6c  69 74 79 2c 22 5e 22 3b  |y ",quality,"^";|
000154a0  0a 20 20 20 69 66 20 28  74 6f 6b 65 6e 5f 77 61  |.   if (token_wa|
000154b0  73 7e 3d 30 20 26 26 20  55 73 65 72 46 69 6c 74  |s~=0 && UserFilt|
000154c0  65 72 28 6f 62 6a 29 3d  3d 30 29 0a 20 20 20 7b  |er(obj)==0).   {|
000154d0  20 20 20 69 66 20 28 70  61 72 73 65 72 5f 74 72  |   if (parser_tr|
000154e0  61 63 65 3e 3d 35 29 20  70 72 69 6e 74 20 22 20  |ace>=5) print " |
000154f0  20 20 20 4d 61 74 63 68  20 66 69 6c 74 65 72 65  |   Match filtere|
00015500  64 20 6f 75 74 5e 22 3b  0a 20 20 20 20 20 20 20  |d out^";.       |
00015510  72 74 72 75 65 3b 0a 20  20 20 7d 0a 20 20 20 69  |rtrue;.   }.   i|
00015520  66 20 28 71 75 61 6c 69  74 79 20 3c 20 6d 61 74  |f (quality < mat|
00015530  63 68 5f 6c 65 6e 67 74  68 29 20 72 74 72 75 65  |ch_length) rtrue|
00015540  3b 0a 20 20 20 69 66 20  28 71 75 61 6c 69 74 79  |;.   if (quality|
00015550  20 3e 20 6d 61 74 63 68  5f 6c 65 6e 67 74 68 29  | > match_length)|
00015560  20 7b 20 6d 61 74 63 68  5f 6c 65 6e 67 74 68 3d  | { match_length=|
00015570  71 75 61 6c 69 74 79 3b  20 6e 75 6d 62 65 72 5f  |quality; number_|
00015580  6d 61 74 63 68 65 64 3d  30 3b 20 7d 0a 20 20 20  |matched=0; }.   |
00015590  65 6c 73 65 0a 20 20 20  7b 20 20 20 69 66 20 28  |else.   {   if (|
000155a0  70 6c 61 63 65 64 5f 69  6e 5f 66 6c 61 67 3d 3d  |placed_in_flag==|
000155b0  31 29 0a 20 20 20 20 20  20 20 7b 20 20 20 66 6f  |1).       {   fo|
000155c0  72 20 28 69 3d 30 3a 69  3c 6e 75 6d 62 65 72 5f  |r (i=0:i<number_|
000155d0  6d 61 74 63 68 65 64 3a  69 2b 2b 29 0a 20 20 20  |matched:i++).   |
000155e0  20 20 20 20 20 20 20 20  20 20 20 20 69 66 20 28  |            if (|
000155f0  6d 61 74 63 68 5f 6c 69  73 74 2d 2d 3e 69 3d 3d  |match_list-->i==|
00015600  6f 62 6a 29 20 72 74 72  75 65 3b 0a 20 20 20 20  |obj) rtrue;.    |
00015610  20 20 20 7d 0a 20 20 20  7d 0a 20 20 20 6d 61 74  |   }.   }.   mat|
00015620  63 68 5f 6c 69 73 74 2d  2d 3e 6e 75 6d 62 65 72  |ch_list-->number|
00015630  5f 6d 61 74 63 68 65 64  2b 2b 20 3d 20 6f 62 6a  |_matched++ = obj|
00015640  3b 0a 20 20 20 69 66 20  28 70 61 72 73 65 72 5f  |;.   if (parser_|
00015650  74 72 61 63 65 3e 3d 35  29 20 70 72 69 6e 74 20  |trace>=5) print |
00015660  22 20 20 20 20 4d 61 74  63 68 20 61 64 64 65 64  |"    Match added|
00015670  20 74 6f 20 6c 69 73 74  5e 22 3b 0a 5d 3b 0a 0a  | to list^";.];..|
00015680  21 20 2d 2d 2d 2d 2d 2d  2d 2d 2d 2d 2d 2d 2d 2d  |! --------------|
00015690  2d 2d 2d 2d 2d 2d 2d 2d  2d 2d 2d 2d 2d 2d 2d 2d  |----------------|
*
000156c0  2d 2d 2d 2d 2d 2d 2d 2d  2d 2d 2d 2d 2d 2d 0a 21  |--------------.!|
000156d0  20 20 54 72 79 47 69 76  65 6e 4f 62 6a 65 63 74  |  TryGivenObject|
000156e0  20 74 72 69 65 73 20 74  6f 20 6d 61 74 63 68 20  | tries to match |
000156f0  61 73 20 6d 61 6e 79 20  77 6f 72 64 73 20 61 73  |as many words as|
00015700  20 70 6f 73 73 69 62 6c  65 20 69 6e 20 77 68 61  | possible in wha|
00015710  74 20 68 61 73 20 62 65  65 6e 0a 21 20 20 74 79  |t has been.!  ty|
00015720  70 65 64 20 74 6f 20 74  68 65 20 67 69 76 65 6e  |ped to the given|
00015730  20 6f 62 6a 65 63 74 2c  20 6f 62 6a 2e 20 20 49  | object, obj.  I|
00015740  66 20 69 74 20 6d 61 6e  61 67 65 73 20 61 6e 79  |f it manages any|
00015750  20 77 6f 72 64 73 20 6d  61 74 63 68 65 64 20 61  | words matched a|
00015760  74 20 61 6c 6c 2c 0a 21  20 20 69 74 20 63 61 6c  |t all,.!  it cal|
00015770  6c 73 20 4d 61 6b 65 4d  61 74 63 68 20 74 6f 20  |ls MakeMatch to |
00015780  73 61 79 20 73 6f 2e 20  20 54 68 65 72 65 20 69  |say so.  There i|
00015790  73 20 6e 6f 20 72 65 74  75 72 6e 20 76 61 6c 75  |s no return valu|
000157a0  65 2e 0a 21 20 2d 2d 2d  2d 2d 2d 2d 2d 2d 2d 2d  |e..! -----------|
000157b0  2d 2d 2d 2d 2d 2d 2d 2d  2d 2d 2d 2d 2d 2d 2d 2d  |----------------|
*
000157f0  2d 0a 0a 5b 20 54 72 79  47 69 76 65 6e 4f 62 6a  |-..[ TryGivenObj|
00015800  65 63 74 20 6f 62 6a 20  74 68 72 65 73 68 6f 6c  |ect obj threshol|
00015810  64 20 6b 3b 0a 0a 20 20  20 69 66 20 28 70 61 72  |d k;..   if (par|
00015820  73 65 72 5f 74 72 61 63  65 3e 3d 35 29 0a 20 20  |ser_trace>=5).  |
00015830  20 7b 20 20 20 70 72 69  6e 74 20 22 20 20 20 20  | {   print "    |
00015840  54 72 79 69 6e 67 20 22  3b 20 44 65 66 41 72 74  |Trying "; DefArt|
00015850  28 6f 62 6a 29 3b 0a 20  20 20 20 20 20 20 70 72  |(obj);.       pr|
00015860  69 6e 74 20 22 20 28 22  2c 20 6f 62 6a 2c 20 22  |int " (", obj, "|
00015870  29 20 61 74 20 77 6f 72  64 20 22 2c 20 77 6e 2c  |) at word ", wn,|
00015880  20 22 5e 22 3b 0a 20 20  20 7d 0a 0a 21 20 20 49  | "^";.   }..!  I|
00015890  66 20 69 6e 70 75 74 20  68 61 73 20 72 75 6e 20  |f input has run |
000158a0  6f 75 74 20 61 6e 64 20  77 65 27 72 65 20 69 6e  |out and we're in|
000158b0  20 69 6e 64 65 66 69 6e  69 74 65 20 6d 6f 64 65  | indefinite mode|
000158c0  2c 20 74 68 65 6e 20 61  6c 77 61 79 73 20 6d 61  |, then always ma|
000158d0  74 63 68 2c 0a 21 20 20  77 69 74 68 20 6f 6e 6c  |tch,.!  with onl|
000158e0  79 20 71 75 61 6c 69 74  79 20 30 20 28 74 68 69  |y quality 0 (thi|
000158f0  73 20 73 61 76 65 73 20  74 69 6d 65 29 2e 0a 0a  |s saves time)...|
00015900  20 20 20 69 66 20 28 69  6e 64 65 66 5f 6d 6f 64  |   if (indef_mod|
00015910  65 20 7e 3d 30 20 26 26  20 77 6e 20 3e 20 70 61  |e ~=0 && wn > pa|
00015920  72 73 65 2d 3e 31 29 20  7b 20 4d 61 6b 65 4d 61  |rse->1) { MakeMa|
00015930  74 63 68 28 6f 62 6a 2c  30 29 3b 20 72 66 61 6c  |tch(obj,0); rfal|
00015940  73 65 3b 20 7d 0a 0a 21  20 20 41 73 6b 20 74 68  |se; }..!  Ask th|
00015950  65 20 6f 62 6a 65 63 74  20 74 6f 20 70 61 72 73  |e object to pars|
00015960  65 20 69 74 73 65 6c 66  20 69 66 20 6e 65 63 65  |e itself if nece|
00015970  73 73 61 72 79 2c 20 73  69 74 74 69 6e 67 20 75  |ssary, sitting u|
00015980  70 20 61 6e 64 20 74 61  6b 69 6e 67 20 6e 6f 74  |p and taking not|
00015990  69 63 65 0a 21 20 20 69  66 20 69 74 20 73 61 79  |ice.!  if it say|
000159a0  73 20 74 68 65 20 70 6c  75 72 61 6c 20 77 61 73  |s the plural was|
000159b0  20 75 73 65 64 3a 0a 0a  20 20 20 69 66 20 28 6f  | used:..   if (o|
000159c0  62 6a 2e 70 61 72 73 65  5f 6e 61 6d 65 7e 3d 30  |bj.parse_name~=0|
000159d0  29 0a 20 20 20 7b 20 20  20 70 61 72 73 65 72 5f  |).   {   parser_|
000159e0  61 63 74 69 6f 6e 3d 2d  31 3b 0a 20 20 20 20 20  |action=-1;.     |
000159f0  20 20 6b 3d 52 75 6e 52  6f 75 74 69 6e 65 73 28  |  k=RunRoutines(|
00015a00  6f 62 6a 2c 70 61 72 73  65 5f 6e 61 6d 65 29 3b  |obj,parse_name);|
00015a10  0a 20 20 20 20 20 20 20  69 66 20 28 6b 3e 30 29  |.       if (k>0)|
00015a20  0a 20 20 20 20 20 20 20  7b 20 20 20 69 66 20 28  |.       {   if (|
00015a30  70 61 72 73 65 72 5f 61  63 74 69 6f 6e 20 3d 3d  |parser_action ==|
00015a40  20 23 23 50 6c 75 72 61  6c 46 6f 75 6e 64 29 0a  | ##PluralFound).|
00015a50  20 20 20 20 20 20 20 20  20 20 20 7b 20 20 20 69  |           {   i|
00015a60  66 20 28 61 6c 6c 6f 77  5f 70 6c 75 72 61 6c 73  |f (allow_plurals|
00015a70  20 3d 3d 20 30 29 20 6a  75 6d 70 20 4e 6f 57 6f  | == 0) jump NoWo|
00015a80  72 64 73 4d 61 74 63 68  3b 0a 20 20 20 20 20 20  |rdsMatch;.      |
00015a90  20 20 20 20 20 20 20 20  20 69 66 20 28 69 6e 64  |         if (ind|
00015aa0  65 66 5f 6d 6f 64 65 3d  3d 30 29 0a 20 20 20 20  |ef_mode==0).    |
00015ab0  20 20 20 20 20 20 20 20  20 20 20 7b 20 20 20 69  |           {   i|
00015ac0  6e 64 65 66 5f 6d 6f 64  65 3d 31 3b 20 69 6e 64  |ndef_mode=1; ind|
00015ad0  65 66 5f 74 79 70 65 3d  30 3b 20 69 6e 64 65 66  |ef_type=0; indef|
00015ae0  5f 77 61 6e 74 65 64 3d  30 3b 20 7d 0a 20 20 20  |_wanted=0; }.   |
00015af0  20 20 20 20 20 20 20 20  20 20 20 20 69 6e 64 65  |            inde|
00015b00  66 5f 74 79 70 65 3d 69  6e 64 65 66 5f 74 79 70  |f_type=indef_typ|
00015b10  65 20 7c 20 50 4c 55 52  41 4c 5f 42 49 54 3b 0a  |e | PLURAL_BIT;.|
00015b20  20 20 20 20 20 20 20 20  20 20 20 20 20 20 20 69  |               i|
00015b30  66 20 28 69 6e 64 65 66  5f 77 61 6e 74 65 64 3d  |f (indef_wanted=|
00015b40  3d 30 29 20 69 6e 64 65  66 5f 77 61 6e 74 65 64  |=0) indef_wanted|
00015b50  3d 31 30 30 3b 0a 20 20  20 20 20 20 20 20 20 20  |=100;.          |
00015b60  20 7d 0a 20 20 20 20 20  20 20 20 20 20 20 4d 61  | }.           Ma|
00015b70  6b 65 4d 61 74 63 68 28  6f 62 6a 2c 6b 29 3b 20  |keMatch(obj,k); |
00015b80  72 66 61 6c 73 65 3b 0a  20 20 20 20 20 20 20 7d  |rfalse;.       }|
00015b90  0a 20 20 20 20 20 20 20  69 66 20 28 6b 3d 3d 30  |.       if (k==0|
00015ba0  29 20 6a 75 6d 70 20 4e  6f 57 6f 72 64 73 4d 61  |) jump NoWordsMa|
00015bb0  74 63 68 3b 0a 20 20 20  7d 0a 0a 21 20 20 54 68  |tch;.   }..!  Th|
00015bc0  65 20 64 65 66 61 75 6c  74 20 61 6c 67 6f 72 69  |e default algori|
00015bd0  74 68 6d 20 69 73 20 73  69 6d 70 6c 79 20 74 6f  |thm is simply to|
00015be0  20 63 6f 75 6e 74 20 75  70 20 68 6f 77 20 6d 61  | count up how ma|
00015bf0  6e 79 20 77 6f 72 64 73  20 70 61 73 73 20 74 68  |ny words pass th|
00015c00  65 0a 21 20 20 52 65 66  65 72 73 20 74 65 73 74  |e.!  Refers test|
00015c10  3a 0a 0a 20 20 20 69 66  20 28 30 20 3d 3d 20 52  |:..   if (0 == R|
00015c20  65 66 65 72 73 28 6f 62  6a 2c 4e 6f 75 6e 57 6f  |efers(obj,NounWo|
00015c30  72 64 28 29 29 29 0a 20  20 20 7b 20 20 20 2e 4e  |rd())).   {   .N|
00015c40  6f 57 6f 72 64 73 4d 61  74 63 68 3b 0a 20 20 20  |oWordsMatch;.   |
00015c50  20 20 20 20 69 66 20 28  69 6e 64 65 66 5f 6d 6f  |    if (indef_mo|
00015c60  64 65 7e 3d 30 29 20 4d  61 6b 65 4d 61 74 63 68  |de~=0) MakeMatch|
00015c70  28 6f 62 6a 2c 30 29 3b  0a 20 20 20 20 20 20 20  |(obj,0);.       |
00015c80  72 66 61 6c 73 65 3b 0a  20 20 20 7d 0a 0a 20 20  |rfalse;.   }..  |
00015c90  20 74 68 72 65 73 68 6f  6c 64 3d 31 3b 0a 0a 20  | threshold=1;.. |
00015ca0  20 20 77 68 69 6c 65 20  28 30 7e 3d 52 65 66 65  |  while (0~=Refe|
00015cb0  72 73 28 6f 62 6a 2c 4e  65 78 74 57 6f 72 64 28  |rs(obj,NextWord(|
00015cc0  29 29 29 20 74 68 72 65  73 68 6f 6c 64 2b 2b 3b  |))) threshold++;|
00015cd0  0a 20 20 20 4d 61 6b 65  4d 61 74 63 68 28 6f 62  |.   MakeMatch(ob|
00015ce0  6a 2c 74 68 72 65 73 68  6f 6c 64 29 3b 0a 0a 20  |j,threshold);.. |
00015cf0  20 20 69 66 20 28 70 61  72 73 65 72 5f 74 72 61  |  if (parser_tra|
00015d00  63 65 3e 3d 35 29 20 70  72 69 6e 74 20 22 20 20  |ce>=5) print "  |
00015d10  20 20 4d 61 74 63 68 65  64 5e 22 3b 0a 5d 3b 0a  |  Matched^";.];.|
00015d20  0a 21 20 2d 2d 2d 2d 2d  2d 2d 2d 2d 2d 2d 2d 2d  |.! -------------|
00015d30  2d 2d 2d 2d 2d 2d 2d 2d  2d 2d 2d 2d 2d 2d 2d 2d  |----------------|
*
00015d60  2d 2d 2d 2d 2d 2d 2d 2d  2d 2d 2d 2d 2d 2d 2d 0a  |---------------.|
00015d70  21 20 20 52 65 66 65 72  73 20 77 6f 72 6b 73 20  |!  Refers works |
00015d80  6f 75 74 20 77 68 65 74  68 65 72 20 74 68 65 20  |out whether the |
00015d90  77 6f 72 64 20 77 69 74  68 20 64 69 63 74 69 6f  |word with dictio|
00015da0  6e 61 72 79 20 61 64 64  72 65 73 73 20 77 64 20  |nary address wd |
00015db0  63 61 6e 20 72 65 66 65  72 20 74 6f 0a 21 20 20  |can refer to.!  |
00015dc0  74 68 65 20 6f 62 6a 65  63 74 20 6f 62 6a 2c 20  |the object obj, |
00015dd0  62 79 20 73 65 65 69 6e  67 20 69 66 20 77 64 20  |by seeing if wd |
00015de0  69 73 20 6c 69 73 74 65  64 20 69 6e 20 74 68 65  |is listed in the|
00015df0  20 22 6e 61 6d 65 73 22  20 70 72 6f 70 65 72 74  | "names" propert|
00015e00  79 20 6f 66 20 6f 62 6a  2e 0a 21 20 2d 2d 2d 2d  |y of obj..! ----|
00015e10  2d 2d 2d 2d 2d 2d 2d 2d  2d 2d 2d 2d 2d 2d 2d 2d  |----------------|
*
00015e50  2d 2d 2d 2d 2d 2d 2d 2d  0a 0a 5b 20 52 65 66 65  |--------..[ Refe|
00015e60  72 73 20 6f 62 6a 20 77  64 20 20 20 6b 20 6c 20  |rs obj wd   k l |
00015e70  6d 3b 0a 20 20 20 20 69  66 20 28 6f 62 6a 3d 3d  |m;.    if (obj==|
00015e80  30 29 20 72 66 61 6c 73  65 3b 0a 20 20 20 20 6b  |0) rfalse;.    k|
00015e90  3d 6f 62 6a 2e 26 31 3b  20 6c 3d 28 6f 62 6a 2e  |=obj.&1; l=(obj.|
00015ea0  23 31 29 2f 32 2d 31 3b  0a 20 20 20 20 66 6f 72  |#1)/2-1;.    for|
00015eb0  20 28 6d 3d 30 3a 6d 3c  3d 6c 3a 6d 2b 2b 29 0a  | (m=0:m<=l:m++).|
00015ec0  20 20 20 20 20 20 20 20  69 66 20 28 77 64 3d 3d  |        if (wd==|
00015ed0  6b 2d 2d 3e 6d 29 20 72  74 72 75 65 3b 0a 20 20  |k-->m) rtrue;.  |
00015ee0  20 20 72 66 61 6c 73 65  3b 0a 5d 3b 0a 0a 21 20  |  rfalse;.];..! |
00015ef0  2d 2d 2d 2d 2d 2d 2d 2d  2d 2d 2d 2d 2d 2d 2d 2d  |----------------|
*
00015f30  2d 2d 2d 2d 2d 2d 2d 2d  2d 2d 2d 2d 0a 21 20 20  |------------.!  |
00015f40  4e 6f 75 6e 57 6f 72 64  20 28 77 68 69 63 68 20  |NounWord (which |
00015f50  74 61 6b 65 73 20 6e 6f  20 61 72 67 75 6d 65 6e  |takes no argumen|
00015f60  74 73 29 20 72 65 74 75  72 6e 73 3a 0a 21 0a 21  |ts) returns:.!.!|
00015f70  20 20 20 31 20 20 69 66  20 74 68 65 20 6e 65 78  |   1  if the nex|
00015f80  74 20 77 6f 72 64 20 69  73 20 22 69 74 22 20 6f  |t word is "it" o|
00015f90  72 20 22 74 68 65 6d 22  2c 0a 21 20 20 20 32 20  |r "them",.!   2 |
00015fa0  20 69 66 20 74 68 65 20  6e 65 78 74 20 77 6f 72  | if the next wor|
00015fb0  64 20 69 73 20 22 68 69  6d 22 2c 0a 21 20 20 20  |d is "him",.!   |
00015fc0  33 20 20 69 66 20 74 68  65 20 6e 65 78 74 20 77  |3  if the next w|
00015fd0  6f 72 64 20 69 73 20 22  68 65 72 22 2c 0a 21 20  |ord is "her",.! |
00015fe0  20 20 34 20 20 69 66 20  22 6d 65 22 2c 20 22 6d  |  4  if "me", "m|
00015ff0  79 73 65 6c 66 22 2c 20  22 73 65 6c 66 22 0a 21  |yself", "self".!|
00016000  20 20 20 30 20 20 69 66  20 74 68 65 20 6e 65 78  |   0  if the nex|
00016010  74 20 77 6f 72 64 20 69  73 20 75 6e 72 65 63 6f  |t word is unreco|
00016020  67 6e 69 73 65 64 20 6f  72 20 64 6f 65 73 20 6e  |gnised or does n|
00016030  6f 74 20 63 61 72 72 79  20 74 68 65 20 22 6e 6f  |ot carry the "no|
00016040  75 6e 22 20 62 69 74 20  69 6e 0a 21 20 20 20 20  |un" bit in.!    |
00016050  20 20 69 74 73 20 64 69  63 74 69 6f 6e 61 72 79  |  its dictionary|
00016060  20 65 6e 74 72 79 2c 0a  21 20 20 20 6f 72 20 74  | entry,.!   or t|
00016070  68 65 20 61 64 64 72 65  73 73 20 69 6e 20 74 68  |he address in th|
00016080  65 20 64 69 63 74 69 6f  6e 61 72 79 20 69 66 20  |e dictionary if |
00016090  69 74 20 69 73 20 61 20  72 65 63 6f 67 6e 69 73  |it is a recognis|
000160a0  65 64 20 6e 6f 75 6e 2e  0a 21 0a 21 20 20 54 68  |ed noun..!.!  Th|
000160b0  65 20 22 63 75 72 72 65  6e 74 20 77 6f 72 64 22  |e "current word"|
000160c0  20 6d 61 72 6b 65 72 20  6d 6f 76 65 73 20 6f 6e  | marker moves on|
000160d0  20 6f 6e 65 2e 0a 21 20  2d 2d 2d 2d 2d 2d 2d 2d  | one..! --------|
000160e0  2d 2d 2d 2d 2d 2d 2d 2d  2d 2d 2d 2d 2d 2d 2d 2d  |----------------|
*
00016120  2d 2d 2d 2d 0a 0a 5b 20  4e 6f 75 6e 57 6f 72 64  |----..[ NounWord|
00016130  20 69 3b 0a 20 20 20 69  3d 4e 65 78 74 57 6f 72  | i;.   i=NextWor|
00016140  64 28 29 3b 0a 20 20 20  69 66 20 28 69 3d 3d 27  |d();.   if (i=='|
00016150  69 74 27 20 6f 72 20 27  74 68 65 6d 27 29 20 72  |it' or 'them') r|
00016160  65 74 75 72 6e 20 31 3b  0a 20 20 20 69 66 20 28  |eturn 1;.   if (|
00016170  69 3d 3d 27 68 69 6d 27  29 20 72 65 74 75 72 6e  |i=='him') return|
00016180  20 32 3b 0a 20 20 20 69  66 20 28 69 3d 3d 27 68  | 2;.   if (i=='h|
00016190  65 72 27 29 20 72 65 74  75 72 6e 20 33 3b 0a 20  |er') return 3;. |
000161a0  20 20 69 66 20 28 69 3d  3d 27 6d 65 27 20 6f 72  |  if (i=='me' or|
000161b0  20 27 6d 79 73 65 6c 66  27 20 6f 72 20 27 73 65  | 'myself' or 'se|
000161c0  6c 66 27 29 20 72 65 74  75 72 6e 20 34 3b 0a 20  |lf') return 4;. |
000161d0  20 20 69 66 20 28 69 3d  3d 30 29 20 72 66 61 6c  |  if (i==0) rfal|
000161e0  73 65 3b 0a 20 20 20 69  66 20 28 28 69 2d 3e 23  |se;.   if ((i->#|
000161f0  64 69 63 74 5f 70 61 72  31 29 26 31 32 38 20 3d  |dict_par1)&128 =|
00016200  3d 20 30 29 20 72 66 61  6c 73 65 3b 0a 20 20 20  |= 0) rfalse;.   |
00016210  72 65 74 75 72 6e 20 69  3b 0a 5d 3b 0a 0a 21 20  |return i;.];..! |
00016220  2d 2d 2d 2d 2d 2d 2d 2d  2d 2d 2d 2d 2d 2d 2d 2d  |----------------|
*
00016260  2d 2d 2d 2d 2d 2d 2d 2d  2d 2d 2d 2d 0a 21 20 20  |------------.!  |
00016270  41 64 6a 65 63 74 69 76  65 20 28 77 68 69 63 68  |Adjective (which|
00016280  20 74 61 6b 65 73 20 6e  6f 20 61 72 67 75 6d 65  | takes no argume|
00016290  6e 74 73 29 20 72 65 74  75 72 6e 73 3a 0a 21 0a  |nts) returns:.!.|
000162a0  21 20 20 20 30 20 20 69  66 20 74 68 65 20 6e 65  |!   0  if the ne|
000162b0  78 74 20 77 6f 72 64 20  69 73 20 6c 69 73 74 65  |xt word is liste|
000162c0  64 20 69 6e 20 74 68 65  20 64 69 63 74 69 6f 6e  |d in the diction|
000162d0  61 72 79 20 61 73 20 70  6f 73 73 69 62 6c 79 20  |ary as possibly |
000162e0  61 6e 20 61 64 6a 65 63  74 69 76 65 2c 0a 21 20  |an adjective,.! |
000162f0  20 20 6f 72 20 69 74 73  20 61 64 6a 65 63 74 69  |  or its adjecti|
00016300  76 65 20 6e 75 6d 62 65  72 20 69 66 20 69 74 20  |ve number if it |
00016310  69 73 2e 0a 21 0a 21 20  20 54 68 65 20 22 63 75  |is..!.!  The "cu|
00016320  72 72 65 6e 74 20 77 6f  72 64 22 20 6d 61 72 6b  |rrent word" mark|
00016330  65 72 20 6d 6f 76 65 73  20 6f 6e 20 6f 6e 65 2e  |er moves on one.|
00016340  0a 21 20 2d 2d 2d 2d 2d  2d 2d 2d 2d 2d 2d 2d 2d  |.! -------------|
00016350  2d 2d 2d 2d 2d 2d 2d 2d  2d 2d 2d 2d 2d 2d 2d 2d  |----------------|
*
00016380  2d 2d 2d 2d 2d 2d 2d 2d  2d 2d 2d 2d 2d 2d 2d 0a  |---------------.|
00016390  0a 5b 20 41 64 6a 65 63  74 69 76 65 20 69 20 6a  |.[ Adjective i j|
000163a0  3b 0a 20 20 20 6a 3d 4e  65 78 74 57 6f 72 64 28  |;.   j=NextWord(|
000163b0  29 3b 0a 20 20 20 69 66  20 28 6a 3d 3d 30 29 20  |);.   if (j==0) |
000163c0  72 66 61 6c 73 65 3b 0a  20 20 20 69 3d 6a 2d 3e  |rfalse;.   i=j->|
000163d0  23 64 69 63 74 5f 70 61  72 31 3b 0a 20 20 20 69  |#dict_par1;.   i|
000163e0  66 20 28 69 26 38 20 3d  3d 20 30 29 20 72 66 61  |f (i&8 == 0) rfa|
000163f0  6c 73 65 3b 0a 20 20 20  72 65 74 75 72 6e 28 6a  |lse;.   return(j|
00016400  2d 3e 23 64 69 63 74 5f  70 61 72 33 29 3b 0a 5d  |->#dict_par3);.]|
00016410  3b 0a 0a 21 20 2d 2d 2d  2d 2d 2d 2d 2d 2d 2d 2d  |;..! -----------|
00016420  2d 2d 2d 2d 2d 2d 2d 2d  2d 2d 2d 2d 2d 2d 2d 2d  |----------------|
*
00016460  2d 0a 21 20 20 41 64 6a  65 63 74 69 76 65 41 64  |-.!  AdjectiveAd|
00016470  64 72 65 73 73 20 77 6f  72 6b 73 20 6f 75 74 20  |dress works out |
00016480  74 68 65 20 61 64 64 72  65 73 73 20 69 6e 20 74  |the address in t|
00016490  68 65 20 64 69 63 74 69  6f 6e 61 72 79 20 6f 66  |he dictionary of|
000164a0  20 74 68 65 20 77 6f 72  64 0a 21 20 20 63 6f 72  | the word.!  cor|
000164b0  72 65 73 70 6f 6e 64 69  6e 67 20 74 6f 20 74 68  |responding to th|
000164c0  65 20 67 69 76 65 6e 20  61 64 6a 65 63 74 69 76  |e given adjectiv|
000164d0  65 20 6e 75 6d 62 65 72  2e 0a 21 0a 21 20 20 49  |e number..!.!  I|
000164e0  74 20 73 68 6f 75 6c 64  20 6e 65 76 65 72 20 70  |t should never p|
000164f0  72 6f 64 75 63 65 20 74  68 65 20 67 69 76 65 6e  |roduce the given|
00016500  20 65 72 72 6f 72 20 28  77 68 69 63 68 20 77 6f  | error (which wo|
00016510  75 6c 64 20 6d 65 61 6e  20 74 68 61 74 20 49 6e  |uld mean that In|
00016520  66 6f 72 6d 0a 21 20 20  68 61 64 20 73 65 74 20  |form.!  had set |
00016530  75 70 20 74 68 65 20 61  64 6a 65 63 74 69 76 65  |up the adjective|
00016540  73 20 74 61 62 6c 65 20  69 6e 63 6f 72 72 65 63  |s table incorrec|
00016550  74 6c 79 29 2e 0a 21 20  2d 2d 2d 2d 2d 2d 2d 2d  |tly)..! --------|
00016560  2d 2d 2d 2d 2d 2d 2d 2d  2d 2d 2d 2d 2d 2d 2d 2d  |----------------|
*
000165a0  2d 2d 2d 2d 0a 0a 5b 20  41 64 6a 65 63 74 69 76  |----..[ Adjectiv|
000165b0  65 41 64 64 72 65 73 73  20 6e 75 6d 62 65 72 20  |eAddress number |
000165c0  6d 3b 0a 20 20 20 6d 3d  23 61 64 6a 65 63 74 69  |m;.   m=#adjecti|
000165d0  76 65 73 5f 74 61 62 6c  65 3b 0a 20 20 20 66 6f  |ves_table;.   fo|
000165e0  72 20 28 3a 3a 29 0a 20  20 20 7b 20 20 20 69 66  |r (::).   {   if|
000165f0  20 28 6e 75 6d 62 65 72  3d 3d 6d 2d 2d 3e 31 29  | (number==m-->1)|
00016600  20 72 65 74 75 72 6e 20  6d 2d 2d 3e 30 3b 0a 20  | return m-->0;. |
00016610  20 20 20 20 20 20 6d 3d  6d 2b 34 3b 0a 20 20 20  |      m=m+4;.   |
00016620  7d 0a 20 20 20 6d 3d 23  61 64 6a 65 63 74 69 76  |}.   m=#adjectiv|
00016630  65 73 5f 74 61 62 6c 65  3b 0a 20 20 20 70 72 69  |es_table;.   pri|
00016640  6e 74 20 22 3c 41 64 6a  65 63 74 69 76 65 20 6e  |nt "<Adjective n|
00016650  6f 74 20 66 6f 75 6e 64  3e 22 3b 0a 20 20 20 72  |ot found>";.   r|
00016660  65 74 75 72 6e 20 6d 3b  0a 5d 3b 0a 0a 21 20 2d  |eturn m;.];..! -|
00016670  2d 2d 2d 2d 2d 2d 2d 2d  2d 2d 2d 2d 2d 2d 2d 2d  |----------------|
*
000166b0  2d 2d 2d 2d 2d 2d 2d 2d  2d 2d 2d 0a 21 20 20 4e  |-----------.!  N|
000166c0  65 78 74 57 6f 72 64 20  28 77 68 69 63 68 20 74  |extWord (which t|
000166d0  61 6b 65 73 20 6e 6f 20  61 72 67 75 6d 65 6e 74  |akes no argument|
000166e0  73 29 20 72 65 74 75 72  6e 73 3a 0a 21 0a 21 20  |s) returns:.!.! |
000166f0  20 30 20 20 20 20 20 20  20 20 20 20 20 20 69 66  | 0            if|
00016700  20 74 68 65 20 6e 65 78  74 20 77 6f 72 64 20 69  | the next word i|
00016710  73 20 75 6e 72 65 63 6f  67 6e 69 73 65 64 2c 0a  |s unrecognised,.|
00016720  21 20 20 63 6f 6d 6d 61  5f 77 6f 72 64 20 20 20  |!  comma_word   |
00016730  69 66 20 69 74 20 69 73  20 61 20 63 6f 6d 6d 61  |if it is a comma|
00016740  20 63 68 61 72 61 63 74  65 72 0a 21 20 20 20 20  | character.!    |
00016750  20 20 20 20 20 20 20 20  20 20 20 28 77 68 69 63  |           (whic|
00016760  68 20 69 73 20 74 72 65  61 74 65 64 20 6f 64 64  |h is treated odd|
00016770  6c 79 20 62 79 20 74 68  65 20 5a 2d 6d 61 63 68  |ly by the Z-mach|
00016780  69 6e 65 2c 20 68 65 6e  63 65 20 74 68 65 20 63  |ine, hence the c|
00016790  6f 64 65 29 0a 21 20 20  6f 72 20 74 68 65 20 64  |ode).!  or the d|
000167a0  69 63 74 69 6f 6e 61 72  79 20 61 64 64 72 65 73  |ictionary addres|
000167b0  73 20 69 66 20 69 74 20  69 73 20 72 65 63 6f 67  |s if it is recog|
000167c0  6e 69 73 65 64 2e 0a 21  0a 21 20 20 54 68 65 20  |nised..!.!  The |
000167d0  22 63 75 72 72 65 6e 74  20 77 6f 72 64 22 20 6d  |"current word" m|
000167e0  61 72 6b 65 72 20 69 73  20 6d 6f 76 65 64 20 6f  |arker is moved o|
000167f0  6e 2e 0a 21 20 2d 2d 2d  2d 2d 2d 2d 2d 2d 2d 2d  |n..! -----------|
00016800  2d 2d 2d 2d 2d 2d 2d 2d  2d 2d 2d 2d 2d 2d 2d 2d  |----------------|
*
00016840  2d 0a 0a 5b 20 4e 65 78  74 57 6f 72 64 20 69 20  |-..[ NextWord i |
00016850  6a 20 6b 3b 0a 0a 20 20  20 69 66 20 28 77 6e 20  |j k;..   if (wn |
00016860  3e 20 70 61 72 73 65 2d  3e 31 29 20 7b 20 77 6e  |> parse->1) { wn|
00016870  2b 2b 3b 20 72 66 61 6c  73 65 3b 20 7d 0a 20 20  |++; rfalse; }.  |
00016880  20 69 3d 77 6e 2a 32 2d  31 3b 20 77 6e 2b 2b 3b  | i=wn*2-1; wn++;|
00016890  0a 20 20 20 6a 3d 70 61  72 73 65 2d 2d 3e 69 3b  |.   j=parse-->i;|
000168a0  0a 20 20 20 69 66 20 28  6a 3d 3d 30 29 0a 20 20  |.   if (j==0).  |
000168b0  20 7b 20 20 20 6b 3d 77  6e 2a 34 2d 33 3b 20 69  | {   k=wn*4-3; i|
000168c0  3d 62 75 66 66 65 72 2d  3e 28 70 61 72 73 65 2d  |=buffer->(parse-|
000168d0  3e 6b 29 3b 0a 20 20 20  20 20 20 20 69 66 20 28  |>k);.       if (|
000168e0  69 3d 3d 27 2c 27 29 20  6a 3d 63 6f 6d 6d 61 5f  |i==',') j=comma_|
000168f0  77 6f 72 64 3b 0a 20 20  20 20 20 20 20 69 66 20  |word;.       if |
00016900  28 69 3d 3d 27 2e 27 29  20 6a 3d 27 74 68 65 6e  |(i=='.') j='then|
00016910  27 3b 0a 20 20 20 7d 0a  20 20 20 72 65 74 75 72  |';.   }.   retur|
00016920  6e 20 6a 3b 0a 5d 3b 20  20 20 0a 0a 21 20 2d 2d  |n j;.];   ..! --|
00016930  2d 2d 2d 2d 2d 2d 2d 2d  2d 2d 2d 2d 2d 2d 2d 2d  |----------------|
*
00016970  2d 2d 2d 2d 2d 2d 2d 2d  2d 2d 0a 21 20 20 54 72  |----------.!  Tr|
00016980  79 4e 75 6d 62 65 72 20  69 73 20 74 68 65 20 6f  |yNumber is the o|
00016990  6e 6c 79 20 72 6f 75 74  69 6e 65 20 77 68 69 63  |nly routine whic|
000169a0  68 20 72 65 61 6c 6c 79  20 64 6f 65 73 20 61 6e  |h really does an|
000169b0  79 20 63 68 61 72 61 63  74 65 72 2d 6c 65 76 65  |y character-leve|
000169c0  6c 0a 21 20 20 70 61 72  73 69 6e 67 2c 20 73 69  |l.!  parsing, si|
000169d0  6e 63 65 20 74 68 61 74  27 73 20 6e 6f 72 6d 61  |nce that's norma|
000169e0  6c 6c 79 20 6c 65 66 74  20 74 6f 20 74 68 65 20  |lly left to the |
000169f0  5a 2d 6d 61 63 68 69 6e  65 2e 0a 21 20 20 49 74  |Z-machine..!  It|
00016a00  20 74 61 6b 65 73 20 77  6f 72 64 20 6e 75 6d 62  | takes word numb|
00016a10  65 72 20 22 77 6f 72 64  6e 75 6d 22 20 61 6e 64  |er "wordnum" and|
00016a20  20 74 72 69 65 73 20 74  6f 20 70 61 72 73 65 20  | tries to parse |
00016a30  69 74 20 61 73 20 61 6e  20 28 75 6e 73 69 67 6e  |it as an (unsign|
00016a40  65 64 29 0a 21 20 20 64  65 63 69 6d 61 6c 20 6e  |ed).!  decimal n|
00016a50  75 6d 62 65 72 2c 20 72  65 74 75 72 6e 69 6e 67  |umber, returning|
00016a60  0a 21 0a 21 20 20 2d 31  30 30 30 20 20 20 20 20  |.!.!  -1000     |
00016a70  20 20 20 20 20 20 20 20  20 20 20 69 66 20 69 74  |           if it|
00016a80  20 69 73 20 6e 6f 74 20  61 20 6e 75 6d 62 65 72  | is not a number|
00016a90  0a 21 20 20 74 68 65 20  6e 75 6d 62 65 72 20 20  |.!  the number  |
00016aa0  20 20 20 20 20 20 20 20  20 69 66 20 69 74 20 68  |         if it h|
00016ab0  61 73 20 62 65 74 77 65  65 6e 20 31 20 61 6e 64  |as between 1 and|
00016ac0  20 34 20 64 69 67 69 74  73 0a 21 20 20 31 30 30  | 4 digits.!  100|
00016ad0  30 30 20 20 20 20 20 20  20 20 20 20 20 20 20 20  |00              |
00016ae0  20 20 69 66 20 69 74 20  68 61 73 20 35 20 6f 72  |  if it has 5 or|
00016af0  20 6d 6f 72 65 20 64 69  67 69 74 73 2e 0a 21 0a  | more digits..!.|
00016b00  21 20 20 28 54 68 65 20  64 61 6e 67 65 72 20 6f  |!  (The danger o|
00016b10  66 20 61 6c 6c 6f 77 69  6e 67 20 35 20 64 69 67  |f allowing 5 dig|
00016b20  69 74 73 20 69 73 20 74  68 61 74 20 5a 2d 6d 61  |its is that Z-ma|
00016b30  63 68 69 6e 65 20 69 6e  74 65 67 65 72 73 20 61  |chine integers a|
00016b40  72 65 20 6f 6e 6c 79 0a  21 20 20 31 36 20 62 69  |re only.!  16 bi|
00016b50  74 73 20 6c 6f 6e 67 2c  20 61 6e 64 20 61 6e 79  |ts long, and any|
00016b60  77 61 79 20 74 68 69 73  20 69 73 6e 27 74 20 6d  |way this isn't m|
00016b70  65 61 6e 74 20 74 6f 20  62 65 20 70 65 72 66 65  |eant to be perfe|
00016b80  63 74 2e 29 0a 21 0a 21  20 20 55 73 69 6e 67 20  |ct.).!.!  Using |
00016b90  4e 75 6d 62 65 72 57 6f  72 64 2c 20 69 74 20 61  |NumberWord, it a|
00016ba0  6c 73 6f 20 63 61 74 63  68 65 73 20 22 6f 6e 65  |lso catches "one|
00016bb0  22 20 75 70 20 74 6f 20  22 74 77 65 6e 74 79 22  |" up to "twenty"|
00016bc0  2e 0a 21 0a 21 20 20 4e  6f 74 65 20 74 68 61 74  |..!.!  Note that|
00016bd0  20 61 20 67 61 6d 65 20  63 61 6e 20 70 72 6f 76  | a game can prov|
00016be0  69 64 65 20 61 20 50 61  72 73 65 4e 75 6d 62 65  |ide a ParseNumbe|
00016bf0  72 20 72 6f 75 74 69 6e  65 20 77 68 69 63 68 20  |r routine which |
00016c00  74 61 6b 65 73 20 70 72  69 6f 72 69 74 79 2c 0a  |takes priority,.|
00016c10  21 20 20 74 6f 20 65 6e  61 62 6c 65 20 70 61 72  |!  to enable par|
00016c20  73 69 6e 67 20 6f 66 20  6f 64 64 65 72 20 6e 75  |sing of odder nu|
00016c30  6d 62 65 72 73 20 28 22  78 34 35 79 31 32 22 2c  |mbers ("x45y12",|
00016c40  20 73 61 79 29 2e 0a 21  20 2d 2d 2d 2d 2d 2d 2d  | say)..! -------|
00016c50  2d 2d 2d 2d 2d 2d 2d 2d  2d 2d 2d 2d 2d 2d 2d 2d  |----------------|
*
00016c90  2d 2d 2d 2d 2d 0a 0a 5b  20 54 72 79 4e 75 6d 62  |-----..[ TryNumb|
00016ca0  65 72 20 77 6f 72 64 6e  75 6d 20 20 20 69 20 6a  |er wordnum   i j|
00016cb0  20 63 20 6e 75 6d 20 6c  65 6e 20 6d 75 6c 20 74  | c num len mul t|
00016cc0  6f 74 20 64 20 64 69 67  69 74 3b 0a 0a 20 20 20  |ot d digit;..   |
00016cd0  69 3d 77 6e 3b 20 77 6e  3d 77 6f 72 64 6e 75 6d  |i=wn; wn=wordnum|
00016ce0  3b 20 6a 3d 4e 65 78 74  57 6f 72 64 28 29 3b 20  |; j=NextWord(); |
00016cf0  77 6e 3d 69 3b 0a 20 20  20 6a 3d 4e 75 6d 62 65  |wn=i;.   j=Numbe|
00016d00  72 57 6f 72 64 28 6a 29  3b 20 69 66 20 28 6a 3e  |rWord(j); if (j>|
00016d10  3d 31 29 20 72 65 74 75  72 6e 20 6a 3b 0a 0a 20  |=1) return j;.. |
00016d20  20 20 69 3d 77 6f 72 64  6e 75 6d 2a 34 2b 31 3b  |  i=wordnum*4+1;|
00016d30  20 6a 3d 70 61 72 73 65  2d 3e 69 3b 20 6e 75 6d  | j=parse->i; num|
00016d40  3d 6a 2b 62 75 66 66 65  72 3b 20 6c 65 6e 3d 70  |=j+buffer; len=p|
00016d50  61 72 73 65 2d 3e 28 69  2d 31 29 3b 0a 0a 20 20  |arse->(i-1);..  |
00016d60  20 74 6f 74 3d 50 61 72  73 65 4e 75 6d 62 65 72  | tot=ParseNumber|
00016d70  28 6e 75 6d 2c 20 6c 65  6e 29 3b 20 20 69 66 20  |(num, len);  if |
00016d80  28 74 6f 74 7e 3d 30 29  20 72 65 74 75 72 6e 20  |(tot~=0) return |
00016d90  74 6f 74 3b 0a 0a 20 20  20 69 66 20 28 6c 65 6e  |tot;..   if (len|
00016da0  3e 3d 34 29 20 6d 75 6c  3d 31 30 30 30 3b 0a 20  |>=4) mul=1000;. |
00016db0  20 20 69 66 20 28 6c 65  6e 3d 3d 33 29 20 6d 75  |  if (len==3) mu|
00016dc0  6c 3d 31 30 30 3b 0a 20  20 20 69 66 20 28 6c 65  |l=100;.   if (le|
00016dd0  6e 3d 3d 32 29 20 6d 75  6c 3d 31 30 3b 0a 20 20  |n==2) mul=10;.  |
00016de0  20 69 66 20 28 6c 65 6e  3d 3d 31 29 20 6d 75 6c  | if (len==1) mul|
00016df0  3d 31 3b 0a 0a 20 20 20  74 6f 74 3d 30 3b 20 63  |=1;..   tot=0; c|
00016e00  3d 30 3b 20 6c 65 6e 3d  6c 65 6e 2d 31 3b 0a 0a  |=0; len=len-1;..|
00016e10  20 20 20 66 6f 72 20 28  63 3d 30 3a 63 3c 3d 6c  |   for (c=0:c<=l|
00016e20  65 6e 3a 63 2b 2b 29 0a  20 20 20 7b 20 20 20 64  |en:c++).   {   d|
00016e30  69 67 69 74 3d 6e 75 6d  2d 3e 63 3b 0a 20 20 20  |igit=num->c;.   |
00016e40  20 20 20 20 69 66 20 28  64 69 67 69 74 3d 3d 27  |    if (digit=='|
00016e50  30 27 29 20 7b 20 64 3d  30 3b 20 6a 75 6d 70 20  |0') { d=0; jump |
00016e60  64 69 67 6f 6b 3b 20 7d  0a 20 20 20 20 20 20 20  |digok; }.       |
00016e70  69 66 20 28 64 69 67 69  74 3d 3d 27 31 27 29 20  |if (digit=='1') |
00016e80  7b 20 64 3d 31 3b 20 6a  75 6d 70 20 64 69 67 6f  |{ d=1; jump digo|
00016e90  6b 3b 20 7d 0a 20 20 20  20 20 20 20 69 66 20 28  |k; }.       if (|
00016ea0  64 69 67 69 74 3d 3d 27  32 27 29 20 7b 20 64 3d  |digit=='2') { d=|
00016eb0  32 3b 20 6a 75 6d 70 20  64 69 67 6f 6b 3b 20 7d  |2; jump digok; }|
00016ec0  0a 20 20 20 20 20 20 20  69 66 20 28 64 69 67 69  |.       if (digi|
00016ed0  74 3d 3d 27 33 27 29 20  7b 20 64 3d 33 3b 20 6a  |t=='3') { d=3; j|
00016ee0  75 6d 70 20 64 69 67 6f  6b 3b 20 7d 0a 20 20 20  |ump digok; }.   |
00016ef0  20 20 20 20 69 66 20 28  64 69 67 69 74 3d 3d 27  |    if (digit=='|
00016f00  34 27 29 20 7b 20 64 3d  34 3b 20 6a 75 6d 70 20  |4') { d=4; jump |
00016f10  64 69 67 6f 6b 3b 20 7d  0a 20 20 20 20 20 20 20  |digok; }.       |
00016f20  69 66 20 28 64 69 67 69  74 3d 3d 27 35 27 29 20  |if (digit=='5') |
00016f30  7b 20 64 3d 35 3b 20 6a  75 6d 70 20 64 69 67 6f  |{ d=5; jump digo|
00016f40  6b 3b 20 7d 0a 20 20 20  20 20 20 20 69 66 20 28  |k; }.       if (|
00016f50  64 69 67 69 74 3d 3d 27  36 27 29 20 7b 20 64 3d  |digit=='6') { d=|
00016f60  36 3b 20 6a 75 6d 70 20  64 69 67 6f 6b 3b 20 7d  |6; jump digok; }|
00016f70  0a 20 20 20 20 20 20 20  69 66 20 28 64 69 67 69  |.       if (digi|
00016f80  74 3d 3d 27 37 27 29 20  7b 20 64 3d 37 3b 20 6a  |t=='7') { d=7; j|
00016f90  75 6d 70 20 64 69 67 6f  6b 3b 20 7d 0a 20 20 20  |ump digok; }.   |
00016fa0  20 20 20 20 69 66 20 28  64 69 67 69 74 3d 3d 27  |    if (digit=='|
00016fb0  38 27 29 20 7b 20 64 3d  38 3b 20 6a 75 6d 70 20  |8') { d=8; jump |
00016fc0  64 69 67 6f 6b 3b 20 7d  0a 20 20 20 20 20 20 20  |digok; }.       |
00016fd0  69 66 20 28 64 69 67 69  74 3d 3d 27 39 27 29 20  |if (digit=='9') |
00016fe0  7b 20 64 3d 39 3b 20 6a  75 6d 70 20 64 69 67 6f  |{ d=9; jump digo|
00016ff0  6b 3b 20 7d 0a 20 20 20  20 20 20 20 72 65 74 75  |k; }.       retu|
00017000  72 6e 20 2d 31 30 30 30  3b 0a 20 20 20 20 20 2e  |rn -1000;.     .|
00017010  64 69 67 6f 6b 3b 0a 20  20 20 20 20 20 20 74 6f  |digok;.       to|
00017020  74 3d 74 6f 74 2b 6d 75  6c 2a 64 3b 20 6d 75 6c  |t=tot+mul*d; mul|
00017030  3d 6d 75 6c 2f 31 30 3b  0a 20 20 20 7d 0a 20 20  |=mul/10;.   }.  |
00017040  20 69 66 20 28 6c 65 6e  3e 33 29 20 74 6f 74 3d  | if (len>3) tot=|
00017050  31 30 30 30 30 3b 0a 20  20 20 72 65 74 75 72 6e  |10000;.   return|
00017060  20 74 6f 74 3b 0a 5d 3b  0a 0a 21 20 2d 2d 2d 2d  | tot;.];..! ----|
00017070  2d 2d 2d 2d 2d 2d 2d 2d  2d 2d 2d 2d 2d 2d 2d 2d  |----------------|
*
000170b0  2d 2d 2d 2d 2d 2d 2d 2d  0a 21 20 20 52 65 73 65  |--------.!  Rese|
000170c0  74 56 61 67 75 65 57 6f  72 64 73 20 64 6f 65 73  |tVagueWords does|
000170d0  2c 20 61 73 73 75 6d 69  6e 67 20 74 68 61 74 20  |, assuming that |
000170e0  69 20 77 61 73 20 74 68  65 20 6f 62 6a 65 63 74  |i was the object|
000170f0  20 6c 61 73 74 20 72 65  66 65 72 72 65 64 20 74  | last referred t|
00017100  6f 0a 21 20 2d 2d 2d 2d  2d 2d 2d 2d 2d 2d 2d 2d  |o.! ------------|
00017110  2d 2d 2d 2d 2d 2d 2d 2d  2d 2d 2d 2d 2d 2d 2d 2d  |----------------|
*
00017150  0a 0a 5b 20 52 65 73 65  74 56 61 67 75 65 57 6f  |..[ ResetVagueWo|
00017160  72 64 73 20 69 3b 0a 20  20 20 69 66 20 28 69 20  |rds i;.   if (i |
00017170  68 61 73 20 61 6e 69 6d  61 74 65 29 0a 20 20 20  |has animate).   |
00017180  7b 20 20 20 69 66 20 28  47 65 74 47 65 6e 64 65  |{   if (GetGende|
00017190  72 28 69 29 3d 3d 31 29  20 68 69 6d 6f 62 6a 3d  |r(i)==1) himobj=|
000171a0  69 3b 0a 20 20 20 20 20  20 20 65 6c 73 65 20 68  |i;.       else h|
000171b0  65 72 6f 62 6a 3d 69 3b  0a 20 20 20 7d 0a 20 20  |erobj=i;.   }.  |
000171c0  20 65 6c 73 65 20 69 74  6f 62 6a 3d 69 3b 0a 5d  | else itobj=i;.]|
000171d0  3b 0a 0a 21 20 2d 2d 2d  2d 2d 2d 2d 2d 2d 2d 2d  |;..! -----------|
000171e0  2d 2d 2d 2d 2d 2d 2d 2d  2d 2d 2d 2d 2d 2d 2d 2d  |----------------|
*
00017220  2d 0a 21 20 20 47 65 74  47 65 6e 64 65 72 20 72  |-.!  GetGender r|
00017230  65 74 75 72 6e 73 20 30  20 69 66 20 74 68 65 20  |eturns 0 if the |
00017240  67 69 76 65 6e 20 61 6e  69 6d 61 74 65 20 6f 62  |given animate ob|
00017250  6a 65 63 74 20 69 73 20  66 65 6d 61 6c 65 2c 20  |ject is female, |
00017260  61 6e 64 20 31 20 69 66  20 6d 61 6c 65 0a 21 20  |and 1 if male.! |
00017270  20 28 6e 6f 74 20 61 6c  6c 20 67 61 6d 65 73 20  | (not all games |
00017280  77 69 6c 6c 20 77 61 6e  74 20 73 75 63 68 20 61  |will want such a|
00017290  20 73 69 6d 70 6c 65 20  64 65 63 69 73 69 6f 6e  | simple decision|
000172a0  20 66 75 6e 63 74 69 6f  6e 21 29 0a 21 20 2d 2d  | function!).! --|
000172b0  2d 2d 2d 2d 2d 2d 2d 2d  2d 2d 2d 2d 2d 2d 2d 2d  |----------------|
*
000172f0  2d 2d 2d 2d 2d 2d 2d 2d  2d 2d 0a 0a 5b 20 47 65  |----------..[ Ge|
00017300  74 47 65 6e 64 65 72 20  70 65 72 73 6f 6e 3b 0a  |tGender person;.|
00017310  20 20 20 69 66 20 28 70  65 72 73 6f 6e 20 68 61  |   if (person ha|
00017320  73 6e 74 20 66 65 6d 61  6c 65 29 20 72 74 72 75  |snt female) rtru|
00017330  65 3b 0a 20 20 20 72 66  61 6c 73 65 3b 0a 5d 3b  |e;.   rfalse;.];|
00017340  0a 0a 21 20 2d 2d 2d 2d  2d 2d 2d 2d 2d 2d 2d 2d  |..! ------------|
00017350  2d 2d 2d 2d 2d 2d 2d 2d  2d 2d 2d 2d 2d 2d 2d 2d  |----------------|
*
00017390  0a 21 20 20 46 6f 72 20  63 6f 70 79 69 6e 67 20  |.!  For copying |
000173a0  62 75 66 66 65 72 73 0a  21 20 2d 2d 2d 2d 2d 2d  |buffers.! ------|
000173b0  2d 2d 2d 2d 2d 2d 2d 2d  2d 2d 2d 2d 2d 2d 2d 2d  |----------------|
*
000173f0  2d 2d 2d 2d 2d 2d 0a 0a  5b 20 43 6f 70 79 20 62  |------..[ Copy b|
00017400  74 6f 20 62 66 72 6f 6d  20 69 20 73 69 7a 65 3b  |to bfrom i size;|
00017410  0a 20 20 20 73 69 7a 65  3d 62 74 6f 2d 3e 30 3b  |.   size=bto->0;|
00017420  0a 20 20 20 66 6f 72 20  28 69 3d 31 3a 69 3c 3d  |.   for (i=1:i<=|
00017430  73 69 7a 65 3a 69 2b 2b  29 20 62 74 6f 2d 3e 69  |size:i++) bto->i|
00017440  3d 62 66 72 6f 6d 2d 3e  69 3b 0a 5d 3b 0a 0a 21  |=bfrom->i;.];..!|
00017450  20 2d 2d 2d 2d 2d 2d 2d  2d 2d 2d 2d 2d 2d 2d 2d  | ---------------|
00017460  2d 2d 2d 2d 2d 2d 2d 2d  2d 2d 2d 2d 2d 2d 2d 2d  |----------------|
*
00017490  2d 2d 2d 2d 2d 2d 2d 2d  2d 2d 2d 2d 2d 0a 21 20  |-------------.! |
000174a0  20 45 6e 64 20 6f 66 20  74 68 65 20 70 61 72 73  | End of the pars|
000174b0  65 72 20 70 72 6f 70 65  72 3a 20 74 68 65 20 72  |er proper: the r|
000174c0  65 6d 61 69 6e 69 6e 67  20 72 6f 75 74 69 6e 65  |emaining routine|
000174d0  73 20 61 72 65 20 69 74  73 20 66 72 6f 6e 74 20  |s are its front |
000174e0  65 6e 64 2e 0a 21 20 2d  2d 2d 2d 2d 2d 2d 2d 2d  |end..! ---------|
000174f0  2d 2d 2d 2d 2d 2d 2d 2d  2d 2d 2d 2d 2d 2d 2d 2d  |----------------|
*
00017530  2d 2d 2d 0a 0a 5b 20 44  69 73 70 6c 61 79 53 74  |---..[ DisplaySt|
00017540  61 74 75 73 3b 0a 20 20  20 69 66 20 28 74 68 65  |atus;.   if (the|
00017550  5f 74 69 6d 65 3d 3d 24  66 66 66 66 29 0a 20 20  |_time==$ffff).  |
00017560  20 7b 20 20 20 73 6c 69  6e 65 31 3d 73 63 6f 72  | {   sline1=scor|
00017570  65 3b 20 73 6c 69 6e 65  32 3d 74 75 72 6e 73 3b  |e; sline2=turns;|
00017580  20 7d 0a 20 20 20 65 6c  73 65 0a 20 20 20 7b 20  | }.   else.   { |
00017590  20 20 73 6c 69 6e 65 31  3d 74 68 65 5f 74 69 6d  |  sline1=the_tim|
000175a0  65 2f 36 30 3b 20 73 6c  69 6e 65 32 3d 74 68 65  |e/60; sline2=the|
000175b0  5f 74 69 6d 65 25 36 30  3b 20 7d 0a 5d 3b 0a 0a  |_time%60; }.];..|
000175c0  5b 20 53 65 74 54 69 6d  65 20 74 20 73 3b 0a 20  |[ SetTime t s;. |
000175d0  20 20 74 68 65 5f 74 69  6d 65 3d 74 3b 20 74 69  |  the_time=t; ti|
000175e0  6d 65 5f 72 61 74 65 3d  73 3b 20 74 69 6d 65 5f  |me_rate=s; time_|
000175f0  73 74 65 70 3d 30 3b 0a  20 20 20 69 66 20 28 73  |step=0;.   if (s|
00017600  3c 30 29 20 74 69 6d 65  5f 73 74 65 70 3d 30 2d  |<0) time_step=0-|
00017610  73 3b 0a 5d 3b 0a 0a 5b  20 50 6c 61 79 54 68 65  |s;.];..[ PlayThe|
00017620  47 61 6d 65 20 69 20 6a  20 6b 20 6c 20 61 66 6c  |Game i j k l afl|
00017630  61 67 3b 0a 0a 20 20 20  74 6f 70 5f 6f 62 6a 65  |ag;..   top_obje|
00017640  63 74 20 3d 20 23 6c 61  72 67 65 73 74 5f 6f 62  |ct = #largest_ob|
00017650  6a 65 63 74 2d 32 35 35  3b 0a 0a 20 20 20 49 6e  |ject-255;..   In|
00017660  69 74 69 61 6c 69 73 65  28 29 3b 0a 0a 20 20 20  |itialise();..   |
00017670  6c 61 73 74 5f 73 63 6f  72 65 20 3d 20 73 63 6f  |last_score = sco|
00017680  72 65 3b 0a 20 20 20 6d  6f 76 65 20 70 6c 61 79  |re;.   move play|
00017690  65 72 20 74 6f 20 6c 6f  63 61 74 69 6f 6e 3b 0a  |er to location;.|
000176a0  20 20 20 77 68 69 6c 65  20 28 70 61 72 65 6e 74  |   while (parent|
000176b0  28 6c 6f 63 61 74 69 6f  6e 29 7e 3d 30 29 20 6c  |(location)~=0) l|
000176c0  6f 63 61 74 69 6f 6e 3d  70 61 72 65 6e 74 28 6c  |ocation=parent(l|
000176d0  6f 63 61 74 69 6f 6e 29  3b 0a 20 20 20 6f 62 6a  |ocation);.   obj|
000176e0  65 63 74 6c 6f 6f 70 20  28 69 20 69 6e 20 70 6c  |ectloop (i in pl|
000176f0  61 79 65 72 29 20 67 69  76 65 20 69 20 6d 6f 76  |ayer) give i mov|
00017700  65 64 3b 0a 20 20 20 70  6c 61 79 65 72 2e 63 61  |ed;.   player.ca|
00017710  70 61 63 69 74 79 20 3d  20 4d 41 58 5f 43 41 52  |pacity = MAX_CAR|
00017720  52 49 45 44 3b 0a 0a 20  20 20 42 61 6e 6e 65 72  |RIED;..   Banner|
00017730  28 29 3b 0a 0a 20 20 20  4c 6f 6f 6b 53 75 62 28  |();..   LookSub(|
00017740  29 3b 0a 0a 20 20 20 66  6f 72 20 28 69 3d 31 3a  |);..   for (i=1:|
00017750  69 3c 3d 31 30 30 3a 69  2b 2b 29 20 6a 3d 72 61  |i<=100:i++) j=ra|
00017760  6e 64 6f 6d 28 69 29 3b  0a 0a 20 20 20 77 68 69  |ndom(i);..   whi|
00017770  6c 65 20 64 65 61 64 66  6c 61 67 3d 3d 30 0a 20  |le deadflag==0. |
00017780  20 20 7b 20 20 20 69 66  20 28 73 63 6f 72 65 20  |  {   if (score |
00017790  7e 3d 20 6c 61 73 74 5f  73 63 6f 72 65 29 0a 20  |~= last_score). |
000177a0  20 20 20 20 20 20 7b 20  20 20 69 66 20 28 6e 6f  |      {   if (no|
000177b0  74 69 66 79 5f 6d 6f 64  65 3d 3d 31 29 0a 20 20  |tify_mode==1).  |
000177c0  20 20 20 20 20 20 20 20  20 7b 20 20 20 70 72 69  |         {   pri|
000177d0  6e 74 20 22 5e 5b 59 6f  75 72 20 73 63 6f 72 65  |nt "^[Your score|
000177e0  20 68 61 73 20 6a 75 73  74 20 67 6f 6e 65 20 22  | has just gone "|
000177f0  3b 0a 20 20 20 20 20 20  20 20 20 20 20 20 20 20  |;.              |
00017800  20 69 66 20 28 6c 61 73  74 5f 73 63 6f 72 65 20  | if (last_score |
00017810  3e 20 73 63 6f 72 65 29  20 7b 20 69 3d 6c 61 73  |> score) { i=las|
00017820  74 5f 73 63 6f 72 65 2d  73 63 6f 72 65 3b 20 70  |t_score-score; p|
00017830  72 69 6e 74 20 22 64 6f  77 6e 22 3b 20 7d 0a 20  |rint "down"; }. |
00017840  20 20 20 20 20 20 20 20  20 20 20 20 20 20 65 6c  |              el|
00017850  73 65 20 7b 20 69 3d 73  63 6f 72 65 2d 6c 61 73  |se { i=score-las|
00017860  74 5f 73 63 6f 72 65 3b  20 70 72 69 6e 74 20 22  |t_score; print "|
00017870  75 70 22 3b 20 7d 0a 20  20 20 20 20 20 20 20 20  |up"; }.         |
00017880  20 20 20 20 20 20 70 72  69 6e 74 20 22 20 62 79  |      print " by|
00017890  20 22 3b 20 45 6e 67 6c  69 73 68 4e 75 6d 62 65  | "; EnglishNumbe|
000178a0  72 28 69 29 3b 20 70 72  69 6e 74 20 22 20 70 6f  |r(i); print " po|
000178b0  69 6e 74 22 3b 0a 20 20  20 20 20 20 20 20 20 20  |int";.          |
000178c0  20 20 20 20 20 69 66 20  28 69 3e 31 29 20 70 72  |     if (i>1) pr|
000178d0  69 6e 74 20 22 73 22 3b  20 70 72 69 6e 74 20 22  |int "s"; print "|
000178e0  2e 5d 5e 22 3b 0a 20 20  20 20 20 20 20 20 20 20  |.]^";.          |
000178f0  20 7d 0a 20 20 20 20 20  20 20 20 20 20 20 6c 61  | }.           la|
00017900  73 74 5f 73 63 6f 72 65  3d 73 63 6f 72 65 3b 0a  |st_score=score;.|
00017910  20 20 20 20 20 20 20 7d  0a 20 20 20 20 20 20 20  |       }.       |
00017920  2e 45 72 72 6f 72 3b 0a  20 20 20 20 20 20 20 69  |.Error;.       i|
00017930  6e 70 31 3d 30 3b 20 69  6e 70 32 3d 30 3b 20 61  |np1=0; inp2=0; a|
00017940  63 74 69 6f 6e 3d 30 3b  20 6d 65 74 61 3d 30 3b  |ction=0; meta=0;|
00017950  0a 20 20 20 20 20 20 20  50 61 72 73 65 72 28 69  |.       Parser(i|
00017960  6e 70 75 74 6f 62 6a 73  29 3b 0a 0a 20 20 20 20  |nputobjs);..    |
00017970  20 20 20 6f 6e 6f 74 68  65 6c 64 5f 6d 6f 64 65  |   onotheld_mode|
00017980  3d 6e 6f 74 68 65 6c 64  5f 6d 6f 64 65 3b 20 6e  |=notheld_mode; n|
00017990  6f 74 68 65 6c 64 5f 6d  6f 64 65 3d 30 3b 0a 0a  |otheld_mode=0;..|
000179a0  20 20 20 20 20 20 20 69  66 20 28 61 63 74 6f 72  |       if (actor|
000179b0  7e 3d 70 6c 61 79 65 72  29 0a 20 20 20 20 20 20  |~=player).      |
000179c0  20 7b 20 20 20 61 63 74  69 6f 6e 3d 69 6e 70 75  | {   action=inpu|
000179d0  74 6f 62 6a 73 2d 2d 3e  30 3b 0a 20 20 20 20 20  |tobjs-->0;.     |
000179e0  20 20 20 20 20 20 69 6e  70 31 3d 69 6e 70 75 74  |      inp1=input|
000179f0  6f 62 6a 73 2d 2d 3e 32  3b 0a 20 20 20 20 20 20  |objs-->2;.      |
00017a00  20 20 20 20 20 69 6e 70  32 3d 69 6e 70 75 74 6f  |     inp2=inputo|
00017a10  62 6a 73 2d 2d 3e 33 3b  0a 20 20 20 20 20 20 20  |bjs-->3;.       |
00017a20  20 20 20 20 69 66 20 28  61 63 74 69 6f 6e 3d 3d  |    if (action==|
00017a30  23 23 47 69 76 65 52 29  0a 20 20 20 20 20 20 20  |##GiveR).       |
00017a40  20 20 20 20 7b 20 20 20  69 6e 70 32 3d 69 6e 70  |    {   inp2=inp|
00017a50  75 74 6f 62 6a 73 2d 2d  3e 32 3b 0a 20 20 20 20  |utobjs-->2;.    |
00017a60  20 20 20 20 20 20 20 20  20 20 20 69 6e 70 31 3d  |           inp1=|
00017a70  69 6e 70 75 74 6f 62 6a  73 2d 2d 3e 33 3b 20 61  |inputobjs-->3; a|
00017a80  63 74 69 6f 6e 3d 23 23  47 69 76 65 3b 0a 20 20  |ction=##Give;.  |
00017a90  20 20 20 20 20 20 20 20  20 7d 0a 20 20 20 20 20  |         }.     |
00017aa0  20 20 20 20 20 20 69 66  20 28 52 75 6e 4c 69 66  |      if (RunLif|
00017ab0  65 28 61 63 74 6f 72 2c  23 23 4f 72 64 65 72 29  |e(actor,##Order)|
00017ac0  3d 3d 30 29 0a 20 20 20  20 20 20 20 20 20 20 20  |==0).           |
00017ad0  7b 20 20 20 43 44 65 66  41 72 74 28 61 63 74 6f  |{   CDefArt(acto|
00017ae0  72 29 3b 20 70 72 69 6e  74 20 22 20 68 61 73 20  |r); print " has |
00017af0  62 65 74 74 65 72 20 74  68 69 6e 67 73 20 74 6f  |better things to|
00017b00  20 64 6f 2e 5e 22 3b 20  7d 0a 20 20 20 20 20 20  | do.^"; }.      |
00017b10  20 20 20 20 20 6a 75 6d  70 20 74 69 6d 65 73 6c  |     jump timesl|
00017b20  69 63 65 3b 0a 20 20 20  20 20 20 20 7d 0a 0a 20  |ice;.       }.. |
00017b30  20 20 20 20 20 20 69 66  20 28 74 6f 6f 6d 61 6e  |      if (tooman|
00017b40  79 5f 66 6c 61 67 3d 3d  31 29 0a 20 20 20 20 20  |y_flag==1).     |
00017b50  20 20 7b 20 20 20 74 6f  6f 6d 61 6e 79 5f 66 6c  |  {   toomany_fl|
00017b60  61 67 3d 30 3b 0a 20 20  20 20 20 20 20 20 20 20  |ag=0;.          |
00017b70  20 70 72 69 6e 74 20 22  28 63 6f 6e 73 69 64 65  | print "(conside|
00017b80  72 69 6e 67 20 74 68 65  20 66 69 72 73 74 20 73  |ring the first s|
00017b90  69 78 74 65 65 6e 20 6f  62 6a 65 63 74 73 20 6f  |ixteen objects o|
00017ba0  6e 6c 79 29 5e 22 3b 0a  20 20 20 20 20 20 20 7d  |nly)^";.       }|
00017bb0  0a 20 20 20 20 20 20 20  61 66 6c 61 67 3d 30 3b  |.       aflag=0;|
00017bc0  0a 20 20 20 20 20 20 20  69 66 20 28 61 63 74 69  |.       if (acti|
00017bd0  6f 6e 7e 3d 30 29 20 61  66 6c 61 67 3d 31 3b 0a  |on~=0) aflag=1;.|
00017be0  20 20 20 20 20 20 20 69  66 20 28 61 63 74 69 6f  |       if (actio|
00017bf0  6e 3d 3d 30 29 20 61 63  74 69 6f 6e 3d 69 6e 70  |n==0) action=inp|
00017c00  75 74 6f 62 6a 73 2d 2d  3e 30 3b 0a 0a 20 20 20  |utobjs-->0;..   |
00017c10  20 20 20 20 69 66 20 28  61 66 6c 61 67 3d 3d 30  |    if (aflag==0|
00017c20  29 0a 20 20 20 20 20 20  20 7b 20 20 20 69 3d 69  |).       {   i=i|
00017c30  6e 70 75 74 6f 62 6a 73  2d 2d 3e 31 3b 0a 20 20  |nputobjs-->1;.  |
00017c40  20 20 20 20 20 20 20 20  20 69 6e 70 31 3d 69 6e  |         inp1=in|
00017c50  70 75 74 6f 62 6a 73 2d  2d 3e 32 3b 0a 20 20 20  |putobjs-->2;.   |
00017c60  20 20 20 20 20 20 20 20  69 6e 70 32 3d 69 6e 70  |        inp2=inp|
00017c70  75 74 6f 62 6a 73 2d 2d  3e 33 3b 0a 20 20 20 20  |utobjs-->3;.    |
00017c80  20 20 20 7d 0a 20 20 20  20 20 20 20 65 6c 73 65  |   }.       else|
00017c90  20 69 3d 32 3b 0a 0a 20  20 20 20 20 20 20 69 66  | i=2;..       if|
00017ca0  20 28 69 3d 3d 30 29 20  7b 20 69 6e 70 31 3d 30  | (i==0) { inp1=0|
00017cb0  3b 20 69 6e 70 32 3d 30  3b 20 7d 0a 20 20 20 20  |; inp2=0; }.    |
00017cc0  20 20 20 69 66 20 28 69  3d 3d 31 29 20 7b 20 69  |   if (i==1) { i|
00017cd0  6e 70 32 3d 30 3b 20 7d  0a 0a 20 20 20 20 20 20  |np2=0; }..      |
00017ce0  20 6d 75 6c 74 69 66 6c  61 67 3d 30 3b 0a 20 20  | multiflag=0;.  |
00017cf0  20 20 20 20 20 69 66 20  28 69 3d 3d 30 29 20 50  |     if (i==0) P|
00017d00  72 6f 63 65 73 73 28 30  2c 30 2c 61 63 74 69 6f  |rocess(0,0,actio|
00017d10  6e 29 3b 0a 20 20 20 20  20 20 20 65 6c 73 65 0a  |n);.       else.|
00017d20  20 20 20 20 20 20 20 7b  20 20 20 69 66 20 28 69  |       {   if (i|
00017d30  6e 70 31 7e 3d 30 29 20  50 72 6f 63 65 73 73 28  |np1~=0) Process(|
00017d40  69 6e 70 31 2c 69 6e 70  32 2c 61 63 74 69 6f 6e  |inp1,inp2,action|
00017d50  29 3b 0a 20 20 20 20 20  20 20 20 20 20 20 65 6c  |);.           el|
00017d60  73 65 0a 20 20 20 20 20  20 20 20 20 20 20 7b 20  |se.           { |
00017d70  20 20 6d 75 6c 74 69 66  6c 61 67 3d 31 3b 0a 20  |  multiflag=1;. |
00017d80  20 20 20 20 20 20 20 20  20 20 20 20 20 20 6a 3d  |              j=|
00017d90  6d 75 6c 74 69 70 6c 65  5f 6f 62 6a 65 63 74 2d  |multiple_object-|
00017da0  2d 3e 30 3b 0a 20 20 20  20 20 20 20 20 20 20 20  |->0;.           |
00017db0  20 20 20 20 69 66 20 28  6a 3d 3d 30 29 20 7b 20  |    if (j==0) { |
00017dc0  70 72 69 6e 74 20 22 4e  6f 74 68 69 6e 67 20 74  |print "Nothing t|
00017dd0  6f 20 64 6f 21 5e 22 3b  20 6a 75 6d 70 20 45 72  |o do!^"; jump Er|
00017de0  72 6f 72 3b 20 7d 0a 20  20 20 20 20 20 20 20 20  |ror; }.         |
00017df0  20 20 20 20 20 20 66 6f  72 20 28 6b 3d 31 3a 6b  |      for (k=1:k|
00017e00  3c 3d 6a 3a 6b 2b 2b 29  0a 20 20 20 20 20 20 20  |<=j:k++).       |
00017e10  20 20 20 20 20 20 20 20  7b 20 20 20 6c 3d 6d 75  |        {   l=mu|
00017e20  6c 74 69 70 6c 65 5f 6f  62 6a 65 63 74 2d 2d 3e  |ltiple_object-->|
00017e30  6b 3b 20 50 72 69 6e 74  53 68 6f 72 74 4e 61 6d  |k; PrintShortNam|
00017e40  65 28 6c 29 3b 20 70 72  69 6e 74 20 22 3a 20 22  |e(l); print ": "|
00017e50  3b 0a 20 20 20 20 20 20  20 20 20 20 20 20 20 20  |;.              |
00017e60  20 20 20 20 20 50 72 6f  63 65 73 73 28 6c 2c 69  |     Process(l,i|
00017e70  6e 70 32 2c 61 63 74 69  6f 6e 29 3b 0a 20 20 20  |np2,action);.   |
00017e80  20 20 20 20 20 20 20 20  20 20 20 20 7d 0a 20 20  |            }.  |
00017e90  20 20 20 20 20 20 20 20  20 7d 0a 20 20 20 20 20  |         }.     |
00017ea0  20 20 7d 0a 0a 20 20 20  20 20 20 20 2e 74 69 6d  |  }..       .tim|
00017eb0  65 73 6c 69 63 65 3b 0a  20 20 20 20 20 20 20 69  |eslice;.       i|
00017ec0  66 20 28 6e 6f 74 68 65  6c 64 5f 6d 6f 64 65 3d  |f (notheld_mode=|
00017ed0  3d 31 29 20 6d 65 74 61  3d 31 3b 0a 20 20 20 20  |=1) meta=1;.    |
00017ee0  20 20 20 69 66 20 28 64  65 61 64 66 6c 61 67 3d  |   if (deadflag=|
00017ef0  3d 30 20 26 26 20 6d 65  74 61 3d 3d 30 29 20 54  |=0 && meta==0) T|
00017f00  69 6d 65 28 29 3b 0a 20  20 20 7d 0a 0a 20 20 20  |ime();.   }..   |
00017f10  69 66 20 28 64 65 61 64  66 6c 61 67 7e 3d 32 29  |if (deadflag~=2)|
00017f20  20 41 66 74 65 72 4c 69  66 65 28 29 3b 0a 20 20  | AfterLife();.  |
00017f30  20 69 66 20 28 64 65 61  64 66 6c 61 67 3d 3d 30  | if (deadflag==0|
00017f40  29 20 6a 75 6d 70 20 45  72 72 6f 72 3b 0a 0a 20  |) jump Error;.. |
00017f50  20 20 70 72 69 6e 74 20  22 5e 5e 20 20 20 20 2a  |  print "^^    *|
00017f60  2a 2a 22 3b 0a 20 20 20  69 66 20 28 64 65 61 64  |**";.   if (dead|
00017f70  66 6c 61 67 3d 3d 31 29  20 70 72 69 6e 74 20 22  |flag==1) print "|
00017f80  20 59 6f 75 20 68 61 76  65 20 64 69 65 64 20 22  | You have died "|
00017f90  3b 0a 20 20 20 69 66 20  28 64 65 61 64 66 6c 61  |;.   if (deadfla|
00017fa0  67 3d 3d 32 29 20 70 72  69 6e 74 20 22 20 59 6f  |g==2) print " Yo|
00017fb0  75 20 68 61 76 65 20 77  6f 6e 20 22 3b 0a 20 20  |u have won ";.  |
00017fc0  20 69 66 20 28 64 65 61  64 66 6c 61 67 3e 32 29  | if (deadflag>2)|
00017fd0  20 20 7b 20 70 72 69 6e  74 20 22 20 22 3b 20 44  |  { print " "; D|
00017fe0  65 61 74 68 4d 65 73 73  61 67 65 28 29 3b 20 70  |eathMessage(); p|
00017ff0  72 69 6e 74 20 22 20 22  3b 20 7d 0a 20 20 20 70  |rint " "; }.   p|
00018000  72 69 6e 74 20 22 2a 2a  2a 5e 5e 5e 22 3b 0a 20  |rint "***^^^";. |
00018010  20 20 53 63 6f 72 65 53  75 62 28 29 3b 0a 20 20  |  ScoreSub();.  |
00018020  20 44 69 73 70 6c 61 79  53 74 61 74 75 73 28 29  | DisplayStatus()|
00018030  3b 0a 0a 20 20 20 2e 52  52 51 50 4c 3b 0a 20 20  |;..   .RRQPL;.  |
00018040  20 70 72 69 6e 74 20 22  5e 57 6f 75 6c 64 20 79  | print "^Would y|
00018050  6f 75 20 6c 69 6b 65 20  74 6f 20 52 45 53 54 41  |ou like to RESTA|
00018060  52 54 2c 20 52 45 53 54  4f 52 45 20 61 20 73 61  |RT, RESTORE a sa|
00018070  76 65 64 20 67 61 6d 65  22 3b 0a 20 20 20 69 66  |ved game";.   if|
00018080  20 28 54 41 53 4b 53 5f  50 52 4f 56 49 44 45 44  | (TASKS_PROVIDED|
00018090  3d 3d 30 29 0a 20 20 20  20 20 20 20 70 72 69 6e  |==0).       prin|
000180a0  74 20 22 2c 20 67 69 76  65 20 74 68 65 20 46 55  |t ", give the FU|
000180b0  4c 4c 20 73 63 6f 72 65  20 66 6f 72 20 74 68 61  |LL score for tha|
000180c0  74 20 67 61 6d 65 22 3b  0a 20 20 20 69 66 20 28  |t game";.   if (|
000180d0  64 65 61 64 66 6c 61 67  3d 3d 32 20 26 26 20 41  |deadflag==2 && A|
000180e0  4d 55 53 49 4e 47 5f 50  52 4f 56 49 44 45 44 3d  |MUSING_PROVIDED=|
000180f0  3d 30 29 0a 20 20 20 20  20 20 20 70 72 69 6e 74  |=0).       print|
00018100  20 22 2c 20 73 65 65 20  73 6f 6d 65 20 73 75 67  | ", see some sug|
00018110  67 65 73 74 69 6f 6e 73  20 66 6f 72 20 41 4d 55  |gestions for AMU|
00018120  53 49 4e 47 20 74 68 69  6e 67 73 20 74 6f 20 64  |SING things to d|
00018130  6f 22 3b 0a 20 20 20 70  72 69 6e 74 20 22 20 6f  |o";.   print " o|
00018140  72 20 51 55 49 54 3f 5e  22 3b 0a 20 20 20 2e 52  |r QUIT?^";.   .R|
00018150  52 51 4c 3b 0a 20 20 20  70 72 69 6e 74 20 22 3e  |RQL;.   print ">|
00018160  20 22 3b 0a 20 20 20 23  49 46 56 33 3b 20 72 65  | ";.   #IFV3; re|
00018170  61 64 20 62 75 66 66 65  72 20 70 61 72 73 65 3b  |ad buffer parse;|
00018180  20 23 45 4e 44 49 46 3b  0a 20 20 20 23 49 46 56  | #ENDIF;.   #IFV|
00018190  35 3b 20 72 65 61 64 20  62 75 66 66 65 72 20 70  |5; read buffer p|
000181a0  61 72 73 65 20 44 72 61  77 53 74 61 74 75 73 4c  |arse DrawStatusL|
000181b0  69 6e 65 3b 20 23 45 4e  44 49 46 3b 0a 20 20 20  |ine; #ENDIF;.   |
000181c0  69 3d 70 61 72 73 65 2d  2d 3e 31 3b 0a 20 20 20  |i=parse-->1;.   |
000181d0  69 66 20 28 69 3d 3d 27  71 75 69 74 27 20 6f 72  |if (i=='quit' or|
000181e0  20 23 77 24 71 29 20 71  75 69 74 3b 0a 20 20 20  | #w$q) quit;.   |
000181f0  69 66 20 28 69 3d 3d 27  72 65 73 74 61 72 74 27  |if (i=='restart'|
00018200  29 20 20 20 20 20 20 72  65 73 74 61 72 74 3b 0a  |)      restart;.|
00018210  20 20 20 69 66 20 28 69  3d 3d 27 72 65 73 74 6f  |   if (i=='resto|
00018220  72 65 27 29 20 20 20 20  20 20 7b 20 52 65 73 74  |re')      { Rest|
00018230  6f 72 65 53 75 62 28 29  3b 20 6a 75 6d 70 20 52  |oreSub(); jump R|
00018240  52 51 50 4c 3b 20 7d 0a  20 20 20 69 66 20 28 69  |RQPL; }.   if (i|
00018250  3d 3d 27 66 75 6c 6c 73  63 6f 72 65 27 20 6f 72  |=='fullscore' or|
00018260  20 27 66 75 6c 6c 27 20  26 26 20 54 41 53 4b 53  | 'full' && TASKS|
00018270  5f 50 52 4f 56 49 44 45  44 3d 3d 30 29 0a 20 20  |_PROVIDED==0).  |
00018280  20 7b 20 20 20 6e 65 77  5f 6c 69 6e 65 3b 20 46  | {   new_line; F|
00018290  75 6c 6c 53 63 6f 72 65  53 75 62 28 29 3b 20 6a  |ullScoreSub(); j|
000182a0  75 6d 70 20 52 52 51 50  4c 3b 20 7d 0a 20 20 20  |ump RRQPL; }.   |
000182b0  69 66 20 28 64 65 61 64  66 6c 61 67 3d 3d 32 20  |if (deadflag==2 |
000182c0  26 26 20 69 3d 3d 27 61  6d 75 73 69 6e 67 27 20  |&& i=='amusing' |
000182d0  26 26 20 41 4d 55 53 49  4e 47 5f 50 52 4f 56 49  |&& AMUSING_PROVI|
000182e0  44 45 44 3d 3d 30 29 0a  20 20 20 7b 20 20 20 6e  |DED==0).   {   n|
000182f0  65 77 5f 6c 69 6e 65 3b  20 41 6d 75 73 69 6e 67  |ew_line; Amusing|
00018300  28 29 3b 20 6a 75 6d 70  20 52 52 51 50 4c 3b 20  |(); jump RRQPL; |
00018310  7d 0a 23 49 46 56 35 3b  0a 20 20 20 69 66 20 28  |}.#IFV5;.   if (|
00018320  69 3d 3d 27 75 6e 64 6f  27 29 0a 20 20 20 7b 20  |i=='undo').   { |
00018330  20 20 69 66 20 28 75 6e  64 6f 5f 66 6c 61 67 3d  |  if (undo_flag=|
00018340  3d 30 29 0a 20 20 20 20  20 20 20 7b 20 20 20 70  |=0).       {   p|
00018350  72 69 6e 74 20 22 5b 59  6f 75 72 20 69 6e 74 65  |rint "[Your inte|
00018360  72 70 72 65 74 65 72 20  64 6f 65 73 20 6e 6f 74  |rpreter does not|
00018370  20 70 72 6f 76 69 64 65  20 7e 75 6e 64 6f 7e 2e  | provide ~undo~.|
00018380  20 20 53 6f 72 72 79 21  5d 5e 22 3b 0a 20 20 20  |  Sorry!]^";.   |
00018390  20 20 20 20 20 20 20 20  6a 75 6d 70 20 52 52 51  |        jump RRQ|
000183a0  50 4c 3b 0a 20 20 20 20  20 20 20 7d 0a 20 20 20  |PL;.       }.   |
000183b0  20 20 20 20 69 66 20 28  75 6e 64 6f 5f 66 6c 61  |    if (undo_fla|
000183c0  67 3d 3d 31 29 20 6a 75  6d 70 20 55 6e 64 6f 46  |g==1) jump UndoF|
000183d0  61 69 6c 65 64 32 3b 0a  20 20 20 20 20 20 20 72  |ailed2;.       r|
000183e0  65 73 74 6f 72 65 5f 75  6e 64 6f 20 69 3b 0a 20  |estore_undo i;. |
000183f0  20 20 20 20 20 20 69 66  20 28 69 3d 3d 30 29 0a  |      if (i==0).|
00018400  20 20 20 20 20 20 20 7b  20 20 20 2e 55 6e 64 6f  |       {   .Undo|
00018410  46 61 69 6c 65 64 32 3b  0a 20 20 20 20 20 20 20  |Failed2;.       |
00018420  20 20 20 20 20 70 72 69  6e 74 20 22 7e 55 6e 64  |     print "~Und|
00018430  6f 7e 20 66 61 69 6c 65  64 2e 20 20 5b 4e 6f 74  |o~ failed.  [Not|
00018440  20 61 6c 6c 20 69 6e 74  65 72 70 72 65 74 65 72  | all interpreter|
00018450  73 20 70 72 6f 76 69 64  65 20 69 74 2e 5d 5e 22  |s provide it.]^"|
00018460  3b 0a 20 20 20 20 20 20  20 7d 0a 20 20 20 20 20  |;.       }.     |
00018470  20 20 6a 75 6d 70 20 52  52 51 50 4c 3b 0a 20 20  |  jump RRQPL;.  |
00018480  20 7d 0a 23 45 4e 44 49  46 3b 0a 20 20 20 70 72  | }.#ENDIF;.   pr|
00018490  69 6e 74 20 22 50 6c 65  61 73 65 20 67 69 76 65  |int "Please give|
000184a0  20 6f 6e 65 20 6f 66 20  74 68 65 20 61 6e 73 77  | one of the answ|
000184b0  65 72 73 20 61 62 6f 76  65 2e 5e 22 3b 0a 20 20  |ers above.^";.  |
000184c0  20 6a 75 6d 70 20 52 52  51 4c 3b 0a 5d 3b 0a 0a  | jump RRQL;.];..|
000184d0  5b 20 52 75 6e 52 6f 75  74 69 6e 65 73 20 6f 66  |[ RunRoutines of|
000184e0  6f 62 6a 20 66 72 6f 6d  70 72 6f 70 20 69 20 6a  |obj fromprop i j|
000184f0  20 6b 20 6c 20 6d 3b 0a  0a 20 20 20 69 66 20 28  | k l m;..   if (|
00018500  6f 66 6f 62 6a 3d 3d 74  68 65 64 61 72 6b 29 20  |ofobj==thedark) |
00018510  6f 66 6f 62 6a 3d 72 65  61 6c 5f 6c 6f 63 61 74  |ofobj=real_locat|
00018520  69 6f 6e 3b 0a 20 20 20  69 66 20 28 6f 66 6f 62  |ion;.   if (ofob|
00018530  6a 2e 66 72 6f 6d 70 72  6f 70 3d 3d 24 66 66 66  |j.fromprop==$fff|
00018540  66 29 20 72 66 61 6c 73  65 3b 0a 0a 23 49 46 44  |f) rfalse;..#IFD|
00018550  45 46 20 44 45 42 55 47  3b 0a 20 69 66 20 28 64  |EF DEBUG;. if (d|
00018560  65 62 75 67 5f 66 6c 61  67 20 26 20 31 20 7e 3d  |ebug_flag & 1 ~=|
00018570  20 30 20 26 26 20 66 72  6f 6d 70 72 6f 70 7e 3d  | 0 && fromprop~=|
00018580  73 68 6f 72 74 5f 6e 61  6d 65 29 0a 20 7b 20 70  |short_name). { p|
00018590  72 69 6e 74 20 22 5b 52  75 6e 6e 69 6e 67 20 22  |rint "[Running "|
000185a0  3b 0a 20 20 20 69 66 20  28 66 72 6f 6d 70 72 6f  |;.   if (frompro|
000185b0  70 3d 3d 62 65 66 6f 72  65 29 20 20 20 7b 20 70  |p==before)   { p|
000185c0  72 69 6e 74 20 22 62 65  66 6f 72 65 22 3b 20 20  |rint "before";  |
000185d0  20 6a 75 6d 70 20 44 65  62 75 67 50 72 74 3b 20  | jump DebugPrt; |
000185e0  7d 0a 20 20 20 69 66 20  28 66 72 6f 6d 70 72 6f  |}.   if (frompro|
000185f0  70 3d 3d 61 66 74 65 72  29 20 20 20 20 7b 20 70  |p==after)    { p|
00018600  72 69 6e 74 20 22 61 66  74 65 72 22 3b 20 20 20  |rint "after";   |
00018610  20 6a 75 6d 70 20 44 65  62 75 67 50 72 74 3b 20  | jump DebugPrt; |
00018620  7d 0a 20 20 20 69 66 20  28 66 72 6f 6d 70 72 6f  |}.   if (frompro|
00018630  70 3d 3d 6c 69 66 65 29  20 20 20 20 20 7b 20 70  |p==life)     { p|
00018640  72 69 6e 74 20 22 6c 69  66 65 22 3b 20 20 20 20  |rint "life";    |
00018650  20 6a 75 6d 70 20 44 65  62 75 67 50 72 74 3b 20  | jump DebugPrt; |
00018660  7d 0a 20 20 20 69 66 20  28 66 72 6f 6d 70 72 6f  |}.   if (frompro|
00018670  70 3d 3d 65 61 63 68 5f  74 75 72 6e 29 20 7b 20  |p==each_turn) { |
00018680  70 72 69 6e 74 20 22 65  61 63 68 5f 74 75 72 6e  |print "each_turn|
00018690  22 3b 20 6a 75 6d 70 20  44 65 62 75 67 50 72 74  |"; jump DebugPrt|
000186a0  3b 20 7d 0a 20 20 20 69  66 20 28 66 72 6f 6d 70  |; }.   if (fromp|
000186b0  72 6f 70 3d 3d 64 65 73  63 72 69 62 65 29 20 7b  |rop==describe) {|
000186c0  20 70 72 69 6e 74 20 22  64 65 73 63 72 69 62 65  | print "describe|
000186d0  22 3b 20 6a 75 6d 70 20  44 65 62 75 67 50 72 74  |"; jump DebugPrt|
000186e0  3b 20 7d 0a 20 20 20 69  66 20 28 66 72 6f 6d 70  |; }.   if (fromp|
000186f0  72 6f 70 3d 3d 69 6e 69  74 69 61 6c 29 20 20 7b  |rop==initial)  {|
00018700  20 70 72 69 6e 74 20 22  69 6e 69 74 69 61 6c 22  | print "initial"|
00018710  3b 20 20 6a 75 6d 70 20  44 65 62 75 67 50 72 74  |;  jump DebugPrt|
00018720  3b 20 7d 0a 20 20 20 69  66 20 28 66 72 6f 6d 70  |; }.   if (fromp|
00018730  72 6f 70 3d 3d 6e 5f 74  6f 29 20 20 20 20 20 7b  |rop==n_to)     {|
00018740  20 70 72 69 6e 74 20 22  6e 5f 74 6f 2f 64 6f 6f  | print "n_to/doo|
00018750  72 5f 74 6f 22 3b 20 20  20 6a 75 6d 70 20 44 65  |r_to";   jump De|
00018760  62 75 67 50 72 74 3b 20  7d 0a 20 20 20 69 66 20  |bugPrt; }.   if |
00018770  28 66 72 6f 6d 70 72 6f  70 3d 3d 73 5f 74 6f 29  |(fromprop==s_to)|
00018780  20 20 20 20 20 7b 20 70  72 69 6e 74 20 22 73 5f  |     { print "s_|
00018790  74 6f 22 3b 20 20 20 6a  75 6d 70 20 44 65 62 75  |to";   jump Debu|
000187a0  67 50 72 74 3b 20 7d 0a  20 20 20 69 66 20 28 66  |gPrt; }.   if (f|
000187b0  72 6f 6d 70 72 6f 70 3d  3d 65 5f 74 6f 29 20 20  |romprop==e_to)  |
000187c0  20 20 20 7b 20 70 72 69  6e 74 20 22 65 5f 74 6f  |   { print "e_to|
000187d0  22 3b 20 20 20 6a 75 6d  70 20 44 65 62 75 67 50  |";   jump DebugP|
000187e0  72 74 3b 20 7d 0a 20 20  20 69 66 20 28 66 72 6f  |rt; }.   if (fro|
000187f0  6d 70 72 6f 70 3d 3d 77  5f 74 6f 29 20 20 20 20  |mprop==w_to)    |
00018800  20 7b 20 70 72 69 6e 74  20 22 77 5f 74 6f 2f 64  | { print "w_to/d|
00018810  6f 6f 72 5f 64 69 72 22  3b 20 20 20 6a 75 6d 70  |oor_dir";   jump|
00018820  20 44 65 62 75 67 50 72  74 3b 20 7d 0a 20 20 20  | DebugPrt; }.   |
00018830  69 66 20 28 66 72 6f 6d  70 72 6f 70 3d 3d 6e 65  |if (fromprop==ne|
00018840  5f 74 6f 29 20 20 20 20  7b 20 70 72 69 6e 74 20  |_to)    { print |
00018850  22 6e 65 5f 74 6f 22 3b  20 20 20 6a 75 6d 70 20  |"ne_to";   jump |
00018860  44 65 62 75 67 50 72 74  3b 20 7d 0a 20 20 20 69  |DebugPrt; }.   i|
00018870  66 20 28 66 72 6f 6d 70  72 6f 70 3d 3d 6e 77 5f  |f (fromprop==nw_|
00018880  74 6f 29 20 20 20 20 7b  20 70 72 69 6e 74 20 22  |to)    { print "|
00018890  6e 77 5f 74 6f 22 3b 20  20 20 6a 75 6d 70 20 44  |nw_to";   jump D|
000188a0  65 62 75 67 50 72 74 3b  20 7d 0a 20 20 20 69 66  |ebugPrt; }.   if|
000188b0  20 28 66 72 6f 6d 70 72  6f 70 3d 3d 73 65 5f 74  | (fromprop==se_t|
000188c0  6f 29 20 20 20 20 7b 20  70 72 69 6e 74 20 22 73  |o)    { print "s|
000188d0  65 5f 74 6f 22 3b 20 20  20 6a 75 6d 70 20 44 65  |e_to";   jump De|
000188e0  62 75 67 50 72 74 3b 20  7d 0a 20 20 20 69 66 20  |bugPrt; }.   if |
000188f0  28 66 72 6f 6d 70 72 6f  70 3d 3d 73 77 5f 74 6f  |(fromprop==sw_to|
00018900  29 20 20 20 20 7b 20 70  72 69 6e 74 20 22 73 77  |)    { print "sw|
00018910  5f 74 6f 22 3b 20 20 20  6a 75 6d 70 20 44 65 62  |_to";   jump Deb|
00018920  75 67 50 72 74 3b 20 7d  0a 20 20 20 69 66 20 28  |ugPrt; }.   if (|
00018930  66 72 6f 6d 70 72 6f 70  3d 3d 75 5f 74 6f 29 20  |fromprop==u_to) |
00018940  20 20 20 20 7b 20 70 72  69 6e 74 20 22 75 5f 74  |    { print "u_t|
00018950  6f 2f 69 6e 76 65 6e 74  22 3b 20 20 20 6a 75 6d  |o/invent";   jum|
00018960  70 20 44 65 62 75 67 50  72 74 3b 20 7d 0a 20 20  |p DebugPrt; }.  |
00018970  20 69 66 20 28 66 72 6f  6d 70 72 6f 70 3d 3d 64  | if (fromprop==d|
00018980  5f 74 6f 29 20 20 20 20  20 7b 20 70 72 69 6e 74  |_to)     { print|
00018990  20 22 64 5f 74 6f 2f 70  6c 75 72 61 6c 22 3b 20  | "d_to/plural"; |
000189a0  20 20 6a 75 6d 70 20 44  65 62 75 67 50 72 74 3b  |  jump DebugPrt;|
000189b0  20 7d 0a 20 20 20 69 66  20 28 66 72 6f 6d 70 72  | }.   if (frompr|
000189c0  6f 70 3d 3d 69 6e 5f 74  6f 29 20 20 20 20 7b 20  |op==in_to)    { |
000189d0  70 72 69 6e 74 20 22 69  6e 5f 74 6f 22 3b 20 20  |print "in_to";  |
000189e0  20 6a 75 6d 70 20 44 65  62 75 67 50 72 74 3b 20  | jump DebugPrt; |
000189f0  7d 0a 20 20 20 69 66 20  28 66 72 6f 6d 70 72 6f  |}.   if (frompro|
00018a00  70 3d 3d 6f 75 74 5f 74  6f 29 20 20 20 7b 20 70  |p==out_to)   { p|
00018a10  72 69 6e 74 20 22 6f 75  74 5f 74 6f 22 3b 20 20  |rint "out_to";  |
00018a20  20 6a 75 6d 70 20 44 65  62 75 67 50 72 74 3b 20  | jump DebugPrt; |
00018a30  7d 0a 20 20 20 69 66 20  28 66 72 6f 6d 70 72 6f  |}.   if (frompro|
00018a40  70 3d 3d 74 69 6d 65 5f  6f 75 74 29 20 7b 20 70  |p==time_out) { p|
00018a50  72 69 6e 74 20 22 64 61  65 6d 6f 6e 2f 74 69 6d  |rint "daemon/tim|
00018a60  65 5f 6f 75 74 22 3b 20  20 20 6a 75 6d 70 20 44  |e_out";   jump D|
00018a70  65 62 75 67 50 72 74 3b  20 7d 0a 20 20 20 69 66  |ebugPrt; }.   if|
00018a80  20 28 66 72 6f 6d 70 72  6f 70 3d 3d 70 61 72 73  | (fromprop==pars|
00018a90  65 5f 6e 61 6d 65 29 20  7b 20 70 72 69 6e 74 20  |e_name) { print |
00018aa0  22 70 61 72 73 65 5f 6e  61 6d 65 22 3b 20 20 20  |"parse_name";   |
00018ab0  6a 75 6d 70 20 44 65 62  75 67 50 72 74 3b 20 7d  |jump DebugPrt; }|
00018ac0  0a 20 20 20 70 72 69 6e  74 20 22 70 72 6f 70 65  |.   print "prope|
00018ad0  72 74 79 20 22 2c 66 72  6f 6d 70 72 6f 70 3b 0a  |rty ",fromprop;.|
00018ae0  20 20 20 2e 44 65 62 75  67 50 72 74 3b 0a 20 20  |   .DebugPrt;.  |
00018af0  20 70 72 69 6e 74 20 22  20 66 6f 72 20 22 2c 20  | print " for ", |
00018b00  6f 62 6a 65 63 74 20 6f  66 6f 62 6a 2c 22 5d 5e  |object ofobj,"]^|
00018b10  22 3b 0a 20 7d 0a 23 45  4e 44 49 46 3b 0a 0a 20  |";. }.#ENDIF;.. |
00018b20  20 20 6a 3d 6f 66 6f 62  6a 2e 26 66 72 6f 6d 70  |  j=ofobj.&fromp|
00018b30  72 6f 70 3b 20 6b 3d 6f  66 6f 62 6a 2e 23 66 72  |rop; k=ofobj.#fr|
00018b40  6f 6d 70 72 6f 70 3b 20  6d 3d 73 65 6c 66 3b 20  |omprop; m=self; |
00018b50  73 65 6c 66 3d 6f 66 6f  62 6a 3b 0a 20 20 20 6e  |self=ofobj;.   n|
00018b60  6f 75 6e 3d 69 6e 70 31  3b 20 73 65 63 6f 6e 64  |oun=inp1; second|
00018b70  3d 69 6e 70 32 3b 0a 20  20 20 69 66 20 28 66 72  |=inp2;.   if (fr|
00018b80  6f 6d 70 72 6f 70 3d 3d  6c 69 66 65 29 20 73 77  |omprop==life) sw|
00018b90  5f 5f 76 61 72 3d 72 65  61 73 6f 6e 5f 63 6f 64  |__var=reason_cod|
00018ba0  65 3b 0a 20 20 20 65 6c  73 65 20 73 77 5f 5f 76  |e;.   else sw__v|
00018bb0  61 72 3d 61 63 74 69 6f  6e 3b 0a 20 20 20 66 6f  |ar=action;.   fo|
00018bc0  72 20 28 69 3d 30 3a 69  3c 6b 2f 32 3a 69 2b 2b  |r (i=0:i<k/2:i++|
00018bd0  29 0a 20 20 20 7b 20 20  20 6c 3d 69 6e 64 69 72  |).   {   l=indir|
00018be0  65 63 74 28 6a 2d 2d 3e  69 29 3b 0a 20 20 20 20  |ect(j-->i);.    |
00018bf0  20 20 20 69 66 20 28 6c  7e 3d 30 29 20 7b 20 73  |   if (l~=0) { s|
00018c00  65 6c 66 3d 6d 3b 20 72  65 74 75 72 6e 20 6c 3b  |elf=m; return l;|
00018c10  20 7d 0a 20 20 20 7d 0a  20 20 20 73 65 6c 66 3d  | }.   }.   self=|
00018c20  6d 3b 0a 20 20 20 72 66  61 6c 73 65 3b 0a 5d 3b  |m;.   rfalse;.];|
00018c30  0a 0a 23 69 66 64 65 66  20 44 45 42 55 47 3b 0a  |..#ifdef DEBUG;.|
00018c40  5b 20 54 72 61 63 65 41  63 74 69 6f 6e 20 73 6f  |[ TraceAction so|
00018c50  75 72 63 65 3b 0a 20 20  70 72 69 6e 74 20 22 5b  |urce;.  print "[|
00018c60  41 63 74 69 6f 6e 20 22  2c 20 61 63 74 69 6f 6e  |Action ", action|
00018c70  3b 0a 20 20 69 66 20 28  6e 6f 75 6e 7e 3d 30 29  |;.  if (noun~=0)|
00018c80  20 20 20 7b 20 70 72 69  6e 74 20 22 20 77 69 74  |   { print " wit|
00018c90  68 20 6e 6f 75 6e 20 22  3b 20 20 44 65 66 41 72  |h noun ";  DefAr|
00018ca0  74 28 6e 6f 75 6e 29 3b  20 20 20 7d 0a 20 20 69  |t(noun);   }.  i|
00018cb0  66 20 28 73 65 63 6f 6e  64 7e 3d 30 29 20 7b 20  |f (second~=0) { |
00018cc0  70 72 69 6e 74 20 22 20  61 6e 64 20 73 65 63 6f  |print " and seco|
00018cd0  6e 64 20 22 3b 20 44 65  66 41 72 74 28 73 65 63  |nd "; DefArt(sec|
00018ce0  6f 6e 64 29 3b 20 7d 0a  20 20 69 66 20 28 73 6f  |ond); }.  if (so|
00018cf0  75 72 63 65 3d 3d 31 29  20 70 72 69 6e 74 20 22  |urce==1) print "|
00018d00  20 28 66 72 6f 6d 20 6f  75 74 73 69 64 65 29 22  | (from outside)"|
00018d10  3b 20 65 6c 73 65 20 70  72 69 6e 74 20 22 20 28  |; else print " (|
00018d20  66 72 6f 6d 20 70 61 72  73 65 72 29 22 3b 0a 20  |from parser)";. |
00018d30  20 70 72 69 6e 74 20 22  5d 5e 22 3b 0a 5d 3b 0a  | print "]^";.];.|
00018d40  23 65 6e 64 69 66 3b 0a  0a 5b 20 52 5f 50 72 6f  |#endif;..[ R_Pro|
00018d50  63 65 73 73 20 61 63 74  69 20 69 20 6a 20 73 6e  |cess acti i j sn|
00018d60  20 73 73 20 73 61 20 73  73 65 3b 0a 20 20 20 73  | ss sa sse;.   s|
00018d70  6e 3d 69 6e 70 31 3b 20  73 73 3d 69 6e 70 32 3b  |n=inp1; ss=inp2;|
00018d80  20 73 61 3d 61 63 74 69  6f 6e 3b 20 73 73 65 3d  | sa=action; sse=|
00018d90  73 65 6c 66 3b 0a 20 20  20 69 6e 70 31 20 3d 20  |self;.   inp1 = |
00018da0  69 3b 20 69 6e 70 32 20  3d 20 6a 3b 20 6e 6f 75  |i; inp2 = j; nou|
00018db0  6e 3d 69 3b 20 73 65 63  6f 6e 64 3d 6a 3b 20 61  |n=i; second=j; a|
00018dc0  63 74 69 6f 6e 3d 61 63  74 69 3b 0a 0a 23 49 46  |ction=acti;..#IF|
00018dd0  44 45 46 20 44 45 42 55  47 3b 0a 20 20 20 69 66  |DEF DEBUG;.   if|
00018de0  20 28 64 65 62 75 67 5f  66 6c 61 67 20 26 20 32  | (debug_flag & 2|
00018df0  20 7e 3d 20 30 29 20 54  72 61 63 65 41 63 74 69  | ~= 0) TraceActi|
00018e00  6f 6e 28 31 29 3b 0a 23  45 4e 44 49 46 3b 0a 0a  |on(1);.#ENDIF;..|
00018e10  20 20 20 69 66 20 28 6d  65 74 61 7e 3d 31 29 0a  |   if (meta~=1).|
00018e20  20 20 20 7b 20 20 20 69  66 20 28 47 61 6d 65 50  |   {   if (GameP|
00018e30  72 65 52 6f 75 74 69 6e  65 28 29 7e 3d 30 29 20  |reRoutine()~=0) |
00018e40  6a 75 6d 70 20 53 75 62  73 69 64 65 3b 0a 20 20  |jump Subside;.  |
00018e50  20 20 20 20 20 69 66 20  28 52 75 6e 52 6f 75 74  |     if (RunRout|
00018e60  69 6e 65 73 28 70 6c 61  79 65 72 2c 62 65 66 6f  |ines(player,befo|
00018e70  72 65 29 7e 3d 30 29 20  6a 75 6d 70 20 53 75 62  |re)~=0) jump Sub|
00018e80  73 69 64 65 3b 0a 20 20  20 20 20 20 20 69 66 20  |side;.       if |
00018e90  28 6c 6f 63 61 74 69 6f  6e 7e 3d 30 20 26 26 20  |(location~=0 && |
00018ea0  52 75 6e 52 6f 75 74 69  6e 65 73 28 6c 6f 63 61  |RunRoutines(loca|
00018eb0  74 69 6f 6e 2c 62 65 66  6f 72 65 29 7e 3d 30 29  |tion,before)~=0)|
00018ec0  20 6a 75 6d 70 20 53 75  62 73 69 64 65 3b 0a 20  | jump Subside;. |
00018ed0  20 20 20 20 20 20 69 66  20 28 69 6e 70 31 3e 31  |      if (inp1>1|
00018ee0  20 26 26 20 52 75 6e 52  6f 75 74 69 6e 65 73 28  | && RunRoutines(|
00018ef0  69 6e 70 31 2c 62 65 66  6f 72 65 29 7e 3d 30 29  |inp1,before)~=0)|
00018f00  20 6a 75 6d 70 20 53 75  62 73 69 64 65 3b 0a 20  | jump Subside;. |
00018f10  20 20 7d 0a 20 20 20 69  6e 64 69 72 65 63 74 28  |  }.   indirect(|
00018f20  23 61 63 74 69 6f 6e 73  5f 74 61 62 6c 65 2d 2d  |#actions_table--|
00018f30  3e 61 63 74 69 6f 6e 29  3b 0a 20 20 20 73 65 6c  |>action);.   sel|
00018f40  66 3d 73 73 65 3b 20 69  6e 70 31 3d 73 6e 3b 20  |f=sse; inp1=sn; |
00018f50  6e 6f 75 6e 3d 73 6e 3b  20 69 6e 70 32 3d 73 73  |noun=sn; inp2=ss|
00018f60  3b 20 73 65 63 6f 6e 64  3d 73 73 3b 20 61 63 74  |; second=ss; act|
00018f70  69 6f 6e 3d 73 61 3b 20  72 66 61 6c 73 65 3b 0a  |ion=sa; rfalse;.|
00018f80  20 20 20 2e 53 75 62 73  69 64 65 3b 0a 20 20 20  |   .Subside;.   |
00018f90  73 65 6c 66 3d 73 73 65  3b 20 69 6e 70 31 3d 73  |self=sse; inp1=s|
00018fa0  6e 3b 20 6e 6f 75 6e 3d  73 6e 3b 20 69 6e 70 32  |n; noun=sn; inp2|
00018fb0  3d 73 73 3b 20 73 65 63  6f 6e 64 3d 73 73 3b 20  |=ss; second=ss; |
00018fc0  61 63 74 69 6f 6e 3d 73  61 3b 20 72 74 72 75 65  |action=sa; rtrue|
00018fd0  3b 0a 5d 3b 0a 0a 5b 20  50 72 6f 63 65 73 73 20  |;.];..[ Process |
00018fe0  69 20 6a 20 61 63 74 69  3b 0a 20 20 20 69 6e 70  |i j acti;.   inp|
00018ff0  31 20 3d 20 69 3b 20 69  6e 70 32 20 3d 20 6a 3b  |1 = i; inp2 = j;|
00019000  20 6e 6f 75 6e 3d 69 3b  20 73 65 63 6f 6e 64 3d  | noun=i; second=|
00019010  6a 3b 20 61 63 74 69 6f  6e 3d 61 63 74 69 3b 0a  |j; action=acti;.|
00019020  20 20 20 69 66 20 28 69  6e 70 31 3d 3d 31 29 20  |   if (inp1==1) |
00019030  6e 6f 75 6e 3d 73 70 65  63 69 61 6c 5f 6e 75 6d  |noun=special_num|
00019040  62 65 72 3b 0a 20 20 20  69 66 20 28 69 6e 70 32  |ber;.   if (inp2|
00019050  3d 3d 31 29 0a 20 20 20  7b 20 20 20 69 66 20 28  |==1).   {   if (|
00019060  69 6e 70 31 3d 3d 31 29  20 73 65 63 6f 6e 64 3d  |inp1==1) second=|
00019070  73 70 65 63 69 61 6c 5f  6e 75 6d 62 65 72 32 3b  |special_number2;|
00019080  0a 20 20 20 20 20 20 20  65 6c 73 65 20 73 65 63  |.       else sec|
00019090  6f 6e 64 3d 73 70 65 63  69 61 6c 5f 6e 75 6d 62  |ond=special_numb|
000190a0  65 72 3b 0a 20 20 20 7d  0a 23 49 46 44 45 46 20  |er;.   }.#IFDEF |
000190b0  44 45 42 55 47 3b 0a 20  20 20 69 66 20 28 64 65  |DEBUG;.   if (de|
000190c0  62 75 67 5f 66 6c 61 67  20 26 20 32 20 7e 3d 20  |bug_flag & 2 ~= |
000190d0  30 29 20 54 72 61 63 65  41 63 74 69 6f 6e 28 30  |0) TraceAction(0|
000190e0  29 3b 0a 23 45 4e 44 49  46 3b 0a 20 20 20 69 66  |);.#ENDIF;.   if|
000190f0  20 28 6d 65 74 61 7e 3d  31 29 0a 20 20 20 7b 20  | (meta~=1).   { |
00019100  20 20 69 66 20 28 47 61  6d 65 50 72 65 52 6f 75  |  if (GamePreRou|
00019110  74 69 6e 65 28 29 7e 3d  30 29 20 72 74 72 75 65  |tine()~=0) rtrue|
00019120  3b 0a 20 20 20 20 20 20  20 69 66 20 28 52 75 6e  |;.       if (Run|
00019130  52 6f 75 74 69 6e 65 73  28 70 6c 61 79 65 72 2c  |Routines(player,|
00019140  62 65 66 6f 72 65 29 7e  3d 30 29 20 6a 75 6d 70  |before)~=0) jump|
00019150  20 53 75 62 73 69 64 65  3b 0a 20 20 20 20 20 20  | Subside;.      |
00019160  20 69 66 20 28 6c 6f 63  61 74 69 6f 6e 7e 3d 30  | if (location~=0|
00019170  20 26 26 20 52 75 6e 52  6f 75 74 69 6e 65 73 28  | && RunRoutines(|
00019180  6c 6f 63 61 74 69 6f 6e  2c 62 65 66 6f 72 65 29  |location,before)|
00019190  7e 3d 30 29 20 72 74 72  75 65 3b 0a 20 20 20 20  |~=0) rtrue;.    |
000191a0  20 20 20 69 66 20 28 69  6e 70 31 3e 31 20 26 26  |   if (inp1>1 &&|
000191b0  20 52 75 6e 52 6f 75 74  69 6e 65 73 28 69 6e 70  | RunRoutines(inp|
000191c0  31 2c 62 65 66 6f 72 65  29 7e 3d 30 29 20 72 74  |1,before)~=0) rt|
000191d0  72 75 65 3b 0a 20 20 20  7d 0a 20 20 20 69 6e 64  |rue;.   }.   ind|
000191e0  69 72 65 63 74 28 23 61  63 74 69 6f 6e 73 5f 74  |irect(#actions_t|
000191f0  61 62 6c 65 2d 2d 3e 61  63 74 69 6f 6e 29 3b 0a  |able-->action);.|
00019200  5d 3b 0a 0a 5b 20 52 75  6e 4c 69 66 65 20 61 20  |];..[ RunLife a |
00019210  6a 3b 0a 20 20 20 72 65  61 73 6f 6e 5f 63 6f 64  |j;.   reason_cod|
00019220  65 20 3d 20 6a 3b 20 72  65 74 75 72 6e 20 52 75  |e = j; return Ru|
00019230  6e 52 6f 75 74 69 6e 65  73 28 61 2c 6c 69 66 65  |nRoutines(a,life|
00019240  29 3b 0a 5d 3b 0a 0a 5b  20 41 66 74 65 72 52 6f  |);.];..[ AfterRo|
00019250  75 74 69 6e 65 73 3b 0a  0a 20 20 20 69 66 20 28  |utines;..   if (|
00019260  52 75 6e 52 6f 75 74 69  6e 65 73 28 70 6c 61 79  |RunRoutines(play|
00019270  65 72 2c 61 66 74 65 72  29 7e 3d 30 29 20 72 74  |er,after)~=0) rt|
00019280  72 75 65 3b 0a 20 20 20  69 66 20 28 6c 6f 63 61  |rue;.   if (loca|
00019290  74 69 6f 6e 7e 3d 30 20  26 26 20 52 75 6e 52 6f  |tion~=0 && RunRo|
000192a0  75 74 69 6e 65 73 28 6c  6f 63 61 74 69 6f 6e 2c  |utines(location,|
000192b0  61 66 74 65 72 29 7e 3d  30 29 20 72 74 72 75 65  |after)~=0) rtrue|
000192c0  3b 0a 20 20 20 69 66 20  28 69 6e 70 31 3e 31 20  |;.   if (inp1>1 |
000192d0  26 26 20 52 75 6e 52 6f  75 74 69 6e 65 73 28 69  |&& RunRoutines(i|
000192e0  6e 70 31 2c 61 66 74 65  72 29 7e 3d 30 29 20 72  |np1,after)~=0) r|
000192f0  74 72 75 65 3b 0a 0a 20  20 20 72 65 74 75 72 6e  |true;..   return|
00019300  20 47 61 6d 65 50 6f 73  74 52 6f 75 74 69 6e 65  | GamePostRoutine|
00019310  28 29 3b 0a 5d 3b 0a 0a  5b 20 4c 41 66 74 65 72  |();.];..[ LAfter|
00019320  52 6f 75 74 69 6e 65 73  3b 0a 20 20 20 69 66 20  |Routines;.   if |
00019330  28 6c 6f 63 61 74 69 6f  6e 7e 3d 30 20 26 26 20  |(location~=0 && |
00019340  52 75 6e 52 6f 75 74 69  6e 65 73 28 6c 6f 63 61  |RunRoutines(loca|
00019350  74 69 6f 6e 2c 61 66 74  65 72 29 7e 3d 30 29 20  |tion,after)~=0) |
00019360  72 74 72 75 65 3b 0a 20  20 20 72 65 74 75 72 6e  |rtrue;.   return|
00019370  20 47 61 6d 65 50 6f 73  74 52 6f 75 74 69 6e 65  | GamePostRoutine|
00019380  28 29 3b 0a 5d 3b 0a 0a  5b 20 42 61 6e 6e 65 72  |();.];..[ Banner|
00019390  20 69 3b 0a 23 49 46 56  35 3b 20 73 74 79 6c 65  | i;.#IFV5; style|
000193a0  20 62 6f 6c 64 3b 20 23  45 4e 44 49 46 3b 0a 20  | bold; #ENDIF;. |
000193b0  20 20 70 72 69 6e 74 5f  70 61 64 64 72 20 23 53  |  print_paddr #S|
000193c0  74 6f 72 79 3b 0a 23 49  46 56 35 3b 20 73 74 79  |tory;.#IFV5; sty|
000193d0  6c 65 20 72 6f 6d 61 6e  3b 20 23 45 4e 44 49 46  |le roman; #ENDIF|
000193e0  3b 0a 20 20 20 70 72 69  6e 74 5f 70 61 64 64 72  |;.   print_paddr|
000193f0  20 23 48 65 61 64 6c 69  6e 65 3b 0a 20 20 20 70  | #Headline;.   p|
00019400  72 69 6e 74 20 22 52 65  6c 65 61 73 65 20 22 2c  |rint "Release ",|
00019410  20 28 30 2d 2d 3e 31 29  20 26 20 24 30 33 66 66  | (0-->1) & $03ff|
00019420  2c 20 22 20 2f 20 53 65  72 69 61 6c 20 6e 75 6d  |, " / Serial num|
00019430  62 65 72 20 22 3b 0a 20  20 20 66 6f 72 20 28 69  |ber ";.   for (i|
00019440  3d 31 38 3a 69 3c 32 34  3a 69 2b 2b 29 20 70 72  |=18:i<24:i++) pr|
00019450  69 6e 74 5f 63 68 61 72  20 30 2d 3e 69 3b 0a 23  |int_char 0->i;.#|
00019460  49 46 56 33 3b 0a 20 20  70 72 69 6e 74 20 22 20  |IFV3;.  print " |
00019470  20 28 43 6f 6d 70 69 6c  65 64 20 62 79 20 49 6e  | (Compiled by In|
00019480  66 6f 72 6d 20 76 22 3b  20 69 6e 76 65 72 73 69  |form v"; inversi|
00019490  6f 6e 3b 0a 23 45 4e 44  49 46 3b 0a 23 49 46 56  |on;.#ENDIF;.#IFV|
000194a0  35 3b 0a 20 20 70 72 69  6e 74 20 22 20 2f 20 49  |5;.  print " / I|
000194b0  6e 74 65 72 70 72 65 74  65 72 20 22 2c 20 30 2d  |nterpreter ", 0-|
000194c0  3e 24 31 65 2c 20 22 20  56 65 72 73 69 6f 6e 20  |>$1e, " Version |
000194d0  22 2c 20 63 68 61 72 20  30 2d 3e 24 31 66 2c 0a  |", char 0->$1f,.|
000194e0  20 20 20 20 20 20 20 20  22 5e 28 43 6f 6d 70 69  |        "^(Compi|
000194f0  6c 65 64 20 62 79 20 49  6e 66 6f 72 6d 20 76 22  |led by Inform v"|
00019500  3b 20 69 6e 76 65 72 73  69 6f 6e 3b 0a 23 45 4e  |; inversion;.#EN|
00019510  44 49 46 3b 0a 23 69 66  64 65 66 20 44 45 42 55  |DIF;.#ifdef DEBU|
00019520  47 3b 0a 20 20 70 72 69  6e 74 20 22 20 44 22 3b  |G;.  print " D";|
00019530  0a 23 65 6e 64 69 66 3b  0a 20 20 70 72 69 6e 74  |.#endif;.  print|
00019540  20 22 29 5e 22 3b 0a 5d  3b 0a 0a 5b 20 56 65 72  | ")^";.];..[ Ver|
00019550  73 69 6f 6e 53 75 62 3b  0a 20 20 42 61 6e 6e 65  |sionSub;.  Banne|
00019560  72 28 29 3b 20 70 72 69  6e 74 20 22 4c 69 62 72  |r(); print "Libr|
00019570  61 72 79 20 72 65 6c 65  61 73 65 20 22 3b 20 70  |ary release "; p|
00019580  72 69 6e 74 5f 70 61 64  64 72 20 23 4c 69 62 52  |rint_paddr #LibR|
00019590  65 6c 65 61 73 65 3b 0a  20 20 70 72 69 6e 74 20  |elease;.  print |
000195a0  22 20 73 65 72 69 61 6c  20 6e 75 6d 62 65 72 20  |" serial number |
000195b0  22 3b 20 70 72 69 6e 74  5f 70 61 64 64 72 20 23  |"; print_paddr #|
000195c0  4c 69 62 53 65 72 69 61  6c 3b 0a 20 20 6e 65 77  |LibSerial;.  new|
000195d0  5f 6c 69 6e 65 3b 0a 5d  3b 0a 0a 23 49 46 56 35  |_line;.];..#IFV5|
000195e0  3b 0a 47 6c 6f 62 61 6c  20 70 72 65 74 74 79 5f  |;.Global pretty_|
000195f0  66 6c 61 67 3d 31 3b 0a  23 45 4e 44 49 46 3b 0a  |flag=1;.#ENDIF;.|
00019600  47 6c 6f 62 61 6c 20 69  74 65 6d 5f 77 69 64 74  |Global item_widt|
00019610  68 3d 38 3b 0a 47 6c 6f  62 61 6c 20 69 74 65 6d  |h=8;.Global item|
00019620  5f 6e 61 6d 65 3d 22 4e  61 6d 65 6c 65 73 73 20  |_name="Nameless |
00019630  69 74 65 6d 22 3b 0a 47  6c 6f 62 61 6c 20 6d 65  |item";.Global me|
00019640  6e 75 5f 69 74 65 6d 3d  30 3b 0a 47 6c 6f 62 61  |nu_item=0;.Globa|
00019650  6c 20 6d 65 6e 75 5f 63  68 6f 69 63 65 73 3d 22  |l menu_choices="|
00019660  22 3b 0a 0a 5b 20 4c 6f  77 4b 65 79 5f 4d 65 6e  |";..[ LowKey_Men|
00019670  75 20 6d 65 6e 75 5f 63  68 6f 69 63 65 73 20 45  |u menu_choices E|
00019680  6e 74 72 79 52 20 43 68  6f 69 63 65 52 20 6c 69  |ntryR ChoiceR li|
00019690  6e 65 73 20 6d 61 69 6e  5f 74 69 74 6c 65 20 69  |nes main_title i|
000196a0  3b 0a 0a 20 20 6d 65 6e  75 5f 69 74 65 6d 3d 30  |;..  menu_item=0|
000196b0  3b 0a 20 20 6c 69 6e 65  73 3d 69 6e 64 69 72 65  |;.  lines=indire|
000196c0  63 74 28 45 6e 74 72 79  52 29 3b 0a 20 20 6d 61  |ct(EntryR);.  ma|
000196d0  69 6e 5f 74 69 74 6c 65  3d 69 74 65 6d 5f 6e 61  |in_title=item_na|
000196e0  6d 65 3b 0a 0a 20 20 70  72 69 6e 74 20 22 2d 2d  |me;..  print "--|
000196f0  2d 20 22 3b 20 70 72 69  6e 74 5f 70 61 64 64 72  |- "; print_paddr|
00019700  20 6d 61 69 6e 5f 74 69  74 6c 65 3b 20 70 72 69  | main_title; pri|
00019710  6e 74 20 22 20 2d 2d 2d  5e 5e 22 3b 0a 20 20 70  |nt " ---^^";.  p|
00019720  72 69 6e 74 5f 70 61 64  64 72 20 6d 65 6e 75 5f  |rint_paddr menu_|
00019730  63 68 6f 69 63 65 73 3b  0a 0a 20 20 20 2e 4c 4b  |choices;..   .LK|
00019740  4d 4c 3b 0a 20 20 70 72  69 6e 74 20 22 5e 54 79  |ML;.  print "^Ty|
00019750  70 65 20 61 20 6e 75 6d  62 65 72 20 66 72 6f 6d  |pe a number from|
00019760  20 31 20 74 6f 20 22 2c  20 6c 69 6e 65 73 2c 20  | 1 to ", lines, |
00019770  22 20 6f 72 20 70 72 65  73 73 20 45 4e 54 45 52  |" or press ENTER|
00019780  2e 5e 3e 20 22 3b 0a 0a  20 20 20 23 49 46 56 33  |.^> ";..   #IFV3|
00019790  3b 20 72 65 61 64 20 62  75 66 66 65 72 20 70 61  |; read buffer pa|
000197a0  72 73 65 3b 20 23 45 4e  44 49 46 3b 0a 20 20 20  |rse; #ENDIF;.   |
000197b0  23 49 46 56 35 3b 20 72  65 61 64 20 62 75 66 66  |#IFV5; read buff|
000197c0  65 72 20 70 61 72 73 65  20 44 72 61 77 53 74 61  |er parse DrawSta|
000197d0  74 75 73 4c 69 6e 65 3b  20 23 45 4e 44 49 46 3b  |tusLine; #ENDIF;|
000197e0  0a 20 20 20 69 3d 70 61  72 73 65 2d 2d 3e 31 3b  |.   i=parse-->1;|
000197f0  0a 20 20 20 69 66 20 28  69 3d 3d 27 71 75 69 74  |.   if (i=='quit|
00019800  27 20 6f 72 20 23 77 24  71 20 7c 7c 20 70 61 72  |' or #w$q || par|
00019810  73 65 2d 3e 31 3d 3d 30  29 0a 20 20 20 7b 20 20  |se->1==0).   {  |
00019820  20 69 66 20 28 64 65 61  64 66 6c 61 67 3d 3d 30  | if (deadflag==0|
00019830  29 20 3c 3c 4c 6f 6f 6b  3e 3e 3b 0a 20 20 20 20  |) <<Look>>;.    |
00019840  20 20 20 72 66 61 6c 73  65 3b 0a 20 20 20 7d 0a  |   rfalse;.   }.|
00019850  20 20 20 69 3d 54 72 79  4e 75 6d 62 65 72 28 31  |   i=TryNumber(1|
00019860  29 3b 0a 20 20 20 69 66  20 28 69 3c 31 20 7c 7c  |);.   if (i<1 |||
00019870  20 69 3e 6c 69 6e 65 73  29 20 6a 75 6d 70 20 4c  | i>lines) jump L|
00019880  4b 4d 4c 3b 0a 20 20 20  6d 65 6e 75 5f 69 74 65  |KML;.   menu_ite|
00019890  6d 3d 69 3b 0a 20 20 20  69 6e 64 69 72 65 63 74  |m=i;.   indirect|
000198a0  28 43 68 6f 69 63 65 52  29 3b 0a 20 20 20 6a 75  |(ChoiceR);.   ju|
000198b0  6d 70 20 4c 4b 4d 4c 3b  0a 5d 3b 0a 0a 23 49 46  |mp LKML;.];..#IF|
000198c0  56 33 3b 0a 5b 20 44 6f  4d 65 6e 75 20 6d 65 6e  |V3;.[ DoMenu men|
000198d0  75 5f 63 68 6f 69 63 65  73 20 45 6e 74 72 79 52  |u_choices EntryR|
000198e0  20 43 68 6f 69 63 65 52  3b 0a 20 20 4c 6f 77 4b  | ChoiceR;.  LowK|
000198f0  65 79 5f 4d 65 6e 75 28  6d 65 6e 75 5f 63 68 6f  |ey_Menu(menu_cho|
00019900  69 63 65 73 2c 45 6e 74  72 79 52 2c 43 68 6f 69  |ices,EntryR,Choi|
00019910  63 65 52 29 3b 0a 5d 3b  0a 23 45 4e 44 49 46 3b  |ceR);.];.#ENDIF;|
00019920  0a 0a 23 49 46 56 35 3b  0a 47 6c 6f 62 61 6c 20  |..#IFV5;.Global |
00019930  6d 65 6e 75 5f 6e 65 73  74 69 6e 67 20 3d 20 30  |menu_nesting = 0|
00019940  3b 0a 5b 20 44 6f 4d 65  6e 75 20 6d 65 6e 75 5f  |;.[ DoMenu menu_|
00019950  63 68 6f 69 63 65 73 20  45 6e 74 72 79 52 20 43  |choices EntryR C|
00019960  68 6f 69 63 65 52 0a 20  20 20 20 20 20 20 20 20  |hoiceR.         |
00019970  6c 69 6e 65 73 20 6d 61  69 6e 5f 74 69 74 6c 65  |lines main_title|
00019980  20 6d 61 69 6e 5f 77 69  64 20 63 6c 20 69 20 6a  | main_wid cl i j|
00019990  20 6f 6c 64 63 6c 20 70  6b 65 79 3b 0a 20 20 69  | oldcl pkey;.  i|
000199a0  66 20 28 70 72 65 74 74  79 5f 66 6c 61 67 3d 3d  |f (pretty_flag==|
000199b0  30 29 0a 20 20 7b 20 20  20 4c 6f 77 4b 65 79 5f  |0).  {   LowKey_|
000199c0  4d 65 6e 75 28 6d 65 6e  75 5f 63 68 6f 69 63 65  |Menu(menu_choice|
000199d0  73 2c 45 6e 74 72 79 52  2c 43 68 6f 69 63 65 52  |s,EntryR,ChoiceR|
000199e0  29 3b 0a 20 20 20 20 20  20 72 66 61 6c 73 65 3b  |);.      rfalse;|
000199f0  0a 20 20 7d 0a 20 20 6d  65 6e 75 5f 6e 65 73 74  |.  }.  menu_nest|
00019a00  69 6e 67 2b 2b 3b 0a 20  20 6d 65 6e 75 5f 69 74  |ing++;.  menu_it|
00019a10  65 6d 3d 30 3b 0a 20 20  6c 69 6e 65 73 3d 69 6e  |em=0;.  lines=in|
00019a20  64 69 72 65 63 74 28 45  6e 74 72 79 52 29 3b 0a  |direct(EntryR);.|
00019a30  20 20 6d 61 69 6e 5f 74  69 74 6c 65 3d 69 74 65  |  main_title=ite|
00019a40  6d 5f 6e 61 6d 65 3b 20  6d 61 69 6e 5f 77 69 64  |m_name; main_wid|
00019a50  3d 69 74 65 6d 5f 77 69  64 74 68 3b 0a 20 20 63  |=item_width;.  c|
00019a60  6c 3d 37 3b 0a 20 20 2e  52 65 44 69 73 70 6c 61  |l=7;.  .ReDispla|
00019a70  79 3b 0a 20 20 20 20 20  20 6f 6c 64 63 6c 3d 30  |y;.      oldcl=0|
00019a80  3b 0a 20 20 20 20 20 20  65 72 61 73 65 5f 77 69  |;.      erase_wi|
00019a90  6e 64 6f 77 20 24 66 66  66 66 3b 0a 20 20 20 20  |ndow $ffff;.    |
00019aa0  20 20 69 3d 6c 69 6e 65  73 2b 37 3b 0a 20 20 20  |  i=lines+7;.   |
00019ab0  20 20 20 73 70 6c 69 74  5f 77 69 6e 64 6f 77 20  |   split_window |
00019ac0  69 3b 0a 20 20 20 20 20  20 69 20 3d 20 30 2d 3e  |i;.      i = 0->|
00019ad0  33 33 3b 0a 20 20 20 20  20 20 69 66 20 69 3d 3d  |33;.      if i==|
00019ae0  30 20 7b 20 69 3d 38 30  3b 20 7d 0a 20 20 20 20  |0 { i=80; }.    |
00019af0  20 20 73 65 74 5f 77 69  6e 64 6f 77 20 31 3b 0a  |  set_window 1;.|
00019b00  20 20 20 20 20 20 73 65  74 5f 63 75 72 73 6f 72  |      set_cursor|
00019b10  20 31 20 31 3b 0a 20 20  20 20 20 20 73 74 79 6c  | 1 1;.      styl|
00019b20  65 20 72 65 76 65 72 73  65 3b 0a 20 20 20 20 20  |e reverse;.     |
00019b30  20 73 70 61 63 65 73 28  69 29 3b 20 6a 3d 69 2f  | spaces(i); j=i/|
00019b40  32 2d 6d 61 69 6e 5f 77  69 64 3b 0a 20 20 20 20  |2-main_wid;.    |
00019b50  20 20 73 65 74 5f 63 75  72 73 6f 72 20 31 20 6a  |  set_cursor 1 j|
00019b60  3b 0a 20 20 20 20 20 20  70 72 69 6e 74 5f 70 61  |;.      print_pa|
00019b70  64 64 72 20 6d 61 69 6e  5f 74 69 74 6c 65 3b 0a  |ddr main_title;.|
00019b80  20 20 20 20 20 20 73 65  74 5f 63 75 72 73 6f 72  |      set_cursor|
00019b90  20 32 20 31 3b 20 73 70  61 63 65 73 28 69 29 3b  | 2 1; spaces(i);|
00019ba0  0a 20 20 20 20 20 20 73  65 74 5f 63 75 72 73 6f  |.      set_curso|
00019bb0  72 20 32 20 32 3b 20 70  72 69 6e 74 20 22 4e 20  |r 2 2; print "N |
00019bc0  3d 20 6e 65 78 74 20 73  75 62 6a 65 63 74 22 3b  |= next subject";|
00019bd0  0a 20 20 20 20 20 20 6a  3d 69 2d 31 32 3b 20 73  |.      j=i-12; s|
00019be0  65 74 5f 63 75 72 73 6f  72 20 32 20 6a 3b 20 70  |et_cursor 2 j; p|
00019bf0  72 69 6e 74 20 22 50 20  3d 20 70 72 65 76 69 6f  |rint "P = previo|
00019c00  75 73 22 3b 0a 20 20 20  20 20 20 73 65 74 5f 63  |us";.      set_c|
00019c10  75 72 73 6f 72 20 33 20  31 3b 20 73 70 61 63 65  |ursor 3 1; space|
00019c20  73 28 69 29 3b 0a 20 20  20 20 20 20 73 65 74 5f  |s(i);.      set_|
00019c30  63 75 72 73 6f 72 20 33  20 32 3b 20 70 72 69 6e  |cursor 3 2; prin|
00019c40  74 20 22 52 45 54 55 52  4e 20 3d 20 72 65 61 64  |t "RETURN = read|
00019c50  20 73 75 62 6a 65 63 74  22 3b 0a 20 20 20 20 20  | subject";.     |
00019c60  20 6a 3d 69 2d 31 37 3b  20 73 65 74 5f 63 75 72  | j=i-17; set_cur|
00019c70  73 6f 72 20 33 20 6a 3b  0a 20 20 20 20 20 20 69  |sor 3 j;.      i|
00019c80  66 20 28 6d 65 6e 75 5f  6e 65 73 74 69 6e 67 3d  |f (menu_nesting=|
00019c90  3d 31 29 0a 20 20 20 20  20 20 20 20 20 20 70 72  |=1).          pr|
00019ca0  69 6e 74 20 22 20 20 51  20 3d 20 72 65 73 75 6d  |int "  Q = resum|
00019cb0  65 20 67 61 6d 65 22 3b  0a 20 20 20 20 20 20 65  |e game";.      e|
00019cc0  6c 73 65 0a 20 20 20 20  20 20 20 20 20 20 70 72  |lse.          pr|
00019cd0  69 6e 74 20 22 51 20 3d  20 70 72 65 76 69 6f 75  |int "Q = previou|
00019ce0  73 20 6d 65 6e 75 22 3b  0a 20 20 20 20 20 20 73  |s menu";.      s|
00019cf0  74 79 6c 65 20 72 6f 6d  61 6e 3b 0a 20 20 20 20  |tyle roman;.    |
00019d00  20 20 73 65 74 5f 63 75  72 73 6f 72 20 35 20 32  |  set_cursor 5 2|
00019d10  3b 20 66 6f 6e 74 20 6f  66 66 3b 0a 0a 20 20 20  |; font off;..   |
00019d20  20 20 20 70 72 69 6e 74  5f 70 61 64 64 72 20 6d  |   print_paddr m|
00019d30  65 6e 75 5f 63 68 6f 69  63 65 73 3b 0a 0a 20 20  |enu_choices;..  |
00019d40  20 20 20 20 2e 4b 65 79  4c 6f 6f 70 3b 0a 20 20  |    .KeyLoop;.  |
00019d50  20 20 20 20 69 66 20 28  63 6c 7e 3d 6f 6c 64 63  |    if (cl~=oldc|
00019d60  6c 29 0a 20 20 20 20 20  20 7b 20 20 20 69 66 20  |l).      {   if |
00019d70  28 6f 6c 64 63 6c 3e 30  29 20 7b 20 73 65 74 5f  |(oldcl>0) { set_|
00019d80  63 75 72 73 6f 72 20 6f  6c 64 63 6c 20 34 3b 20  |cursor oldcl 4; |
00019d90  70 72 69 6e 74 20 22 20  22 3b 20 7d 0a 20 20 20  |print " "; }.   |
00019da0  20 20 20 20 20 20 20 73  65 74 5f 63 75 72 73 6f  |       set_curso|
00019db0  72 20 63 6c 20 34 3b 20  70 72 69 6e 74 20 22 3e  |r cl 4; print ">|
00019dc0  22 3b 0a 20 20 20 20 20  20 7d 0a 20 20 20 20 20  |";.      }.     |
00019dd0  20 6f 6c 64 63 6c 3d 63  6c 3b 0a 20 20 20 20 20  | oldcl=cl;.     |
00019de0  20 72 65 61 64 5f 63 68  61 72 20 31 20 30 20 30  | read_char 1 0 0|
00019df0  20 70 6b 65 79 3b 0a 20  20 20 20 20 20 69 66 20  | pkey;.      if |
00019e00  28 70 6b 65 79 3d 3d 27  4e 27 20 6f 72 20 27 6e  |(pkey=='N' or 'n|
00019e10  27 20 6f 72 20 31 33 30  29 0a 20 20 20 20 20 20  |' or 130).      |
00019e20  20 20 20 20 7b 20 63 6c  2b 2b 3b 20 69 66 20 28  |    { cl++; if (|
00019e30  63 6c 3d 3d 37 2b 6c 69  6e 65 73 29 20 63 6c 3d  |cl==7+lines) cl=|
00019e40  37 3b 20 6a 75 6d 70 20  4b 65 79 4c 6f 6f 70 3b  |7; jump KeyLoop;|
00019e50  20 7d 0a 20 20 20 20 20  20 69 66 20 28 70 6b 65  | }.      if (pke|
00019e60  79 3d 3d 27 50 27 20 6f  72 20 27 70 27 20 6f 72  |y=='P' or 'p' or|
00019e70  20 31 32 39 29 0a 20 20  20 20 20 20 20 20 20 20  | 129).          |
00019e80  7b 20 63 6c 2d 2d 3b 20  69 66 20 28 63 6c 3d 3d  |{ cl--; if (cl==|
00019e90  36 29 20 20 63 6c 3d 36  2b 6c 69 6e 65 73 3b 20  |6)  cl=6+lines; |
00019ea0  6a 75 6d 70 20 4b 65 79  4c 6f 6f 70 3b 20 7d 0a  |jump KeyLoop; }.|
00019eb0  20 20 20 20 20 20 69 66  20 28 70 6b 65 79 3d 3d  |      if (pkey==|
00019ec0  27 51 27 20 6f 72 20 27  71 27 29 20 7b 20 6a 75  |'Q' or 'q') { ju|
00019ed0  6d 70 20 51 75 69 74 48  65 6c 70 3b 20 7d 0a 20  |mp QuitHelp; }. |
00019ee0  20 20 20 20 20 69 66 20  28 70 6b 65 79 3d 3d 31  |     if (pkey==1|
00019ef0  30 20 6f 72 20 31 33 29  0a 20 20 20 20 20 20 7b  |0 or 13).      {|
00019f00  20 20 20 73 65 74 5f 77  69 6e 64 6f 77 20 30 3b  |   set_window 0;|
00019f10  20 66 6f 6e 74 20 6f 6e  3b 0a 20 20 20 20 20 20  | font on;.      |
00019f20  20 20 20 20 6e 65 77 5f  6c 69 6e 65 3b 20 6e 65  |    new_line; ne|
00019f30  77 5f 6c 69 6e 65 3b 20  6e 65 77 5f 6c 69 6e 65  |w_line; new_line|
00019f40  3b 0a 0a 20 20 20 20 20  20 20 20 20 20 6d 65 6e  |;..          men|
00019f50  75 5f 69 74 65 6d 3d 63  6c 2d 36 3b 0a 20 20 20  |u_item=cl-6;.   |
00019f60  20 20 20 20 20 20 20 69  6e 64 69 72 65 63 74 28  |       indirect(|
00019f70  45 6e 74 72 79 52 29 3b  0a 0a 20 20 20 20 20 20  |EntryR);..      |
00019f80  20 20 20 20 65 72 61 73  65 5f 77 69 6e 64 6f 77  |    erase_window|
00019f90  20 24 66 66 66 66 3b 0a  20 20 20 20 20 20 20 20  | $ffff;.        |
00019fa0  20 20 73 70 6c 69 74 5f  77 69 6e 64 6f 77 20 31  |  split_window 1|
00019fb0  3b 0a 20 20 20 20 20 20  20 20 20 20 69 20 3d 20  |;.          i = |
00019fc0  30 2d 3e 33 33 3b 20 69  66 20 69 3d 3d 30 20 7b  |0->33; if i==0 {|
00019fd0  20 69 3d 38 30 3b 20 7d  0a 20 20 20 20 20 20 20  | i=80; }.       |
00019fe0  20 20 20 73 65 74 5f 77  69 6e 64 6f 77 20 31 3b  |   set_window 1;|
00019ff0  20 73 65 74 5f 63 75 72  73 6f 72 20 31 20 31 3b  | set_cursor 1 1;|
0001a000  20 73 74 79 6c 65 20 72  65 76 65 72 73 65 3b 20  | style reverse; |
0001a010  73 70 61 63 65 73 28 69  29 3b 0a 20 20 20 20 20  |spaces(i);.     |
0001a020  20 20 20 20 20 6a 3d 69  2f 32 2d 69 74 65 6d 5f  |     j=i/2-item_|
0001a030  77 69 64 74 68 3b 0a 20  20 20 20 20 20 20 20 20  |width;.         |
0001a040  20 73 65 74 5f 63 75 72  73 6f 72 20 31 20 6a 3b  | set_cursor 1 j;|
0001a050  0a 20 20 20 20 20 20 20  20 20 20 70 72 69 6e 74  |.          print|
0001a060  5f 70 61 64 64 72 20 69  74 65 6d 5f 6e 61 6d 65  |_paddr item_name|
0001a070  3b 0a 20 20 20 20 20 20  20 20 20 20 73 74 79 6c  |;.          styl|
0001a080  65 20 72 6f 6d 61 6e 3b  20 73 65 74 5f 77 69 6e  |e roman; set_win|
0001a090  64 6f 77 20 30 3b 20 6e  65 77 5f 6c 69 6e 65 3b  |dow 0; new_line;|
0001a0a0  0a 0a 20 20 20 20 20 20  20 20 20 20 69 66 20 28  |..          if (|
0001a0b0  69 6e 64 69 72 65 63 74  28 43 68 6f 69 63 65 52  |indirect(ChoiceR|
0001a0c0  29 3d 3d 32 29 20 6a 75  6d 70 20 52 65 44 69 73  |)==2) jump ReDis|
0001a0d0  70 6c 61 79 3b 0a 0a 20  20 20 20 20 20 20 20 20  |play;..         |
0001a0e0  20 70 72 69 6e 74 20 22  5e 5b 50 6c 65 61 73 65  | print "^[Please|
0001a0f0  20 70 72 65 73 73 20 53  50 41 43 45 2e 5d 5e 22  | press SPACE.]^"|
0001a100  3b 0a 20 20 20 20 20 20  20 20 20 20 72 65 61 64  |;.          read|
0001a110  5f 63 68 61 72 20 31 20  30 20 30 20 70 6b 65 79  |_char 1 0 0 pkey|
0001a120  3b 20 6a 75 6d 70 20 52  65 44 69 73 70 6c 61 79  |; jump ReDisplay|
0001a130  3b 0a 20 20 20 20 20 20  7d 0a 20 20 20 20 20 20  |;.      }.      |
0001a140  6a 75 6d 70 20 4b 65 79  4c 6f 6f 70 3b 0a 20 20  |jump KeyLoop;.  |
0001a150  20 20 20 20 2e 51 75 69  74 48 65 6c 70 3b 0a 20  |    .QuitHelp;. |
0001a160  20 20 20 20 20 6d 65 6e  75 5f 6e 65 73 74 69 6e  |     menu_nestin|
0001a170  67 2d 2d 3b 20 69 66 20  28 6d 65 6e 75 5f 6e 65  |g--; if (menu_ne|
0001a180  73 74 69 6e 67 3e 30 29  20 72 66 61 6c 73 65 3b  |sting>0) rfalse;|
0001a190  0a 20 20 20 20 20 20 66  6f 6e 74 20 6f 6e 3b 20  |.      font on; |
0001a1a0  73 65 74 5f 63 75 72 73  6f 72 20 31 20 31 3b 0a  |set_cursor 1 1;.|
0001a1b0  20 20 20 20 20 20 65 72  61 73 65 5f 77 69 6e 64  |      erase_wind|
0001a1c0  6f 77 20 24 66 66 66 66  3b 20 73 65 74 5f 77 69  |ow $ffff; set_wi|
0001a1d0  6e 64 6f 77 20 30 3b 0a  20 20 20 20 20 20 6e 65  |ndow 0;.      ne|
0001a1e0  77 5f 6c 69 6e 65 3b 20  6e 65 77 5f 6c 69 6e 65  |w_line; new_line|
0001a1f0  3b 20 6e 65 77 5f 6c 69  6e 65 3b 0a 20 20 20 20  |; new_line;.    |
0001a200  20 20 69 66 20 28 64 65  61 64 66 6c 61 67 3d 3d  |  if (deadflag==|
0001a210  30 29 20 3c 3c 4c 6f 6f  6b 3e 3e 3b 0a 5d 3b 20  |0) <<Look>>;.]; |
0001a220  20 0a 23 45 4e 44 49 46  3b 0a 0a 44 65 66 61 75  | .#ENDIF;..Defau|
0001a230  6c 74 20 4d 41 58 5f 54  49 4d 45 52 53 20 20 33  |lt MAX_TIMERS  3|
0001a240  32 3b 0a 47 6c 6f 62 61  6c 20 61 63 74 69 76 65  |2;.Global active|
0001a250  5f 74 69 6d 65 72 73 20  3d 20 30 3b 0a 47 6c 6f  |_timers = 0;.Glo|
0001a260  62 61 6c 20 74 68 65 5f  74 69 6d 65 72 73 20 20  |bal the_timers  |
0001a270  64 61 74 61 20 4d 41 58  5f 54 49 4d 45 52 53 3b  |data MAX_TIMERS;|
0001a280  0a 47 6c 6f 62 61 6c 20  74 69 6d 65 72 5f 66 6c  |.Global timer_fl|
0001a290  61 67 73 20 64 61 74 61  20 4d 41 58 5f 54 49 4d  |ags data MAX_TIM|
0001a2a0  45 52 53 3b 0a 0a 5b 20  54 69 6d 65 72 45 3b 20  |ERS;..[ TimerE; |
0001a2b0  22 2a 2a 20 54 6f 6f 20  6d 61 6e 79 20 74 69 6d  |"** Too many tim|
0001a2c0  65 72 73 2f 64 61 65 6d  6f 6e 73 21 20 49 6e 63  |ers/daemons! Inc|
0001a2d0  72 65 61 73 65 20 4d 41  58 5f 54 49 4d 45 52 53  |rease MAX_TIMERS|
0001a2e0  20 2a 2a 22 3b 20 5d 3b  0a 5b 20 54 69 6d 65 72  | **"; ];.[ Timer|
0001a2f0  45 32 20 6f 62 6a 3b 20  70 72 69 6e 74 20 22 2a  |E2 obj; print "*|
0001a300  2a 20 4f 62 6a 65 63 74  20 22 3b 20 50 72 69 6e  |* Object "; Prin|
0001a310  74 53 68 6f 72 74 4e 61  6d 65 28 6f 62 6a 29 3b  |tShortName(obj);|
0001a320  0a 20 20 20 20 20 20 22  20 68 61 73 20 6e 6f 20  |.      " has no |
0001a330  74 69 6d 65 5f 6c 65 66  74 20 70 72 6f 70 65 72  |time_left proper|
0001a340  74 79 21 20 2a 2a 22 3b  0a 5d 3b 0a 0a 5b 20 53  |ty! **";.];..[ S|
0001a350  74 61 72 74 54 69 6d 65  72 20 6f 62 6a 20 74 69  |tartTimer obj ti|
0001a360  6d 65 72 20 69 3b 0a 20  20 20 66 6f 72 20 28 69  |mer i;.   for (i|
0001a370  3d 30 3a 69 3c 61 63 74  69 76 65 5f 74 69 6d 65  |=0:i<active_time|
0001a380  72 73 3a 69 2b 2b 29 0a  20 20 20 20 20 20 20 69  |rs:i++).       i|
0001a390  66 20 28 74 68 65 5f 74  69 6d 65 72 73 2d 3e 69  |f (the_timers->i|
0001a3a0  3d 3d 30 29 20 6a 75 6d  70 20 46 6f 75 6e 64 54  |==0) jump FoundT|
0001a3b0  53 6c 6f 74 3b 0a 20 20  20 69 3d 61 63 74 69 76  |Slot;.   i=activ|
0001a3c0  65 5f 74 69 6d 65 72 73  2b 2b 3b 0a 20 20 20 69  |e_timers++;.   i|
0001a3d0  66 20 28 69 3d 3d 4d 41  58 5f 54 49 4d 45 52 53  |f (i==MAX_TIMERS|
0001a3e0  29 20 54 69 6d 65 72 45  28 29 3b 0a 20 20 20 2e  |) TimerE();.   .|
0001a3f0  46 6f 75 6e 64 54 53 6c  6f 74 3b 0a 20 20 20 69  |FoundTSlot;.   i|
0001a400  66 20 28 6f 62 6a 2e 26  74 69 6d 65 5f 6c 65 66  |f (obj.&time_lef|
0001a410  74 3d 3d 30 29 20 54 69  6d 65 72 45 32 28 6f 62  |t==0) TimerE2(ob|
0001a420  6a 29 3b 0a 20 20 20 74  68 65 5f 74 69 6d 65 72  |j);.   the_timer|
0001a430  73 2d 3e 69 3d 6f 62 6a  3b 20 74 69 6d 65 72 5f  |s->i=obj; timer_|
0001a440  66 6c 61 67 73 2d 3e 69  3d 31 3b 20 6f 62 6a 2e  |flags->i=1; obj.|
0001a450  74 69 6d 65 5f 6c 65 66  74 3d 74 69 6d 65 72 3b  |time_left=timer;|
0001a460  0a 5d 3b 0a 0a 5b 20 53  74 6f 70 54 69 6d 65 72  |.];..[ StopTimer|
0001a470  20 6f 62 6a 20 69 3b 0a  20 20 20 66 6f 72 20 28  | obj i;.   for (|
0001a480  69 3d 30 3a 69 3c 61 63  74 69 76 65 5f 74 69 6d  |i=0:i<active_tim|
0001a490  65 72 73 3a 69 2b 2b 29  0a 20 20 20 20 20 20 20  |ers:i++).       |
0001a4a0  69 66 20 28 74 68 65 5f  74 69 6d 65 72 73 2d 3e  |if (the_timers->|
0001a4b0  69 3d 3d 6f 62 6a 29 20  6a 75 6d 70 20 46 6f 75  |i==obj) jump Fou|
0001a4c0  6e 64 54 53 6c 6f 74 32  3b 0a 20 20 20 72 66 61  |ndTSlot2;.   rfa|
0001a4d0  6c 73 65 3b 0a 20 20 20  2e 46 6f 75 6e 64 54 53  |lse;.   .FoundTS|
0001a4e0  6c 6f 74 32 3b 0a 20 20  20 69 66 20 28 6f 62 6a  |lot2;.   if (obj|
0001a4f0  2e 26 74 69 6d 65 5f 6c  65 66 74 3d 3d 30 29 20  |.&time_left==0) |
0001a500  54 69 6d 65 72 45 32 28  6f 62 6a 29 3b 0a 20 20  |TimerE2(obj);.  |
0001a510  20 74 68 65 5f 74 69 6d  65 72 73 2d 3e 69 3d 30  | the_timers->i=0|
0001a520  3b 20 6f 62 6a 2e 74 69  6d 65 5f 6c 65 66 74 3d  |; obj.time_left=|
0001a530  30 3b 0a 5d 3b 0a 0a 5b  20 53 74 61 72 74 44 61  |0;.];..[ StartDa|
0001a540  65 6d 6f 6e 20 6f 62 6a  20 69 3b 0a 20 20 20 66  |emon obj i;.   f|
0001a550  6f 72 20 28 69 3d 30 3a  69 3c 61 63 74 69 76 65  |or (i=0:i<active|
0001a560  5f 74 69 6d 65 72 73 3a  69 2b 2b 29 0a 20 20 20  |_timers:i++).   |
0001a570  20 20 20 20 69 66 20 28  74 68 65 5f 74 69 6d 65  |    if (the_time|
0001a580  72 73 2d 3e 69 3d 3d 30  29 20 6a 75 6d 70 20 46  |rs->i==0) jump F|
0001a590  6f 75 6e 64 54 53 6c 6f  74 33 3b 0a 20 20 20 69  |oundTSlot3;.   i|
0001a5a0  3d 61 63 74 69 76 65 5f  74 69 6d 65 72 73 2b 2b  |=active_timers++|
0001a5b0  3b 0a 20 20 20 69 66 20  28 69 3d 3d 4d 41 58 5f  |;.   if (i==MAX_|
0001a5c0  54 49 4d 45 52 53 29 20  54 69 6d 65 72 45 28 29  |TIMERS) TimerE()|
0001a5d0  3b 0a 20 20 20 2e 46 6f  75 6e 64 54 53 6c 6f 74  |;.   .FoundTSlot|
0001a5e0  33 3b 0a 20 20 20 74 68  65 5f 74 69 6d 65 72 73  |3;.   the_timers|
0001a5f0  2d 3e 69 3d 6f 62 6a 3b  20 74 69 6d 65 72 5f 66  |->i=obj; timer_f|
0001a600  6c 61 67 73 2d 3e 69 3d  32 3b 0a 5d 3b 0a 0a 5b  |lags->i=2;.];..[|
0001a610  20 53 74 6f 70 44 61 65  6d 6f 6e 20 6f 62 6a 20  | StopDaemon obj |
0001a620  69 3b 0a 20 20 20 66 6f  72 20 28 69 3d 30 3a 69  |i;.   for (i=0:i|
0001a630  3c 61 63 74 69 76 65 5f  74 69 6d 65 72 73 3a 69  |<active_timers:i|
0001a640  2b 2b 29 0a 20 20 20 20  20 20 20 69 66 20 28 74  |++).       if (t|
0001a650  68 65 5f 74 69 6d 65 72  73 2d 3e 69 3d 3d 6f 62  |he_timers->i==ob|
0001a660  6a 29 20 6a 75 6d 70 20  46 6f 75 6e 64 54 53 6c  |j) jump FoundTSl|
0001a670  6f 74 34 3b 0a 20 20 20  72 66 61 6c 73 65 3b 0a  |ot4;.   rfalse;.|
0001a680  20 20 20 2e 46 6f 75 6e  64 54 53 6c 6f 74 34 3b  |   .FoundTSlot4;|
0001a690  0a 20 20 20 74 68 65 5f  74 69 6d 65 72 73 2d 3e  |.   the_timers->|
0001a6a0  69 3d 30 3b 0a 5d 3b 0a  0a 5b 20 54 69 6d 65 20  |i=0;.];..[ Time |
0001a6b0  69 20 6a 3b 0a 0a 20 20  20 74 75 72 6e 73 2b 2b  |i j;..   turns++|
0001a6c0  3b 0a 20 20 20 69 66 20  28 74 68 65 5f 74 69 6d  |;.   if (the_tim|
0001a6d0  65 7e 3d 24 66 66 66 66  29 0a 20 20 20 7b 20 20  |e~=$ffff).   {  |
0001a6e0  20 69 66 20 28 74 69 6d  65 5f 72 61 74 65 3e 3d  | if (time_rate>=|
0001a6f0  30 29 20 74 68 65 5f 74  69 6d 65 3d 74 68 65 5f  |0) the_time=the_|
0001a700  74 69 6d 65 2b 74 69 6d  65 5f 72 61 74 65 3b 0a  |time+time_rate;.|
0001a710  20 20 20 20 20 20 20 65  6c 73 65 0a 20 20 20 20  |       else.    |
0001a720  20 20 20 7b 20 20 20 74  69 6d 65 5f 73 74 65 70  |   {   time_step|
0001a730  2d 2d 3b 0a 20 20 20 20  20 20 20 20 20 20 20 69  |--;.           i|
0001a740  66 20 28 74 69 6d 65 5f  73 74 65 70 3d 3d 30 29  |f (time_step==0)|
0001a750  0a 20 20 20 20 20 20 20  20 20 20 20 7b 20 20 20  |.           {   |
0001a760  74 68 65 5f 74 69 6d 65  2b 2b 3b 0a 20 20 20 20  |the_time++;.    |
0001a770  20 20 20 20 20 20 20 20  20 20 20 74 69 6d 65 5f  |           time_|
0001a780  73 74 65 70 20 3d 20 2d  74 69 6d 65 5f 72 61 74  |step = -time_rat|
0001a790  65 3b 0a 20 20 20 20 20  20 20 20 20 20 20 7d 0a  |e;.           }.|
0001a7a0  20 20 20 20 20 20 20 7d  0a 20 20 20 20 20 20 20  |       }.       |
0001a7b0  74 68 65 5f 74 69 6d 65  3d 74 68 65 5f 74 69 6d  |the_time=the_tim|
0001a7c0  65 20 25 20 31 34 34 30  3b 0a 20 20 20 7d 0a 23  |e % 1440;.   }.#|
0001a7d0  49 46 44 45 46 20 44 45  42 55 47 3b 0a 20 20 20  |IFDEF DEBUG;.   |
0001a7e0  69 66 20 28 64 65 62 75  67 5f 66 6c 61 67 20 26  |if (debug_flag &|
0001a7f0  20 34 20 7e 3d 20 30 29  0a 20 20 20 7b 20 20 20  | 4 ~= 0).   {   |
0001a800  66 6f 72 20 28 69 3d 30  3a 20 69 3c 61 63 74 69  |for (i=0: i<acti|
0001a810  76 65 5f 74 69 6d 65 72  73 3a 20 69 2b 2b 29 0a  |ve_timers: i++).|
0001a820  20 20 20 20 20 20 20 7b  20 20 20 6a 3d 74 68 65  |       {   j=the|
0001a830  5f 74 69 6d 65 72 73 2d  3e 69 3b 0a 20 20 20 20  |_timers->i;.    |
0001a840  20 20 20 20 20 20 20 70  72 69 6e 74 20 69 2c 20  |       print i, |
0001a850  22 3a 20 22 3b 20 50 72  69 6e 74 53 68 6f 72 74  |": "; PrintShort|
0001a860  4e 61 6d 65 28 6a 29 3b  0a 20 20 20 20 20 20 20  |Name(j);.       |
0001a870  20 20 20 20 69 66 20 28  6a 7e 3d 30 29 0a 20 20  |    if (j~=0).  |
0001a880  20 20 20 20 20 20 20 20  20 7b 20 20 20 69 66 20  |         {   if |
0001a890  28 74 69 6d 65 72 5f 66  6c 61 67 73 2d 3e 69 3d  |(timer_flags->i=|
0001a8a0  3d 32 29 20 70 72 69 6e  74 20 22 3a 20 64 61 65  |=2) print ": dae|
0001a8b0  6d 6f 6e 22 3b 0a 20 20  20 20 20 20 20 20 20 20  |mon";.          |
0001a8c0  20 20 20 20 20 65 6c 73  65 0a 20 20 20 20 20 20  |     else.      |
0001a8d0  20 20 20 20 20 20 20 20  20 7b 20 70 72 69 6e 74  |         { print|
0001a8e0  20 22 3a 20 74 69 6d 65  72 20 77 69 74 68 20 22  | ": timer with "|
0001a8f0  2c 20 6a 2e 74 69 6d 65  5f 6c 65 66 74 2c 20 22  |, j.time_left, "|
0001a900  20 74 75 72 6e 73 20 74  6f 20 67 6f 22 3b 20 7d  | turns to go"; }|
0001a910  0a 20 20 20 20 20 20 20  20 20 20 20 7d 0a 20 20  |.           }.  |
0001a920  20 20 20 20 20 20 20 20  20 6e 65 77 5f 6c 69 6e  |         new_lin|
0001a930  65 3b 0a 20 20 20 20 20  20 20 7d 0a 20 20 20 7d  |e;.       }.   }|
0001a940  0a 23 45 4e 44 49 46 3b  0a 20 20 20 66 6f 72 20  |.#ENDIF;.   for |
0001a950  28 69 3d 30 3a 20 64 65  61 64 66 6c 61 67 3d 3d  |(i=0: deadflag==|
0001a960  30 20 26 26 20 69 3c 61  63 74 69 76 65 5f 74 69  |0 && i<active_ti|
0001a970  6d 65 72 73 3a 20 69 2b  2b 29 0a 20 20 20 7b 20  |mers: i++).   { |
0001a980  20 20 6a 3d 74 68 65 5f  74 69 6d 65 72 73 2d 3e  |  j=the_timers->|
0001a990  69 3b 0a 20 20 20 20 20  20 20 69 66 20 28 6a 7e  |i;.       if (j~|
0001a9a0  3d 30 29 0a 20 20 20 20  20 20 20 7b 20 20 20 69  |=0).       {   i|
0001a9b0  66 20 28 74 69 6d 65 72  5f 66 6c 61 67 73 2d 3e  |f (timer_flags->|
0001a9c0  69 3d 3d 32 29 20 52 75  6e 52 6f 75 74 69 6e 65  |i==2) RunRoutine|
0001a9d0  73 28 6a 2c 64 61 65 6d  6f 6e 29 3b 0a 20 20 20  |s(j,daemon);.   |
0001a9e0  20 20 20 20 20 20 20 20  65 6c 73 65 0a 20 20 20  |        else.   |
0001a9f0  20 20 20 20 20 20 20 20  7b 20 20 20 69 66 20 28  |        {   if (|
0001aa00  6a 2e 74 69 6d 65 5f 6c  65 66 74 3d 3d 30 29 0a  |j.time_left==0).|
0001aa10  20 20 20 20 20 20 20 20  20 20 20 20 20 20 20 7b  |               {|
0001aa20  20 20 20 53 74 6f 70 54  69 6d 65 72 28 6a 29 3b  |   StopTimer(j);|
0001aa30  0a 20 20 20 20 20 20 20  20 20 20 20 20 20 20 20  |.               |
0001aa40  20 20 20 20 52 75 6e 52  6f 75 74 69 6e 65 73 28  |    RunRoutines(|
0001aa50  6a 2c 74 69 6d 65 5f 6f  75 74 29 3b 0a 20 20 20  |j,time_out);.   |
0001aa60  20 20 20 20 20 20 20 20  20 20 20 20 7d 0a 20 20  |            }.  |
0001aa70  20 20 20 20 20 20 20 20  20 20 20 20 20 65 6c 73  |             els|
0001aa80  65 0a 20 20 20 20 20 20  20 20 20 20 20 20 20 20  |e.              |
0001aa90  20 20 20 20 20 6a 2e 74  69 6d 65 5f 6c 65 66 74  |     j.time_left|
0001aaa0  3d 6a 2e 74 69 6d 65 5f  6c 65 66 74 2d 31 3b 0a  |=j.time_left-1;.|
0001aab0  20 20 20 20 20 20 20 20  20 20 20 7d 0a 20 20 20  |           }.   |
0001aac0  20 20 20 20 7d 0a 20 20  20 7d 0a 20 20 20 69 66  |    }.   }.   if|
0001aad0  20 28 64 65 61 64 66 6c  61 67 3d 3d 30 29 0a 20  | (deadflag==0). |
0001aae0  20 20 7b 20 20 20 65 74  5f 66 6c 61 67 3d 31 3b  |  {   et_flag=1;|
0001aaf0  20 76 65 72 62 5f 77 6f  72 64 3d 30 3b 0a 20 20  | verb_word=0;.  |
0001ab00  20 20 20 20 20 44 6f 45  61 63 68 54 75 72 6e 28  |     DoEachTurn(|
0001ab10  6c 6f 63 61 74 69 6f 6e  29 3b 0a 20 20 20 20 20  |location);.     |
0001ab20  20 20 53 65 61 72 63 68  53 63 6f 70 65 28 6c 6f  |  SearchScope(lo|
0001ab30  63 61 74 69 6f 6e 2c 70  6c 61 79 65 72 2c 30 29  |cation,player,0)|
0001ab40  3b 0a 20 20 20 20 20 20  20 65 74 5f 66 6c 61 67  |;.       et_flag|
0001ab50  3d 30 3b 0a 20 20 20 7d  0a 20 20 20 69 66 20 28  |=0;.   }.   if (|
0001ab60  64 65 61 64 66 6c 61 67  3d 3d 30 29 20 54 69 6d  |deadflag==0) Tim|
0001ab70  65 50 61 73 73 65 73 28  29 3b 0a 20 20 20 69 66  |ePasses();.   if|
0001ab80  20 28 64 65 61 64 66 6c  61 67 3d 3d 30 29 0a 20  | (deadflag==0). |
0001ab90  20 20 7b 20 20 20 41 64  6a 75 73 74 4c 69 67 68  |  {   AdjustLigh|
0001aba0  74 28 29 3b 0a 20 20 20  20 20 20 20 6f 62 6a 65  |t();.       obje|
0001abb0  63 74 6c 6f 6f 70 20 28  69 20 69 6e 20 70 6c 61  |ctloop (i in pla|
0001abc0  79 65 72 29 0a 20 20 20  20 20 20 20 20 20 20 20  |yer).           |
0001abd0  69 66 20 28 69 20 68 61  73 6e 74 20 6d 6f 76 65  |if (i hasnt move|
0001abe0  64 29 0a 20 20 20 20 20  20 20 20 20 20 20 7b 20  |d).           { |
0001abf0  20 20 67 69 76 65 20 69  20 6d 6f 76 65 64 3b 0a  |  give i moved;.|
0001ac00  20 20 20 20 20 20 20 20  20 20 20 20 20 20 20 69  |               i|
0001ac10  66 20 28 6e 6f 75 6e 20  68 61 73 20 73 63 6f 72  |f (noun has scor|
0001ac20  65 64 29 0a 20 20 20 20  20 20 20 20 20 20 20 20  |ed).            |
0001ac30  20 20 20 7b 20 20 20 73  63 6f 72 65 3d 73 63 6f  |   {   score=sco|
0001ac40  72 65 2b 4f 42 4a 45 43  54 5f 53 43 4f 52 45 3b  |re+OBJECT_SCORE;|
0001ac50  0a 20 20 20 20 20 20 20  20 20 20 20 20 20 20 20  |.               |
0001ac60  20 20 20 20 74 68 69 6e  67 73 5f 73 63 6f 72 65  |    things_score|
0001ac70  3d 74 68 69 6e 67 73 5f  73 63 6f 72 65 2b 4f 42  |=things_score+OB|
0001ac80  4a 45 43 54 5f 53 43 4f  52 45 3b 0a 20 20 20 20  |JECT_SCORE;.    |
0001ac90  20 20 20 20 20 20 20 20  20 20 20 7d 0a 20 20 20  |           }.   |
0001aca0  20 20 20 20 20 20 20 20  7d 0a 20 20 20 7d 0a 5d  |        }.   }.]|
0001acb0  3b 0a 0a 5b 20 41 64 6a  75 73 74 4c 69 67 68 74  |;..[ AdjustLight|
0001acc0  20 66 6c 61 67 20 69 3b  0a 20 20 20 69 3d 6c 69  | flag i;.   i=li|
0001acd0  67 68 74 66 6c 61 67 3b  0a 20 20 20 6c 69 67 68  |ghtflag;.   ligh|
0001ace0  74 66 6c 61 67 3d 4f 66  66 65 72 73 4c 69 67 68  |tflag=OffersLigh|
0001acf0  74 28 70 61 72 65 6e 74  28 70 6c 61 79 65 72 29  |t(parent(player)|
0001ad00  29 3b 0a 0a 20 20 20 69  66 20 28 69 3d 3d 30 20  |);..   if (i==0 |
0001ad10  26 26 20 6c 69 67 68 74  66 6c 61 67 3d 3d 31 29  |&& lightflag==1)|
0001ad20  0a 20 20 20 7b 20 20 20  6c 6f 63 61 74 69 6f 6e  |.   {   location|
0001ad30  3d 72 65 61 6c 5f 6c 6f  63 61 74 69 6f 6e 3b 0a  |=real_location;.|
0001ad40  20 20 20 20 20 20 20 69  66 20 28 66 6c 61 67 3d  |       if (flag=|
0001ad50  3d 30 29 0a 20 20 20 20  20 20 20 7b 20 20 20 6e  |=0).       {   n|
0001ad60  65 77 5f 6c 69 6e 65 3b  20 3c 4c 6f 6f 6b 3e 3b  |ew_line; <Look>;|
0001ad70  20 7d 0a 20 20 20 7d 0a  0a 20 20 20 69 66 20 28  | }.   }..   if (|
0001ad80  69 3d 3d 31 20 26 26 20  6c 69 67 68 74 66 6c 61  |i==1 && lightfla|
0001ad90  67 3d 3d 30 29 0a 20 20  20 7b 20 20 20 72 65 61  |g==0).   {   rea|
0001ada0  6c 5f 6c 6f 63 61 74 69  6f 6e 3d 6c 6f 63 61 74  |l_location=locat|
0001adb0  69 6f 6e 3b 20 6c 6f 63  61 74 69 6f 6e 3d 74 68  |ion; location=th|
0001adc0  65 64 61 72 6b 3b 0a 20  20 20 20 20 20 20 69 66  |edark;.       if|
0001add0  20 28 66 6c 61 67 3d 3d  30 29 0a 20 20 20 20 20  | (flag==0).     |
0001ade0  20 20 20 20 20 20 22 5e  49 74 20 69 73 20 6e 6f  |      "^It is no|
0001adf0  77 20 70 69 74 63 68 20  64 61 72 6b 20 69 6e 20  |w pitch dark in |
0001ae00  68 65 72 65 21 22 3b 0a  20 20 20 7d 0a 5d 3b 0a  |here!";.   }.];.|
0001ae10  0a 5b 20 4f 66 66 65 72  73 4c 69 67 68 74 20 69  |.[ OffersLight i|
0001ae20  20 6a 3b 0a 20 20 20 69  66 20 28 69 3d 3d 30 29  | j;.   if (i==0)|
0001ae30  20 72 66 61 6c 73 65 3b  0a 20 20 20 69 66 20 28  | rfalse;.   if (|
0001ae40  69 20 68 61 73 20 6c 69  67 68 74 29 20 72 74 72  |i has light) rtr|
0001ae50  75 65 3b 0a 20 20 20 6f  62 6a 65 63 74 6c 6f 6f  |ue;.   objectloo|
0001ae60  70 20 28 6a 20 69 6e 20  69 29 0a 20 20 20 20 20  |p (j in i).     |
0001ae70  20 20 69 66 20 28 48 61  73 4c 69 67 68 74 53 6f  |  if (HasLightSo|
0001ae80  75 72 63 65 28 6a 29 3d  3d 31 29 20 72 74 72 75  |urce(j)==1) rtru|
0001ae90  65 3b 0a 20 20 20 69 66  20 28 69 20 68 61 73 20  |e;.   if (i has |
0001aea0  73 75 70 70 6f 72 74 65  72 20 7c 7c 20 69 20 68  |supporter || i h|
0001aeb0  61 73 20 74 72 61 6e 73  70 61 72 65 6e 74 20 7c  |as transparent ||
0001aec0  7c 0a 20 20 20 20 20 20  20 69 20 68 61 73 20 65  ||.       i has e|
0001aed0  6e 74 65 72 61 62 6c 65  20 7c 7c 20 28 69 20 68  |nterable || (i h|
0001aee0  61 73 20 63 6f 6e 74 61  69 6e 65 72 20 26 26 20  |as container && |
0001aef0  69 20 68 61 73 20 6f 70  65 6e 29 29 0a 20 20 20  |i has open)).   |
0001af00  20 20 20 20 72 65 74 75  72 6e 20 4f 66 66 65 72  |    return Offer|
0001af10  73 4c 69 67 68 74 28 70  61 72 65 6e 74 28 69 29  |sLight(parent(i)|
0001af20  29 3b 0a 20 20 20 72 66  61 6c 73 65 3b 0a 5d 3b  |);.   rfalse;.];|
0001af30  0a 0a 5b 20 48 61 73 4c  69 67 68 74 53 6f 75 72  |..[ HasLightSour|
0001af40  63 65 20 69 3b 0a 20 20  20 69 66 20 28 69 3d 3d  |ce i;.   if (i==|
0001af50  30 29 20 72 66 61 6c 73  65 3b 0a 20 20 20 69 66  |0) rfalse;.   if|
0001af60  20 28 69 20 68 61 73 20  6c 69 67 68 74 29 20 72  | (i has light) r|
0001af70  74 72 75 65 3b 0a 20 20  20 69 66 20 28 69 20 68  |true;.   if (i h|
0001af80  61 73 20 73 75 70 70 6f  72 74 65 72 20 7c 7c 20  |as supporter || |
0001af90  69 20 68 61 73 20 74 72  61 6e 73 70 61 72 65 6e  |i has transparen|
0001afa0  74 20 7c 7c 0a 20 20 20  20 20 20 20 69 20 68 61  |t ||.       i ha|
0001afb0  73 20 65 6e 74 65 72 61  62 6c 65 20 7c 7c 20 28  |s enterable || (|
0001afc0  69 20 68 61 73 20 63 6f  6e 74 61 69 6e 65 72 20  |i has container |
0001afd0  26 26 20 69 20 68 61 73  20 6f 70 65 6e 29 29 0a  |&& i has open)).|
0001afe0  20 20 20 7b 20 20 20 6f  62 6a 65 63 74 6c 6f 6f  |   {   objectloo|
0001aff0  70 20 28 69 20 69 6e 20  69 29 0a 20 20 20 20 20  |p (i in i).     |
0001b000  20 20 20 20 20 20 69 66  20 28 48 61 73 4c 69 67  |      if (HasLig|
0001b010  68 74 53 6f 75 72 63 65  28 69 29 3d 3d 31 29 20  |htSource(i)==1) |
0001b020  72 74 72 75 65 3b 0a 20  20 20 7d 0a 20 20 20 72  |rtrue;.   }.   r|
0001b030  66 61 6c 73 65 3b 0a 5d  3b 0a 0a 5b 20 53 61 79  |false;.];..[ Say|
0001b040  50 72 6f 53 20 78 3b 0a  20 20 69 66 20 28 78 3d  |ProS x;.  if (x=|
0001b050  3d 30 29 20 70 72 69 6e  74 20 22 69 73 20 75 6e  |=0) print "is un|
0001b060  73 65 74 22 3b 0a 20 20  65 6c 73 65 20 7b 20 70  |set";.  else { p|
0001b070  72 69 6e 74 20 22 6d 65  61 6e 73 20 22 3b 20 44  |rint "means "; D|
0001b080  65 66 41 72 74 28 78 29  3b 20 7d 0a 5d 3b 0a 0a  |efArt(x); }.];..|
0001b090  5b 20 50 72 6f 6e 6f 75  6e 73 53 75 62 3b 0a 20  |[ PronounsSub;. |
0001b0a0  20 70 72 69 6e 74 20 22  41 74 20 74 68 65 20 6d  | print "At the m|
0001b0b0  6f 6d 65 6e 74 2c 20 7e  69 74 7e 20 22 3b 20 53  |oment, ~it~ "; S|
0001b0c0  61 79 50 72 6f 53 28 69  74 6f 62 6a 29 3b 0a 20  |ayProS(itobj);. |
0001b0d0  20 70 72 69 6e 74 20 22  2c 20 7e 68 69 6d 7e 20  | print ", ~him~ |
0001b0e0  22 3b 20 53 61 79 50 72  6f 53 28 68 69 6d 6f 62  |"; SayProS(himob|
0001b0f0  6a 29 3b 0a 20 20 69 66  20 28 70 6c 61 79 65 72  |j);.  if (player|
0001b100  3d 3d 73 65 6c 66 6f 62  6a 29 20 70 72 69 6e 74  |==selfobj) print|
0001b110  20 22 20 61 6e 64 22 3b  20 65 6c 73 65 20 70 72  | " and"; else pr|
0001b120  69 6e 74 20 22 2c 22 3b  0a 20 20 70 72 69 6e 74  |int ",";.  print|
0001b130  20 22 20 7e 68 65 72 7e  20 22 3b 20 53 61 79 50  | " ~her~ "; SayP|
0001b140  72 6f 53 28 68 65 72 6f  62 6a 29 3b 0a 20 20 69  |roS(herobj);.  i|
0001b150  66 20 28 70 6c 61 79 65  72 3d 3d 73 65 6c 66 6f  |f (player==selfo|
0001b160  62 6a 29 20 22 2e 22 3b  0a 20 20 70 72 69 6e 74  |bj) ".";.  print|
0001b170  20 22 20 61 6e 64 20 7e  6d 65 7e 20 6d 65 61 6e  | " and ~me~ mean|
0001b180  73 20 22 2c 20 6f 62 6a  65 63 74 20 70 6c 61 79  |s ", object play|
0001b190  65 72 3b 20 22 2e 22 3b  0a 5d 3b 0a 0a 5b 20 43  |er; ".";.];..[ C|
0001b1a0  68 61 6e 67 65 50 6c 61  79 65 72 20 6f 62 6a 20  |hangePlayer obj |
0001b1b0  66 6c 61 67 20 69 3b 0a  20 20 69 66 20 28 6f 62  |flag i;.  if (ob|
0001b1c0  6a 2e 26 6e 75 6d 62 65  72 3d 3d 30 29 20 22 2a  |j.&number==0) "*|
0001b1d0  2a 20 50 6c 61 79 65 72  20 6f 62 6a 20 6d 75 73  |* Player obj mus|
0001b1e0  74 20 68 61 76 65 20 6e  75 6d 62 65 72 20 70 72  |t have number pr|
0001b1f0  6f 70 20 2a 2a 22 3b 0a  20 20 67 69 76 65 20 70  |op **";.  give p|
0001b200  6c 61 79 65 72 20 7e 74  72 61 6e 73 70 61 72 65  |layer ~transpare|
0001b210  6e 74 20 7e 63 6f 6e 63  65 61 6c 65 64 3b 0a 20  |nt ~concealed;. |
0001b220  20 70 6c 61 79 65 72 2e  6e 75 6d 62 65 72 3d 72  | player.number=r|
0001b230  65 61 6c 5f 6c 6f 63 61  74 69 6f 6e 3b 20 70 6c  |eal_location; pl|
0001b240  61 79 65 72 3d 6f 62 6a  3b 0a 20 20 67 69 76 65  |ayer=obj;.  give|
0001b250  20 70 6c 61 79 65 72 20  74 72 61 6e 73 70 61 72  | player transpar|
0001b260  65 6e 74 20 63 6f 6e 63  65 61 6c 65 64 20 61 6e  |ent concealed an|
0001b270  69 6d 61 74 65 20 70 72  6f 70 65 72 3b 0a 20 20  |imate proper;.  |
0001b280  69 3d 70 6c 61 79 65 72  3b 20 77 68 69 6c 65 28  |i=player; while(|
0001b290  70 61 72 65 6e 74 28 69  29 7e 3d 30 29 20 69 3d  |parent(i)~=0) i=|
0001b2a0  70 61 72 65 6e 74 28 69  29 3b 20 6c 6f 63 61 74  |parent(i); locat|
0001b2b0  69 6f 6e 3d 69 3b 0a 20  20 72 65 61 6c 5f 6c 6f  |ion=i;.  real_lo|
0001b2c0  63 61 74 69 6f 6e 3d 70  6c 61 79 65 72 2e 6e 75  |cation=player.nu|
0001b2d0  6d 62 65 72 3b 0a 20 20  69 66 20 28 72 65 61 6c  |mber;.  if (real|
0001b2e0  5f 6c 6f 63 61 74 69 6f  6e 3d 3d 30 29 20 72 65  |_location==0) re|
0001b2f0  61 6c 5f 6c 6f 63 61 74  69 6f 6e 3d 6c 6f 63 61  |al_location=loca|
0001b300  74 69 6f 6e 3b 0a 20 20  6c 69 67 68 74 66 6c 61  |tion;.  lightfla|
0001b310  67 3d 4f 66 66 65 72 73  4c 69 67 68 74 28 70 61  |g=OffersLight(pa|
0001b320  72 65 6e 74 28 70 6c 61  79 65 72 29 29 3b 0a 20  |rent(player));. |
0001b330  20 69 66 20 28 6c 69 67  68 74 66 6c 61 67 3d 3d  | if (lightflag==|
0001b340  30 29 20 6c 6f 63 61 74  69 6f 6e 3d 74 68 65 64  |0) location=thed|
0001b350  61 72 6b 3b 0a 20 20 70  72 69 6e 74 5f 70 6c 61  |ark;.  print_pla|
0001b360  79 65 72 5f 66 6c 61 67  3d 66 6c 61 67 3b 0a 5d  |yer_flag=flag;.]|
0001b370  3b 0a 0a 5b 20 49 6e 64  65 66 61 72 74 20 6f 3b  |;..[ Indefart o;|
0001b380  0a 20 20 20 69 66 20 28  6f 20 68 61 73 6e 74 20  |.   if (o hasnt |
0001b390  70 72 6f 70 65 72 29 20  7b 20 70 72 69 6e 74 5f  |proper) { print_|
0001b3a0  70 61 64 64 72 20 6f 2e  61 72 74 69 63 6c 65 3b  |paddr o.article;|
0001b3b0  20 70 72 69 6e 74 20 22  20 22 3b 20 7d 0a 20 20  | print " "; }.  |
0001b3c0  20 50 72 69 6e 74 53 68  6f 72 74 4e 61 6d 65 28  | PrintShortName(|
0001b3d0  6f 29 3b 0a 5d 3b 0a 0a  5b 20 44 65 66 61 72 74  |o);.];..[ Defart|
0001b3e0  20 6f 3b 0a 20 20 20 69  66 20 28 6f 20 68 61 73  | o;.   if (o has|
0001b3f0  6e 74 20 70 72 6f 70 65  72 29 20 70 72 69 6e 74  |nt proper) print|
0001b400  20 22 74 68 65 20 22 3b  20 50 72 69 6e 74 53 68  | "the "; PrintSh|
0001b410  6f 72 74 4e 61 6d 65 28  6f 29 3b 0a 5d 3b 0a 0a  |ortName(o);.];..|
0001b420  5b 20 43 44 65 66 61 72  74 20 6f 3b 0a 20 20 20  |[ CDefart o;.   |
0001b430  69 66 20 28 6f 20 68 61  73 6e 74 20 70 72 6f 70  |if (o hasnt prop|
0001b440  65 72 29 20 70 72 69 6e  74 20 22 54 68 65 20 22  |er) print "The "|
0001b450  3b 20 50 72 69 6e 74 53  68 6f 72 74 4e 61 6d 65  |; PrintShortName|
0001b460  28 6f 29 3b 0a 5d 3b 0a  0a 5b 20 50 72 69 6e 74  |(o);.];..[ Print|
0001b470  53 68 6f 72 74 4e 61 6d  65 20 6f 20 69 3b 0a 20  |ShortName o i;. |
0001b480  20 20 69 66 20 28 6f 3d  3d 30 29 20 7b 20 70 72  |  if (o==0) { pr|
0001b490  69 6e 74 20 22 6e 6f 74  68 69 6e 67 22 3b 20 72  |int "nothing"; r|
0001b4a0  74 72 75 65 3b 20 7d 0a  20 20 20 69 66 20 28 6f  |true; }.   if (o|
0001b4b0  3e 74 6f 70 5f 6f 62 6a  65 63 74 29 20 7b 20 70  |>top_object) { p|
0001b4c0  72 69 6e 74 20 22 3c 6e  6f 20 73 75 63 68 20 6f  |rint "<no such o|
0001b4d0  62 6a 65 63 74 3e 22 3b  20 72 74 72 75 65 3b 20  |bject>"; rtrue; |
0001b4e0  7d 0a 20 20 20 69 66 20  28 6f 3d 3d 70 6c 61 79  |}.   if (o==play|
0001b4f0  65 72 29 20 7b 20 70 72  69 6e 74 20 22 79 6f 75  |er) { print "you|
0001b500  72 73 65 6c 66 22 3b 20  72 74 72 75 65 3b 20 7d  |rself"; rtrue; }|
0001b510  0a 20 20 20 69 3d 6f 2e  73 68 6f 72 74 5f 6e 61  |.   i=o.short_na|
0001b520  6d 65 3b 0a 20 20 20 69  66 20 28 28 69 2d 23 73  |me;.   if ((i-#s|
0001b530  74 72 69 6e 67 73 5f 6f  66 66 73 65 74 29 3e 3d  |trings_offset)>=|
0001b540  30 29 20 7b 20 70 72 69  6e 74 5f 70 61 64 64 72  |0) { print_paddr|
0001b550  20 69 3b 20 72 74 72 75  65 3b 20 7d 0a 20 20 20  | i; rtrue; }.   |
0001b560  69 66 20 28 52 75 6e 52  6f 75 74 69 6e 65 73 28  |if (RunRoutines(|
0001b570  6f 2c 73 68 6f 72 74 5f  6e 61 6d 65 29 7e 3d 30  |o,short_name)~=0|
0001b580  29 20 72 74 72 75 65 3b  0a 20 20 20 70 72 69 6e  |) rtrue;.   prin|
0001b590  74 5f 6f 62 6a 20 6f 3b  0a 5d 3b 0a 0a 21 20 2d  |t_obj o;.];..! -|
0001b5a0  2d 2d 2d 2d 2d 2d 2d 2d  2d 2d 2d 2d 2d 2d 2d 2d  |----------------|
*
0001b5e0  2d 2d 2d 2d 2d 2d 2d 2d  2d 2d 2d 0a              |-----------.|
0001b5ec