Tek-Tips is the largest IT community on the Internet today!

Members share and learn making Tek-Tips Forums the best source of peer-reviewed technical information on the Internet!

  • Congratulations TouchToneTommy on being selected by the Tek-Tips community for having the most helpful posts in the forums last week. Way to Go!

Prolog DCG

Status
Not open for further replies.

Darkstar3000

Programmer
Apr 24, 2012
3
GB
Hello, I have been following this tutorial ( in an attempt to create my own version of "nani search" the only problem I have now is the last chapter which deals with Definite clause grammar, every single time I try to use DCG in my program while in the command_loop, e.g take the apple. I get error messages like : "ERROR: Stream user_input:7:436 Syntax error: Operator expected" or "ERROR: Stream user_input:7:424 Syntax error: Operator expected" I'm using SWI-prolog to write this program. I have a predicate get_command which also points to command/2 but after following the tutorial command/2 no longer exists and I tried modifying command(CL,L) to command(CL,L,[]) but I still get errors. Here is my source code.

Code:
:-dynamic (location/2),(here/1),(have/1),(turned_off/1),(turned_on/1).

%%%%%%%%%%%%%%%%%%%%%%%%%RULES AND FACTS%%%%%%%%%%%%%%%%%%%%%%%%%


%%Fact defining the Rooms
room(kitchen).
room(office).
room(hall).
room('dining room').
room(cellar).

location(object(desk,big), office).
location(object(apple,small), kitchen).
location(object(flashlight,small), desk).
location(object('washing machine',big), cellar).
location(object(nani,small), 'washing machine').
location(object(broccoli,small), kitchen).
location(object(crackers,small), kitchen).
location(object(computer,big), office).


door(office,hall).
door(kitchen,office).
door(hall,'dining room').
door(kitchen,cellar).
door('dining room',kitchen).

%%Fact for Items that are edible.
edible(apple).
edible(crackers).


tastes_yucky(broccoli).


turned_off(flashlight).


here(kitchen).


where_food(X,Y) :-
  location(object(X,small),Y),
  edible(X).


where_food(X,Y) :-
  location(object(X,small),Y),
  tastes_yucky(X).
  %%%where_food(_).


connect(X,Y) :- door(X,Y).
connect(X,Y) :- door(Y,X).



look_in(Area):- location(object(X,_),Area),is_contained_in(X,Area),write(X),nl,fail.
look_in(_).%%This will unify with anything and will always return true.


list_things(Place) :-
  location(object(X,_), Place),
  tab(2),
  write(X),nl,
  fail.

list_things(_).%%This clause will match with anything and it will return true

%%List connection between two places
list_connections(Place) :-
  connect(Place, X),
  tab(2),
  write(X),
  nl,
  fail.
list_connections(_).


look :-
  here(Place),
  write('You are in the '), write(Place), nl,
  write('You can see:'), nl,
  list_things(Place),
  write('You can go to:'), nl,
  list_connections(Place).


move(Place):- retract(here(X)),asserta(here(Place)).

%%Move the player to the desired location
goto(Place):-
  puzzle(goto(Place)),
  can_go(Place),
  move(Place),
  look.


can_go(Place):-
  here(X),
  connect(X, Place).



can_go(Place):- write('You can''t get to the '),write(Place),write(' from here.'), nl,fail.



can_take(X) :- here(Place),location(object(X,small),_),is_contained_in(X,Place).
can_take(X) :- here(Place),location(object(X,big),Place),write('The '),write(X),write(' is too big'),nl,fail.
can_take(X) :- here(Place),not(location(object(X,_),Place)),write('There is no '),write(X),write(' here'),nl,fail.


take_object(X):- retract(location(object(X,_),_)),asserta(have(X)),write('taken'), nl,!.

take(X):- can_take(X),take_object(X).



eat(X) :- have(X),edible(X),retract(have(X)),write('You have eaten the '),write(X),!.
eat(X) :- have(X),tastes_yucky(X),retract(have(X)),write('Ehhhh, tastes yucky'),!.

eat(X) :- not(edible(X)),write('You cannot eat that'),nl,!.
eat(X) :- not(have(X)),write('You do not have the '),write(X),write(' to eat'),nl,fail.


drop(X) :- here(Place),retract(have(X)),asserta(location(object(X,_,_,_),Place)),write('Dropped').

items_I_have :- have(X),tab(2),write(X),nl,fail.
items_I_have.


inventory  :- have(X),write('You have'),nl,items_I_have.
inventory  :- not(have(_)), write('There is nothing here'),nl.

%%Check for items hiden within other items.
is_contained_in(T1,T2) :- location(object(T1,_),T2).
is_contained_in(T1,T2) :- location(object(X,_),T2),is_contained_in(T1,X).


turn_on(flashlight) :- have(flashlight),retract(turned_off(flashlight)),asserta(turned_on(flashlight)),write('Flashlight is on').

turn_on(flashlight) :- not(have(flashlight)),write('You do not have a flashlight'),nl,fail.

turn_off(flashlight) :- have(flashlight),retract(turned_on(flashlight)),asserta(turned_off(flashlight)),write('Flashlight is off').


puzzle(goto(cellar)):- have(flashlight),turned_on(flashlight),!.

	puzzle(goto(cellar)):-
	write('It\'s too dark, you can\'t go in there'),nl,!, fail.
	puzzle(_).

command_loop:-
  write('Welcome to Nani Search'), nl,
  repeat,
  write('>nani> '),
  read(X),get_command(X),
  do(X), nl,
  end_condition(X).
  end_condition(end).
  end_condition(_) :-
  have(nani),
  write('Congratulations, you have found nani and now you can rest safe and easy').

  do(goto(X)):-goto(X),!.
  do(go(X)):-goto(X),!.
  do(inventory):-inventory,!.
  do(look):-look,!.
  do(look_in(X)) :- look_in(X),!.
  do(take(X)) :- take(X),!.
  do(drop(X)) :- drop(X),!.
  do(eat(X)) :- eat(X),!.
  do(turn_on(flashlight)) :- turn_on(flashlight),!.
  do(turn_off(flashlight)) :- turn_off(flashlight),!.
  do(items_I_have) :- items_I_have,!.
  do(end).
  do(_) :- write('Invalid Command'),!.

  get_command(C) :-
  read_list(L),
  command(CL,L),
  C =..  CL, !.
  get_command(_) :-
  write('I don''t understand'), nl, fail.


  command([V])--> verb(V).

  command([goto, Place]) --> noun(place, Place).

  command([V,O]) -->
  verb(Object_Type,V),
  object(Object_Type, O).


  verb(place, goto) --> [go,to].
  verb(place, goto) --> [go].
  verb(place, goto) --> [move,to].
  verb(place, goto) --> [X],{room(X)}.
  verb(place, goto) -->  [dining,room].

  verb(thing, take) --> [take].
  verb(thing, drop) --> [drop].
  verb(thing, drop) --> [put].
  verb(thing, turn_on) --> [turn,on].


  verb(look) --> [look].
  verb(look) --> [look,around].
  verb(inventroy) --> [bag].
  verb(inventory) --> [inventory].
  verb(end) --> [end].
  verb(end) --> [quit].
  verb(end) --> [good,bye].


  det --> [the].
  det --> [a].
  det --> [an].



  object(Type, N) -->
  det,
  noun(Type, N).

  object(Type, N) -->
  noun(Type, N).


  noun(place, R) --> [R],{room(R)}.
  noun(place, 'dining room') --> [dining,room].


  noun(thing, T) --> [T],{location(object(T,_),_)}.
  noun(thing, T) --> [T],{have(T)}.
  noun(thing, 'washing machine') --> [washing,machine].
  noun(thing, flashlight) --> [light], {have(flashlight)}.


   %read a line of words from the user

   read_list(L) :-
   write('> '),
   read_line(CL),
   wordlist(L,CL,[]), !.

   read_line(L) :-
   get0(C),
   buildlist(C,L).

   buildlist(13,[]) :- !.
   buildlist(C,[C|X]) :-
   get0(C2),
   buildlist(C2,X).

   wordlist([X|Y]) --> word(X), whitespace, wordlist(Y).
   wordlist([X]) --> whitespace, wordlist(X).
   wordlist([X]) --> word(X).
   wordlist([X]) --> word(X), whitespace.

   word(W) --> charlist(X), {name(W,X)}.

   charlist([X|Y]) --> chr(X), charlist(Y).
   charlist([X]) --> chr(X).

   chr(X) --> [X],{X>=48}.

   whitespace --> whsp, whitespace.
   whitespace --> whsp.

   whsp --> [X], {X<48}.
 
If you use SWI-Prolog, use read_line_to_codes instead of read in command_loop.
read reads a Prolog term and you type (I think) a line like "go to dining room" which is not a Prolog term.
 
Status
Not open for further replies.

Part and Inventory Search

Sponsor

Back
Top