Reputation: 1174
My goal is to print all forms of trees with N nodes in parenthetical notation, which can be defined as follows in terms of a Context-Free Grammar:
T → tree is empty
T → (T.T) a node with left & right children
For instance, all trees with 3 nodes will look like:
(((.).).)
((.(.)).)
((.).(.))
(.((.).))
(.(.(.)))
And I've written the following code in Prolog,
form1(Prev, Next) :-
string_concat("(", Prev, Inter),
string_concat(Inter, ".)", Next).
form2(Prev, Next) :-
string_concat("(.", Prev, Inter),
string_concat(Inter, ")", Next).
tree(1, ["(.)"]) :- !.
tree(N, Strings) :-
A is N - 1, tree(A, PrevStrings1),
maplist(form1 , PrevStrings1, List1),
maplist(form2 , PrevStrings1, List2),
append(List1, List2, Result),
Strings is Result.
But I get this error:
?- tree(2, L).
ERROR: Type error: `character' expected, found `"((.).)"' (a string)
ERROR: In:
ERROR: [9] _3182 is ["((.).)","(.(.))"]
ERROR: [7] <user>
I've made no reference to a Character in my code. What's wrong?
Upvotes: 2
Views: 1742
Reputation: 10102
The best way to solve such problems is to start with the abstract representation first. Abstract means that all syntactic details have been removed. What you actually want is trees of the following form
is_tree(empty).
is_tree(node(Left, Right)) :-
is_tree(Left),
is_tree(Right).
Then, based on this representation you can define a concrete representation using the syntactic bells and whistles you like most.
:- set_prolog_flag(double_quotes, chars).
tree(empty) --> "".
tree(node(Left, Right)) -->
"(",
tree(Left),
".",
tree(Right),
")".
?- length(Text, N), phrase(tree(Tree), Text).
Text = [], N = 0, Tree = empty
; Text = ['(','.',')'], N = 3, Tree = node(empty,empty)
; Text = ['(','.','(','.',')',')'], N = 6, Tree = node(empty,node(empty,empty))
; Text = ['(','(','.',')','.',')'], N = 6, Tree = node(node(empty,empty),empty)
; ... .
To improve readability of the answers, use [library(double_quotes)
for SWI and SICStus.
?- use_module(double_quotes).
?- length(Text, N), phrase(tree(Tree), Text).
Text = [], N = 0, Tree = empty
; Text = "(.)", N = 3, Tree = node(empty,empty)
; Text = "(.(.))", N = 6, Tree = node(empty,node(empty,empty))
; Text = "((.).)", N = 6, Tree = node(node(empty,empty),empty)
; Text = "(.(.(.)))", N = 9, Tree = node(empty,node(empty,node(empty,empty)))
; ... .
Finally, you might now skip the abstract syntax tree completely, thus:
tree --> "".
tree --> "(", tree, ".", tree, ")".
?- length(Text, N), phrase(tree, Text).
Text = [], N = 0
; Text = "(.)", N = 3
; Text = "(.(.))", N = 6
; Text = "((.).)", N = 6
; Text = "(.(.(.)))", N = 9
; Text = "(.((.).))", N = 9
; Text = "((.).(.))", N = 9
; ... .
At first sight this compact grammar seems to be preferable, but in many situations it is very inconvenient. In particular, if you are designing a new grammar and you are not sure whether or not your grammar contains ambiguities. With the help of the previous version, it is very simple to prove such things.
Upvotes: 2