Relate Roman and Arabic numerals

585 views Asked by At

How to relate Roman and Arabic numerals up to 899999 in a pure manner? And this time without using arithmetic! Thus without (is)/2 nor clpfd/clpz/clpq. Lacking any means to relate to integers, Arabic numerals have to be represented as a list of characters. Thus :- set_prolog_flag(double_quotes, chars).. The characters used for Roman numbers are below.

As usual, Arabic numerals do not have leading zeroes, nor spaces in between, the Roman numerals use the "common" subtractive rules. See below.

What I have tried so far was to use integers. But this here should be without them. Efficiency isn't the goal, but termination is.

The pure part includes dif/2 and dif_si/2 although 90 facts could express the inequality between decimal digits as well.

?- arabic_roman(A,R) , false.
   false.  % it terminates, we have only 899999 numbers, very finite
?- arabic_roman("0",R).
   false. % no zero
?- arabic_roman(['0'|_],R).
   false. % and in general no leading zeros
?- R=[_], arabic_roman(A,R).
   R = "I", A = "1"
;  R = "V", A = "5"
;  R = "X", A = "10"
;  R = "L", A = "50"
;  R = "C", A = "100"
;  R = "D", A = "500" % no apostrophus "IↃ"
;  R = "M", A = "1000" % no "CIↃ"
;  R = "ↁ", A = "5000" % idem
;  R = "ↂ", A = "10000"
;  R = "ↇ", A = "50000"
;  R = "ↈ", A = "100000"
;  R = "@", A = "500000" % poor support in Unicode
;  false.
?- arabic_roman("899999",R).
   R = "@ↈↈↈↂↈMↂCMXCIX" % the largest number
;  false.
?- arabic_roman(  ['9',_,_, _,_,_],R).
   false. % no six digit number starting with 9
?- arabic_roman( [_, _,_,_, _,_,_|_],R).
   false. % no seven or more digit numbers
?- setof(R,A^arabic_roman(A,R),Rs),length(Rs,N).
   Rs = ["@","@C","@CC","@CCC"|_], N = 899999.  % terms omitted at _
?- setof(A,R^arabic_roman(A,R),As),length(As,N).
   As = ["1","10","100","1000","10000","100000","100001"|_], N = 899999.
?- setof(A-R,arabic_roman(A,R),ARs),length(ARs,N).
   ARs = ["1"-"I","10"-"X","100"-"C","1000"-"M","10000"-"ↂ"|_], N = 899999.
?- arabic_roman(A,"IL").
   false. % no generalized subtractive rule
?- arabic_roman(A,"IM").
   false. % idem
?- arabic_roman(A,R), phrase((...,[X,X,X,X],...),R).
   false.
3

There are 3 answers

10
notoria On BEST ANSWER

With 15 clauses (depending how we are counting). It terminates.

:- use_module(library(dcgs)).
:- use_module(library(lists)).
:- use_module(library(dif)).

foldl(G__3, [], S, S) --> [].
foldl(G__3, [E|Es], S0, S) --> call(G__3, E, S0, S1), foldl(G__3, Es, S1, S).

d5u('0', s([R10|Rs],[R5,R1|Ds]), s([R1,R5,R10|Rs],Ds)) --> [].
d5u('1', s(Rs,[R5,R1|Ds]), s([R1,R5|Rs],Ds)) --> [R1].
d5u('2', s(Rs,[R5,R1|Ds]), s([R1,R5|Rs],Ds)) --> [R1,R1].
d5u('3', s(Rs,[R5,R1|Ds]), s([R1,R5|Rs],Ds)) --> [R1,R1,R1].
d5u('4', s(Rs,[R5,R1|Ds]), s([R1,R5|Rs],Ds)) --> [R1,R5].
d5u('5', s(Rs,[R5,R1|Ds]), s([R1,R5|Rs],Ds)) --> [R5].
d5u('6', s(Rs,[R5,R1|Ds]), s([R1,R5|Rs],Ds)) --> [R5,R1].
d5u('7', s(Rs,[R5,R1|Ds]), s([R1,R5|Rs],Ds)) --> [R5,R1,R1].
d5u('8', s(Rs,[R5,R1|Ds]), s([R1,R5|Rs],Ds)) --> [R5,R1,R1,R1].
d5u('9', s([R10|Rs],[R5,R1|Ds]), s([R1,R5,R10|Rs],Ds)) --> [R1,R10].

au5(_, s([R1,R5|Rs0],Rs), s(Rs0,[R5,R1|Rs])).

arabic_roman([C|Cs]) -->
    { foldl(au5, [C|Cs], s("IVXLCDMↁↂↇↈ@",[]), S0) },
    foldl(d5u,[C|Cs], S0, s([_|_],[])),
    { dif(C, '0') }.

arabic_roman(A, R) :-
    phrase(arabic_roman(A), R).
10
gusbro On

Here is my solution. I have changed some roman symbols because my setup has poor support for unicode, so P is 5000, T is 10000, F is 50000, Q is 100000 and @ is 500000.

:- set_prolog_flag(double_quotes, chars).

arabic_roman(A, R):- phrase(arabic_roman(A), R).

arabic_roman([A|As])-->
  { dif(A, '0') },
  arabic_roman_skip("Q@!TFMPCDXLIV!!", [A|As]).

arabic_roman_skip([P,_,_,P1,C1|S], As)-->
  arabic_roman_skip([P1,C1,P|S], As).
arabic_roman_skip(S, As)-->
  arabic_roman(S, As).

arabic_roman("!!I", [])-->[].
arabic_roman([P,C,N,P1,C1|S], [A|As])-->
  arabic_digit_roman(A, P,C,N),
  arabic_roman([P1,C1,P|S], As).

arabic_digit_roman('0', _,_,_) --> [].
arabic_digit_roman('1', P,_,_) --> [P].
arabic_digit_roman('2', P,_,_) --> [P,P].
arabic_digit_roman('3', P,_,_) --> [P,P,P].
arabic_digit_roman('4', P,C,_) --> [P,C].
arabic_digit_roman('5', _,C,_) --> [C].
arabic_digit_roman('6', P,C,_) --> [C,P].
arabic_digit_roman('7', P,C,_) --> [C,P,P].
arabic_digit_roman('8', P,C,_) --> [C,P,P,P].
arabic_digit_roman('9', P,_,N) --> [P,N], {dif(N,'!')}.

Sample runs:

?- arabic_roman("899999",R).
R = [@, 'Q', 'Q', 'Q', 'T', 'Q', 'M', 'T', 'C', 'M', 'X', 'C', 'I', 'X'].
?- time((setof(A1,R^A^(arabic_roman(A,R), atom_codes(A1,A)),As),length(As,N))).
% 3,118,631 inferences, 1.841 CPU in 1.879 seconds (98% CPU, 1694161 Lips)
As = ['1', '10', '100', '1000', '10000', '100000', '100001', '100002', '100003'|...],
N = 899999.
5
brebs On

Doesn't quite seem worth using DCG:

% Need nan, to fill the last group of [I, V, X]
roman_chars(['I', 'V', 'X', 'L', 'C', 'D', 'M', 'ↁ', 'ↂ', 'ↇ', 'ↈ', '@', nan]).

arabic_digit_roman('0', _I, _V, _X, T, T).
arabic_digit_roman('1', I, _, _, [I|T], T).
arabic_digit_roman('2', I, _, _, [I, I|T], T).
arabic_digit_roman('3', I, _, _, [I, I, I|T], T).
arabic_digit_roman('4', I, V, _, [I, V|T], T).
arabic_digit_roman('5', _, V, _, [V|T], T).
arabic_digit_roman('6', I, V, _, [V, I|T], T).
arabic_digit_roman('7', I, V, _, [V, I, I|T], T).
arabic_digit_roman('8', I, V, _, [V, I, I, I|T], T).
arabic_digit_roman('9', I, _, X, [I, X|T], T) :-
    dif(X, nan).

arabic_roman(A, R) :-
    % No leading zero
    A = [First|_],
    dif(First, '0'),
    roman_chars(RCs),
    arabic_roman_(A, RCs, R).

arabic_roman_([], _, []).
arabic_roman_([AH|AT], RCs, R) :-
    arabic_length(AT, RCs, I, V, X, RCs0),
    arabic_digit_roman(AH, I, V, X, R, T),
    arabic_roman_(AT, RCs0, T).
    
arabic_length([], [I, V, X|_], I, V, X, [I]).
arabic_length([_|T], [II, VV|R], I, V, X, [II, VV|RC]) :-
    arabic_length(T, R, I, V, X, RC).

There are no unwanted choicepoints when the Arabic list is ground, e.g.:

?- arabic_roman(['1', '2', '3', '4', '5', '6'], R).
R = [ↈ, ↂ, ↂ, 'M', 'M', 'M', 'C', 'D', 'L', 'V', 'I'].

Performance in swi-prolog:

?- time((bagof(A-R, arabic_roman(A, R), ARs), length(ARs, N))).
% 2,312,762 inferences, 0.726 CPU in 0.726 seconds (100% CPU, 3184610 Lips)
ARs = [['1']-['I'], ['2']-['I', 'I'], ['3']-['I', 'I', 'I'], ...
N = 899999.