Convert peano number s(N) to integer in Prolog
Asked Answered
B

4

8

I came across this natural number evaluation of logical numbers in a tutorial and it's been giving me some headache:

natural_number(0).
natural_number(s(N)) :- natural_number(N).

The rule roughly states that: if N is 0 it's natural, if not we try to send the contents of s/1 back recursively to the rule until the content is 0, then it's a natural number if not then it's not.

So I tested the above logic implementation, thought to myself, well this works if I want to represent s(0) as 1 and s(s(0)) as 2, but I´d like to be able to convert s(0) to 1 instead.

I´ve thought of the base rule:

sToInt(0,0). %sToInt(X,Y) Where X=s(N) and Y=integer of X

So here is my question: How can I convert s(0) to 1 and s(s(0)) to 2?

Has been answered

Edit: I modified the base rule in the implementation which the answer I accepted pointed me towards:

decode(0,0). %was orignally decode(z,0).
decode(s(N),D):- decode(N,E), D is E +1.

encode(0,0). %was orignally encode(0,z).
encode(D,s(N)):- D > 0, E is D-1, encode(E,N).

So I can now use it like I wanted to, thanks everyone!

Bicker answered 21/1, 2012 at 16:6 Comment(2)
(a) Is this homework? (b) This is a standard problem - you should be able to find it in any tutorial or textbook on logic programming.Jodijodie
a)No, I'm just trying to learn Prolog b)One would think that, but I´ve spent the better half of one day trying to find an answer to this question to no availBicker
P
7

Here is another solution that works "both ways" using library(clpfd) of SWI, YAP, or SICStus

:- use_module(library(clpfd)).

natsx_int(0, 0).
natsx_int(s(N), I1) :-
   I1 #> 0,
   I2 #= I1 - 1,
   natsx_int(N, I2).
Pitts answered 28/7, 2012 at 19:32 Comment(0)
R
5

No problemo with nest_right/4 in tandem with Prolog lambdas!

:- use_module(library(lambda)).
:- use_module(library(clpfd)).

:- meta_predicate nest_right(2,?,?,?).
nest_right(P_2,N,X0,X) :-
   zcompare(Op,N,0),
   ord_nest_right_(Op,P_2,N,X0,X).

:- meta_predicate ord_nest_right_(?,2,?,?,?).
ord_nest_right_(=,_,_,X,X).
ord_nest_right_(>,P_2,N,X0,X2) :-
   N0 #= N-1,
   call(P_2,X1,X2),
   nest_right(P_2,N0,X0,X1).

Sample queries:

?- nest_right(\X^s(X)^true,3,0,N).
N = s(s(s(0))).                 % succeeds deterministically

?- nest_right(\X^s(X)^true,N,0,s(s(0))).
N = 2 ;                         % succeeds, but leaves behind choicepoint
false.                          % terminates universally
Ricker answered 3/6, 2015 at 1:54 Comment(0)
O
1

Without using clp, and using tail-end recursion (for performance):

peano_int(P, I) :-
    (   integer(I)
    ->  I @>= 0
    ;   var(I)
    ),
    peano_int_(P, 0, I).

peano_int_(P, U, I) :-
    (   U == I
    ->  ! 
    ;   P == I
    ->  !,
        % Can only happen with P & U both 0
        U == 0
    ;   I = U
    ),
    % After cuts have been performed
    P = 0.
peano_int_(s(P), U, I) :-
    U1 is U + 1,
    peano_int_(P, U1, I).

Is deterministic in all ways:

?- peano_int(P, 3).
P = s(s(s(0))).

?- peano_int(s(s(s(0))), I).
I = 3.

?- peano_int(s(s(0)), 2).
true.

?- peano_int(P, I).
P = I, I = 0 ;
P = s(0),
I = 1 ;
P = s(s(0)),
I = 2 ;

?- peano_int(P, P).
P = 0.

% Safeguards
?- peano_int(s(P), P).
false.

?- dif(P, s(0)), peano_int(P, 1).
false.

% Fast tail-end recursion, when converting to integer
?- time(peano_int(P, 1_000_000)).
% 1,000,003 inferences, 0.084 CPU in 0.084 seconds (100% CPU, 23830428 Lips)
P = s(s(s(...
Oxblood answered 5/3, 2023 at 22:12 Comment(6)
In all directions? Really? ?- peano_int(P, P). P = 0 ; loops.Pitts
And ?- peano_int(s(P),P).Pitts
Couldn't this peano_int_p_/2 be a bit more convincing? After all, this is no longer any relation. Like, ensuring that the second argument can be an integer or so.Pitts
Removed unwanted choicepoint with (P, P).Oxblood
Simplified, reduced code needed.Oxblood
Simplified, added guard against: dif(P, s(0)), peano_int(P, 1).Oxblood
S
0

Here is mine:

Peano numbers that are actually better adapted to Prolog, in the form of lists.

Why lists?

  • There is an isomorphism between
    • a list of length N containing only s and terminating in the empty list
    • a recursive linear structure of depth N with function symbols s terminating in the symbol zero
    • ... so these are the same things (at least in this context).
  • There is no particular reason to hang onto what 19th century mathematicians (i.e Giuseppe Peano ) considered "good structure structure to reason with" (born from function application I imagine).
  • It's been done before: Does anyone actually use Gödelization to encode strings? No! People use arrays of characters. Fancy that.

Let's get going, and in the middle there is a little riddle I don't know how to solve (use annotated variables, maybe?)

% ===
% Something to replace (frankly badly named and ugly) "var(X)" and "nonvar(X)"
% ===

ff(X) :- var(X).     % is X a variable referencing a fresh/unbound/uninstantiated term? (is X a "freshvar"?)
bb(X) :- nonvar(X).  % is X a variable referencing an nonfresh/bound/instantiated term? (is X a "boundvar"?)

% ===
% This works if:
% Xn is boundvar and Xp is freshvar: 
%    Map Xn from the domain of integers >=0 to Xp from the domain of lists-of-only-s.
% Xp is boundvar and Xn is freshvar: 
%    Map from the domain of lists-of-only-s to the domain of integers >=0
% Xp is boundvar and Xp is boundvar: 
%    Make sure the two representations are isomorphic to each other (map either
%    way and fail if the mapping gives something else than passed)
% Xp is freshvar and Xp is freshvar: 
%    WE DON'T HANDLE THAT!
%    If you have a freshvar in one domain and the other (these cannot be the same!)
%    you need to set up a constraint between the freshvars (via coroutining?) so that
%    if any of the variables is bound with a value from its respective domain, the
%    other is bound auotmatically with the corresponding value from ITS domain. How to
%    do that? I did it awkwardly using a lookup structure that is passed as 3rd/4th
%    argument, but that's not a solution I would like to see.
% ===

peanoify(Xn,Xp) :-
   (bb(Xn) -> integer(Xn),Xn>=0 ; true),                  % make sure Xn is a good value if bound
   (bb(Xp) -> is_list(Xp),maplist(==(s),Xp) ; true),      % make sure Xp is a good value if bound 
   ((ff(Xn),ff(Xp)) -> throw("Not implemented!") ; true), % TODO
   length(Xp,Xn),maplist(=(s),Xp).

% ===
% Testing is rewarding! 
% Run with: ?- rt(_).
% ===

:- begin_tests(peano).

test(left0,true(Xp=[]))          :- peanoify(0,Xp).
test(right0,true(Xn=0))          :- peanoify(Xn,[]).
test(left1,true(Xp=[s]))         :- peanoify(1,Xp).
test(right1,true(Xn=1))          :- peanoify(Xn,[s]).
test(left2,true(Xp=[s,s]))       :- peanoify(2,Xp).
test(right2,true(Xn=2))          :- peanoify(Xn,[s,s]).
test(left3,true(Xp=[s,s,s]))     :- peanoify(3,Xp).
test(right3,true(Xn=3))          :- peanoify(Xn,[s,s,s]).
test(f1,fail)                    :- peanoify(-1,_).
test(f2,fail)                    :- peanoify(_,[k]).
test(f3,fail)                    :- peanoify(a,_).
test(f4,fail)                    :- peanoify(_,a).
test(f5,fail)                    :- peanoify([s],_).
test(f6,fail)                    :- peanoify(_,1).
test(bi0)                        :- peanoify(0,[]).
test(bi1)                        :- peanoify(1,[s]).
test(bi2)                        :- peanoify(2,[s,s]).

:- end_tests(peano).

rt(peano) :- run_tests(peano).
Sharpset answered 30/5, 2020 at 23:19 Comment(0)

© 2022 - 2024 — McMap. All rights reserved.