Bobazonski
Bobazonski

Reputation: 1565

Prolog: Take the first "N" elements of a list

I need to write a Prolog predicate take(L, N, L1) which succeeds if list L1 contains the first N elements of list L, in the same order. For example:

?- take([5,1,2,7], 3, L1).
L1 = [5,1,2]
?- take([5,1,2,7], 10, L1).
L1 = [5,1,2,7] 

Prolog thus far is making little sense to me, and I'm having a hard time breaking it down. Here is what I have so far:

take([H|T], 0, []).
take([H|T], N, L1) :-
   take(T, X, L2),
   X is N-1.

Can you please explain what I did wrong here?

Upvotes: 9

Views: 14775

Answers (8)

Trevor Merrifield
Trevor Merrifield

Reputation: 4701

You can squeeze a little more generality out with reif and clpfd.

:- use_module(library(reif)).
:- use_module(library(clpfd)).
take(N, Xs, Xs1) :-
    N #>= 0,
    if_(;(N = 0, Xs = []),
        Xs1 = [],
        (
            [H|T]=Xs,
            [H|T1]=Xs1,
            N1 #= N - 1,
            take(N1, T, T1)
        )).

Note: If you replace the ;(N = 0, Xs = []) (by the way, the ;/3 comes from reif) in the code with just N = 0, then the implementation no longer tolerates the case where N > length of Xs.

It works deterministically for both examples in the original question.

?- take(3, [5,1,2,7], L1).
L1 = [5,1,2].
?- take(10, [5,1,2,7], L1).
L1 = [5,1,2,7] 

Handles the query given as an example in false's answer

?- take(2, Xs, Ys).
Xs = Ys, Ys = [] ;
Xs = Ys, Ys = [_] ;
Xs = [_A, _B|_],
Ys = [_A, _B].

And in other directions. (I think any direction, if I'm not missing something).

?- take(N, [3,4,5], [3,4]).
N = 2 ;
false.

Upvotes: 0

brebs
brebs

Reputation: 4456

This is performant, general and deterministic:

first_elements_of_list(IntElems, LongLst, ShortLst) :-
    LongLst = [H|T],
    (   nonvar(IntElems) -> Once = true
    ;   is_list(ShortLst) -> Once = true
    ;   Once = false
    ),
    first_elements_of_list_(T, H, 1, IntElems, ShortLst),
    (Once = true -> ! ; true).

first_elements_of_list_([], H, I, I, [H]).

first_elements_of_list_([_|_], H, I, I, [H]).

first_elements_of_list_([H|LongLst], PrevH, Upto, IntElems, [PrevH|ShortLst]) :-
    Upto1 is Upto + 1,
    first_elements_of_list_(LongLst, H, Upto1, IntElems, ShortLst).

Result in swi-prolog:

?- first_elements_of_list(N, [a, b, c], S).
N = 1,
S = [a] ;
N = 2,
S = [a,b] ;
N = 3,
S = [a,b,c].

?- first_elements_of_list(2, [a, b, c], S).
S = [a,b].

Below is a variant which also supports:

?- first_elements_of_list_more(10, [5, 1, 2, 7], L1).
L1 = [5,1,2,7].
first_elements_of_list_more(IntElems, [H|LongLst], [H|ShortLst]) :-
    once_if_nonvar(IntElems, first_elements_of_list_more_(LongLst, 1, IntElems, ShortLst)).

first_elements_of_list_more_([], Inc, Elems, []) :-
    (var(Elems) -> Inc = Elems
    ; Elems >= Inc).

first_elements_of_list_more_([_|_], E, E, []).

first_elements_of_list_more_([H|LongLst], Upto, IntElems, [H|ShortLst]) :-
    succ(Upto, Upto1),
    first_elements_of_list_more_(LongLst, Upto1, IntElems, ShortLst).

once_if_nonvar(Var, Expr) :-
    nonvar(Var, Bool),
    call(Expr),
    (Bool == true -> ! ; true).

nonvar(Var, Bool) :-
    (nonvar(Var) -> Bool = true ; Bool = false).

Upvotes: 0

repeat
repeat

Reputation: 18726

The code by @CapelliC works if the instantiation is right; if not, it can show erratic behavior:

?- take(Es, 0, Xs).
**LOOPS**                   % trouble: goal does not terminate

?- take([A,_], 1, [x]).          
true.                       % trouble: variable A remains unbound

To safeguard against this you can use iwhen/2 like so:

take(Src, N, L) :-
   iwhen(ground(N+Src), findall(E, (nth1(I,Src,E), I =< N), L)).

Sample queries run with SWI-Prolog 8.0.0:

?- take([a,b,c,d,e,f], 3, Ls).
Ls = [a,b,c].

?- take([a,b,c,d,e,f], N, Ls).
ERROR: Arguments are not sufficiently instantiated

?- take(Es, 0, Xs).
ERROR: Arguments are not sufficiently instantiated

?- take([A,_], 1, [x]).
ERROR: Arguments are not sufficiently instantiated

Safer now!

Upvotes: 3

false
false

Reputation: 10152

Here is a definition that implements the relational counterpart to take in functional languages like Haskell1. First, the argument order should be different which facilitates partial application. There is a cut, but only after the error checking built-in (=<)/2 which produces an instantiation_error should the argument contain a variable.

take(N, _, Xs) :- N =< 0, !, N =:= 0, Xs = [].
take(_, [], []).
take(N, [X|Xs], [X|Ys]) :- M is N-1, take(M, Xs, Ys).

?- take(2, Xs, Ys).
   Xs = [], Ys = []
;  Xs = [_A], Ys = [_A]
;  Xs = [_A,_B|_C], Ys = [_A,_B].

Note how above query reads:

How can one take 2 elements from Xs to get Ys?

And there are 3 different answers. If Xs is empty, then so is Ys. If Xs is a list with one element, then so is Ys. If Xs has at least 2 elements, then those two are Ys.


1) The only difference being that take(-1, Xs,Ys) fails (for all Xs, Ys). Probably the best would be to issue a domain_error similar to arg(-1,s(1),2)

Upvotes: 8

rajashekar
rajashekar

Reputation: 3793

take(L, N, L1) :- length(L1, N), append(L1, _, L).

Upvotes: 0

Rasika Weragoda
Rasika Weragoda

Reputation: 984

your base case is fine

take([H|T], 0, []).

And also you can say what if N is 1

take([H|T],1,[H]).

But you recursive case some variable is not defined like L2. So we can write this as

take([X|T1],N,[X|T2]):-
N>=0,
N1 is N-1,
take(T1,N1,T2).

which case all varibles are pattern-matched.

Upvotes: 1

CapelliC
CapelliC

Reputation: 60034

findall/3 it's a bit the 'swiss knife' of Prolog. I would use this snippet:

take(Src,N,L) :- findall(E, (nth1(I,Src,E), I =< N), L).

Upvotes: 3

user1812457
user1812457

Reputation:

The obvious solution would be:

take(List, N, Prefix) :-
    length(List, Len),
    (   Len =< N
    ->  Prefix = List
    ;   length(Prefix, N),
        append(Prefix, _, List)
    ).

Less thinking means less opportunity for mistakes. It also makes the predicate more general.

Upvotes: 1

Related Questions