This is done by describing the makeup of the language in terms of abstract components, and then in turn describing the makeup of each component.
Ultimately we define the bottom level of abstract components in terms of the concrete items which can actually appear as part of the language.
For instance, suppose we are trying to represent what constitutes a valid sentence in our language.
We identify what a sentence is composed of, e.g. we decide a sentence has two parts, a noun phrase and a verb phrase.
Our notation in a DCG is as follows:
sentence --> nounphrase, verbphrase.
Now, of course, we must decide what the phrases are made up of, e.g.:
% possible sentence structures sentence --> nounphrase, verbphrase. % possible noun phrase structures nounphrase --> qualifiednoun. nounphrase --> article, qualifiednoun. % possible verb phrase structures verbphrase --> verb, adverb. verbphrase --> adverb, verb.We still need to identify the actual words in our vocabulary, and what kind of sentence component they are, e.g.:
% list the valid nouns noun --> [ plane ]. noun --> [ bird ]. % list the valid verbs verb --> [ flew ]. verb --> [ landed ]. % list the valid adjectives adjective --> [ red ]. adjective --> [ big ]. % list the valid adverbs adverb --> [ safely ]. adverb --> [ quickly ]. % list the valid articles article --> [ the ]. article --> [ a ].If we fire up the prolog engine and load the rules above, we can issue queries to ask if something is a valid sentence (or valid verb phrase, or adjective, etc).
The basic query format uses phrase, which expects us to provide the kind of phrase we're expecting (sentence), the list of atoms second, and to provide an option list last. In the queries below we'll just use the default options, so the last list will always be empty.
% ask if "The bird flew" is a valid sentence phrase(sentence, [the, bird, flew], []). % ask if "The big bird flew quickly" is a valid sentence % (again it should say yes) phrase(sentence, [the, big, bird, flew, quickly], []). % ask if "The big red bird flew quickly" is a valid sentence % (should say no, since our rules above don't account % for multiple adjectives in the noun phrase) phrase(sentence, [the, big, red, bird, flew, quickly], []).We can also use combinations of words as components, e.g.
If we want to use regular prolog queries to evaluate the properties of parts of the statement we can do that too, e.g. allowing phrases like "The bird flew 5 times", using the prolog number() to test that 5 is actually a number.
% doing an action "N times" is a valid adverb adverb --> [N, times], { number(N) }.Note that the 'regular prolog query' part is enclosed in parenthesis.
We can also allow the query process to analyze the sentence in question and tell us things about it. For example, suppose we wanted the sentence analyzed, and to tell us whether the verb used was past, present, or future tense, and whether the noun in question was a living creature or inanimate thing.
For the query, we use an uninstantiated variable as the first argument,
and the query will be responsible for filling that in for us, e.g.
phrase(sentence(Info), [the, bird, flew], []).
We can add parameters to our sentence and other components and have the query resolution process fill in the blanks for us.
In the sample below, Info will be filled in with a list of two elements, the first will specify whether the noun was living or inanimate, the second will specify whether the verb is past or future tense.
% nouns will be categorized as living or inanimate noun(inanimate) --> [plane]. noun(inanimate) --> [rock]. noun(living) --> [bird]. noun(living) --> [frog]. % valid verbs verb(past) --> [flew]. verb(future) --> [will, fly]. % valid articles article --> [the]. article --> [a]. % valid adverbs adverb --> [safely]. adverb --> [quickly]. adverb --> [N, times], { number(N) }. % valid adjectives adjective --> [red]. adjective --> [big]. % valid verb phrases, Info will be instantiated with the verb tense verbphrase(Info) --> verb(Info). verbphrase(Info) --> verb(Info), adverb. verbphrase(Info) --> adverb, verb(Info). % valid nouns and noun phrases, Info will be instantiated with living or inanimate qualifiednoun(Info) --> noun(Info). qualifiednoun(Info) --> adjective, noun(Info). nounphrase(Info) --> qualifiednoun(Info). nounphrase(Info) --> article, qualifiednoun(Info). % a sentences is formed by a noun phrase followed by a verb phrase sentence([NounInfo, VerbInfo]) --> nounphrase(NounInfo), verbphrase(VerbInfo).
Reading the list of words
Of course, we have to be able to read the user input and turn in into a valid list of words and symbols, based on what is valid for the language we are working with. The code snippet below illustrates how this can be achieved.
Examples
The ability to describe a language in this way, whether natural language, programming language, or ???, and have the prolog engine automatically analyze input is tremendously helpful (and not unlike the process followed by compilers in analyzing source code and translating it into machine code).
We'll return to discussing this when we look at the semantics of languages later in the semester, but here are a few short examples along the lines of our in-class discussions. Version 1 is the most basic, version 2 adds handling of if statements, version 3 produces a list of the types of statements found in the program, and version 4 checks to make sure variables are initialized before being used.
% intended to recognize a simple language handling basic floating point % input, output, and computation % a program consists of a single large block of the form % begin % ... one or more statements ... % end program --> block. block --> [begin], statements, [end]. statements --> statement, statements. statements --> statement. % a statement can be either a read, write, assignment, or if statement statement --> assignstmt. statement --> readstmt. statement --> writestmt. % an assignment statement has a variable, followed by the assignment % operator, followed by an arithmetic expression % e.g. f1 assign f2 % e.g. f3 assign f2 times f3 assignstmt --> variable, [assign], arithexpr. % an arithmetic expression can be either a single variable or the sum, % difference, product, or division of a variable and an expression, % e.g. f1 plus f2 % e.g. f1 minus f3 plus f2 arithexpr --> variable. arithexpr --> variable, mathop, variable. % a read statement is simply the keyword read followed by a variable, % e.g. read f1 readstmt --> [read], variable. % a write statement is simply the keyword write followed by a variable, % e.g. write f1 writestmt --> [write], variable. % the supported math operators are plus, minus, times, div mathop --> [plus]; [minus]; [times]; [div]. % the supported floating point variables are f1, f2, ..., f5 variable --> [f1]; [f2]; [f3]; [f4]; [f5]. % ============================================================== % sample queries q1 :- phrase(program, [begin, read, f1, end], []). q2 :- phrase(program, [begin, read, f1, write, f1, end], []). q3 :- phrase(program, [begin, read, f1, f2, assign, f1, write, f2, end], []). |
% intended to recognize a simple language handling basic floating point % input, output, and computation % a program consists of a single large block of the form % begin % ... one or more statements ... % end program(Info) --> block(Info). block(Info) --> [begin], statements(Info), [end]. statements([H|T]) --> statement(H), statements(T). statements([H]) --> statement(H). % a statement can be either a read, write, assignment, or if statement statement(assign) --> assignstmt. statement(read) --> readstmt. statement(write) --> writestmt. statement([if, Info]) --> ifstmt(Info). % an if statement begins with the keyword if, % followed by a boolean expression, % followed by the code block to execute if the expression is true % e.g. if f1 equals f2 % begin % write f1 % end ifstmt(Info) --> [if], boolexpr, block(Info). % a boolean expression can be either a simple comparison, % e.g. f1 lessthan f2 % or an expression built of comparisons and boolean operators, % e.g. not f1 lessthan f2 or f1 greaterthan f3 boolexpr --> compexpr, [and], boolexpr. boolexpr --> compexpr, [or], boolexpr. boolexpr --> [not], boolexpr. boolexpr --> compexpr. % a comparison expression uses less than, equals, or greater than % to compare two variables, % e.g. f1 lessthan f2 compexpr --> variable, compop, variable. % an assignment statement has a variable, followed by the assignment % operator, followed by an arithmetic expression % e.g. f1 assign f2 % e.g. f3 assign f2 times f3 assignstmt --> variable, [assign], arithexpr. % an arithmetic expression can be either a single variable or the sum, % difference, product, or division of a variable and an expression, % e.g. f1 plus f2 % e.g. f1 minus f3 plus f2 arithexpr --> variable. arithexpr --> variable, mathop, arithexpr. % a read statement is simply the keyword read followed by a variable, % e.g. read f1 readstmt --> [read], variable. % a write statement is simply the keyword write followed by a variable, % e.g. write f1 writestmt --> [write], variable. % the supported math operators are plus, minus, times, div mathop --> [plus]; [minus]; [times]; [div]. % the supported comparison operators are less than, equals, and greater than, % e.g. f1 lessthan f2 compop --> [lessthan]; [equals]; [greaterthan]. % the supported boolean operators are and, or, and not, % e.g. not f1 equals f2 % e.g. f1 lessthan f2 and f2 lessthan f3 boolop --> [and]; [or]; [not]. % the supported floating point variables are f1, f2, ..., f5 variable --> [f1]; [f2]; [f3]; [f4]; [f5]. % ============================================================== % sample queries writeProg(Info) :- write('program statements: '), write(Info), nl. q1 :- phrase(program(Info), [begin, read, f1, end], []), writeProg(Info). q2 :- phrase(program(Info), [begin, read, f1, write, f1, end], []), writeProg(Info). q3 :- phrase(program(Info), [begin, read, f1, f2, assign, f1, write, f2, end], []), writeProg(Info). q4 :- phrase(program(Info), [begin, read, f1, f2, assign, f1, f3, assign, f1, plus, f2, f4, assign, f1, plus, f2, times, f3, write, f2, end], []), writeProg(Info). q5 :- phrase(program(Info), [begin, read, f1, f2, assign, f1, f3, assign, f1, plus, f2, f4, assign, f1, plus, f2, times, f3, if, f3, lessthan, f2, begin, f5, assign, f3, end, if, f3, greaterthan, f2, or, f3, equals, f2, begin, f5, assign, f2, end, write, f2, end], []), writeProg(Info). |
% intended to recognize a simple language handling basic floating point % input, output, and computation % a program consists of a single large block of the form % begin % ... one or more statements ... % end program([VarsSet]) --> block([[], VarsSet]). block(VarInfo) --> [begin], statements(VarInfo), [end]. statements([VarsBefore, VarsAfter]) --> statement([VarsBefore, VarsInter]), statements([VarsInter, VarsAfter]). statements(VarInfo) --> statement(VarInfo). % a statement can be either a read, write, assignment, or if statement statement(VarInfo) --> assignstmt(VarInfo). statement(VarInfo) --> readstmt(VarInfo). statement([VarsSet, VarsSet]) --> writestmt. statement(VarInfo) --> ifstmt(VarInfo). % an if statement begins with the keyword if, % followed by a boolean expression, % followed by the code block to execute if the expression is true % e.g. if f1 equals f2 % begin % write f1 % end ifstmt(VarInfo) --> [if], boolexpr, block(VarInfo). % a boolean expression can be either a simple comparison, % e.g. f1 lessthan f2 % or an expression built of comparisons and boolean operators, % e.g. not f1 lessthan f2 or f1 greaterthan f3 boolexpr --> compexpr, [and], boolexpr. boolexpr --> compexpr, [or], boolexpr. boolexpr --> [not], boolexpr. boolexpr --> compexpr. % a comparison expression uses less than, equals, or greater than % to compare two variables, % e.g. f1 lessthan f2 compexpr --> variable(_), compop, variable(_). % an assignment statement has a variable, followed by the assignment % operator, followed by an arithmetic expression % e.g. f1 assign f2 % e.g. f3 assign f2 times f3 assignstmt([VarsSet, VarsSet]) --> variable(V), [assign], arithexpr, { member(V, VarsSet) }. assignstmt([VarsSet, [V | VarsSet]]) --> variable(V), [assign], arithexpr. % an arithmetic expression can be either a single variable or the sum, % difference, product, or division of a variable and an expression, % e.g. f1 plus f2 % e.g. f1 minus f3 plus f2 arithexpr --> variable(_). arithexpr --> variable(_), mathop, arithexpr. % a read statement is simply the keyword read followed by a variable, % e.g. read f1 readstmt([VarsSet, VarsSet]) --> [read], variable(V), { member(V, VarsSet) }. readstmt([VarsSet, [V | VarsSet]]) --> [read], variable(V). % a write statement is simply the keyword write followed by a variable, % e.g. write f1 writestmt --> [write], variable(_). % the supported math operators are plus, minus, times, div mathop --> [plus]; [minus]; [times]; [div]. % the supported comparison operators are less than, equals, and greater than, % e.g. f1 lessthan f2 compop --> [lessthan]; [equals]; [greaterthan]. % the supported boolean operators are and, or, and not, % e.g. not f1 equals f2 % e.g. f1 lessthan f2 and f2 lessthan f3 boolop --> [and]; [or]; [not]. % the supported floating point variables are f1, f2, ..., f5 variable(f1) --> [f1]. variable(f2) --> [f2]. variable(f3) --> [f3]. variable(f4) --> [f4]. variable(f5) --> [f5]. % ============================================================== % sample queries writeProg(Vars) :- write('variables set: '), write(Vars), nl. q1 :- phrase(program(Info), [begin, read, f1, end], []), writeProg(Info). q2 :- phrase(program(Info), [begin, read, f1, write, f1, end], []), writeProg(Info). q3 :- phrase(program(Info), [begin, read, f1, f2, assign, f1, write, f2, end], []), writeProg(Info). q4 :- phrase(program(Info), [begin, read, f1, f2, assign, f1, f3, assign, f1, plus, f2, f4, assign, f1, plus, f2, times, f3, write, f2, end], []), writeProg(Info). q5 :- phrase(program(Info), [begin, read, f1, f2, assign, f1, f3, assign, f1, plus, f2, f4, assign, f1, plus, f2, times, f3, if, f3, lessthan, f2, begin, f5, assign, f3, end, if, f3, greaterthan, f2, or, f3, equals, f2, begin, f5, assign, f2, end, write, f2, end], []), writeProg(Info). q6 :- phrase(program(Info), [begin, read, f1, f2, assign, f1, f3, assign, f1, plus, f2, f4, assign, f1, plus, f2, times, f3, if, f3, lessthan, f2, begin, f5, assign, f3, end, if, f3, greaterthan, f2, or, f3, equals, f2, begin, f5, assign, f2, end, write, f2, read, f1, f2, assign, f1, write, f1, end], []), writeProg(Info). |
% intended to recognize a simple language handling basic floating point % input, output, and computation % a program consists of a single large block of the form % begin % ... one or more statements ... % end program([VarsSet]) --> block([[], VarsSet]). block(VarInfo) --> [begin], statements(VarInfo), [end]. statements(VarInfo) --> statement(VarInfo). statements([VarsBefore, VarsAfter]) --> statement([VarsBefore, VarsInter]), statements([VarsInter, VarsAfter]). % a statement can be either a read, write, assignment, or if statement statement(VarInfo) --> assignstmt(VarInfo). statement(VarInfo) --> readstmt(VarInfo). statement([VarsSet, VarsSet]) --> writestmt(VarsSet). statement(VarInfo) --> ifstmt(VarInfo). % an if statement begins with the keyword if, % followed by a boolean expression, % followed by the code block to execute if the expression is true % e.g. if f1 equals f2 % begin % write f1 % end ifstmt([VarsSet, VarsAfter]) --> [if], boolexpr(VarsSet), block([VarsSet, VarsAfter]). % a boolean expression can be either a simple comparison, % e.g. f1 lessthan f2 % or an expression built of comparisons and boolean operators, % e.g. not f1 lessthan f2 or f1 greaterthan f3 boolexpr(VarsSet) --> compexpr(VarsSet), [and], boolexpr(VarsSet). boolexpr(VarsSet) --> compexpr(VarsSet), [or], boolexpr(VarsSet). boolexpr(VarsSet) --> [not], boolexpr(VarsSet). boolexpr(VarsSet) --> compexpr(VarsSet). % a comparison expression uses less than, equals, or greater than % to compare two variables, % e.g. f1 lessthan f2 compexpr(VarsSet) --> variable(V1), { member(V1, VarsSet) }, compop, variable(V2), { member(V2, VarsSet) }. % an assignment statement has a variable, followed by the assignment % operator, followed by an arithmetic expression % e.g. f1 assign f2 % e.g. f3 assign f2 times f3 assignstmt([VarsSet, VarsSet]) --> variable(V), [assign], arithexpr(VarsSet), { member(V, VarsSet) }. assignstmt([VarsSet, [V | VarsSet]]) --> variable(V), [assign], arithexpr(VarsSet). % an arithmetic expression can be either a single variable or the sum, % difference, product, or division of a variable and an expression, % e.g. f1 plus f2 % e.g. f1 minus f3 plus f2 arithexpr(VarsSet) --> variable(V), { member(V, VarsSet) }. arithexpr(VarsSet) --> variable(V), { member(V, VarsSet) }, mathop, arithexpr(VarsSet). % a read statement is simply the keyword read followed by a variable, % e.g. read f1 readstmt([VarsSet, VarsSet]) --> [read], variable(V), { member(V, VarsSet) }. readstmt([VarsSet, [V | VarsSet]]) --> [read], variable(V). % a write statement is simply the keyword write followed by a variable, % e.g. write f1 writestmt(VarsSet) --> [write], variable(V), { member(V, VarsSet) }. % the supported math operators are plus, minus, times, div mathop --> [plus]; [minus]; [times]; [div]. % the supported comparison operators are less than, equals, and greater than, % e.g. f1 lessthan f2 compop --> [lessthan]; [equals]; [greaterthan]. % the supported boolean operators are and, or, and not, % e.g. not f1 equals f2 % e.g. f1 lessthan f2 and f2 lessthan f3 boolop --> [and]; [or]; [not]. % the supported floating point variables are f1, f2, ..., f5 variable(f1) --> [f1]. variable(f2) --> [f2]. variable(f3) --> [f3]. variable(f4) --> [f4]. variable(f5) --> [f5]. % ============================================================== % sample queries writeProg([Info]) :- write('variables initialized were: '), write(Info), nl. q1 :- phrase(program(Info), [begin, read, f1, write, f1, end], []), writeProg(Info). q2 :- phrase(program(Info), [begin, read, f1, write, f2, end], []), writeProg(Info). q3 :- phrase(program(Info), [begin, read, f1, f2, assign, f1, write, f2, end], []), writeProg(Info). q4 :- phrase(program(Info), [begin, read, f1, f2, assign, f1, f3, assign, f3, plus, f4, f4, assign, f1, plus, f2, times, f3, write, f2, end], []), writeProg(Info). q5 :- phrase(program(Info), [begin, read, f1, f2, assign, f1, f3, assign, f1, plus, f2, f4, assign, f1, plus, f2, times, f3, if, f3, lessthan, f2, begin, f5, assign, f3, end, if, f3, greaterthan, f2, or, f3, equals, f2, begin, f5, assign, f2, end, write, f2, end], []), writeProg(Info). q6 :- phrase(program(Info), [begin, read, f1, f2, assign, f1, f3, assign, f1, plus, f2, f4, assign, f1, plus, f2, times, f3, if, f3, lessthan, f2, begin, f5, assign, f3, end, if, f3, greaterthan, f2, or, f3, equals, f2, begin, f5, assign, f2, end, write, f2, read, f1, f2, assign, f1, write, f1, end], []), writeProg(Info). |
Version 5: order of evaluation |
% ================================================================== % example of grammars that expand the right vs left non-terminal % evaluate applies rules to the leftmost non-terminal(s), % while wrongeval applies rules to the rightmost non-terminal(s) % running q1a and q1b on the same expression (which is technically % valid under the language) causes a stack overflow on wrongeval, % effectively the result of infinite recursion % % Sample queries q1a :- L = [3, '+', 4, '*', 6, '-', 1], evaluate(L, Answer), write(L), write('='), write(Answer), nl. q1b :- L = [3, '+', 4, '*', 6, '-', 1], wrongeval(L, Answer), write(L), write('='), write(Answer), nl. % ================================================================== numberval(N) --> [N], { number(N) }. operator(sum) --> ['+']. operator(div) --> ['/']. operator(mul) --> ['*']. operator(sub) --> ['-']. % ================================================================== evaluate(List, Answer) :- phrase(expression(Answer), List, []). expression(N) --> numberval(N). expression(Answer) --> numberval(N), operator(sum), expression(SubAnswer), { Answer is N + SubAnswer }. expression(Answer) --> numberval(N), operator(div), expression(SubAnswer), { Answer is N / SubAnswer }. expression(Answer) --> numberval(N), operator(mul), expression(SubAnswer), { Answer is N * SubAnswer }. expression(Answer) --> numberval(N), operator(sub), expression(SubAnswer), { Answer is N - SubAnswer }. % ================================================================== wrongeval(List, Answer) :- phrase(wrongexpr(Answer), List, []). wrongexpr(N) --> numberval(N). wrongexpr(Answer) --> wrongexpr(SubAnswer), operator(sum), numberval(N), { Answer is SubAnswer + N }. wrongexpr(Answer) --> wrongexpr(SubAnswer), operator(div), numberval(N), { Answer is SubAnswer / N }. wrongexpr(Answer) --> wrongexpr(SubAnswer), operator(mul), numberval(N), { Answer is SubAnswer * N }. wrongexpr(Answer) --> wrongexpr(SubAnswer), operator(sub), numberval(N), { Answer is SubAnswer - N }. |
One set of rules (the tokenizer/reader) is used to read in characters one at a time, identifying where words begin and end, seperating punctuation symbols, etc, and creating a list from the words.
A set of DCG grammar rules is used to try and construct meaningful sentences out of the list of words, and determine what actions need to be taken as a result.
The state of the game world is maintained/updated through the assertion and retraction of dynamic facts.
(Begin the game by loading the file and typing start.)
% %%%%%%%%%%%% USE INSTRUCTIONS %%%%%%%%%%%%%%%%%%%%%%%%%% % fire up prolog, use ['filename']. to load this file, % then type "start." to begin the game %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% % dynamic setup notes: % % we will want to change the set of facts during the game, % for instance if the player takes something from a % location we want to add a new fact saying the player % has the item, and remove the fact that says the thing % is at the location % % to enable such dynamic facts we specify the name of the % fact and the number of parameters it can take, % then we use asserta(...new fact...) to add new facts or % retract(...old fact...) to remove them % for instance, our dynamic facts may focus on what the player % possesses and which lights are currently turned on :- dynamic(have/1). :- dynamic(turned_on/1). % we will also have the "main routine" make a series of % assertions to establish the initial location of % items and the player %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% % main routine: % displays the opening messages and instructions, % gives the user a look around their starting location, % and starts the command/execution sequence start:- % make a series of initial assertions about item locations etc init_dynamic_facts, % give the player an intro to the game write('The search for better karma...'), nl, nl, write('You can try using simple English commands such as'),nl, write('take the whatever, look around, go to the kitchen, etc)'),nl, write('I''ll let you know if I cannot understand a command.'),nl, nl, write('Hit any key to begin.'),get0(_), write('Type ''quit'' to give up.'),nl, nl, % the majority of the game is controlled through the % command execution loop command_loop. %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% % command_loop - repeats until the game ends, % gets the next user command, executes it, % and checks to see if the game should end % (if the player won or quit) command_loop:- get_command(X), execute(X), check_for_quit(X). check_for_quit(quit). check_for_quit(_) :- victory. check_for_quit(_) :- command_loop. %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% % execute - matches the user's input command with the the predicate % which will actually carry out the command. % % The currently supported commands are to go to a location, % take something, drop something, eat something, % turn something on/off, look around, % list your current items, get help, get a hint, or quit % % Note: the cuts at the end of each do are there to prevent % the command_loop from backtracking after one command % has been successfully processed % % We have to identify the set of user actions we can support, % then create further facts/rules to interpret and support % those actions. execute(goto(X)):-goto(X),!. execute(take(X)):-take(X),!. execute(eat(X)):-eat(X),!. execute(look):-look,!. execute(turn_on(X)):-turn_on(X),!. execute(look_in(X)):-look_in(X),!. execute(quit):-quit,!. %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% % The player has won if they've found some karma victory:- have(karma), write('Congratulations, you gained karma.'),nl, write('Now you can rest secure.'),nl,nl. %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% % The game is over if the user decided to quit quit:- write('Giving up? It''s a scary world with bad karma!'),nl,nl. %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% %%%%%%%%%%%%%%%%%% GENERAL FACTS/RULES %%%%%%%%%%%%%%%%%%%%%% %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% % Initial facts describing the world. Rooms and doors do not change, % so their facts do not need to be established dynamically % available rooms room(office). room(kitchen). room(cellar). % doors between the rooms door(kitchen,cellar). door(kitchen,office). % rules to specify rooms are connected if there is % a door (in either direction) connect(Room1,Room2):- door(Room1,Room2). connect(Room1,Room2):- door(Room2,Room1). %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% % These facts are all subject to change during the game, % so we assert them at the start of the game init_dynamic_facts:- assertz(location(desk,office)), assertz(location(apple,kitchen)), assertz(location(flashlight,desk)), assertz(location('mini fridge',cellar)), assertz(location(karma,'mini fridge')), assertz(location(cabbage,kitchen)), assertz(here(kitchen)), assertz(turned_off(flashlight)). %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% % Items of furniture cannot be taken, but they can be % climbed on, looked in, etc (depending on the item) furniture(desk). furniture('mini fridge'). %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% % Well, folks are likely to stick things in their mouth, % so we better tell them when it's actually edible edible(apple). % Of course, some things are going to taste pretty gross... tastes_gross(cabbage). %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% %%%%%%%%%%%%%%%%%%%%%%%%% COMMANDS %%%%%%%%%%%%%%%%%%%%%%%%%% %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% % goto attempts to move the player from one room to another % % this involves checking if the move is legal, % updating any special conditions relating to victory, % adjusting the player's current location, % and giving them a look around the new room. goto(Room):- valid_move(Room), cellar_puzzle(goto(Room)), move_to(Room). goto(_). %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% % an attempt to move to a room is legal if there is a % connection from the player's current room to % the desired room % % (display an error message if they attempt an illegal move) valid_move(Room):- here(Here), connect(Here,Room),!. valid_move(Room):- respond(['You can''t get to the ',Room,' from here']),fail. %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% % when they actually make the move we have to wipe out their % old location and assert their new location move_to(Room):- retract(here(_)), asserta(here(Room)). %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% % the look command tells the player what is in their current % room and which other rooms it's connected to look:- here(Here), 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 displays the items in the specified location list_things(Place):- location(X,Place), tab(2),write(X),nl, fail. list_things(_). %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% % list connections displays the locations adjacent to the % specified location list_connections(Place):- connect(Place,X), tab(2),write(X),nl, fail. list_connections(_). %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% % look_in allows the player to look inside anything which might % contain other things, % % It does so by checking to see if the item they specify is % currently the location of one or more other items, % otherwise it says there is nothing there look_in(Thing):- location(_,Thing), 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 an item as long as it is % in the current room and is listed as a takeable object % (even if it is inside something else that is in the room) take(Thing):- is_here(Thing), is_takable(Thing), move(Thing,have), respond(['You now have the ',Thing]). %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% % is here checks to see if the specified item is located % in the current room, even if it's inside something else % in the room % (but not including things the player already possesses) is_here(Thing):- here(Here), contains(Thing,Here),!. is_here(Thing):- respond(['There is no ',Thing,' here']), fail. %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% % contains checks to see if what is in the specified item, % and also what is inside things inside the item (if anything) % (and what is inside those items, etc) contains(Thing,Here):- location(Thing,Here). contains(Thing,Here):- location(Thing,X), contains(X,Here). %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% % this check prevents the player from trying to take something % they can't pick up (just furniture at the moment) is_takable(Thing):- furniture(Thing), respond(['You can''t pick up a ',Thing]), !,fail. is_takable(_). %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% % move is used to transfer the location of an item, % right now it's only used/implemented to pick things up, % so the item goes from its current location to your possession move(Thing,have):- retract(location(Thing,_)), asserta(have(Thing)). %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% % eat allows the player to ATTEMPT to eat something, but only % REALLY allows the attempt if they currently have the item % % it uses edible to check if the thing can actually be eaten, % tastes_gross to handle eating anything disgusting, % or assumes it tasted pretty good eat(Thing):- have(Thing), really_eat(Thing). eat(Thing):- respond(['You don''t have the ',Thing]). really_eat(Thing):- edible(Thing), retract(have(Thing)), respond(['That ',Thing,' was good']). really_eat(Thing):- tastes_gross(Thing), respond(['OK, that was pretty gross']). really_eat(Thing):- respond(['You can''t eat a ',Thing]). %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% % list_possessions displays all the items you currently have, % i.e. all the haves that have been asserted % and not retracted so far list_possessions:- have(X), tab(2),write(X),nl, fail. list_possessions. %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% % if the player tries to turn on a light % they're told they can't find a switch % if they try to turn on an item they don't have % they'll get an error message % if they try to turn on something they DO have % it works if the item was previously turned off % and it is something that can be turned on % (otherwise appropriate error messages are generated) % % The list of things that are initially on/off % needs to be established in the init_dynamic_facts, % so we can use assert and retract to keep % them up to date turn_on(light):- respond(['You can''t find the switch']). turn_on(Thing):- have(Thing), turn_on_item(Thing). turn_on(Thing):- respond(['You don''t have the ',Thing]). turn_on_item(Thing):- turned_on(Thing), respond(['The ',Thing,' is already on']). turn_on_item(Thing):- turned_off(Thing), retract(turned_off(Thing)), asserta(turned_on(Thing)), respond(['The ',Thing,' is now on']). turn_on_item(Thing):- respond(['You can''t turn a ',Thing,' on']). %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% % Each puzzle will need its own set of static rules and % dynamic facts to keep track of whether it has been solved. % % For this one, to get into the cellar you must have a flashlight % and it must be turned on, % but if you're trying to get into any other room this part of % the code ignores it (the anonymous accept case at the end) cellar_puzzle(goto(cellar)):- have(flashlight), turned_on(flashlight),!. cellar_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. cellar_puzzle(_). %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% % respond takes a list of text items and variables and displays % each of them in turn, % then follows it with a period and a blank line respond([]):- write('.'),nl,nl. respond([H|T]):- write(H), respond(T). %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% %%%%%%%%%%%%%%%%%%% INTERPRETTER %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% % This is a very simple command interpretter for the few English % phrases this thing understands. % % It's pretty loose on grammar, letting the player get away with % a lot. % get_command prompts the user, % reads in a sentence and stores it as a list of words, % calls command to work out the grammatical structure, % and stores it as a structure get_command(C):- write('cmd> '), read_word_list(L), phrase(command(Grammar),L,[]), C =.. Grammar,!. % if we get to this version of get_command it means the tokenizer % above failed to make sense of the command sentence get_command(_):- respond(['Sorry, I did not understand that']),fail. %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% % Right now it will accept as commands: % - a location name (meaning go to the location) % - a command with one argument (e.g. eat dirt) % - a command with no arguments (e.g. look) % check for verb+item combinations command([Pred,Arg]) --> verb(Type,Pred), nounphrase(Type,Arg). % check for solitary verb combinations command([Pred]) --> verb(intran,Pred). % check for goto+destination combinations command([goto,Arg]) --> noun(go_place,Arg). %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% % Right now it recognizes three general forms of verb, but % it also recognizes some loose phrases as equivalent to single % word commands for a little more flexibility verb(go_place,goto) --> go_verb. verb(thing,V) --> tran_verb(V). verb(intran,V) --> intran_verb(V). %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% % Here we check to see if the potential verb matches any of % the go-to phrases, i.e. "go", "go to", or "g" go_verb --> [go,to]. %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% % Here we check to see if the potential verb matches any of % the verb phrases which are supposed to be applied to % an object (e.g. take, drop, eat, etc) % verbs to grab an item tran_verb(take) --> [take]. tran_verb(take) --> [pick,up]. % verbs to eat something tran_verb(eat) --> [eat]. % verbs to turn things on/off tran_verb(turn_on) --> [turn,on]. tran_verb(turn_on) --> [switch,on]. % verbs to specifically look in/at things tran_verb(look_in) --> [look,in]. tran_verb(look_in) --> [open]. %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% % Here we check to see if the potential verb matches any of % the simple verb phrases which are supposed to represent % independent commands (e.g. look around, quit, get help) % verbs to look around intran_verb(look) --> [look,around]. intran_verb(look) --> [l]. % verbs to quit intran_verb(quit) --> [quit]. %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% % a noun phrase is just a noun with an optional determiner % in front (e.g. "the book") nounphrase(Type,Noun) --> det,noun(Type,Noun). nounphrase(Type,Noun) --> noun(Type,Noun). %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% % just handles "the" for now det --> [the]. %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% % Nouns might be a single word describing a place or thing % or a pair of words (e.g. dining room) % check if the item is a recognized room, noun(go_place,R) --> [R], {room(R)}. % check if the item is a valid location noun(thing,T) --> [T], {location(T,_)}. % if it's a thing check to make sure we actually have it noun(thing,T) --> [T], {have(T)}. % if it's a flashlight treat it specially (see below) noun(thing,flashlight) --> [flash,light]. % identify any acceptable two-word nouns noun(thing,'mini fridge') --> [mini,fridge]. % If the player has just typed light, (e.g. to turn it on/off) % they could mean a room light or a flashlight, % and we'll default to just a light noun(thing,light) --> [X,light], {room(X)}. noun(thing,flashlight) --> [light], {have(flashlight)}. noun(thing,light) --> [light]. %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% %%%%%%%%%%%% TOKENIZER / READER %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% % The tokenizer reads characters typed by the user, % building them into words, recognizing where % one word has ended and a new one has begun, % and putting the words together into a list. % % Certain symbols and punctuation marks will be % seperated at this point, setting them aside % as distinct items. % % Once the list is complete, the interpretter (above) % can be used to try and determine the meaning % of the word as a statement or sentence. % % Read the first character of the next word with get0, % finish composing the word (W) using read_word, % finish composing the rest of the words in the % sentence (Ws) using rest_of_sentence read_word_list([W|Ws]) :- get0(C), read_word(C, W, C1), rest_of_sentence(C1, Ws), !. %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% % Here we grab the rest of the sentence % end_of_sentence tells us if we're at the end % (when we've hit a ! . ? or end-of-line) rest_of_sentence(C,[]) :- end_of_sentence(C), !. % the general case is that we have to read the next word % and the rest of the sentence % (just as with read_word_list) rest_of_sentence(C,[W1|Ws]) :- read_word(C,W1,C1), rest_of_sentence(C1,Ws). %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% % Here we grab the rest of a word, storing it in W, % assuming the first character was read in in C % We wind up with C1 being the first character % AFTER the current word's completion % if C is a punctuation mark it is treated as a valid % word all by itself, so set W to contain just that character read_word(C,W,C1) :- single_char(C), !, name(W, [C]), get0(C1). % if C is a valid character to appear in a "regular" word % (i.e. alphanumeric) then continue building the word % using rest_of_word and glue it together to form W read_word(C,W,C2) :- char_in_word(C, NewC), get0(C1), rest_of_word(C1,Cs,C2), name(W, [NewC|Cs]). % otherwise C must be a seperator (pretty much anything not % covered above) so it's time to start a new word read_word(_,W,C2) :- get0(C1), read_word(C1,W,C2). %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% % rest_of_word checks that the latest character is valid for % the body of a word, tacks it on to our word-in-progress, % and continues % We wind up with C2 being the first character % AFTER the current word's completion rest_of_word(C, [NewC|Cs], C2) :- char_in_word(C, NewC), get0(C1), rest_of_word(C1, Cs, C2). % our base/stopping case rest_of_word(C, [], C). %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% % here we list all the characters that will be treated % as if they were words by themselves, % i.e. punctuation that doesn't appear in the middle of a word single_char(0',). single_char(0';). single_char(0':). single_char(0'?). single_char(0'!). single_char(0'.). %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% % here we list all the characters that can appear as a valid % part of a larger word, mostly alpha-numeric char_in_word(C, C) :- C >= 0'a, C =< 0'z. char_in_word(C, C) :- C >= 0'0, C =< 0'9. char_in_word(C, L) :- C >= 0'A, C =< 0'Z, L is C + 32. char_in_word(0'-,0'-). %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% % end_of_sentence checks if the character is the valid end of a % sentence, i.e. a newline, . ! or ? end_of_sentence(10). % end if new line entered end_of_sentence(0'.). end_of_sentence(0'!). end_of_sentence(0'?). |