RabbitFarm

2021-01-10

The Weekly Challenge 094 (Prolog Solutions)

The examples used here are from the weekly challenge problem statement and demonstrate the working solution.

Part 1

You are given a list of strings S. Write a script to group Anagrams together in any random order.

Solution


:-initialization(main).

letter_factor(e, 2). 
letter_factor(t, 3). 
letter_factor(a, 5).
letter_factor(o, 7). 
letter_factor(i, 11).
letter_factor(n, 13).
letter_factor(s, 17).
letter_factor(h, 19).
letter_factor(r, 23).
letter_factor(d, 29).
letter_factor(l, 31).
letter_factor(c, 37).
letter_factor(u, 41).
letter_factor(m, 43).
letter_factor(w, 47).
letter_factor(f, 53).
letter_factor(g, 59).
letter_factor(y, 61).
letter_factor(p, 67).
letter_factor(b, 71).
letter_factor(v, 73).
letter_factor(k, 79).
letter_factor(j, 83).
letter_factor(x, 89).
letter_factor(q, 97).
letter_factor(z, 101). 

chars_product([], 1).
chars_product([H|T], Product):-
    letter_factor(H, Factor),
    chars_product(T, Product0), 
    Product is Factor * Product0.  

word_product(Word, Product):-
    atom_chars(Word, Chars),
    chars_product(Chars, Product).  

organize([]):-
    findall(Words, bagof(Word, word_product(Word-_), Words), WordsList),
    write(WordsList). 
organize([H|T]):-
    word_product(H, P),
    assertz(word_product(H-P)),
    organize(T). 

main:-
    Anagrams = [opt, bat, saw, tab, pot, top, was],
    organize(Anagrams), nl,
    halt.

Sample Run


$ gplc ch-1.p
$ ./ch-1
[[bat,tab],[opt,pot,top],[saw,was]]

Notes

This is a Prolog version of Perl code I wrote for the same problem. In translating the approach of using the Fundamental Theorem of Arithmetic I tried to make sure the result was idiomatic Prolog as much as I could. I think I pulled that off!?!? In Prolog there is sometimes an over temptation to end up writing a bunch of mostly functional code. That is, code that could just as easily be written in, say, Haskell or ML. The organize/1 predicate is pretty much that sort of functional code but it is very short and wraps Prolog concepts such as assertz/1, findall/3, and bagof/3.

Part 2

You are given a binary tree. Write a script to represent the given binary tree as an object and flatten it to a linked list object. Finally, print the linked list object.

Solution


:-initialization(main).
 
dfs(Node, Graph, [Node|Path]):- 
    dfs(Node, Graph, Path, []).
dfs(_, _, [], _).
dfs(Node, Graph, [AdjNode|Path], Seen) :-
    member(r(Node, Adjacent), Graph),
    member(AdjNode, Adjacent),
    \+ memberchk(AdjNode, Seen),
    dfs(AdjNode, Graph, Path, [Node|Seen]).

unseen_nodes(Nodes, NodeList, Unseen):-
    unseen_nodes(Nodes, NodeList, [], Unseen).
unseen_nodes([], _, Unseen, Unseen).
unseen_nodes([H|T], NodeList, UnseenAccum, Unseen):- 
    \+ memberchk(H, NodeList),
    unseen_nodes(T, NodeList, [H|UnseenAccum], Unseen).  
unseen_nodes([H|T], NodeList, UnseenAccum, Unseen):-
    memberchk(H, NodeList),
    unseen_nodes(T, NodeList, UnseenAccum, Unseen).  

paths_list(Paths, List):-
    paths_list(Paths, [], List).
paths_list([], List, List).
paths_list([H|T], ListAccum, List):-
    unseen_nodes(H, ListAccum, Unseen),
    append(ListAccum, Unseen, ListAccum0), 
    paths_list(T, ListAccum0, List).    

print_list([H|[]]):-
    format("~d~n", [H]).  
print_list([H|T]):-
    format("~d -> ", [H]),   
    print_list(T).

main:-
    findall(Path, dfs(1,[r(1,[2]),r(1,[3]),r(2,[4,5]),r(5,[6,7])], Path), Paths),
    paths_list(Paths, List),  
    print_list(List), halt.

Sample Run


$ gplc ch-2.p
-bash-5.0$ ./ch-2
1 -> 2 -> 4 -> 5 -> 6 -> 7 -> 3

Notes

References

Challenge 094

Fundamental Theorem of Arithmetic

Lewand Ordering

posted at: 12:09 by: Adam Russell | path: /prolog | permanent link to this entry