Skip to content

Instantly share code, notes, and snippets.

@K9-guardian
Last active February 22, 2023 09:34
Show Gist options
  • Save K9-guardian/652ea9e52567cb322f4b7c9f512b15c9 to your computer and use it in GitHub Desktop.
Save K9-guardian/652ea9e52567cb322f4b7c9f512b15c9 to your computer and use it in GitHub Desktop.
Cursed probabilistic parity checker based on the length of the number in English. Grammar currently supports numbers up to 10^64 trillion. Run with scryer-prolog.
:- use_module(library(clpz)).
:- use_module(library(dcgs)).
:- use_module(library(lambda)).
:- use_module(library(lists)).
:- use_module(library(reif)).
num_to_parity(N, odds_evens(Os, Es)) :-
num_word(N, W),
same_length(W, Ls),
findall(M, word_to_num(Ls, M), Ms),
tpartition(odd_t, Ms, Os, Es).
num_word(N, W) :-
num_coefficients(N, Cs),
phrase(chunks_word_(Cs), W).
% Specialized predicate using horner's method when word is ground.
word_to_num(W, N) :-
phrase(chunks_word_(Cs), W),
foldl(\V^S0^S^(S #= S0 * 1000 + V), Cs, 0, N).
% Convert a number to a list of each thousands place coefficient.
% ?- num_coefficients(69420727, Cs).
% Cs = [69, 420, 727].
num_coefficients(N, Cs) :- num_coefficients_(N, [], Cs).
num_coefficients_(N, Cs0, Cs) :-
if_(N #< 1000,
Cs = [N|Cs0],
(Quot #= N // 1000,
Rem #= N mod 1000,
Cs1 = [Rem|Cs0],
num_coefficients_(Quot, Cs1, Cs))).
odd_t(N, T) :- N mod 2 #= 1 #<==> T0, =(T0, 1, T).
% Use macroexpansion for each thousands place to get argument indexing.
term_expansion(chunk_name(N0, P), Rule) :-
N #= N0 + 1,
length([C|Cs], N),
Rule = (
chunks_word_([C|Cs]) -->
{ C in 1..999, num_digits(C, Ds) },
digits_word_(Ds),
" ", P,
dropzero_chunks_word_(Cs)
).
chunks_word_([A]) --> { A in 0..999, num_digits(A, ADs) }, digits_word_(ADs).
chunk_name(1, "thousand").
chunk_name(2, "million").
chunk_name(3, "billion").
chunk_name(4, "trillion").
chunk_name(5, "quintillion").
chunk_name(6, "sextillion").
chunk_name(7, "septillion").
chunk_name(8, "octillion").
chunk_name(9, "nonillion").
chunk_name(10, "decillion").
chunk_name(11, "undecillion").
chunk_name(12, "duodecillion").
chunk_name(13, "tredecillion").
chunk_name(14, "quattuordecillion").
chunk_name(15, "quindecillion").
chunk_name(16, "sexdecillion").
chunk_name(17, "septendecillion").
chunk_name(18, "octodecillion").
chunk_name(19, "novemdecillion").
chunk_name(20, "vigintillion").
% Convert a number to a list of its digits.
num_digits(N, Ds) :- num_digits_(N, [], Ds).
num_digits_(N, Ds0, Ds) :-
N #>= 0,
if_(N #< 10,
Ds = [N|Ds0],
(Quot #= N // 10,
Rem #= N mod 10,
Ds1 = [Rem|Ds0],
num_digits_(Quot, Ds1, Ds))).
% Removes preceding zeros before converting chunks to word.
dropzero_chunks_word_([]) --> [].
dropzero_chunks_word_([X|Xs]) -->
if_(X = 0, dropzero_chunks_word_(Xs), (" ", chunks_word_([X|Xs]))).
digits_word_([0]) --> "zero".
digits_word_([1]) --> "one".
digits_word_([2]) --> "two".
digits_word_([3]) --> "three".
digits_word_([4]) --> "four".
digits_word_([5]) --> "five".
digits_word_([6]) --> "six".
digits_word_([7]) --> "seven".
digits_word_([8]) --> "eight".
digits_word_([9]) --> "nine".
digits_word_([1, 0]) --> "ten".
digits_word_([1, 1]) --> "eleven".
digits_word_([1, 2]) --> "twelve".
digits_word_([1, 3]) --> "thirteen".
digits_word_([1, 4]) --> "fourteen".
digits_word_([1, 5]) --> "fifteen".
digits_word_([1, 6]) --> "sixteen".
digits_word_([1, 7]) --> "seventeen".
digits_word_([1, 8]) --> "eighteen".
digits_word_([1, 9]) --> "nineteen".
digits_word_([2, N]) --> "twenty", dropzero_digits_word_([N]).
digits_word_([3, N]) --> "thirty", dropzero_digits_word_([N]).
digits_word_([4, N]) --> "forty", dropzero_digits_word_([N]).
digits_word_([5, N]) --> "fifty", dropzero_digits_word_([N]).
digits_word_([6, N]) --> "sixty", dropzero_digits_word_([N]).
digits_word_([7, N]) --> "seventy", dropzero_digits_word_([N]).
digits_word_([8, N]) --> "eighty", dropzero_digits_word_([N]).
digits_word_([9, N]) --> "ninety", dropzero_digits_word_([N]).
digits_word_([A, B, C]) -->
{ A in 1..9 },
digits_word_([A]),
" hundred",
dropzero_digits_word_([B, C]).
% Removes preceding zeros before converting digits to word.
dropzero_digits_word_([]) --> [].
dropzero_digits_word_([L|Ls]) -->
if_(L = 0, dropzero_digits_word_(Ls), (" ", digits_word_([L|Ls]))).
if_(C_1, G__0, H__0) --> { if_(C_1, Ls = G__0, Ls = H__0) }, Ls.
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment