Jump to content

ABC incremental counts

From Rosetta Code
ABC incremental counts is a draft programming task. It is not yet considered ready to be promoted as a complete task, for reasons that should be found in its talk page.

Write a routine (function, subroutine, procedure, whatever it may be called in your language,) that when given a set of three letters, (a, b, c) for instance, will identify words that contain each of those letters, in differing amounts, and where each count differs from another by exactly 1. Ignore any characters that are not in the given search group.

For example: using the letters (a, b, c) the "word" 'abbccc' would be valid (1(a), 2(b) & 3(c)), as would 'acodablaccab' (2(b), 3(c) & 4(a)).

Do not hard code the letters to search for. Do not create three different single purpose search routines. Instead, create a generic routine that uses a given set of letters as its search criteria. Include some mechanism to limit the minimum count for the least common letter.

You may assume that the words are all lower case, or may choose to regularize the case of the words. In either case assume upper and lower case are the same. (The test files contain all and only lower case.)


Task

Write a general purpose routine to identify incremental letter count words following the above description.

Using the unixdict.txt from http://wiki.puzzlers.org, find and display the words that are identified as incremental count words, or <none> if no words are found that match.

  • Search for words containing (a b c) with a minimum count of 1
  • Search for words containing (t h e) with a minimum count of 1
  • Search for words containing (c i o) with a minimum count of 2

Show the output here, on this page.


Stretch

Use the same routine to search the words_alpha.txt file from https://github.com/dwyl/english-words using the same letter groups, but with a minimum 1 higher.

  • Search for words containing (a b c) with a minimum count of 2
  • Search for words containing (t h e) with a minimum count of 2
  • Search for words containing (c i o) with a minimum count of 3


Related

ABC correlation

ALGOL 68

Although not used here, this can do case sensitive or case insensitive searches. It can also handle searches where the counts differ by amounts other than 1 - e.g.: 0 which reproduces the results of the ABC correlation tsk.

Library: ALGOL 68-sort

Note, the source of sort.incl.a68 is on a separate page on Rosetta Code, see the above link.

BEGIN # Rosetta Code "ABC incremental counts" task                               #

    PR read "sort.incl.a68" PR                          # include file utilities #

    [ 1 : 0 ]STRING empty list;

    # return the words from dictionary that contain required characters with the #
    # character counts matching the expected counts ( though not necessarily in  #
    # the same order as required characters ), the words will be treated as case #
    # sensitive or not, depending on case sensitive                              #
    PROC iwords = ( STRING dictionary, required characters
                  , []INT  expected counts
                  , BOOL   case sensitive
                  )[]STRING:
         IF FILE input file;
            STRING file name = dictionary;
            open( input file, file name, stand in channel ) /= 0
         THEN                                          # failed to open the file #
            print( ( "Unable to open """ + file name + """", newline ) );
            empty list
         ELSE                                                   # file opened OK #
            BOOL at eof := FALSE;
            on logical file end( input file   # set the EOF handler for the file #
                                     # notes that EOF reached and returns TRUE   #
                                     # so processing can continue                #
                               , ( REF FILE f )BOOL: at eof := TRUE
                               );

            # returns the counts of each character in c that is in s             #
            PRIO COUNT = 5;
            OP   COUNT = ( STRING s, c )[]INT:
                 BEGIN
                    [ LWB c : UPB c ]INT result;
                    FOR i FROM LWB c TO UPB c DO result[ i ] := 0 OD;
                    FOR i FROM LWB s TO UPB s DO
                        INT c pos := 0;
                        IF char in string( s[ i ], c pos, c ) THEN result[ c pos ] +:= 1 FI
                    OD;
                    result
                 END # COUNT # ;
            # returns TRUE if the corresponding elements of a equal those of b   #
            #         FALSE otherwise                                            #
            OP   = = ( []INT a, b )BOOL:
                 IF LWB a /= LWB b OR UPB a /= UPB b
                 THEN FALSE                                   # different bounds #
                 ELSE
                    BOOL same := TRUE;
                    FOR i FROM LWB a TO UPB a WHILE same := a[ i ] = b[ i ] DO SKIP OD;
                    same
                 FI # = # ;
            
            STRING characters = IF case sensitive
                                THEN required characters
                                ELSE TOLOWER required characters
                                FI;
            FLEX[ 1 : 100 ]STRING words;      # will be enlarged as required #

            [ LWB expected counts : UPB expected counts ]INT expected
                := expected counts;   # a sorted copy of the expected counts #
            expected QUICKSORT ELEMENTS( LWB expected, UPB expected );
            [ LWB expected counts : UPB expected counts ]INT actual;

            INT w count := 0;
            WHILE STRING word;
                  get( input file, ( word, newline ) );
                  NOT at eof
            DO                                           # have another word #
               IF case sensitive THEN word := TOLOWER word FI;
               IF actual := word COUNT characters; # get and sort the counts #
                  actual QUICKSORT ELEMENTS( LWB actual, UPB actual );
                  expected = actual
               THEN            # word has the expected pattern of characters #
                  w count +:= 1;
                  IF w count > UPB words THEN              # need more words #
                      [ 1 : UPB words ]STRING current words := words;
                      words := HEAP[ 1 : UPB words * 2 ]STRING;
                      words[ 1 : UPB current words ] := current words
                  FI;
                  words[ w count ] := word
               FI
            OD;
            words[ 1 : w count ]
         FI # iwords # ;

    # returns c converted to lowercase if it is uppercase, c otherwise           #
    OP   TOLOWER = ( CHAR c )CHAR:
         IF c >= "A" AND c <= "Z" THEN REPR( ( ABS c - ABS "A" ) + ABS "a" ) ELSE c FI;
    # returns s converted to lowercase                                           #
    OP   TOLOWER = ( STRING s )STRING:
         BEGIN
            STRING result := s;
            FOR r pos FROM LWB result TO UPB result DO result[ r pos ] := TOLOWER result[ r pos ] OD;
            result
         END # TOLOWER # ;

    # return the words from dictionary that contain required characters with the #
    # character counts (when sorted) differing by delta and with the minimum     #
    # count being min count; the words will be treated as case sensitive or not, #
    # depending on case sensitive                                                #
    PROC dwords = ( STRING dictionary, required characters
                  , INT    min count,  delta
                  , BOOL   case sensitive
                  )[]STRING:
         IF INT len characters = 1 + ( UPB required characters - LWB required characters );
            len characters < 1
         THEN                                        # no characters specified ? #
            print( ( "At least one character to find required", newline ) );
            empty list
         ELSE
            # construct the expected counts based on min count and delta         #
            [ 1 : len characters ]INT expected counts;
            expected counts[ 1 ] := min count;
            FOR i FROM 2 TO len characters DO
                expected counts[ i ] := expected counts[ i - 1 ] + delta
            OD;
            # get the words from the dictionary file                             #
            iwords( dictionary, required characters, expected counts, case sensitive )
         FI # dwords # ;

    # returns s left-padded with blanks to w characters                          #
    PRIO PAD = 1;
    OP   PAD = ( INT w, STRING s )STRING:
         IF   INT len = ( UPB s - LWB s ) + 1;
              len >= w
         THEN s
         ELSE ( ( w - len ) * " " ) + s
         FI # PAD # ;
    # show the words found by dwords                                             #
    PROC show words = ( STRING dictionary, required characters
                      , INT    min count, delta
                      , BOOL   case sensitive
                      )VOID:
         BEGIN
            print( ( "Searching ", dictionary, " for """, required characters, """ words" ) );
            print( ( ", minimum count: ", whole( min count, 0 ) ) );
            IF delta /= 1 THEN print( ( ", delta: ", whole( delta, 0 ) ) ) FI;
            print( ( newline ) );
            []STRING words
                = dwords( dictionary, required characters, min count, delta, case sensitive );
            INT n words = ( UPB words - LWB words ) + 1;
            IF n words = 0 THEN
                print( ( 32 PAD "<none>", newline, newline ) )
            ELSE
                FOR w FROM LWB words TO UPB words DO
                    IF ODD w
                    THEN print( ( 32 PAD words[ w ] ) )
                    ELSE print( ( " ", words[ w ], newline ) )
                    FI
                OD;
                IF ODD n words THEN print( ( newline ) ) FI;
                print( ( newline ) )
            FI
         END # show words # ;

    # task test cases                                                            #
    show words( "unixdict.txt",    "abc", 1, 1, FALSE );
    show words( "unixdict.txt",    "the", 1, 1, FALSE );
    show words( "unixdict.txt",    "cio", 2, 1, FALSE );

    show words( "words_alpha.txt", "abc", 2, 1, FALSE );
    show words( "words_alpha.txt", "the", 2, 1, FALSE );
    show words( "words_alpha.txt", "cio", 3, 1, FALSE );

    show words( "words_alpha.txt", "abc", 2, 0, FALSE )

END
Output:
Searching unixdict.txt for "abc" words, minimum count: 1
                        baccarat canvasback
                      sabbatical

Searching unixdict.txt for "the" words, minimum count: 1
                        aesthete afterthought
                    authenticate bethlehem
                     cheesecloth diethylstilbestrol
                    eratosthenes heathenish
                      letterhead liechtenstein
                  mephistopheles nineteenth
                  orthophosphate seventieth
                      sweetheart teethe
                         teethed thereafter
                     theretofore thirtieth
              triphenylphosphine twentieth
                     westchester wholehearted

Searching unixdict.txt for "cio" words, minimum count: 2
                   socioeconomic

Searching words_alpha.txt for "abc" words, minimum count: 2
                          <none>

Searching words_alpha.txt for "the" words, minimum count: 2
       demethylchlortetracycline dichlorodiphenyltrichloroethane
              hyperthermesthesia tetrachloroethylene
             thermohyperesthesia trinitrophenylmethylnitramine

Searching words_alpha.txt for "cio" words, minimum count: 3
          scleroticochorioiditis

Searching words_alpha.txt for "abc" words, minimum count: 2, delta: 0
                       abboccato bambocciade
                      beccabunga blackback
                    bombacaceous brachiocubital
                     buccolabial cabbalistic
                subbrachycephaly subcarbonaceous

F#

This task uses countChars from F# Implementation of ABC correlation

// ABC incremental counts. Nigel Galloway: August 29th., 2024
let abc:string -> Map<char,int>=countChars ['a';'b';'c']
let the:string -> Map<char,int>=countChars ['t';'h';'e']
let cio:string -> Map<char,int>=countChars ['c';'i';'o']
let predicate n g=let g=(Map.values>>Array.ofSeq>>Array.sort)g in g[0]>=n && g|>Array.pairwise|>Array.forall(fun(n,g)->g=n+1)
printfn "Results from unixdict.txt:"
System.IO.File.ReadLines "unixdict.txt"|>Seq.filter(abc>>predicate 1)|>Seq.iter(printfn "%s")
System.IO.File.ReadLines "unixdict.txt"|>Seq.filter(the>>predicate 1)|>Seq.iter(printfn "%s")
System.IO.File.ReadLines "unixdict.txt"|>Seq.filter(cio>>predicate 2)|>Seq.iter(printfn "%s")
printfn "\nResults from words_alpha.txt:"
System.IO.File.ReadLines "words_alpha.txt"|>Seq.filter(abc>>predicate 2)|>Seq.iter(printfn "%s")
System.IO.File.ReadLines "words_alpha.txt"|>Seq.filter(the>>predicate 2)|>Seq.iter(printfn "%s")
System.IO.File.ReadLines "words_alpha.txt"|>Seq.filter(cio>>predicate 3)|>Seq.iter(printfn "%s")
Output:
Results from unixdict.txt:
baccarat
canvasback
sabbatical
aesthete
afterthought
authenticate
bethlehem
cheesecloth
diethylstilbestrol
eratosthenes
heathenish
letterhead
liechtenstein
mephistopheles
nineteenth
orthophosphate
seventieth
sweetheart
teethe
teethed
thereafter
theretofore
thirtieth
triphenylphosphine
twentieth
westchester
wholehearted
socioeconomic

Results from words_alpha.txt
demethylchlortetracycline
dichlorodiphenyltrichloroethane
hyperthermesthesia
tetrachloroethylene
thermohyperesthesia
trinitrophenylmethylnitramine
scleroticochorioiditis

FreeBASIC

Translation of: Julia
Sub SortInt(array() As Integer)
    Dim As Integer i, j, min
    Dim As Integer lb = Lbound(array), ub = Ubound(array)
    For i = lb To ub - 1
        min = i
        For j = i + 1 To ub
            If array(j) < array(min) Then min = j
        Next j
        Swap array(min), array(i)
    Next i
End Sub

Function Incremental(text As String, letters() As String, casesensitive As Boolean = True, minfirstcount As Integer = 1) As Boolean
    Dim As Integer i, j
    Dim As Integer ub = Ubound(letters)
    If Not casesensitive Then
        text = Lcase(text)
        For i = 0 To ub
            letters(i) = Lcase(letters(i))
        Next
    End If
    
    Dim counts(ub) As Integer
    For i = 0 To ub
        counts(i) = 0
        For j = 1 To Len(text)
            If Mid(text, j, 1) = letters(i) Then counts(i) += 1
        Next
    Next
    
    SortInt(counts())
    
    If counts(0) >= minfirstcount Then
        For i = 1 To Ubound(counts)
            If counts(i) - counts(i - 1) <> 1 Then Return False
        Next
        Return True
    End If
    
    Return False
End Function

Sub ReadFile(filename As String, words() As String)
    Dim f As Integer = Freefile
    Open filename For Input As #f
    Dim linea As String
    While Not Eof(f)
        Line Input #f, linea
        Redim Preserve words(Ubound(words) + 1)
        words(Ubound(words)) = linea
    Wend
    Close #f
End Sub

Dim uwords() As String
Dim awords() As String
ReadFile("unixdict.txt", uwords())
ReadFile("words_alpha.txt", awords())

Dim tests(5, 2) As String
tests(0, 0) = "unixdict.txt": tests(0, 1) = "a,b,c": tests(0, 2) = "1"
tests(1, 0) = "unixdict.txt": tests(1, 1) = "t,h,e": tests(1, 2) = "1"
tests(2, 0) = "unixdict.txt": tests(2, 1) = "c,i,o": tests(2, 2) = "2"
tests(3, 0) = "words_alpha.txt": tests(3, 1) = "a,b,c": tests(3, 2) = "2"
tests(4, 0) = "words_alpha.txt": tests(4, 1) = "t,h,e": tests(4, 2) = "2"
tests(5, 0) = "words_alpha.txt": tests(5, 1) = "c,i,o": tests(5, 2) = "3"

Dim As Integer i, j
For i = 0 To 5
    Dim wordlist() As String
    If tests(i, 0) = "unixdict.txt" Then
        Redim wordlist(Ubound(uwords))
        For j = 0 To Ubound(uwords)
            wordlist(j) = uwords(j)
        Next
    Else
        Redim wordlist(Ubound(awords))
        For j = 0 To Ubound(awords)
            wordlist(j) = awords(j)
        Next
    End If
    
    Dim chars(2) As String
    chars(0) = Mid(tests(i, 1), 1, 1)
    chars(1) = Mid(tests(i, 1), 3, 1)
    chars(2) = Mid(tests(i, 1), 5, 1)
    Dim minreq As Integer = Val(tests(i, 2))
    
    Print "Filtering "; tests(i, 0); " for letters <"; tests(i, 1); "> and minimum count"; minreq; ":"
    
    Dim results() As String
    For j = 0 To Ubound(wordlist)
        If Incremental(wordlist(j), chars(), True, minreq) Then
            Redim Preserve results(Ubound(results) + 1)
            results(Ubound(results)) = wordlist(j)
        End If
    Next
    
    If Ubound(results) = -1 Then
        Print "<none>"
    Else
        For j = 0 To Ubound(results)
            Print results(j)
        Next
    End If
    Print
Next

Sleep
Output:
Same as Julia entry.

jq

Adapted from Wren

Works with jq, the C implementation of jq

Works with gojq, the Go implementation of jq

With a small adjustment as a concession to jaq's lack of support for the `--argjson` command-line option, the program also works with jaq, the Rust implementation of jq.

def count(stream): reduce stream as $x (0; .+1);

# Count the number of occurrences of $char in .
def occurrences($char):
  ($char[0:1]|explode[0]) as $codepoint
  | count( explode[] | select(. == $codepoint));
 
# Input: an array of "words"
# Output: an array of words satisfying the conditions
def abcIncrementalCounts($letters; $minCount):
  reduce (.[] | ascii_downcase) as $word ([]; 
    ($word | occurrences($letters[0])) as $c1
    | if $c1 < $minCount then .
      else ($word|occurrences($letters[1])) as $c2
      | if $c2 < $minCount then .
        else ($word|occurrences($letters[2])) as $c3
        | if $c3 < $minCount then .
          else  ([$c1, $c2, $c3] | sort) as $l
          | if $l[1] != ($l[0] + 1) or $l[2] != ($l[1] + 1) then .
            else . + [$word]
            end
          end
        end
      end);
  
def letters:
  [["a", "b", "c"], ["t", "h", "e"], ["c", "i", "o"]];

# Requires: $mincount
# Reads from STDIN
def incremental_counts:
   [inputs]
   | range(0; letters|length) as $j
   | letters[$j] as $letters
   | "Letters: \($letters) -- Minimum count \($mincount[$j])",
      ( (abcIncrementalCounts($letters; $mincount[$j]) ) as $res
        | if ($res|length) > 0
          then $res[] | sub("\r$";"")
          else "<none>"
          end ),
      "";

incremental_counts
Output:

Invocation:

echo Using unixdict.txt:
jq -nRr -f abc-incremental-counts.jq --argjson mincount '[1, 1, 2]' unixdict.txt
echo
echo Using words_alpha.txt:
jq -nRrf abc-incremental-counts.jq --argjson mincount '[2, 2, 3]' words_alpha.txt

Essentially as for #Wren

Julia

function incremental(text, letters; casesensitive = true, minfirstcount = 1)
    if !casesensitive
        text = lowercase(text)
        letters = map(lowercase, letters)
    end
    counts = map(c -> count(==(c), text), letters) |> sort!
    return !isempty(counts) && counts[begin] >= minfirstcount && all(==(1), diff(counts))
end

const uwords = split(read("unixdict.txt", String), r"\s+")
const awords = split(read("words_alpha.txt", String), r"\s+")
const tests = [
   (uwords, ['a', 'b', 'c'], 1), (uwords, ['t', 'h', 'e'], 1), (uwords, ['c', 'i', 'o'], 2),
   (awords, ['a', 'b', 'c'], 2), (awords, ['t', 'h', 'e'], 2), (awords, ['c', 'i', 'o'], 3),
]

for (wordlist, chars, minreq) in tests
	fname = wordlist == uwords ? "unixdict.txt" : "words_alpha.txt"
	println("Filtering $fname for letters <$(String(chars))> and minimum count $minreq:")
	results = filter(s -> incremental(s, chars, minfirstcount = minreq), wordlist)
	println(isempty(results) ? "<none>" : join(results, "\n"), "\n")
end
Output:
Filtering unixdict.txt for letters <abc> and minimum count 1:
baccarat
canvasback
sabbatical

Filtering unixdict.txt for letters <the> and minimum count 1:
aesthete
afterthought
authenticate
bethlehem
cheesecloth
diethylstilbestrol
eratosthenes
heathenish
letterhead
liechtenstein
mephistopheles
nineteenth
orthophosphate
seventieth
sweetheart
teethe
teethed
thereafter
theretofore
thirtieth
triphenylphosphine
twentieth
westchester
wholehearted

Filtering unixdict.txt for letters <cio> and minimum count 2:
socioeconomic

Filtering words_alpha.txt for letters <abc> and minimum count 2:
<none>

Filtering words_alpha.txt for letters <the> and minimum count 2:
demethylchlortetracycline
dichlorodiphenyltrichloroethane
hyperthermesthesia
tetrachloroethylene
thermohyperesthesia
trinitrophenylmethylnitramine

Filtering words_alpha.txt for letters <cio> and minimum count 3:
scleroticochorioiditis

PascalABC.NET

This task uses countChars from Words with more than 3 ez

// ABC incremental counts. Nigel Galloway: August 29th., 2024
function predicate(g:Sequence of (integer,integer);m:integer):boolean;
begin
  result:=false; if g.First[0]<m then exit;
  foreach n:(integer,integer) in g do if n[1]<>n[0]+1 then exit; result:=true;
end;
var
  abc:string->Sequence of (integer,integer):=n->countChars('abc',n).Values.Sorted.Pairwise;
  the:string->Sequence of (integer,integer):=n->countChars('the',n).Values.Sorted.Pairwise;
  cio:string->Sequence of (integer,integer):=n->countChars('cio',n).Values.Sorted.Pairwise;
begin
  println('Results from unixdict.txt:');
  foreach s:string in System.IO.File.ReadLines('unixdict.txt') do
     if predicate(abc(s),1) or predicate(the(s),1) or predicate(cio(s),2) then println(s);
  println; println('Results from words_alpha.txt:');
  foreach s:string in System.IO.File.ReadLines('words_alpha.txt') do
     if predicate(abc(s),2) or predicate(the(s),2) or predicate(cio(s),3) then println(s);
end.
Output:
Results from unixdict.txt:
aesthete
afterthought
authenticate
baccarat
bethlehem
canvasback
cheesecloth
diethylstilbestrol
eratosthenes
heathenish
letterhead
liechtenstein
mephistopheles
nineteenth
orthophosphate
sabbatical
seventieth
socioeconomic
sweetheart
teethe
teethed
thereafter
theretofore
thirtieth
triphenylphosphine
twentieth
westchester
wholehearted

Results from words_alpha.txt:
demethylchlortetracycline
dichlorodiphenyltrichloroethane
hyperthermesthesia
scleroticochorioiditis
tetrachloroethylene
thermohyperesthesia
trinitrophenylmethylnitramine

Phix

with javascript_semantics
function incrementing_counts(string word, sequence letn)
    {string letters, integer minc} = letn
    sequence c = unique(apply(apply(true,filter,{{word},{"="},letters}),length))
    return c[1]>=minc and length(c)=length(letters) and c[$]-c[1]=length(letters)-1
end function
for i,d in {"unixdict.txt","words_alpha.txt"} do
    sequence words = unix_dict(6,d)
    --    (aside: may as well, ^nowt < 6 letters would ever pass muster)
    for j,t in {"abc","the","cio"} do
        integer n = 1+(i>1)+(j>2)
        sequence r = filter(words,incrementing_counts,{t,n})
        printf(1,"Filtering %s for %s >= %d: %s\n",
                 {d,t,n,join(shorten(r,"found",1),",")})
    end for
    if platform()=JS then exit end if
end for
Output:

words_alpha.txt only on desktop/Phix (since only unixdict.txt has as yet been repackaged for use in a browser).

Filtering unixdict.txt for abc >= 1: baccarat,canvasback,sabbatical
Filtering unixdict.txt for the >= 1: aesthete,...,wholehearted, (24 found)
Filtering unixdict.txt for cio >= 2: socioeconomic
Filtering words_alpha.txt for abc >= 2:
Filtering words_alpha.txt for the >= 2: demethylchlortetracycline,...,trinitrophenylmethylnitramine, (6 found)
Filtering words_alpha.txt for cio >= 3: scleroticochorioiditis

Python

import os
from collections import Counter
from functools import partial
from itertools import pairwise  # requires Python >= 3.10
from typing import Iterable


def incrementing_counts(word: str, letters: Iterable[str], minimum: int) -> bool:
    counter = Counter({c: 0 for c in letters})
    counter.update(c for c in word if c in letters)
    counts = counter.most_common()
    return (
        all(a[1] - b[1] == 1 for a, b in pairwise(counts)) and counts[-1][1] >= minimum
    )


def display_incrementing_words(
    filename: str,
    words: Iterable[str],
    letters: Iterable[str],
    minimum: int,
) -> None:
    print(
        f"Incrementing counts of {letters} "
        f"in {filename} "
        f"with a minimum count of {minimum}:"
    )

    _func = partial(incrementing_counts, letters=letters, minimum=minimum)
    print(os.linesep.join(filter(_func, words)) or "<none>", "\n")


if __name__ == "__main__":
    with open("unixdict.txt") as fd:
        unix_dict = [line.strip() for line in fd]

    with open("words_alpha.txt") as fd:
        words_alpha = [line.strip() for line in fd]

    test_cases = [
        ("unixdict.txt", unix_dict, ["a", "b", "c"], 1),
        ("unixdict.txt", unix_dict, ["t", "h", "e"], 1),
        ("unixdict.txt", unix_dict, ["c", "i", "o"], 2),
        ("words_alpha.txt", words_alpha, ["a", "b", "c"], 2),
        ("words_alpha.txt", words_alpha, ["t", "h", "e"], 2),
        ("words_alpha.txt", words_alpha, ["c", "i", "o"], 3),
    ]

    for case in test_cases:
        display_incrementing_words(*case)
Output:
Incrementing counts of ['a', 'b', 'c'] in unixdict.txt with a minimum count of 1:
baccarat
canvasback
sabbatical 

Incrementing counts of ['t', 'h', 'e'] in unixdict.txt with a minimum count of 1:
aesthete
afterthought
authenticate
bethlehem
cheesecloth
diethylstilbestrol
eratosthenes
heathenish
letterhead
liechtenstein
mephistopheles
nineteenth
orthophosphate
seventieth
sweetheart
teethe
teethed
thereafter
theretofore
thirtieth
triphenylphosphine
twentieth
westchester
wholehearted 

Incrementing counts of ['c', 'i', 'o'] in unixdict.txt with a minimum count of 2:
socioeconomic 

Incrementing counts of ['a', 'b', 'c'] in words_alpha.txt with a minimum count of 2:
<none> 

Incrementing counts of ['t', 'h', 'e'] in words_alpha.txt with a minimum count of 2:
demethylchlortetracycline
dichlorodiphenyltrichloroethane
hyperthermesthesia
tetrachloroethylene
thermohyperesthesia
trinitrophenylmethylnitramine 

Incrementing counts of ['c', 'i', 'o'] in words_alpha.txt with a minimum count of 3:
scleroticochorioiditis

Raku

say "\nUsing ", my $dict = 'unixdict.txt';
my @tests = <a b c>, 1, <t h e>, 1, <c i o>, 2;
filter $dict.IO.words;

say "\n\nUsing ", $dict = 'words_alpha.txt';
@tests[1,3,5]».++;
filter $dict.IO.words;

sub filter (@words) {
    for @tests -> ($a, $b, $c), $min {
        say "\nLetters: ($a $b $c) -- Minimum count $min\n",
          @words.race.grep(&incremental).sort.join("\n") || '<none>';

        sub incremental ($word) {
            my @v = $word.comb.Bag{$a,$b,$c}.values.sort;
            (@v[0] >= $min) && (@v[0]+1 == @v[1]) && (@v[0]+2 == @v[2])
        }
    }
}
Output:
Using unixdict.txt

Letters: (a b c) -- Minimum count 1
baccarat
canvasback
sabbatical

Letters: (t h e) -- Minimum count 1
aesthete
afterthought
authenticate
bethlehem
cheesecloth
diethylstilbestrol
eratosthenes
heathenish
letterhead
liechtenstein
mephistopheles
nineteenth
orthophosphate
seventieth
sweetheart
teethe
teethed
thereafter
theretofore
thirtieth
triphenylphosphine
twentieth
westchester
wholehearted

Letters: (c i o) -- Minimum count 2
socioeconomic


Using words_alpha.txt

Letters: (a b c) -- Minimum count 2
<none>

Letters: (t h e) -- Minimum count 2
demethylchlortetracycline
dichlorodiphenyltrichloroethane
hyperthermesthesia
tetrachloroethylene
thermohyperesthesia
trinitrophenylmethylnitramine

Letters: (c i o) -- Minimum count 3
scleroticochorioiditis

RPL

The only way in RPL to use unixdict.txt as input is to convert it into a list of 25,104 strings, stored in the global variable Dict. This implementation is case-sensitive.

Works with: RPL version HP-49C
« → w
  « 0. 26 NDUPN →LIST 
    1 w SIZE FOR j
       w j DUP SUB NUM 96 -
       IF DUP 1 ≥ OVER 26 ≤ AND THEN DUP2 GET 1 + PUT ELSE DROP END
    NEXT
» » 'LCNT'  STO     @ ( "word" → { letter_count .. } )

« « j » 'j' ROT DUP 5 PICK SIZE + 1 - 1 SEQ 
  SWAP LCNT 
  → c mask
  « Dict 
    DUP 1 « mask SWAP LCNT IFT SORT c == » DOLIST 
    SWAP IFT
» » 'αINCC' STO     @ ( "abc" val → { "word" .. )
"abc" 1 αINCC
"the" 1 αINCC
"cio" 2 αINCC
Output:
3: { "baccarat" "canvasback" "sabbatical" }
2: { "aesthete" "afterthought" "authenticate" "bethlehem" "cheesecloth" "diethylstilbestrol" "eratosthenes" "heathenish" "letterhead" "liechtenstein" "mephistopheles" "nineteenth" "orthophosphate" "seventieth" "sweetheart" "teethe" "teethed" "thereafter" "theretofore" "thirtieth" "triphenylphosphine" "twentieth" "westchester" "wholehearted" }
1: { "socioeconomic" }

Wren

Library: Wren-ioutil
Library: Wren-str
import "./ioutil" for FileUtil
import "./str" for Str

var abcIncrementalCounts = Fn.new { |fileName, letters, minCount|
    var res = []
    var words = FileUtil.readLines(fileName) // local copy
    for (word in words) {
        word = Str.lower(word)
        var c1 = Str.occurs(word, letters[0])
        if (c1 < minCount) continue
        var c2 = Str.occurs(word, letters[1])
        if (c2 < minCount) continue
        var c3 = Str.occurs(word, letters[2])
        if (c3 < minCount) continue
        var l = [c1, c2, c3].sort()
        if (l[1] != l[0] + 1 || l[2] != l[1] + 1) continue
        res.add(word)
    }
    return res
}

var fileNames = ["unixdict.txt", "words_alpha.txt"]
var letters = [["a", "b", "c"], ["t", "h", "e"], ["c", "i", "o"]]
var minCounts = [[1, 1, 2], [2, 2, 3]]
for (i in 0...fileNames.count) {
    System.print("Using %(fileNames[i]):\n")
    for (j in 0...letters.count) {
        System.print("Letters: %(letters[j]) -- Minimum count %(minCounts[i][j])")
        var res = abcIncrementalCounts.call(fileNames[i], letters[j], minCounts[i][j])
        if (res.count > 0) {
            System.print(res.join("\n"))
        } else {
            System.print("<none>")
        }
        System.print()
    }
    System.print()
}
Output:
Using unixdict.txt:

Letters: [a, b, c] -- Minimum count 1
baccarat
canvasback
sabbatical

Letters: [t, h, e] -- Minimum count 1
aesthete
afterthought
authenticate
bethlehem
cheesecloth
diethylstilbestrol
eratosthenes
heathenish
letterhead
liechtenstein
mephistopheles
nineteenth
orthophosphate
seventieth
sweetheart
teethe
teethed
thereafter
theretofore
thirtieth
triphenylphosphine
twentieth
westchester
wholehearted

Letters: [c, i, o] -- Minimum count 2
socioeconomic


Using words_alpha.txt:

Letters: [a, b, c] -- Minimum count 2
<none>

Letters: [t, h, e] -- Minimum count 2
demethylchlortetracycline
dichlorodiphenyltrichloroethane
hyperthermesthesia
tetrachloroethylene
thermohyperesthesia
trinitrophenylmethylnitramine

Letters: [c, i, o] -- Minimum count 3
scleroticochorioiditis

XPL0

string 0;                       \use zero-terminated strings
proc IncCounts(File, Let, Min);
char File, Let, Min;
char Cnt(3), Word(100);
int  Set, I, J, Ch, Len, None;
def  LF=$0A, CR=$0D, EOF=$1A;
[Text(0, "Letters: '");  Text(0, Let);
 Text(0, "'  Minimum count: ");  IntOut(0, Min);  CrLf(0);
FSet(FOpen(File, 0), ^I);       \set dictionary file to device 3
OpenI(3);
None:= true;
repeat  I:= 0;
        loop    [repeat Ch:= ChIn(3) until Ch # CR;     \remove possible CR
                if Ch=LF or Ch=EOF then quit;
                Word(I):= Ch;
                I:= I+1;
                ];
        Word(I):= 0;            \terminate string
        Len:= I;
        [for J:= 0 to 2 do Cnt(J):= 0;
        for I:= 0 to Len-1 do
            [for J:= 0 to 2 do
                if Word(I) = Let(J) then Cnt(J):= Cnt(J)+1;
            ];
        Set:= 0;
        for J:= 0 to 2 do
            Set:= Set or 1<<Cnt(J);
        if Set>>Min = $7 then
            [Text(0, Word);  CrLf(0);  None:= false];
        ];
until   Ch = EOF;
if None then Text(0, "<none>^m^j");
CrLf(0);
];

int  Files, Letters, MinCounts, I, J;
[Files:= ["unixdict.txt", "words_alpha.txt"];
Letters:= ["abc", "the", "cio"];
MinCounts:= [[1, 1, 2], [2, 2, 3]];
for I:= 0 to 1 do
    [Text(0, "Using: ");  Text(0, Files(I));  CrLf(0);  CrLf(0);
    for J:= 0 to 2 do
        IncCounts(Files(I), Letters(J), MinCounts(I, J));
    ];
]
Output:
Using: unixdict.txt

Letters: 'abc'  Minimum count: 1
baccarat
canvasback
sabbatical

Letters: 'the'  Minimum count: 1
aesthete
afterthought
authenticate
bethlehem
cheesecloth
diethylstilbestrol
eratosthenes
heathenish
letterhead
liechtenstein
mephistopheles
nineteenth
orthophosphate
seventieth
sweetheart
teethe
teethed
thereafter
theretofore
thirtieth
triphenylphosphine
twentieth
westchester
wholehearted

Letters: 'cio'  Minimum count: 2
socioeconomic

Using: words_alpha.txt

Letters: 'abc'  Minimum count: 2
<none>

Letters: 'the'  Minimum count: 2
demethylchlortetracycline
dichlorodiphenyltrichloroethane
hyperthermesthesia
tetrachloroethylene
thermohyperesthesia
trinitrophenylmethylnitramine

Letters: 'cio'  Minimum count: 3
scleroticochorioiditis
Cookies help us deliver our services. By using our services, you agree to our use of cookies.