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