Playing with WordNet
As described in its Wikipedia
article, WordNet is a lexical database for the English language. It groups
English words into sets of synonyms called synsets, provides
short definitions and usage examples, and records a number of relations among
these synonym sets or their members. WordNet can thus be seen as a combination of
dictionary and thesaurus. While it is accessible to human users via a web browser,
its primary use is in automatic text analysis and artificial intelligence
applications.
Serious stuff, that is, but here we shall only play around with it a bit and write
a program that generates random haiku poetry.
Haiku poetry
Haiku is a Japanese form of poetry which in its classical form
consists of seventeen syllables. In English haiku poems,
these are distributed over three lines:
- Five syllables
- Seven syllables
- Five syllables
Syntactically, they may for example look as follows:
- Preposition+Determiner+Adjective+Noun
- Determiner+Adjective+Noun+Particle+Verb
- Modifier+Adverb
The loaded version of WordNet used contains 212558 wordforms,
so the possibilities are endless. Most of the generated haikus
are bad, but who knows, perhaps some really beautiful ones will
emerge in the process. (They are in there...)
Generating haikus
The implementation needs to non-deterministically generate
random words of particular parts of speech and calculate their
number of syllables. It must also make sure that each line
contains the correct number, and backtrack if not.
/* Generating haiku poetry */
% Load wordnet interface.
% See http://www.swi-prolog.org/pack/file_details/wordnet/prolog/wn.pl
:- use_module(library(wn)).
:- use_module(library(mcintyre)).
:- mc.
:- begin_lpad.
print_haiku :-
haiku_lines(Lines),
format("~w~n~w~n~w~n", Lines).
haiku_lines([Line1, Line2, Line3]) :-
line1(Line1),
line2(Line2),
line3(Line3).
% preposition determiner adjective noun
% N11 + N12 =< 3,
% N11 + N12 + N13 =< 4,
% N11 + N12 + N13 + N14 =:= 5,
line1(Line) :-
first_couple1(W1,W2,N0),
third_word1(W3,N0,N1),
fourth_word1(W4,N1),
atomic_list_concat([W1, W2, W3, W4], ' ',Line).
first_couple1(W1,W2,2):-
random_word_syll(preposition, 1,W1, 1),
random_word_syll(determiner, 1,W2, 1).
first_couple1(W1,W2,3):-
random_word_syll(preposition, 1,W1, 2),
random_word_syll(determiner, 1,W2, 1).
first_couple1(W1,W2,3):-
random_word_syll(preposition, 1,W1, 1),
random_word_syll(determiner, 1,W2, 2).
third_word1(W3,2,3):-
random_word_syll(adjective, 1,W3, 1).
third_word1(W3,2,4):-
random_word_syll(adjective, 1,W3, 2).
fourth_word1(W4,3):-
random_word_syll(noun, 1,W4, 2).
fourth_word1(W4,4):-
random_word_syll(noun, 1,W4, 1).
% determiner adjective noun particle verb
% N21 + N22 =< 4,
% N21 + N22 + N23 =< 5,
% N21 + N22 + N23 + N24 =< 6,
% N21 + N22 + N23 + N24 + N25 =:= 7,
line2(Line) :-
first_couple2(W1,W2,N0),
third_word2(W3,N0,N1),
fourth_word2(W4,N1,N2),
fifth_word2(W5,N2),
atomic_list_concat([W1, W2, W3, W4, W5], ' ', Line).
first_couple2(W1,W2,2):-
random_word_syll(determiner,2, W1, 1),
random_word_syll(adjective,2, W2, 1).
first_couple2(W1,W2,3):-
random_word_syll(determiner,2, W1, 1),
random_word_syll(adjective,2, W2, 2).
first_couple2(W1,W2,3):-
random_word_syll(determiner,2, W1, 2),
random_word_syll(adjective,2, W2, 1).
first_couple2(W1,W2,4):-
random_word_syll(determiner,2, W1, 1),
random_word_syll(adjective,2, W2, 3).
first_couple2(W1,W2,4):-
random_word_syll(determiner,2, W1, 2),
random_word_syll(adjective,2, W2, 2).
first_couple2(W1,W2,4):-
random_word_syll(determiner,2, W1, 3),
random_word_syll(adjective,2, W2, 1).
third_word2(W3,2,3):-
random_word_syll(noun,2, W3, 1).
third_word2(W3,2,4):-
random_word_syll(noun,2, W3, 2).
third_word2(W3,2,5):-
random_word_syll(noun,2, W3, 3).
third_word2(W3,3,4):-
random_word_syll(noun,2, W3, 1).
third_word2(W3,3,4):-
random_word_syll(noun,2, W3, 1).
third_word2(W3,4,5):-
random_word_syll(noun,2, W3, 2).
third_word2(W3,5,5):-
random_word_syll(noun,2, W3, 1).
fourth_word2(W4,3,4):-
random_word_syll(particle,2, W4, 1).
fourth_word2(W4,3,5):-
random_word_syll(particle,2, W4, 2).
fourth_word2(W4,3,6):-
random_word_syll(particle,2, W4, 3).
fourth_word2(W4,4,5):-
random_word_syll(particle,2, W4, 1).
fourth_word2(W4,4,6):-
random_word_syll(particle,2, W4, 2).
fourth_word2(W4,5,6):-
random_word_syll(particle,2, W4, 1).
fifth_word2(W5,4):-
random_word_syll(verb, 2,W5, 3).
fifth_word2(W5,5):-
random_word_syll(verb, 2,W5, 2).
fifth_word2(W5,6):-
random_word_syll(verb, 2,W5, 1).
% modifier adverb
% N31 + N32 =:= 5.
line3(Line) :-
random_word_syll(modifier,3, W1, 1),
random_word_syll(adverb,3, W2, 4),
atomic_list_concat([W1, W2], ' ', Line).
line3(Line) :-
random_word_syll(modifier,3, W1, 2),
random_word_syll(adverb,3, W2, 3),
atomic_list_concat([W1, W2], ' ', Line).
line3(Line) :-
random_word_syll(modifier,3, W1, 3),
random_word_syll(adverb,3, W2, 2),
atomic_list_concat([W1, W2], ' ', Line).
line3(Line) :-
random_word_syll(modifier,3, W1, 4),
random_word_syll(adverb,3, W2, 1),
atomic_list_concat([W1, W2], ' ', Line).
%! random_word_syll(+PoS, +Line,-Word, -N) is nondet.
%
% Given a part of speech, generate a random word and
% its number of syllables.
random_word_syll(PoS,L, Word, N) :-
random_word(PoS,L,N, Word).
%! random_word(+PoS, Word) is nondet.
%
% Given a part of speech, generate a random word.
random_word(PoS,_, N,Word):uniform(Word,List) :-
findall(W, (call(PoS, W),count_syllables(W, N)), List),List\=[].
% Predicates for the parts of speech. The open word
% classes are fetched from WordNet, the closed ones
% (or some of them) are just enumerated. Note that
% the verbs are converted to their third person
% singular forms.
noun(Word) :-
wn_s(_, _, Word, n, _, _).
adjective(Word) :-
wn_s(_, _, Word, a, _, _).
verb(Word) :-
wn_s(_, _, Word0, v, _, _),
make_sg3_form(Word0, Word).
adverb(Word) :-
wn_s(_, _, Word, r, _, _).
preposition(in).
preposition(on).
preposition(to).
preposition(from).
preposition(around).
preposition(besides).
preposition(along).
preposition(aboard).
preposition(above).
preposition(among).
preposition(behind).
preposition(inside).
preposition(outside).
preposition(under).
preposition(without).
preposition(within).
determiner(a).
determiner(the).
determiner(any).
determiner(your).
determiner(each).
determiner(her).
determiner(his).
determiner(my).
determiner(one).
determiner(our).
determiner(their).
determiner(some).
determiner(this).
particle(still).
modifier(extremely).
modifier(heavily).
modifier(awfully).
modifier(seemingly).
modifier(dreadfully).
modifier(alarmingly).
modifier(exceedingly).
modifier(intensely).
modifier(distinctly).
modifier(profoundly).
modifier(tediously).
modifier(very).
modifier(outstandingly).
modifier(unusually).
modifier(decidedly).
modifier(supremely).
modifier(highly).
modifier(remarkably).
modifier(truly).
modifier(seriously).
modifier(frightfully).
modifier(apparently).
modifier(evidently).
modifier(superficially).
modifier(supposedly).
%! make_sg3_form(+Word, -NewWord) is det.
%
% Create a third person singular word form.
% If the verb ends in y, remove it and add ies.
make_sg3_form(Word, SG3) :-
atom_concat(Prefix, y, Word),
atom_concat(_, C, Prefix),
consonant(C),
!,
atom_concat(Prefix, ies, SG3).
% If the verb ends in o, ch, s, sh, x or z, add es.
make_sg3_form(Word, SG3) :-
member(Suffix, [o, ch, s, sh, x, z]),
atom_concat(_Prefix, Suffix, Word),
!,
atom_concat(Word, es, SG3).
% By default just add s.
make_sg3_form(Word, SG3) :-
atom_concat(Word, s, SG3).
%! count_syllables(+Word, -N) is det.
%
% Count the number of syllables in a word
% form. This is in fact a hard problem so
% here there is room for impreovements.
count_syllables(Word, N) :-
atom_chars(Word, Chars),
count_syllables_chars(Chars, N).
count_syllables_chars([], 0) :- !.
count_syllables_chars([C,l,e], 1) :-
consonant(C), !.
count_syllables_chars([C,e], 0) :-
consonant(C), !.
count_syllables_chars([C|Cs], N) :-
consonant(C), !,
count_syllables_chars(Cs, N).
count_syllables_chars([_, C|Cs], N) :-
vowel(C), !,
count_syllables_chars(Cs, NN),
N is NN + 1.
count_syllables_chars([_|Cs], N) :-
count_syllables_chars(Cs, NN),
N is NN + 1.
vowel(a).
vowel(e).
vowel(i).
vowel(o).
vowel(u).
vowel(y).
consonant(b).
consonant(c).
consonant(d).
consonant(f).
consonant(g).
consonant(h).
consonant(j).
consonant(k).
consonant(l).
consonant(m).
consonant(n).
consonant(p).
consonant(q).
consonant(r).
consonant(s).
consonant(t).
consonant(v).
consonant(x).
consonant(z).
:- end_lpad.
haiku(Li1,Li2,Li3):-mc_sample_arg_first(haiku_lines([L1,L2,L3]),1,(L1,L2,L3),L),L=[(Li1,Li2,Li3)-_].
haiku(L1,L2,L3).
To test it, run the following query:
mc_sample_arg_first(print_haiku,1,X,L).
Meet the crazy haiku poet!
Tickle him with your mouse pointer and he will produce a haiku poem. Make sure your sound isn't muted, and he will even speak!