1% Space Escape, by Gabe Colton 
    2
    3%makes i_am_at, at, holding, alive retract/assertable
    4%then retracts all instances of those predicates in the database
    5:- dynamic i_am_at/1, at/2, holding/1, alive/1, path/3, 
    6	health/1, loaded/1, hand/1, selfdes_init/1, infrared_vision/1, lasers/1.    7:- retractall(at(_, _)), retractall(i_am_at(_)), retractall(alive(_)),
    8    retractall(path(_,_,_)), retractall(health(_)), retractall(loaded(_)),
    9    retractall(hand(_)), retractall(sd_init(_)), retractall(infrared_vision(_)),
   10    retractall(lasers(_)).   11
   12%sets initial some conditions.
   13hand(attached).
   14health(injured).
   15loaded(no).
   16alive(alien).
   17%self destruct sequence not initiated
   18selfdes_init(not_init).
   19infrared_vision(off).
   20lasers(active).
   21
   22%Location at beginning of game
   23i_am_at('Engine Room').
   24
   25%defines paths between rooms on the space ship
   26
   27path('Engine Room', e, 'Arsenal').
   28path('Arsenal', w, 'Engine Room').
   29
   30path('Engine Room', s, 'Infirmary').
   31path('Infirmary', n, 'Engine Room').
   32
   33path('Infirmary', e, 'Dining Hall').
   34path('Dining Hall', w, 'Infirmary'). 
   35
   36path('Dining Hall', s, 'Command Deck'):- 
   37	write('Opening this door requires the ID of a commanding officer'),
   38	nl,
   39	fail.
   40
   41path('Command Deck', n, 'Dining Hall'). 
   42
   43path('Command Deck', w, 'Hallway').
   44path('Hallway', e, 'Command Deck').
   45
   46path('Hallway', w, 'Escape Pod Entrance'):-
   47%if you have used and are still holding the goggles, and if the lasers are active.
   48	\+ infrared_vision(off),
   49	holding(infrared_goggles),
   50	lasers(active),
   51	write('You are able to maneuver through the deadly lasers.'),
   52	nl, write('You deactivate the laser field.'),nl,
   53	retract(lasers(active)),!.
   54
   55path('Hallway', w, 'Escape Pod Entrance').
   56	
   57  
   58path('Escape Pod Entrance', w, 'Escape Pod'):-
   59	holding(blaster),	
   60	write('Unfortunately the blaster is too big to fit in the Escape Pod.'),
   61	nl,!,
   62	fail.
   63
   64path('Escape Pod Entrance', w, 'Escape Pod').
   65
   66
   67path('Escape Pod Entrance', e, 'Hallway').
   68path('Escape Pod', e, 'Escape Pod Entrance'). 
   69
   70
   71%defines where each item is
   72	at(blaster, 'Arsenal').
   73	at(burst_cartridge, 'Arsenal').
   74	at(id, 'Arsenal'). 
   75	at(infrared_goggles, 'Arsenal').
   76	at(medicine,'Infirmary').
   77	at(self_destruct_button, 'Command Deck').
   78	at(launch_button, 'Escape Pod'). 
   79
   80%These rules describe how to pick up an object. 
   81
   82take(id) :-
   83		i_am_at('Arsenal'), 
   84		hand(attached),
   85		at(id, 'Arsenal'),
   86		
   87		retract(hand(attached)),
   88		assert(at(hand,'Arsenal')),
   89		
   90		retract(at(id, 'Arsenal')),
   91		assert(holding(id)),
   92		
   93		write('When you try to take the id, you realize your commanding officer '),
   94		nl,
   95		write('is still holding it very tight. You pull harder'),
   96		nl,
   97		write('and you take the id, but you detach his hand from'),
   98		nl,
   99		write('his arm in the process.'),
  100		!, nl. 
  101		
  102take(X) :-
  103        holding(X),
  104        write('You''re already holding it!'),
  105        !, nl.
  106
  107take(self_destruct_button):-
  108		write('You can''t take that button, but you can use it.'), !, fail.
  109
  110take(launch_button):-
  111		write('You can''t take that button, but you can use it.'), !, fail.
  112
  113take(X) :-
  114        i_am_at(Place),
  115        at(X, Place),
  116        retract(at(X, Place)),
  117        assert(holding(X)),
  118        write('You have taken the '), write(X), write('.'),
  119        !, nl.
  120
  121take(_) :-
  122        write('I don''t see it here.'),
  123        nl.
  124
  125
  126% These rules describe how to put down an object. 
  127
  128drop(infrared_goggles) :-
  129		holding(infrared_goggles),
  130        i_am_at(Place),
  131        retract(holding(infrared_goggles)),
  132        assert(at(infrared_goggles, Place)),
  133        assert(infrared_vision(off)),
  134        write('You drop the goggles on the ground.'),
  135        !, nl.
  136drop(X) :-
  137        holding(X),
  138        i_am_at(Place),
  139        retract(holding(X)),
  140        assert(at(X, Place)),
  141        write('You drop the '), write(X), write(' on the ground.'),
  142        !, nl.
  143
  144drop(_) :-
  145        write('You aren''t holding it!'),
  146        nl.
  147
  148%These rules describe how and where each object can be used.
  149
  150%makes it so the only item you can use is a loaded blaster
  151%otherwise, you are injured and are forced to retreat to the Infirmary
  152
  153use(blaster) :- 
  154		holding(blaster),
  155		loaded(yes),
  156		alive(alien),
  157		i_am_at('Dining Hall'),
  158		write('You blast the alien right in its weakspot'), nl,
  159		write('The alien is no longer a threat'),
  160		retract(alive(alien)), 
  161		!.
  162
  163use(blaster) :- 
  164		i_am_at('Dining Hall'),
  165		alive(alien),
  166		health(healthy),
  167		retract(health(healthy)),
  168		assert(health(injured)), 
  169		use(blaster),
  170		nl,
  171		write('You''re injured by the alien and'),
  172		nl,
  173		write('forced to retreat to the Infirmary.'),
  174		nl,
  175		go(w),!.
  176
  177use(blaster) :- 
  178		holding(blaster),
  179		loaded(no),
  180		write('You have to load it first!'), !.
  181
  182use(_) :- 
  183		i_am_at('Dining Hall'),
  184		alive(alien),
  185		health(healthy),
  186		retract(health(healthy)),
  187		assert(health(injured)),
  188		nl,
  189		write('Before you can do that,'),
  190		nl,
  191		write('you''re injured by the alien and'),
  192		nl,
  193		write('forced to retreat to the Infirmary.'),
  194		nl,
  195		go(w),!.
  196
  197use(id) :-
  198		holding(id),
  199		i_am_at('Dining Hall'),
  200		asserta(path('Dining Hall', s, 'Command Deck')),
  201		write('You swipe the ID card and enter the Command Deck'),
  202		nl,
  203		go(s),
  204		retract(path('Dining Hall', s, 'Command Deck')),
  205		!.
  206		
  207
  208use(blaster) :- 
  209		holding(blaster),
  210		loaded(no),
  211		write('You have to load it first!'), !.
  212
  213
  214		
  215use(burst_cartridge):-
  216		holding(blaster),
  217		holding(burst_cartridge),
  218		retract(loaded(no)),
  219		assert(loaded(yes)),
  220		retract(holding(burst_cartridge)),
  221		write('Your blaster is now loaded'),!.
  222
  223use(medicine) :-
  224		holding(medicine),
  225		health(injured),		
  226		alive(alien),
  227		i_am_at('Dining Hall'),
  228		write('You are now healthy, and your vision has returned'),
  229		retract(health(injured)),
  230		assert(health(healthy)),
  231		look,
  232		!.
  233		
  234use(medicine) :-
  235		health(injured),
  236		holding(medicine),
  237		write('You are now healthy, and your vision has returned'),
  238		retract(health(injured)),
  239		assert(health(healthy)),
  240		!.
  241use(medicine) :-
  242		holding(medicine),
  243		write('You don''t need to use the medicine '),
  244		write('because you''re already healthy'), !.		
  245
  246use(self_destruct_button) :-
  247		selfdes_init(not_init),
  248		i_am_at('Command Deck'),
  249		holding(hand),
  250		write('You use your commanding officer''s severed hand to'),
  251		nl,
  252		write('initiate the ship''s self destruct sequence.'),
  253		nl, 
  254		write('The ship will self-destruct shortly after the escape pod launches.'),
  255		nl,
  256		retract(selfdes_init(not_init)),
  257		!.
  258
  259		
  260use(self_destruct_button) :-
  261		selfdes_init(not_init),
  262		i_am_at('Command Deck'),
  263		write('The computer requires the finger prints of a commanding officer'),
  264		nl,
  265		write('to cause a system override and initiate the self destruct sequence.'),
  266		nl,
  267		!,fail.
  268
  269use(self_destruct_button) :-
  270		i_am_at('Command Deck'),
  271		write('The self destruct sequence has already been initiated.'),
  272		!, nl.
  273		
  274		
  275use(infrared_goggles) :-
  276		retract(infrared_vision(off)),
  277		write('You put on the infrared goggles and now can see infrared signatures.'),
  278		nl,!.
  279
  280use(launch_button):-
  281		i_am_at('Escape Pod'),
  282		\+ selfdes_init(not_init), 
  283		write('You successfully escape the ship.'),nl,
  284		write('You survived the alien onslaught, blew up the ship,'), nl, 
  285		write('and successfully destroyed the energy orb'),nl,
  286		write('preventing the rest of the alien army from using its power.'),
  287		!, finish. 
  288use(launch_button):-
  289		i_am_at('Escape Pod'),
  290		write('You have not initialized the ship''s self destruct sequence.'),
  291		nl, !, fail. 
  292		
  293use(hand) :- 
  294		holding(hand),
  295		i_am_at('Command Deck'),
  296		use(self_destruct_button),!.
  297		
  298use(X) :-
  299		holding(X),
  300		write('Looks like you can''t use that here'),!.
  301
  302use(_) :-
  303		write('You can''t use something you don''t have').  
  304		
  305
  306% These rules define the direction letters as calls to go/1. 
  307
  308n :- go(n).
  309
  310s :- go(s).
  311
  312e :- go(e).
  313
  314w :- go(w).
  315
  316
  317% This rule tells how to move in a given direction. 
  318
  319go(w) :- 
  320		i_am_at('Hallway'),
  321		infrared_vision(off),
  322	    lasers(active),
  323		write('The deadly lasers slice your body into 700 pieces.'),
  324		nl, !, die.
  325		
  326		
  327go(Direction) :-
  328        i_am_at(Here),
  329        path(Here, Direction, There),
  330        retract(i_am_at(Here)),
  331        assert(i_am_at(There)),
  332        look, !.
  333
  334go(_) :-
  335        write('You can''t go that way.').
  336
  337
  338% This rule tells how to look about you. 
  339
  340look :-
  341        i_am_at('Infirmary'),
  342        health(injured),
  343        describe('Infirmary'),
  344        notice_objects_at('Infirmary'),
  345        nl,!.
  346look :-
  347        i_am_at(Place),
  348        health(injured),
  349        describe(Place),
  350        write('Looks like you''re injured though. '), nl,
  351				write('Your vision is greatly impaired. '), nl,
  352				write('Better go find some medicine '), 
  353				write('before you''ll be able to see what''s here'),
  354				nl, !.
  355look :- 
  356		i_am_at(Place),		
  357        nl,
  358        describe(Place),
  359        nl, 
  360        notice_objects_at(Place),
  361        nl.
  362
  363
  364% These rules set up a loop to mention all the objects
  365  % in your vicinity. 
  366
  367notice_objects_at(Place) :-
  368        at(X, Place),
  369        write('You see the '), write(X), write(' here.'), nl,
  370        fail.
  371
  372notice_objects_at(_).
  373
  374
  375% This rule tells how to die. 
  376
  377die :-
  378        write('You died.'),
  379        finish.
  380
  381
  382
  383
  384finish :-
  385        nl,
  386        write('The game is over. Please enter the "halt." command.'),
  387        nl.
  388
  389
  390% This rule just writes out game instructions. 
  391
  392help :-
  393        nl,
  394        write('Enter commands using standard Prolog syntax.'), nl,
  395        write('Available commands are:'), nl,
  396        write('start.             -- to start the game.'), nl,
  397        write('n.  s.  e.  w.     -- to go in that direction.'), nl,
  398        write('take(Object).      -- to pick up an object.'), nl,
  399        write('drop(Object).      -- to put down an object.'), nl,
  400        write('use(Object).       -- to use an object (e.g. push a button, shoot a gun)'), nl,
  401        write('look.              -- to look around you again.'), nl,
  402        write('i.                 -- to show your inventory.'), nl,
  403        write('help.              -- to see this message again.'), nl,
  404        write('halt.              -- to end the game and quit.'), nl,nl,
  405        write('Your goal is to initiate the ship''s self destruct sequence'),nl,
  406        write('in order to destroy the energy orb that powers the ship'),nl,
  407        write('and then escape using the Escape Pod'), nl,nl.
  408
  409
  410% This rule prints out instructions and tells where you are. 
  411
  412start :-
  413        help,
  414        look.
  415
  416
  417
  418%this rule prints out everything the player is holding
  419
  420i :- 
  421		holding(_),
  422		write('You are holding the following:'), nl,!,
  423		holding(X),
  424        write(X), nl,
  425        fail.	
  426
  427% These rules describe the various rooms.  Depending on
  428  % circumstances, a room may have more than one description. 
  429
  430describe(Place) :- 
  431		health(injured), 
  432		write('It seems like you''re in the '), 
  433		write(Place), nl. 
  434
  435describe('Engine Room') :-
  436		write('You are in the Engine Room. Not much to see here'), 
  437		nl,		
  438		write('other than a large energy orb that supplies power to the ship.'),
  439		nl. 
  440		
  441describe('Infirmary') :-
  442		write('You are in the Infirmary. It is very bright in here.'),
  443		nl,
  444		write('The walls and cabinets are mostly empty,'),
  445		nl,
  446		write('and there is blood splattered everywhere.'),
  447		nl.
  448
  449describe('Command Deck') :-
  450		write('You are in the Command Deck. Many of your fallen'),
  451		nl, 
  452		write('comrades are eviscerated and their entrails'),
  453		nl, 
  454		write('seem to be jamming up most of the controls.'),
  455		nl.
  456
  457describe('Dining Hall') :-
  458		alive(alien),
  459		write('You are in the Dining Hall and see a murderous alien.'),
  460		nl,
  461		write('In your healthy state, it views you as a threat'),
  462		nl,
  463		write('It lunges at you!!!!'), 
  464		!,
  465		nl.
  466		
  467describe('Dining Hall') :-
  468		write('The alien''s amorphous body has'),
  469		nl,
  470		write('shrivelled into a pile of mucous').
  471		
  472describe('Arsenal') :-
  473		hand(attached), 
  474		write('You are in the Arsenal. Most of the ships weapons'),
  475		nl,
  476		write('stock was ransacked during the fight.'), 
  477		nl,
  478		write('You also see your commanding officer.'),
  479		nl, 
  480		write('He is dead and is holding his ID in his hand'),
  481		!, nl.
  482
  483describe('Arsenal') :-
  484		at(hand, 'Arsenal'),
  485		write('You are in the Arsenal. Most of the ships weapons'),
  486		nl,
  487		write('stock was ransacked during the fight.'), 
  488		nl,
  489		write('You also see your commanding officer.'),
  490		nl, 
  491		write('He is dead and his severed hand lays next to his body.'),
  492		!, nl.
  493
  494describe('Arsenal') :-
  495		write('You are in the Arsenal. Most of the ships weapons'),
  496		nl,
  497		write('stock was ransacked during the fight.'), 
  498		nl,
  499		write('You also see your commanding officer.'),
  500		nl, 
  501		write('His hand-less arm is unnerving '),
  502		nl.
  503
  504describe('Hallway') :-
  505		write('You are in an unassuming hallway, and see the words'),
  506		nl, 
  507		write('Escape Pod written on a door to the west,'),
  508		nl.
  509
  510describe('Escape Pod Entrance') :-
  511		
  512		write('You are now at the entrance to the Escape Pod.'),
  513		nl.
  514		
  515describe('Escape Pod') :-
  516		
  517		write('You are now in the Escape Pod'),
  518		nl,
  519		write('all you have to do is launch yourself to safety'), nl