Skip to content

Commit

Permalink
add one way (num -> name) support for { N : abs(N) > 999 }
Browse files Browse the repository at this point in the history
  • Loading branch information
zmughal committed Nov 18, 2011
1 parent a4f4c42 commit 813ae1f
Show file tree
Hide file tree
Showing 2 changed files with 62 additions and 13 deletions.
55 changes: 44 additions & 11 deletions numberals.pl
Original file line number Diff line number Diff line change
@@ -1,5 +1,13 @@
% Numberals

%:- use_module(library(chr)).
%:- chr_type digit ---> 0; 1; 2; 3; 4; 5; 6; 7; 8; 9.
%:- chr_type positional_system ---> [digit]; [digit|list(digit)]; ['-', digit|list(digit)].
%:- chr_type list(T) ---> []; [T|list(T)].
%:- chr_constraint chr_number_to_name(?positional_system, ?list(int)).
%chr_number_to_name([0], "zero") ==> true.


isdigit(X) :- member(X, [0,1,2,3,4,5,6,7,8,9]).

% number <-> name table {{{
Expand Down Expand Up @@ -34,6 +42,7 @@
number_to_name_t([9,0], "ninety").
% }}}
% powers table {{{
power_name(0, "").
power_name(3, "thousand").
power_name(6, "million").
power_name(9, "billion").
Expand All @@ -60,13 +69,11 @@
Positive \= [-|_],
number_to_name(Positive, Positive_Name),
append(["negative ", Positive_Name], Name).
number_to_name(Number, Name) :-
number_to_name([-|Positive], Name) :-
ground(Name),
append(["negative ", Positive_Name], Name),
number_to_name(Positive, Positive_Name),
Positive \= [-|_],
Number = [-|Positive].

Positive \= [-|_].
% }}}
% tens {{{
% Num >= 21, Num =< 99,
Expand All @@ -82,7 +89,9 @@
number_to_name([Tens, Ones], Name) :-
ground(Name),
append([Tens_Name, "-", Ones_Name], Name),
isdigit(Tens),
number_to_name_t([Tens, 0], Tens_Name),
isdigit(Ones),
number_to_name_t([ Ones ], Ones_Name).
% }}}
% hundreds {{{
Expand All @@ -100,16 +109,37 @@
ground(Name),
append([Hundreds_Name, " hundred", Rest_Name], Name),
number_to_name_t( [Hundreds], Hundreds_Name),
Hundreds > 0,
isdigit(Hundreds), Hundreds > 0,
isdigit(Tens), isdigit(Ones),
hundred_build([Tens, Ones], Rest_Name).
% }}}

% group {{{
number_to_name(Num, Name) :-
ground(Num), length(Num, NumL), NumL > 3,
append(First, NumNext, Num),
length(First, First_l), First_l < 4,
length(NumNext, NumNext_l), NumNext_l mod 3 =:= 0,
number_to_name_add_prefix(First, FirstPrefix),
FirstPrefix \= [0, 0, 0],
append(FirstPrefix, NumNext, PrefixNum),
number_to_name_group(PrefixNum, Name, NumNext_l).
number_to_name_group([H,T,O|NumNext], Name, Group) :-
Group >= 0,
( [H, T, O] = [0, 0, 0] -> Group_Name = ""; power_name(Group, Group_Name) ),
(Group_Name \= "" -> Space = " "; Space = ""),
number_to_name_prefix([H,T,O], Group_Prefix),
GroupNext is Group - 3,
number_to_name_group(NumNext, NameNext, GroupNext),
append([Group_Prefix, Space, Group_Name, NameNext], Name).
number_to_name_group([], "", _).
% }}}
% hundred helpers {{{
number_to_name_prefix([ 0, 0, 0], "").
number_to_name_prefix([ 0, Tens, Ones], Name) :- number_to_name( [Tens, Ones], Name).
number_to_name_prefix([Hundreds, Tens, Ones], Name) :- number_to_name( [Hundreds, Tens, Ones], Name).
number_to_name_prefix([ 0, 0, Ones], Name) :- Ones \= 0, number_to_name( [Ones], Name).
number_to_name_prefix([ 0, Tens, Ones], Name) :- Tens \= 0, number_to_name( [Tens, Ones], Name).
number_to_name_prefix([Hundreds, Tens, Ones], Name) :- [Hundreds, Tens] \= [0, 0], number_to_name( [Hundreds, Tens, Ones], Name).
number_to_name_prefix([ 0, Ones], Name) :- number_to_name( [Ones], Name).
number_to_name_prefix([Tens, Ones], Name) :- number_to_name( [Tens, Ones], Name).
number_to_name_prefix([Tens, Ones], Name) :- Tens \= 0, number_to_name( [Tens, Ones], Name).
number_to_name_prefix([One], Name) :- number_to_name([One], Name).

hundred_build( [Tens, Ones], Rest_Name) :-
Expand All @@ -120,13 +150,16 @@
hundred_build( [Tens, Ones], Rest_Name) :-
ground(Rest_Name),
append([" and ", Rest_Name_Part], Rest_Name),
isdigit(Tens), isdigit(Ones),
number_to_name_prefix([Tens, Ones], Rest_Name_Part),
[Tens, Ones] \= [ 0, 0].
hundred_build( [0, 0], "").
% }}}

% }}}

% -->
number_to_name_add_prefix([H,T,O], [H,T,O]).
number_to_name_add_prefix([ T,O], [0,T,O]).
number_to_name_add_prefix([ O], [0,0,O]).


% vim:ft=prolog:fdm=marker
20 changes: 18 additions & 2 deletions numberals.plt
Original file line number Diff line number Diff line change
Expand Up @@ -14,26 +14,30 @@ test_both_ways(Num, Name) :-
test_name_fail(Name) :-
log_writef( 'Testing name %s : ', [Name]),
(\+ number_to_name(_, Name) -> log_writef('not found - ok'), log_writef('\n');
log_writef('found - fail'), log_writef('\n')), log_writef('\n').
log_writef('found - fail'), log_writef('\n'), fail), log_writef('\n').
test_num_fail(Num) :-
log_writef( 'Testing number %q : ', [Num]),
(\+ number_to_name(Num, _) -> log_writef('not found - ok'), log_writef('\n');
log_writef('found - fail'), log_writef('\n')), log_writef('\n').
log_writef('found - fail'), log_writef('\n'), fail), log_writef('\n').

test_both_ways_test([0], "zero").
test_both_ways_test(['-',0], "negative zero"). % signed zero

test_both_ways_test([1,0], "ten").
test_both_ways_test([-,1,0], "negative ten").
test_both_ways_test([1,4], "fourteen").
test_both_ways_test([-,1,4], "negative fourteen").

test_both_ways_test([2,0], "twenty").
test_both_ways_test([-,2,0], "negative twenty").
test_both_ways_test([2,1], "twenty-one").
test_both_ways_test([-,2,1], "negative twenty-one").

test_both_ways_test([3,2], "thirty-two").
test_both_ways_test([-,3,2], "negative thirty-two").
test_both_ways_test([3,5], "thirty-five").
test_both_ways_test([-,3,5], "negative thirty-five").

test_both_ways_test([1, 3,5], "one hundred and thirty-five").
test_both_ways_test([-,1, 3,5], "negative one hundred and thirty-five").
test_both_ways_test([1,0,0], "one hundred").
Expand All @@ -51,9 +55,19 @@ test_both_ways_test([-,3,1,0], "negative three hundred and ten").
test_both_ways_test([9,9,9], "nine hundred and ninety-nine").
test_both_ways_test([-,9,9,9], "negative nine hundred and ninety-nine").

test_both_ways_test([-,9,9,9], "negative nine hundred and ninety-nine").

test(test_both_ways, [nondet, forall( test_both_ways_test(Num, Name) )]) :-
test_both_ways(Num, Name).

test_to_name_test([1,0,0,0], "one thousand").
test_to_name_test([1,0,0,0,0,0,0], "one million").
test_to_name_test([2,0,0,0,0,0,0], "two million").
test_to_name_test([1,0,2,0,0,0,0,0,0], "one hundred and two million").
test_to_name_test([-,1,0,2,0,0,0,0,0,0], "negative one hundred and two million").
test(test_to_name, [nondet, forall( test_to_name_test(Num, Name) )]) :-
number_to_name(Num, Test_Name), Test_Name = Name.

test_name_fail_test("zero hundred").
test(test_name_fail, [nondet, forall( test_name_fail_test(Name) )]) :-
test_name_fail(Name).
Expand All @@ -62,6 +76,8 @@ test_num_fail_test([1,-,0]).
test_num_fail_test([-,-,0]).
test_num_fail_test([-,-,-]).
test_num_fail_test([0,0,0]).
test_num_fail_test([0,0,0,0]).
test_num_fail_test([-,-,-,-]).
test(test_num_fail, [nondet, forall( test_num_fail_test(Num) )]) :-
test_num_fail(Num).

Expand Down

0 comments on commit 813ae1f

Please sign in to comment.