2:- module(number_to_word,
    3     [ number_word/2 ]).    4
    5:- initialization compile_predicates([gen//1]).    6
    7:- dynamic gen//1.

number_to_word

Small utility pack for converting integers to English words.

author
- Ebrahim Azarisooreh
license
- MIT

*/

   18term_expansion(beyond(N, Word), Rule) :-
   19  succ(N0, N),
   20  atom_concat(x_, N, Name),
   21  atom_concat(x_, N0, Name0),
   22  Head =.. [Name, Word0],
   23  Prev =.. [Name0, W2],
   24  Rule = (  Head -->
   25	      x(W1),
   26	      call(Prev),
   27	      {  W1 \== [zero]
   28	      -> Word0 = [W1,Word|Rest],
   29		 (  W2 == [zero]
   30		 -> Rest = []
   31		 ;  Rest = W2
   32		 )
   33	      ;  Word0 = W2
   34	      }
   35	 ),
   36  Gen =.. [Name, A, B, C],
   37  GenRule = ( gen(A,B,C) :- Gen ),
   38  assertz(GenRule).
 number_word(?Num, ?Word) is nondet
True if Word is a (possibly) nested list of English words that represents the integer that Num is trying to represent.
Arguments:
Num- is a flat list of integer digits that correspond to the number in each place of the entire number. A whole number must be represented with a length that's a multiple of 3. For example, [0,0,3] is correct, but [3] is not.
Word- is a list of English words correspond to an integer. Every number that represents a magnitude that increases by the order of 10^3, is encased in its own list.

In example,

?- number_word([5,5,2,0,1,2,0,0,6], Word).
Word = [[five, hundred, fifty, two], million, [twelve], thousand, six]

?- number_word([0,0,6], Word).
Word = [six]

?- number_word(Number, [[one], thousand, three, hundred, seventy, two]).
Number = [0, 0, 1, 3, 7, 2]

?- number_word(Number, [[one], thousand, X, hundred, seventy, two]).
Number = [0, 0, 1, 1, 7, 2],
X = one ;
Number = [0, 0, 1, 2, 7, 2],
X = two ;
Number = [0, 0, 1, 3, 7, 2],
X = three ;
... etc.
   76number_word(Num, Word) :-
   77  (  nonvar(Num)
   78  -> phrase(gen(Word), Num)
   79  ;  term_variables(Word, [_|_])
   80  -> include(is_list, Word, Ws),
   81     length(Ws, N0),
   82     N is N0*3+3,
   83     length(Num, N),
   84     phrase(gen(Word), Num)
   85  ;  once(phrase(gen(Word), Num))
   86  ).
   87
   88
   89gen(Ws) --> x(Ws).
   90gen(Ws) --> x_2(Ws).
   91
   92
   93x_2(Word) -->
   94  x(W1),
   95  x(W2),
   96  {  W1 \== [zero]
   97  -> Word = [W1,thousand|Rest],
   98     (  W2 == [zero]
   99     -> Rest = []
  100     ;  Rest = W2
  101     )
  102  ;  Word = W2
  103  }.
  104
  105
  106x([Word]) -->
  107  dig(zero),
  108  dig(zero),
  109  dig(Word).
  110
  111x([Word]) -->
  112  dig(zero),
  113  special(Word).
  114
  115x(Word) -->
  116  dig(zero),
  117  ten(W1),
  118  dig(W2),
  119  {  W2 == zero
  120  -> Word = [W1]
  121  ;  Word = [W1,W2]
  122  }.
  123
  124x(Word) -->
  125  dig(W1),
  126  { W1 \== zero },
  127  % Second digit is either single digit or special number
  128  (  (  dig(zero),
  129        dig(W2)
  130     ;  special(W2)
  131     ),
  132     {  W2 == zero
  133     -> Word = [W1,hundred]
  134     ;  Word = [W1,hundred,W2]
  135     }
  136  ;  ten(W2),
  137     dig(W3),
  138     { W2 \== zero,
  139       (  W3 == zero
  140       -> Word = [W1,hundred,W2]
  141       ;  Word = [W1,hundred,W2,W3]
  142       )
  143     }
  144  ).
  145
  146
  147dig(zero) --> [0].
  148dig(one) --> [1].
  149dig(two) --> [2].
  150dig(three) --> [3].
  151dig(four) --> [4].
  152dig(five) --> [5].
  153dig(six) --> [6].
  154dig(seven) --> [7].
  155dig(eight) --> [8].
  156dig(nine) --> [9].
  157
  158
  159special(ten) --> [1,0].
  160special(eleven) --> [1,1].
  161special(twelve) --> [1,2].
  162special(thirteen) --> [1,3].
  163special(fourteen) --> [1,4].
  164special(fifteen) --> [1,5].
  165special(sixteen) --> [1,6].
  166special(seventeen) --> [1,7].
  167special(eighteen) --> [1,8].
  168special(nineteen) --> [1,9].
  169
  170
  171ten(twenty) --> [2].
  172ten(thirty) --> [3].
  173ten(forty) --> [4].
  174ten(fifty) --> [5].
  175ten(sixty) --> [6].
  176ten(seventy) --> [7].
  177ten(eighty) --> [8].
  178ten(ninety) --> [9].
  179
  180
  181beyond(3, million).
  182beyond(4, billion).
  183beyond(5, trillion).
  184beyond(6, quadrillion).
  185beyond(7, quintillion).
  186beyond(8, sextillion).
  187beyond(9, septillion).
  188beyond(10, octillion).
  189beyond(11, nonillion).
  190beyond(12, decillion).
  191beyond(13, undecillion).
  192beyond(14, duodecillion).
  193beyond(15, tredecillion).
  194beyond(16, quattuordecillion).
  195beyond(17, quindecillion).
  196beyond(18, sexdecillion).
  197beyond(19, septendecillion).
  198beyond(20, octodecillion).
  199beyond(21, novemdecillion).
  200beyond(22, vigintillion)