RabbitFarm

2022-04-24

The Weekly Challenge 161 (Prolog Solutions)

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

Part 1

Output or return a list of all abecedarian words in the dictionary, sorted in decreasing order of length.

Solution


check_and_read(10, [] ,_):-
    !.
check_and_read(13, [], _):-
    !.
check_and_read(32, [], _):-
    !.
check_and_read(44, [], _):-
    !.
check_and_read(end_of_file, [], _):-
    !.
check_and_read(Char, [Char|Chars], Stream):-
    get_code(Stream, NextChar),
    check_and_read(NextChar, Chars, Stream).

read_data(Stream, []):-
    at_end_of_stream(Stream).
read_data(Stream, [X|L]):-
    \+ at_end_of_stream(Stream),
    get_code(Stream, Char),
    check_and_read(Char, Chars, Stream),
    atom_codes(X, Chars),
    read_data(Stream, L).

abecedarian(Words, Abecedarian):-
    member(Word, Words),
    atom_chars(Word, Chars),
    sort(Chars, SortedChars),
    atom_chars(W, SortedChars),
    W = Word,
    Abecedarian = Word.

word_length(Word, LengthWord):-
    atom_chars(Word, Chars),
    length(Chars, Length),
    LengthWord = Length-Word. 

abecedarians(Words, Abecedarians):-
    findall(Abecedarian, abecedarian(Words, Abecedarian), A),
    maplist(word_length, A, AL), 
    keysort(AL, ALSorted),
    reverse(ALSorted, Abecedarians).

main:-
    open('dictionary', read, Stream),
    read_data(Stream, Dictionary),
    close(Stream),
    abecedarians(Dictionary, Abecedarians),
    write(Abecedarians), nl, 
    halt.

Sample Run


$ gprolog --consult-file prolog/ch-1.p --entry-goal main
[6-chintz,6-chimps,6-begins,6-almost,6-abhors,5-glory,5-ghost,5-forty,5-flops,5-first,5-filmy,5-films,5-empty,5-dirty,5-deity,5-chops,5-chips,5-chins,5-chimp,5-below,5-begin,5-befit,5-aglow,5-adopt,5-adept,5-abort,5-abhor,4-nosy,4-most,4-mops,4-lost,4-lops,4-know,4-knot,4-imps,4-host,4-hops,4-hips,4-hint,4-hims,4-hilt,4-gory,4-glow,4-gist,4-gins,4-gilt,4-foxy,4-fort,4-flux,4-flow,4-flop,4-fist,4-firs,4-fins,4-film,4-envy,4-elms,4-egos,4-dirt,4-dips,4-dins,4-dims,4-deny,4-dent,4-dens,4-defy,4-deft,4-crux,4-cost,4-copy,4-cops,4-clot,4-city,4-chow,4-chop,4-chip,4-chin,4-cent,4-blow,4-blot,4-bins,4-best,4-bent,4-belt,4-begs,4-amps,4-alms,4-airy,4-airs,4-aims,4-ails,4-ahoy,4-aces,4-ably,4-abet,3-pry,3-opt,3-now,3-not,3-nor,3-mow,3-mop,3-low,3-lot,3-lop,3-joy,3-jot,3-ivy,3-ins,3-imp,3-how,3-hot,3-hop,3-hit,3-his,3-hip,3-him,3-guy,3-got,3-gnu,3-gin,3-fry,3-fox,3-for,3-fly,3-flu,3-fix,3-fit,3-fir,3-fin,3-elm,3-ego,3-dry,3-dot,3-dos,3-dip,3-din,3-dim,3-dew,3-den,3-cry,3-coy,3-cox,3-cow,3-cot,3-cop,3-chi,3-buy,3-boy,3-box,3-bow,3-bop,3-bit,3-bin,3-bet,3-beg,3-art,3-apt,3-any,3-ant,3-amp,3-air,3-aim,3-ail,3-ago,3-ads,3-ado,3-act,3-ace,2-qt,2-ox,2-or,2-no,2-my,2-mu,2-ms,2-ix,2-iv,2-it,2-(is),2-in,2-ho,2-hi,2-go,2-em,2-eh,2-do,2-cs,2-by,2-be,2-ax,2-at,2-as,2-an,2-am,2-ah,2-ad,1-x,1-m,1-a]

Notes

Most of the code here is just for reading the provided dictionary of words. Once that is complete Prolog really shines. abecedarian/2 is the majority of the logic: if a word's characters when sorted and re-assembled are the original word then it is an Abecedarian.

abecedarians/2 is necessary only to fulfill the requirements of the problem specification which is that all Abecedarians be sorted by length and returned in descending order.

References

Challenge 161

posted at: 14:27 by: Adam Russell | path: /prolog | permanent link to this entry