1/* Space Race -- first one to bring their moonrocks to Saturn wins, by Paul Lee.
    2   Consult this file and issue the command:   start.  */
    3
    4:- dynamic at/2, i_am_at/1, alive/1, confirm/1.   /* Needed by SWI-Prolog. */
    5:- retractall(at(_, _)), retractall(i_am_at(_)), retractall(alive(_)).    6
    7/* This defines my current location. */
    8i_am_at(earth).
    9
   10/* defines the security code to the mars_lab */
   11code(333).
   12
   13/* defines whether or not the correct code was entered at the mars_lab */
   14confirm(false).
   15
   16/* These facts describe how to travel from planet to planet and within each planet. */
   17path(earth, fly, moon).
   18path(moon, forward, cave).
   19path(cave, turn, moon_station).
   20path(moon_station, fly, mars) :- at(gas, cargohold).
   21path(moon_station, fly, mars) :- write('You need gas to travel to Mars!'), nl, !, fail.
   22path(moon_station, lightspeed, saturn) :- at(rockets, cargohold), at(moonrocks, cargohold).
   23
   24
   25/* on mars, stumble upon mars_lab and break in by guessing security code -- HIDDEN OBJECT component */
   26path(mars_station, fly_back, moon) :- at(gas, cargohold).
   27path(mars_station, fly_back, moon) :- write('You need gas to travel back to the Moon!'), nl, !, fail.
   28path(mars, forward, mars_lab).
   29path(mars_lab, enter, rocket_room) :- confirm(true).
   30path(rocket_room, exit, mars_lab).
   31path(mars_lab, turn, mars_station).
   32path(mars, turn, mars_station).
   33path(mars_station, fly, jupiter) :- at(gas, cargohold).
   34path(mars_station, fly, jupiter) :- write('You need gas to travel to Jupiter!'), nl, !, fail.
   35path(mars_station, lightspeed, saturn) :- at(rockets, cargohold), at(moonrocks, cargohold).
   36
   37/* as on every planet, will need to get gas on jupiter */
   38path(jupiter_station, fly_back, mars) :- at(gas, cargohold).
   39path(jupiter_station, fly_back, mars) :- write('You need gas to travel back to Mars!'), nl, !, fail.
   40path(jupiter, turn, jupiter_station).
   41path(jupiter_station, fly, saturn) :- at(moonrocks, cargohold), at(gas, cargohold).
   42path(jupiter_station, lightspeed, saturn) :- at(rockets, cargohold), at(moonrocks, cargohold).
   43path(jupiter_station, fly, saturn) :- at(moonrocks, cargohold), at(rockets, cargohold).
   44path(jupiter_station, fly, saturn) :- at(moonrocks, cargohold), at(gas, cargohold).
   45path(jupiter_station, fly, saturn) :- at(moonrocks, cargohold), at(rockets, cargohold), at(gas, cargohold).
   46path(jupiter_station, fly, saturn) :- 
   47        write('Are you crazy?! You are not ready to finish the race yet!'), nl,
   48        !, fail.
   49
   50/* These facts tell where the various objects in the game
   51   are located. */
   52
   53at(gas, moon_station).
   54at(gas, mars_station).
   55at(gas, jupiter_station).
   56at(moonrocks, cave).
   57at(rockets, rocket_room).
   58
   59/* These rules describe how to pick up an object. */
   60
   61take(X) :-
   62        at(X, cargohold),
   63        write('You already have this in your cargohold!'),
   64        nl, !.
   65
   66take(X) :-
   67        i_am_at(Place),
   68        at(X, Place),
   69        retract(at(X, Place)),
   70        assert(at(X, cargohold)),
   71        write('Added to cargohold.'),
   72        nl, !.
   73
   74take(_) :-
   75        write('That is not here.'),
   76        nl.
   77
   78
   79/* These rules describe how to put down an object. */
   80
   81takeoff(X, Place) :-
   82        retract(at(X, cargohold)),
   83        assert(at(X, Place)),
   85        
   86        write('over and out'),
   87        nl, !
   87.
   88
   89drop(X) :-
   90        i_am_at(Place),
   91        at(X, Place),
   92        retract(at(X, cargohold)),
   93        assert(at(X, Place)),
   94        write('OK.'),
   95        nl, !.
   96
   97drop(_) :-
   98        write('Not in the cargobay'),
   99        nl.
  100
  101/* These rules define the six direction letters as calls to go/1. */
  102
  103forward :- go(forward).
  104
  105turn :- go(turn).
  106
  107enter :- go(enter).
  108
  109exit :- go(exit).
  110
  111fly :- i_am_at(Place), go(fly),
  112        takeoff(gas, Place).
  113
  114fly_back :- i_am_at(Place), go(fly_back),
  115        takeoff(gas, Place).
  116
  117lightspeed :- at(rockets, cargohold), go(lightspeed), nl.
  118
  119lightspeed :- write('You need new rockets to use lightspeed'), nl.
  120
  121guess(X) :- i_am_at(mars_lab), code(X), assert(confirm(true)), retract(confirm(false)), nl,
  122        write('You guessed correctly! Type enter and exit to get in and out.'), nl, !.
  123
  124guess(_) :- i_am_at(mars_lab), write('Guess again!'), nl, !.
  125
  126guess(_) :- write('There is nothing to guess!'), nl.
  127
  128
  129
  130/* This rule tells how to move in a given direction. */
  131
  132go(Direction) :-
  133        i_am_at(Here),
  134        path(Here, Direction, There),
  135        retract(i_am_at(Here)),
  136        assert(i_am_at(There)),
  137        look, !.
  138
  139go(_) :-
  140        write('That is impossible due to the constraints of space travel.').
  141
  142/* This rule tells how to look about you. */
  143
  144look :-
  145        i_am_at(Place),
  146        describe(Place),
  147        nl,
  148        notice_objects_at(Place),
  149        nl.
  150
  151/* tells the current inventory of the playear. */
  152i :-
  153        write('Inventory: '), nl,
  154        at(X, cargohold),
  155        write(X), nl,
  156        fail.
  157
  158/* These rules set up a loop to mention all the objects
  159   in your vicinity. */
  160
  161notice_objects_at(Place) :-
  162        at(X, Place),
  163        write('Theres '), write(X), write(' here.'), nl,
  164        fail.
  165
  166notice_objects_at(_).
  167
  168/* Under UNIX, the   halt.  command quits Prolog but does not
  169   remove the output window. On a PC, however, the window
  170   disappears before the final output can be seen. Hence this
  171   routine requests the user to perform the final  halt.  */
  172
  173finish :-
  174        nl,
  175        write('The game is over. Please enter the   halt.   command.'),
  176        nl, !.
  177
  178
  179/* This rule just writes out game instructions. */
  180
  181instructions :-
  182        nl,
  183        write('Enter commands using standard Prolog syntax.'), nl,
  184        write('Available commands are:'), nl,
  185        write('start.                         -- to start the game.'), nl,
  186        write('fly.  fly_back.  lightspeed.   -- to takeoff and fly'), nl,
  187        write('forward.    turn.              -- to go in that direction'), nl,
  188        write('take(Object).                  -- to pick up an object.'), nl,
  189        write('drop(Object).                  -- to put down an object.'), nl,
  190        write('i.                             -- check inventory'), nl,
  191        write('look.                          -- to look around you again.'), nl,
  192        write('guess.                         -- use to enter security code at mars_lab'), nl,
  193        write('lightspeed.                    -- use to fly directly to saturn. requires rockets'), nl,
  194        write('instructions.                  -- to see this message again.'), nl,
  195        write('halt.                          -- to end the game and quit.'), nl,
  196        nl.
  197
  198/* This rule prints out instructions and tells where you are. */
  199
  200start :-
  201        instructions,
  202        look.
  203
  204/* These rules describe the various rooms.  Depending on
  205   circumstances, a room may have more than one description. */
  206
  207describe(earth) :-
  208        write('     |     | | '), nl,
  209        write('    / \\    | | Welcome to the Space Race!'), nl,
  210        write('   |--o|===|-| Be the first to reach Saturn with'), nl,
  211        write('   |---|   | | rocks from the Moon and you win!'), nl,
  212        write('  /     \\  | | '), nl,
  213        write(' | SPACE | | | Make sure you re-fuel on every planet.'), nl,
  214        write(' |  RACE |=| | And, be sure to look around on Mars'), nl,
  215        write(' |_______| |_| for something that could turn'), nl,
  216        write('  |@| |@|  | | out to be very useful.'), nl,
  217        write('___________|_| '), nl.
  218
  219describe(moon) :-
  220        write('Welcome to the Moon!'), nl,
  221        write('         ___---___'), nl,
  222        write('      .--         --.'), nl,
  223        write('    ./   ()      .-. \\.'), nl,
  224        write('   /   o    .   (   )  \\'), nl,
  225        write('  / .            '-'    \\'), nl,
  226        write(' | ()    .  O         .  |'), nl,
  227        write('|                         |'), nl,
  228        write('|    o           ()       |'), nl,
  229        write('|       .--.          O   |'), nl,
  230        write(' | .   |    |            |'), nl,
  231        write('  \\    `.__.\\''    o   .  /'), nl,
  232        write('   \\                  /'), nl,
  233        write('    `\\  o    ()      /\''), nl,
  234        write('      `--___   ___--\''), nl,
  235        write('            ---'), nl.
  236
  237describe(cave) :-
  238        write('You are in a dark and mysterious cave. Look!'), nl,
  239        write(''), nl,
  240        write('There are moonrocks here!'), nl.
  241
  242describe(moon_station) :-
  243        write('Welcome to the Moon Station: The one stop shop to get you to Mars'), nl,
  244        write('use take and fly to refuel and takeoff'), nl,
  245        write(''), nl,
  246        write('                   .-.'), nl,
  247        write('    .-""`""-.    |(@ @)'), nl,
  248        write(' _/`oOoOoOoOo`\\_ \\ \\-/'), nl,
  249        write('''.-=-=-=-=-=-=-.''  / \\'), nl,
  250        write('  `-=.=-.-=.=-''    \\ /\\'), nl,
  251        write('     ^  ^  ^       _H_ \\'), nl.
  252
  253describe(mars_station) :-
  254        write('Welcome to the Mars Station: The one stop shop to get you to Jupiter'), nl,
  255        write('use take and fly to refuel and takeoff'), nl,
  256        write(''), nl,
  257        write('                   .-.'), nl,
  258        write('    .-""`""-.    |(@ @)'), nl,
  259        write(' _/`oOoOoOoOo`\\_ \\ \\-/'), nl,
  260        write('''.-=-=-=-=-=-=-.''  / \\'), nl,
  261        write('  `-=.=-.-=.=-''    \\ /\\'), nl,
  262        write('     ^  ^  ^       _H_ \\'), nl.
  263
  264describe(jupiter_station) :-
  265        write('Welcome to the Jupiter Gas Station: The one stop shop to get you to Saturn'), nl,
  266        write('use take and fly to refuel and takeoff'), nl,
  267        write(''), nl,
  268        write('                   .-.'), nl,
  269        write('    .-""`""-.    |(@ @)'), nl,
  270        write(' _/`oOoOoOoOo`\\_ \\ \\-/'), nl,
  271        write('''.-=-=-=-=-=-=-.''  / \\'), nl,
  272        write('  `-=.=-.-=.=-''    \\ /\\'), nl,
  273        write('     ^  ^  ^       _H_ \\'), nl.
  274
  275describe(mars) :-
  276        write('Welcome to the Red Planet'), nl,
  277        write(''), nl,
  278        write('There used to be a famous labratory here.'), nl,
  279        write('I wonder if it still exists...?'), nl.
  280
  281descrite(mars_lab) :- confirm(true), 
  282        write('The door is wide open,'), nl,
  283        write('type enter and exit'), nl,
  284        write('to make your way through.'), nl.
  285
  286describe(mars_lab) :-
  287        write('This is the legendary Mars Lab!'), nl,
  288        write('Try to guess the security code and see what''s inside.'), nl,
  289        write('hint: it''s 3 of the same number').
  290
  291describe(rocket_room) :-
  292        write('Welcome to the secret Rocket Room!'), nl,
  293        write('Take these supercharged rockets, and'), nl,
  294        write('use lightspeed at the next station you visit!'), nl, !.
  295
  296describe(jupiter) :-
  297        write('Welcome to Jupiter.'), nl,
  298        write('Almost there.'), nl,
  299        write('If you were lucky enough to get into'), nl,
  300        write('the Mars Lab, try using lightspeed to get to'), nl,
  301        write('Saturn without refueling...'), nl, !.
  302
  303describe(saturn) :-
  304        write('Congratulations!!  You are the first to arrive with the moonrocks!'), nl,
  305        write('You win the race!'), nl,
  306        write('                                          _.oo.'), nl,
  307        write('                  _.u[[/;:,.         .odMMMMMM'), nl,
  308        write('               .o888UU[[[/;:-.  .o@P^    MMM^'), nl,
  309        write('              oN88888UU[[[/;::-.        dP^'), nl,
  310        write('             dNMMNN888UU[[[/;:--.   .o@P^'), nl,
  311        write('            ,MMMMMMN888UU[[/;::-. o@^'), nl,
  312        write('            888888888UU[[[/o@^-..'), nl,
  313        write('           oI8888UU[[[/o@P^:--..'), nl,
  314        write('        .@^  YUU[[[/o@^;::---..'), nl,
  315        write('      oMP     ^/o@P^;:::---..'), nl,
  316        write('   .dMMM    .o@^ ^;::---...'), nl,
  317        write('  dMMMMMMM@^       ^^^^'), nl,
  318        write(' YMMMUP^'), nl, finish, !