% --------------- query format --------------
%  examine(S) where S is the sentence as a list of atoms,
%     e.g. examine([the, strange, bird, flew, quickly ]).
%          Valid sentence: [indefinite,[nature,animate]]
%
examine(S) :- phrase(sentence(Info), S, []),
              format("Valid sentence: ~w~n", Info).


% --------- accepted forms of speech ----------------

% nouns will be categorized as living or inanimate
noun(inanimate) --> [plane].
noun(inanimate) --> [rock].
noun(animate) --> [bird].
noun(animate) --> [frog].

% valid verbs
verb(past) --> [flew].
verb(present) --> [flies].
verb(future) --> [will, fly].

% valid articles
article(indefinite) --> [the].
article(indefinite) --> [a].

% valid adverbs
adverb(speed) --> [safely].
adverb(speed) --> [quickly].
adverb(frequency) --> [N, times], { number(N) }.

% valid adjectives
adjective(demonstrative) --> [that].
adjective(colour) --> [red].
adjective(size) --> [big].
adjective(nature) --> [strange].

% valid verb phrases, Info will be instantiated with the verb tense
verbphrase(Info) --> verb(Info).
verbphrase([AInfo, VInfo]) --> verb(VInfo), adverb(AInfo).
verbphrase([qualified, Info]) --> adverb, verb(Info).

% valid nouns and noun phrases, Info will be instantiated with living or inanimate
qualifiednoun(Info) --> noun(Info).
qualifiednoun([AInfo,NInfo]) --> adjective(AInfo), noun(NInfo).
nounphrase(Info) --> qualifiednoun(Info).
nounphrase([AInfo,NInfo]) --> article(AInfo), qualifiednoun(NInfo).

% a sentences is formed by a noun phrase followed by a verb phrase
sentence([NounInfo, VerbInfo]) --> nounphrase(NounInfo), verbphrase(VerbInfo).

