1/* BEVERLY HILLS THIEF -- an adventure game by Jasmine Lee. */
    2
    3:- dynamic at/2, i_am_at/1, asleep/1, visible_object/1, holding/1, fed/1, battery_life/1, hammer_count/1.   
    4
    5/* Needed by SWI-Prolog. */
    6
    7:- retractall(at(_, _)), retractall(i_am_at(_)), retractall(visible_object(_)), retractall(holding(_)), 
    8   retractall(battery_life(_)), retractall(hammer_count(_)).    9
   10/* This defines my current location. */
   11
   12i_am_at(garage).
   13
   14/* set up facts specific to this game */
   15
   16visible_object(flashlight).
   17visible_object(meatloaf).
   18battery_life(4).
   19hammer_count(0).
   20
   21/* These facts describe how the rooms are connected. */
   22
   23path(garage, n, kitchen).
   24path(kitchen, s, garage).
   25
   26path(kitchen, u, fridge).
   27path(fridge, d, kitchen).
   28
   29path(kitchen, w, living_room).
   30path(living_room, e, kitchen).
   31
   32path(living_room, s, lobby).
   33path(lobby, n, living_room).
   34
   35path(garage, w, lobby).
   36path(lobby, e, garage).
   37
   38path(lobby, s, study).
   39path(study, n, lobby).
   40
   41path(lobby, u, hallway).
   42path(hallway, d, lobby).
   43
   44path(hallway, n, closet) :- fed(bambi).
   45path(hallway, n, closet) :- write('You notice that Paris''s precious chihuahua Bambi stands in front of the entrance to the room, glaring at you with its hungry eyes. You better leave now before it barks and wakes the owner up.'), nl, nl,
   46        !, fail.
   47path(closet, s, hallway).
   48
   49path(hallway, s, bedroom).
   50path(bedroom, n, hallway).
   51
   52path(hallway, e, clothes_closet).
   53path(clothes_closet, w, hallway).
   54
   55/* These facts tell where the various objects in the game
   56   are located. */
   57
   58at(flashlight, living_room).
   59at(nightgoggles, study).
   60at(carkey, bedroom).
   61at(meatloaf, fridge).
   62at(handbag, closet).
   63at(hammer, lobby).
   64
   65/* These rules describe how to pick up an object. */
   66
   67take(fridge) :-
   68        i_am_at(kitchen),
   69        write('It''s too heavy to lift.'), nl,
   70	!, fail.
   71
   72take(box) :-
   73        i_am_at(closet),
   74        write('It is firmly nailed to the ground!'), nl,
   75	!, fail.
   76
   77take(X) :-
   78        at(X, in_bag),
   79        write('You already have it!'),
   80        nl, !.
   81
   82take(X) :-
   83        i_am_at(Place),
   84        at(X, Place),
   85        retract(at(X, Place)),
   86        assert(at(X, in_bag)),
   87        write('OK.'),
   88        nl, !.
   89
   90take(_) :-
   91        write('I don''t see it here.'),
   92        nl, !, fail.
   93
   94
   95/* These rules describe how to put down an object. */
   96
   97drop(X) :-
   98        at(X, in_bag),
   99        i_am_at(Place),
  100        retract(at(X, in_bag)),
  101        update_holding(X),
  102        assert(at(X, Place)),
  103        write('OK.'),
  104        nl, !.
  105
  106drop(_) :-
  107        write('You don''t have it!'),
  108        nl, !, fail.
  109
  110update_holding(X) :-
  111        \+ holding(X).
  112
  113update_holding(X) :-
  114        holding(X),
  115        retract(holding(X)).
  116
  117
  118/* These rules define the six direction letters as calls to go/1. */
  119
  120n :- go(n).
  121
  122s :- go(s).
  123
  124e :- go(e).
  125
  126w :- go(w).
  127
  128u :- go(u).
  129
  130d :- go(d).
  131
  132
  133/* This rule tells how to move in a given direction. */
  134
  135go(Direction) :-
  136        i_am_at(Here),
  137        path(Here, Direction, There),
  138        retract(i_am_at(Here)),
  139        assert(i_am_at(There)),
  140        look, !.
  141
  142go(_) :-
  143        write('You can''t go that way.').
  144
  145
  146/* This rule tells how to look about you. */
  147
  148look :-
  149        i_am_at(Place),
  150        describe(Place),
  151        nl,
  152        notice_objects_at(Place),
  153        nl.
  154
  155
  156/* These rules set up a loop to mention all the objects
  157   in your vicinity. */
  158
  159notice_objects_at(Place) :-
  160        at(X, Place),
  161        visible_object(X),
  162        write('There is a '), write(X), write(' here.'), nl,
  163        fail.
  164
  165notice_objects_at(_).
  166
  167/* Tells what the player has in the bag. */
  168
  169inventory :-
  170        at(X, in_bag),
  171        write('There is a '), write(X), write(' in the bag.'), 
  172        nl, fail.
  173
  174/* Tells what the player is holding */
  175
  176using :-
  177        holding(X),
  178        write('You are holding the '), write(X), write('.'),
  179        nl, fail.
  180
  181/* These rules are specific to this game. */
  182
  183use(flashlight) :-
  184        \+ battery_life(0),
  185        at(flashlight, in_bag),
  186        hold(flashlight),
  187        lower_battery_life,
  188        make_visible(nightgoggles),
  189        make_visible(hammer),
  190        make_invisible(carkey),
  191        flashlight_on, !.
  192
  193use(flashlight) :-
  194        at(flashlight, in_bag),
  195        hold(flashlight),
  196        make_invisible(nightgoggles),
  197        make_invisible(hammer),
  198        write('Your flashlight is out of batteries.'), nl, !, fail.
  199
  200use(nightgoggles) :-
  201        at(nightgoggles, in_bag),
  202        hold(nightgoggles), 
  203        make_visible(carkey),
  204        make_invisible(hammer),
  205        goggles_on, !.
  206        
  207use(fridge) :-
  208        i_am_at(kitchen), !, 
  209        u.
  210
  211use(fridge) :- 
  212        write('The fridge is in the kitchen.'), nl, !, fail.
  213
  214use(hammer) :- 
  215        at(hammer, in_bag),
  216        hold(hammer),
  217        i_am_at(closet),
  218        bump_hammer_count,
  219        hit, !.
  220
  221use(meatloaf) :-
  222        at(meatloaf, in_bag),
  223        i_am_at(hallway),
  224        assert(fed(bambi)), !.
  225
  226use(carkey) :-
  227        at(carkey, in_bag),
  228        i_am_at(garage),
  229        write('Congratulations!'), nl,
  230	write('You have successfully completed the mission by stealing the hand bag'), nl, 
  231	write('and discovering the car keys to the Bentley.'), nl,        !, 
  232	write('You smirk under your breath as the engine turns on with a roar.'), nl,
  233	write('You drive through the garage door into the beautiful Hollywood sunrise.'), nl, finish.
  234
  235use(X) :-
  236        at(X, in_bag), 
  237        hold(X),
  238        !.
  239
  240use(_) :-
  241        write('You can''t use this item.'), nl, !, fail.
  242
  243hit :- 
  244        hammer_count(3),
  245        make_visible(handbag),
  246        write('You slam the hammer one last time against the box which breaks into pieces.'), nl,
  247        write('Right at the center of the box, you spot the limited edition Hermes handbag!'), nl.
  248
  249hit :- 
  250        hammer_count(2),
  251        write('You hit the box with the hammer once more, making a crack on the right side of the box. Any time now.'),
  252        nl.
  253
  254hit :- 
  255        hammer_count(1),
  256        write('You swing the hammer behind you and hit the box hard. This leaves behind a crack on the left.'), nl.
  257
  258hit :- 
  259        write('The box has already been broken.'), nl, !, fail.
  260
  261flashlight_on :- 
  262        i_am_at(study),
  263        \+ at(nightgoggles, in_bag),
  264        write('You spot some nightgoggles on the desk.'), nl.
  265
  266flashlight_on :- 
  267        i_am_at(bedroom),
  268        write('Your flashlight hits Paris''s sleepy face.'), nl,
  269        write('She detects your presence and screams at the top of her lungs!!'), nl,
  270        finish.
  271
  272flashlight_on :-
  273        i_am_at(closet),
  274        \+ at(handbag, in_bag),
  275        write('Your flashlight shines across a mysterious wooden box.'), nl.
  276
  277flashlight_on :-
  278        i_am_at(lobby),
  279        \+ at(hammer, in_bag),
  280        write('You spot a hammer.'), nl.
  281
  282flashlight_on.
  283
  284goggles_on :-
  285        i_am_at(bedroom),
  286        \+ at('access key', in_bag),
  287        write('You spot an access key under the bed.'), nl.
  288
  289goggles_on :- !.
  290
  291hold(X) :- holding(X).
  292
  293hold(X) :-
  294        retractall(holding(_)),
  295        assert(holding(X)).
  296
  297exit :-
  298        i_am_at(fridge), !,
  299        d.
  300
  301exit :- 
  302        write('Please specify which direction you''d like to go.').
  303
  304bump_hammer_count :-
  305        retract(hammer_count(X)),
  306        Y is X + 1,
  307        assert(hammer_count(Y)).
  308
  309lower_battery_life :-
  310        retract(battery_life(X)),
  311        Y is X - 1,
  312        assert(battery_life(Y)).
  313
  314make_visible(X) :-
  315	visible_object(X).
  316
  317make_visible(X) :-
  318	assert(visible_object(X)).
  319
  320make_invisible(X) :- \+ visible_object(X).
  321
  322make_invisible(X) :-
  323        retract(visible_object(X)).
  324        
  325/* Under UNIX, the   halt.  command quits Prolog but does not
  326   remove the output window. On a PC, however, the window
  327   disappears before the final output can be seen. Hence this
  328   routine requests the user to perform the final  halt.  */
  329
  330finish :-
  331        nl,
  332        write('The game is over. Please enter the   halt.   command.'),
  333        nl, !.
  334
  335
  336/* This rule just writes out game instructions. */
  337
  338instructions :-
  339        nl,
  340        write('Enter commands using standard Prolog syntax.'), nl,
  341        write('Available commands are:'), nl,
  342        write('start.                   -- to start the game.'), nl,
  343        write('n.  s.  e.  w.  u.  d.   -- to go in that direction.'), nl,
  344        write('take(Object).            -- to pick up an object.'), nl,
  345        write('use(Object).             -- to use an object. Note: You can only use one object at any given time.'), nl,
  346        write('drop(Object).            -- to put down an object.'), nl,
  347        write('inventory.               -- to see what''s currently in your bag.'), nl,
  348        write('using.                   -- to see what you are currently holding.'), nl,
  349        write('look.                    -- to look around you again.'), nl,
  350        write('instructions.            -- to see this message again.'), nl,
  351        write('halt.                    -- to end the game and quit.'), nl,
  352        nl.
  353
  354
  355/* This rule prints out instructions and tells where you are. */
  356
  357start :-
  358        instructions,
  359        look.
  360
  361/* These rules describe the various rooms.  Depending on
  362   circumstances, a room may have more than one description. */
  363
  364describe(garage) :-
  365	at(carkey, in_bag),
  366        at(handbag, in_bag),
  367        write('You have returned to the garage with the stolen hand bag,'), nl,
  368	write('and the carkey. Time to leave this house!'), nl, !.
  369
  370describe(garage) :-
  371	\+ at(carkey, in_bag),
  372        at(handbag, in_bag),
  373        write('You are back in the garage with the stolen hand bag,'), nl,
  374        write('To the north is an unlocked door to the kitchen;'), nl, 
  375	write('to the west is the entrance to the lobby of the mansion'), nl,
  376	write('but you must also fetch the car keys before you can leave.'), nl, !.
  377
  378describe(garage) :-
  379	\+ at(handbag, in_bag),
  380        at(carkey, in_bag),
  381        write('You are back in the garage with the carkey.'), nl,
  382        write('To the north is an unlocked door to the kitchen;'), nl, 
  383	write('to the west is the entrance to the lobby of the mansion'), nl,
  384	write('But wait - you forgot the most important thing - to steal the hand bag!'), nl, !.
  385
  386describe(garage) :-
  387        write('You stand next to Paris Hilton''s pink studded Bentley car in the garage at 5 in the morning.'), nl,
  388	write('To the north is an unlocked door to the kitchen;'), nl, 
  389	write('to the west is the entrance to the lobby of the mansion'), nl,
  390	write('And how did you end up here, you ask?'), nl,
  391	write('You are the stealthiest thief in all of Beverly Hills.'), nl,
  392	write('Tonight you have decided to undertake one of the riskiest projects yet,'), nl,
  393	write('which is to steal Paris Hilton''s most expensive handbag.'), nl,
  394	write('Your mission, should you accept it, is to find and take Paris''s'), nl,
  395	write('limited edition Hermes Birkin hand bag, then return to the garage'), nl,
  396	write('with her car keys so that you escape fashionably.'), nl.
  397
  398describe(kitchen) :-
  399	write('You are in the kitchen. The garage door is to the south;'), nl,
  400	write('The living room is to the west.'), nl,
  401	write('You look around and see the most enormous fridge you''ve seen in your whole life.'), nl,
  402	write('You''d be able to feed the whole city with the amount of food in this fridge, you thought to yourself.'), nl.
  403
  404describe(fridge) :-
  405	write('You are inside the fridge. Type exit if you want to close the fridge.'), nl.
  406
  407describe(living_room) :-
  408	write('You are in the living room. The kitchen is to the east;'), nl,
  409	write('The lobby is to the south.'), nl.
  410
  411describe(lobby) :-
  412        write('You are in the lobby. The living room is to the north;'), nl,
  413	write('the garage is to the east; and the study is to the south.'), nl,
  414	write('An elegant spiral staircase leads directly to the second floor'), nl.
  415
  416describe(study) :-
  417        write('You are in the study. The lobby is to the north.'), nl,
  418	write('You wonder why Paris would ever need a study room.'), nl,
  419	write('Does she even read?'), nl.
  420
  421describe(hallway) :-
  422        write('You are in the second floor hallway.'), nl,
  423	write('To the north is the entrance to a room;'), nl,
  424	write('To the east is the walk-in closet;'), nl,
  425	write('To the south is Paris''s bedroom.'), nl.
  426
  427describe(bedroom) :-
  428	holding(flashlight),
  429        \+ battery_life(0),
  430        write('Your blinding flashlight hits Paris''s sleepy face.'), nl,
  431        write('She detects your presence and screams at the top of her lungs!!'), nl, !.
  432
  433describe(bedroom) :-
  434	holding(nightgoggles),
  435        write('You are inside the bedroom.'), nl,
  436	write('You put on the nightgoggles and tip-toe quietly across the room.'), nl, !.
  437
  438describe(bedroom) :-
  439        write('You are inside the bedroom.'), nl,
  440	write('It is pitch dark and you can barely see anything.'), nl,
  441	write('As you make your way across the room, you trip over'), nl,
  442	write('a pair of heels and fall flat on your face.'), nl,
  443        write('Oh no, how could you be so clumsy?'), nl,
  444	write('The sound startles Paris and she wakes up with a scream!!'), nl,
  445	finish.
  446
  447describe(closet) :-
  448        holding(flashlight),
  449        \+ battery_life(0),
  450        write('You are in an unfurnished closet. The hallway is to the south.'), nl, !.
  451
  452describe(closet) :-
  453	write('You are inside a dark closet. The hallway is to the south.'), nl,
  454	write('You suspect there might be something in the far corner,'), nl,
  455	write('but you can''t quite make out what it is...'), nl.
  456
  457describe(clothes_closet) :-
  458        holding(flashlight),
  459        \+ battery_life(0),
  460        write('You are in the walk-in closet. The exit is to the west.'), nl,
  461	write('The two sides of the room are lined with shelves full of clothing'), nl,
  462	write('in every color and style anyone could ever dream of.'), nl,
  463	write('If there was ever an earthquake, the clothes in this room would most certainly bury someone alive.'), nl, !.
  464
  465describe(clothes_closet) :-
  466	write('You are in the walk-in closet. The exit is to the west.'), nl