vasily
vasily

Reputation: 2920

Flattening a list

Trying to solve exercise 07 from http://www.ic.unicamp.br/~meidanis/courses/mc336/2009s2/prolog/problemas/

I've started with a single iteration which looks like following

my_flatten1([], []).
my_flatten1([[A|T]|U], [A|V]) :-
   append(T, U1, V),
   my_flatten1(U, U1).
my_flatten1([A|T], [A|U]) :-
   not(is_list(A)),
   my_flatten1(T, U).

is_flat(A) :-
   my_flatten1(A, A).

it seems to work just fine for the following set of queries

my_flatten1([a, [b, [c, d], e]], X).
my_flatten1(X, [a, b, c]).
my_flatten1(X, [a|T]).
my_flatten1(X, [a, b, A]).
my_flatten1([a, X], M).
my_flatten1([a|X], M).

is_flat([a|X]).
is_flat([a,[c]|X]).
is_flat([F,[c]|X]).

my_flatten1(A, B).
my_flatten1([A], B).
my_flatten1([[A]], B).
my_flatten1([[a|A]], B).
my_flatten1([a|A], B).
my_flatten1([X|B], [1,2,3,4]).
my_flatten1([[a,c|D]|X], [a|B]).

However I wasn't successful to build my_flatten based on my_flatten1. There's always some queries that fail or end up in endless loops, or produce just one, most obvious result.

Edit to clarify what I am after, for example I can call my_flatten1 with a variable as a first argument in order to distribute brackets:

?- my_flatten1(X, [a, b]).
X = [[a], [b]] ;
X = [[a], b] ;
X = [[a, b]] ;
X = [a, [b]] ;
X = [a, b].

Upvotes: 5

Views: 2151

Answers (3)

Kintalken
Kintalken

Reputation: 783

  :- [library(plunit)] .

  :- abolish(flatten/2) .
  :- mode(flatten(+,-)) .

  flatten(0,_) --> [Q] , flatten(1,Q) .
  flatten(1,Q) --> \+ {is_list(Q)} , flatten(2,Q) .
  flatten(1,Q) --> \+ \+ {is_list(Q)} , flatten(3,Q) .
  flatten(2,Q) , [Q] --> flatten(0,_) .
  flatten(3,Q) --> {Q=[]} , flatten(0,_) .
  flatten(3,Q) --> {Q=[R|Ts]} , flatten(1,R) , flatten(1,Ts) .

  :- begin_tests(flatten) .

  test('1',[true(Ps=[4,5,6,7,8,9,1,2])]) :-
  flatten([4,5,[6],[7,8,9],[1,2]],Ps) .

  test('2',[true(Ps=[1,2,3,4])]) :-
  flatten([1,[2,3],[],4],Ps) .

  test('3',[true(Ps=Qs)]) :-
  flatten(Qs,Ps) .

  :- end_tests(flatten) .

/* sample run .

  ?- run_tests .

  % PL-Unit: flatten ... done               
  % All 3 tests passed

  ?- flatten([1,[2,3],[],4],Ps).
  Ps = [1,2,3,4].

  ?- flatten([4,5,[6],[7,8,9],[1,2]],Ps) .
  Ps = [4,5,6,7,8,9,1,2].

  ?- flatten(Qs,Ps) .
  Ps = [Qs].

*/

Upvotes: 0

Zebollo
Zebollo

Reputation: 1

This straightforward implementation is not reversible, but it does not inccur in infinite loops. It will fail, instead.

flat2([],[]) :- 
    !.
flat2(X,[X]) :-
    X \= [_|_],
    !.
flat2([X|R],Result) :-
    flat2(X,XF),
    flat2(R,XR),
    append(XF,XR,Result).

Test:

?- flat2([[a,b],[c,[d,e,[f]]]],X).
X = [a, b, c, d, e, f].

Test (reverse):

?- flat2(X,[1,2]).
false.
?- flat2(X,[X]).
false.

It may be simplified, but this implementation is not reversible and will inccur in infinite loops in such case:

flat([X|R],Result) :-
    !,
    flat(X,XF),
    flat(R,XR),
    append(XF,XR,Result).

flat([],[]) :- !.
flat(X,[X]).

Upvotes: 0

SND
SND

Reputation: 1557

I'm not sure if you are aware that the 99 Prolog problems contain solutions when you click on the problem title?

Anyways, my_flatten looks, for example, like following:

my_flatten(X,[X]) :- \+ is_list(X).
my_flatten([],[]).
my_flatten([H|T],R) :-
    my_flatten(H,HFlat),
    my_flatten(T,TFlat),
    append(HFlat,TFlat,R).

Some queries:

?- my_flatten([[]],R).
   R = [].

?- my_flatten([[1],[2]],R).
   R = [1, 2].

?- my_flatten([[1],[[3]]],R).
   R = [1, 3].

EDIT

As correctly observed by @lambda.xy.y, above version does not terminate for the query:

?- my_flatten(X,[X]).

So I took a look at the behaviour of SWI's built-in flatten/2 and observed:

?- flatten([],[]).
   true.

?- flatten([],X).
   X = [].

?- flatten(X,[]).
   false.

?- flatten(X,Y).
   Y = [X].

?- flatten(X,[X]).
   true.

Implementation:

my_flatten(L,R) :-
    my_flatten(L,[],Flat),
    !,
    R=Flat.

my_flatten(X,R,[X|R])  :- \+ is_list(X), !.
my_flatten([],R,R)     :- !.
my_flatten([H|T],A1,R) :- !,
    my_flatten(H,A2,R),
    my_flatten(T,A1,A2).
my_flatten(NonList,T,[NonList|T]).

Upvotes: 2

Related Questions