Advertisement
logicmoo

Untitled

Nov 18th, 2016
366
0
Never
Not a member of Pastebin yet? Sign Up, it unlocks many cool features!
Prolog 15.74 KB | None | 0 0
  1. % NANI SEARCH - A sample adventure game
  2.  
  3. % Nani Search is designed to illustrate Prolog programming.  It
  4. % is an implementation of the principle example used in
  5. % this tutorial.
  6.  
  7. main:- nani_search.       % main entry point
  8.  
  9. nani_search:-
  10.   init_dynamic_facts,     % predicates which are not compiled
  11.  
  12.   write('NANI SEARCH - A Sample Adventure Game'),nl,
  13.   write('Copyright (C) Amzi! inc. 1990-2010'),nl,
  14.   write('No rights reserved, use it as you wish'),nl,
  15.   nl,
  16.   write('Nani Search is designed to illustrate Prolog programming.'),nl,
  17.   write('As such, it might be the simplest adventure game.  The game'),nl,
  18.   write('is the primary example used in this tutorial.'),nl,
  19.   write('Full source is included as well.'),nl,
  20.   nl,
  21.   write('Your persona as the adventurer is that of a three year'),nl,
  22.   write('old.  The Nani is your security blanket.  It is getting'),nl,
  23.   write('late and you''re tired, but you can''t go to sleep'),nl,
  24.   write('without your Nani.  Your mission is to find the Nani.'),nl,
  25.   nl,
  26.   write('You control the game by using simple English commands'),nl,
  27.   write('expressing the action you wish to take.  You can go to'),nl,
  28.   write('other rooms, look at your surroundings, look in things'),nl,
  29.   write('take things, drop things, eat things, inventory the'),nl,
  30.   write('things you have, and turn things on and off.'),nl,
  31.   nl,
  32.   write('Hit any key to continue.'),get0(_),
  33.   write('Type "help" if you need more help on mechanics.'),nl,
  34.   write('Type "hint" if you want a big hint.'),nl,
  35.   write('Type "quit" if you give up.'),nl,
  36.   nl,
  37.   write('Enjoy the hunt.'),nl,
  38.  
  39.   look,                   % give a look before starting the game
  40.   command_loop.
  41.  
  42. % command_loop - repeats until either the nani is found or the
  43. %     player types quit
  44.  
  45. command_loop:-
  46.   repeat,
  47.   get_command(X),
  48.   do(X),
  49.   (nanifound; X == quit).
  50.  
  51. % do - matches the input command with the predicate which carries out
  52. %     the command.  More general approaches which might work in the
  53. %     listener are not supported in the compiler.  This approach
  54. %     also gives tighter control over the allowable commands.
  55.  
  56. %     The cuts prevent the forced failure at the end of "command_loop"
  57. %     from backtracking into the command predicates.
  58.  
  59. do(goto(X)):-goto(X),!.
  60. do(nshelp):-nshelp,!.
  61. do(hint):-hint,!.
  62. do(inventory):-inventory,!.
  63. do(take(X)):-take(X),!.
  64. do(drop(X)):-drop(X),!.
  65. do(eat(X)):-eat(X),!.
  66. do(look):-look,!.
  67. do(turn_on(X)):-turn_on(X),!.
  68. do(turn_off(X)):-turn_off(X),!.
  69. do(look_in(X)):-look_in(X),!.
  70. do(quit):-quit,!.
  71.  
  72. % These are the predicates which control exit from the game.  If
  73. % the player has taken the nani, then the call to "have(nani)" will
  74. % succeed and the command_loop will complete.  Otherwise it fails
  75. % and command_loop will repeat.
  76.  
  77. nanifound:-
  78.   have(nani),        
  79.   write('Congratulations, you saved the Nani.'),nl,
  80.   write('Now you can rest secure.'),nl,nl.
  81.  
  82. quit:-
  83.   write('Giving up?  It''s going to be a scary night'),nl,
  84.   write('and when you get the Nani it''s not going'),nl,
  85.   write('to smell right.'),nl,nl.
  86.  
  87. % The help command
  88.  
  89. nshelp:-
  90.   write('Use simple English sentences to enter commands.'),nl,
  91.   write('The commands can cause you to:'),nl,
  92.   nl,
  93.   write('   go to a room          (ex. go to the office)'),nl,
  94.   write('   look around           (ex. look)'),nl,
  95.   write('   look in something     (ex. look in the desk)'),nl,
  96.   write('   take something        (ex. take the apple)'),nl,
  97.   write('   drop something        (ex. drop the apple)'),nl,
  98.   write('   eat something         (ex. eat the apple)'),nl,
  99.   write('   turn something on     (ex. turn on the light)'),nl,
  100.   write('   inventory your things (ex. inventory)'),nl,
  101.   nl,
  102.   write('The examples are verbose, terser commands and synonyms'),nl,
  103.   write('are usually accepted.'),nl,nl,
  104.   write('Hit any key to continue.'),nl,
  105.   get0(_),
  106.   look.
  107.  
  108. hint:-
  109.   write('You need to get to the cellar, and you can''t unless'),nl,
  110.   write('you get some light.  You can''t turn on the cellar'),nl,
  111.   write('light, but there is a flash light in the desk in the'),nl,
  112.   write('office you might use.'),nl,nl,
  113.   look.
  114.  
  115. % Initial facts describing the world.  Rooms and doors do not change,
  116. % so they are compiled.
  117.  
  118. room(office).
  119. room(kitchen).
  120. room('dining room').
  121. room(hall).
  122. room(cellar).
  123.  
  124. door(office,hall).
  125. door(hall,'dining room').
  126. door('dining room',kitchen).
  127. door(kitchen,cellar).
  128. door(kitchen,office).
  129.  
  130. connect(X,Y):-
  131.   door(X,Y).
  132. connect(X,Y):-
  133.   door(Y,X).
  134.  
  135. % These facts are all subject to change during the game, so rather
  136. % than being compiled, they are "asserted" to the listener at
  137. % run time.  This predicate is called when "nanisrch" starts up.
  138.  
  139. init_dynamic_facts:-
  140.   assertz(location(desk,office)),
  141.   assertz(location(apple,kitchen)),
  142.   assertz(location(flashlight,desk)),
  143.   assertz(location('washing machine',cellar)),
  144.   assertz(location(nani,'washing machine')),
  145.   assertz(location(table,kitchen)),
  146.   assertz(location(crackers,desk)),
  147.   assertz(location(broccoli,kitchen)),
  148.   assertz(here(kitchen)),
  149.   assertz(turned_off(flashlight)).
  150.  
  151. furniture(desk).
  152. furniture('washing machine').
  153. furniture(table).
  154.  
  155. edible(apple).
  156. edible(crackers).
  157.  
  158. tastes_yuchy(broccoli).
  159.  
  160. %%%%%%%% COMMANDS %%%%%%%%%%%%%%%%%%%%%%%%%%
  161.  
  162. % goto moves the player from room to room.
  163.  
  164. goto(Room):-
  165.   can_go(Room),                 % check for legal move
  166.   puzzle(goto(Room)),           % check for special conditions
  167.   moveto(Room),                 % go there and tell the player
  168.   look.
  169. goto(_):- look.
  170.  
  171. can_go(Room):-                  % if there is a connection it
  172.   here(Here),                   % is a legal move.
  173.   connect(Here,Room),!.
  174. can_go(Room):-
  175.   respond(['You can''t get to ',Room,' from here']),fail.
  176.  
  177. moveto(Room):-                  % update the logicbase with the
  178.   retract(here(_)),             % new room
  179.   asserta(here(Room)).
  180.  
  181. % look lists the things in a room, and the connections
  182.  
  183. look:-
  184.   here(Here),
  185.   respond(['You are in the ',Here]),
  186.   write('You can see the following things:'),nl,
  187.   list_things(Here),
  188.   write('You can go to the following rooms:'),nl,
  189.   list_connections(Here).
  190.  
  191. list_things(Place):-
  192.   location(X,Place),
  193.   tab(2),write(X),nl,
  194.   fail.
  195. list_things(_).
  196.  
  197. list_connections(Place):-
  198.   connect(Place,X),
  199.   tab(2),write(X),nl,
  200.   fail.
  201. list_connections(_).
  202.  
  203. % look_in allows the player to look inside a thing which might
  204. % contain other things
  205.  
  206. look_in(Thing):-
  207.   location(_,Thing),               % make sure there's at least one
  208.   write('The '),write(Thing),write(' contains:'),nl,
  209.   list_things(Thing).
  210. look_in(Thing):-
  211.   respond(['There is nothing in the ',Thing]).
  212.  
  213. % take allows the player to take something.  As long as the thing is
  214. % contained in the room it can be taken, even if the adventurer hasn't
  215. % looked in the the container which contains it.  Also the thing
  216. % must not be furniture.
  217.  
  218. take(Thing):-
  219.   is_here(Thing),
  220.   is_takable(Thing),
  221.   move(Thing,have),
  222.   respond(['You now have the ',Thing]).
  223.  
  224. is_here(Thing):-
  225.   here(Here),
  226.   contains(Thing,Here),!.          % don't backtrack
  227. is_here(Thing):-
  228.   respond(['There is no ',Thing,' here']),
  229.   fail.
  230.  
  231. contains(Thing,Here):-             % recursive definition to find
  232.   location(Thing,Here).            % things contained in things etc.
  233. contains(Thing,Here):-
  234.   location(Thing,X),
  235.   contains(X,Here).
  236.  
  237. is_takable(Thing):-                % you can't take the furniture
  238.   furniture(Thing),
  239.   respond(['You can''t pick up a ',Thing]),
  240.   !,fail.
  241. is_takable(_).                     % not furniture, ok to take
  242.  
  243. move(Thing,have):-
  244.   retract(location(Thing,_)),      % take it from its old place
  245.   asserta(have(Thing)).            % and add to your possessions
  246.  
  247. % drop - allows the player to transfer a possession to a room
  248.  
  249. drop(Thing):-
  250.   have(Thing),                     % you must have the thing to drop it
  251.   here(Here),                      % where are we
  252.   retract(have(Thing)),
  253.   asserta(location(Thing,Here)).
  254. drop(Thing):-
  255.   respond(['You don''t have the ',Thing]).
  256.  
  257.  
  258. % eat, because every adventure game lets you eat stuff.
  259.  
  260. eat(Thing):-
  261.   have(Thing),
  262.   eat2(Thing).
  263. eat(Thing):-
  264.   respond(['You don''t have the ',Thing]).
  265.  
  266. eat2(Thing):-
  267.   edible(Thing),
  268.   retract(have(Thing)),
  269.   respond(['That ',Thing,' was good']).
  270. eat2(Thing):-
  271.   tastes_yuchy(Thing),
  272.   respond(['Three year olds don''t eat ',Thing]).
  273. eat2(Thing):-
  274.   respond(['You can''t eat a ',Thing]).
  275.  
  276. % inventory list your possesions
  277.  
  278. inventory:-
  279.   have(X),                         % make sure you have at least one thing
  280.   write('You have: '),nl,
  281.   list_possessions.
  282. inventory:-
  283.   write('You have nothing'),nl.
  284.  
  285. list_possessions:-
  286.   have(X),
  287.   tab(2),write(X),nl,
  288.   fail.
  289. list_possessions.
  290.  
  291. % turn_on recognizes two cases.  If the player tries to simply turn
  292. % on the light, it is assumed this is the room light, and the
  293. % appropriate error message is issued.  Otherwise turn_on has to
  294. % refer to an object which is turned_off.
  295.  
  296. turn_on(light):-
  297.   respond(['You can''t reach the switch and there''s nothing to stand on']).
  298. turn_on(Thing):-
  299.   have(Thing),
  300.   turn_on2(Thing).
  301. turn_on(Thing):-
  302.   respond(['You don''t have the ',Thing]).
  303.  
  304. turn_on2(Thing):-
  305.   turned_on(Thing),
  306.   respond([Thing,' is already on']).
  307. turn_on2(Thing):-
  308.   turned_off(Thing),
  309.   retract(turned_off(Thing)),
  310.   asserta(turned_on(Thing)),
  311.   respond([Thing,' turned on']).
  312. turn_on2(Thing):-
  313.   respond(['You can''t turn a ',Thing,' on']).
  314.  
  315. % turn_off - I didn't feel like implementing turn_off
  316.  
  317. turn_off(Thing):-
  318.   respond(['I lied about being able to turn things off']).
  319.  
  320. % The only special puzzle in Nani Search has to do with going to the
  321. % cellar.  Puzzle is only called from goto for this reason.  Other
  322. % puzzles pertaining to other commands could easily be added.
  323.  
  324. puzzle(goto(cellar)):-
  325.   have(flashlight),
  326.   turned_on(flashlight),!.
  327. puzzle(goto(cellar)):-
  328.   write('You can''t go to the cellar because it''s dark in the'),nl,
  329.   write('cellar, and you''re afraid of the dark.'),nl,
  330.   !,fail.
  331. puzzle(_).
  332.  
  333. % respond simplifies writing a mixture of literals and variables
  334.  
  335. respond([]):-
  336.   write('.'),nl,nl.
  337. respond([H|T]):-
  338.   write(H),
  339.   respond(T).
  340.  
  341. % Simple English command listener.  It does some semantic checking
  342. % and allows for various synonyms.  Within a restricted subset of
  343. % English, a command can be phrased many ways.  Also non grammatical
  344. % constructs are understood, for example just giving a room name
  345. % is interpreted as the command to goto that room.
  346.  
  347. % Some interpretation is based on the situation.  Notice that when
  348. % the player says turn on the light it is ambiguous.  It could mean
  349. % the room light (which can't be turned on in the game) or the
  350. % flash light.  If the player has the flash light it is interpreted
  351. % as flash light, otherwise it is interpreted as room light.
  352.  
  353. get_command(C):-
  354.   readlist(L),        % reads a sentence and puts [it,in,list,form]
  355.   command(X,L,[]),    % call the grammar for command
  356.   C =.. X,!.          % make the command list a structure
  357. get_command(_):-
  358.   respond(['I don''t understand, try again or type help']),fail.
  359.  
  360. % The grammar doesn't have to be real English.  There are two
  361. % types of commands in Nani Search, those with and without a
  362. % single argument.  A special case is also made for the command
  363. % goto which can be activated by simply giving a room name.
  364.  
  365. command([Pred,Arg]) --> verb(Type,Pred),nounphrase(Type,Arg).
  366. command([Pred]) --> verb(intran,Pred).
  367. command([goto,Arg]) --> noun(go_place,Arg).
  368.  
  369. % Recognize three types of verbs.  Each verb corresponds to a command,
  370. % but there are many synonyms allowed.  For example the command
  371. % turn_on will be triggered by either "turn on" or "switch on".
  372.  
  373. verb(go_place,goto) --> go_verb.
  374. verb(thing,V) --> tran_verb(V).
  375. verb(intran,V) --> intran_verb(V).
  376.  
  377. go_verb --> [go].
  378. go_verb --> [go,to].
  379. go_verb --> [g].
  380.  
  381. tran_verb(take) --> [take].
  382. tran_verb(take) --> [pick,up].
  383. tran_verb(drop) --> [drop].
  384. tran_verb(drop) --> [put].
  385. tran_verb(drop) --> [put,down].
  386. tran_verb(eat) --> [eat].
  387. tran_verb(turn_on) --> [turn,on].
  388. tran_verb(turn_on) --> [switch,on].
  389. tran_verb(turn_off) --> [turn,off].
  390. tran_verb(look_in) --> [look,in].
  391. tran_verb(look_in) --> [look].
  392. tran_verb(look_in) --> [open].
  393.  
  394. intran_verb(inventory) --> [inventory].
  395. intran_verb(inventory) --> [i].
  396. intran_verb(look) --> [look].
  397. intran_verb(look) --> [look,around].
  398. intran_verb(look) --> [l].
  399. intran_verb(quit) --> [quit].
  400. intran_verb(quit) --> [exit].
  401. intran_verb(quit) --> [end].
  402. intran_verb(quit) --> [bye].
  403. intran_verb(nshelp) --> [help].
  404. intran_verb(hint) --> [hint].
  405.  
  406. % a noun phrase is just a noun with an optional determiner in front.
  407.  
  408. nounphrase(Type,Noun) --> det,noun(Type,Noun).
  409. nounphrase(Type,Noun) --> noun(Type,Noun).
  410.  
  411. det --> [the].
  412. det --> [a].
  413.  
  414. % Nouns are defined as rooms, or things located somewhere.  We define
  415. % special cases for those things represented in Nani Search by two
  416. % words.  We can't expect the user to type the name in quotes.
  417.  
  418. noun(go_place,R) --> [R], {room(R)}.
  419. noun(go_place,'dining room') --> [dining,room].
  420.  
  421. noun(thing,T) --> [T], {location(T,_)}.
  422. noun(thing,T) --> [T], {have(T)}.
  423. noun(thing,flashlight) --> [flash,light].
  424. noun(thing,'washing machine') --> [washing,machine].
  425. noun(thing,'dirty clothes') --> [dirty,clothes].
  426.  
  427. % If the player has just typed light, it can be interpreted three ways.
  428. % If a room name is before it, it must be a room light.  If the
  429. % player has the flash light, assume it means the flash light.  Otherwise
  430. % assume it is the room light.
  431.  
  432. noun(thing,light) --> [X,light], {room(X)}.
  433. noun(thing,flashlight) --> [light], {have(flashlight)}.
  434. noun(thing,light) --> [light].
  435.  
  436. % readlist - read a list of words, based on a Clocksin & Mellish
  437. % example.
  438.  
  439. readlist(L):-
  440.   write('> '),
  441.   read_word_list(L).
  442.  
  443. read_word_list([W|Ws]) :-
  444.   get0(C),
  445.   readword(C, W, C1),       % Read word starting with C, C1 is first new
  446.   restsent(C1, Ws), !.      % character - use it to get rest of sentence
  447.  
  448. restsent(C,[]) :- lastword(C), !. % Nothing left if hit last-word marker
  449. restsent(C,[W1|Ws]) :-
  450.   readword(C,W1,C1),        % Else read next word and rest of sentence
  451.   restsent(C1,Ws).
  452.  
  453. readword(C,W,C1) :-         % Some words are single characters
  454.   single_char(C),           % i.e. punctuation
  455.   !,
  456.   name(W, [C]),             % get as an atom
  457.   get0(C1).
  458. readword(C, W, C1) :-
  459.   is_num(C),                % if we have a number --
  460.   !,
  461.   number_word(C, W, C1, _). % convert it to a genuine number
  462. readword(C,W,C2) :-         % otherwise if character does not
  463.   in_word(C, NewC),         % delineate end of word - keep
  464.   get0(C1),                 % accumulating them until
  465.   restword(C1,Cs,C2),       % we have all the word    
  466.   name(W, [NewC|Cs]).       % then make it an atom
  467. readword(C,W,C2) :-         % otherwise
  468.   get0(C1),      
  469.   readword(C1,W,C2).        % start a new word
  470.  
  471. restword(C, [NewC|Cs], C2) :-
  472.   in_word(C, NewC),
  473.   get0(C1),
  474.   restword(C1, Cs, C2).
  475. restword(C, [], C).
  476.  
  477.  
  478. single_char(0',).
  479. single_char(0';).
  480. single_char(0':).
  481. single_char(0'?).
  482. single_char(0'!).
  483. single_char(0'.).
  484.  
  485.  
  486. in_word(C, C) :- C >= 0'a, C =< 0'z.
  487. in_word(C, L) :- C >= 0'A, C =< 0'Z, L is C + 32.
  488. in_word(0'',0'').
  489. in_word(0'-,0'-).
  490.  
  491. % Have character C (known integer) - keep reading integers and build
  492. % up the number until we hit a non-integer. Return this in C1,
  493. % and return the computed number in W.
  494.  
  495. number_word(C, W, C1, Pow10) :-
  496.   is_num(C),
  497.   !,
  498.   get0(C2),
  499.   number_word(C2, W1, C1, P10),
  500.   Pow10 is P10 * 10,
  501.   W is integer(((C - 0'0) * Pow10) + W1).
  502. number_word(C, 0, C, 0.1).
  503.  
  504.  
  505. is_num(C) :-
  506.  C =< 0'9,
  507.   C >= 0'0.
  508.  
  509. % These symbols delineate end of sentence
  510.  
  511. lastword(10).   % end if new line entered
  512. lastword(0'.).
  513. lastword(0'!).
  514. lastword(0'?).
Advertisement
Add Comment
Please, Sign In to add comment
Advertisement