Reputation: 83
I am making a program that solves a puzzle. but I need to make a predicate that returns the transpose given a matrix(list of lists) and I can't use the predefined one. but whatever I do I can't get the predicate to work backwards without getting a stack limit exceeded, ex: trans([[1,2],[3,4]],X).
returns [[1,3],[2,4]]
but trans(X,[[1,3],[2,4]]).
exceeds the stack limit.
here is the trans predicate:
trans(M,M1):-
length(M,L),
trans1(0,L,M,R).
trans1(N,N,_,[]).
trans1(I,N,M,M1):-
I1 is I+1,
column(M,I1,C),
trans1(I1,N,M,M2).
and here is the column predicate that I used:
row([H|_],1,H):-!.
row([_|T],I,X) :-
I1 is I-1,
row(T,I1,X).
column([],_,[]).
column([H|T], I, [R|X]):-
row(H, I, R),
column(T,I,X).
any idea how I can use trans give the list if I give its transpose?
Upvotes: 1
Views: 296
Reputation: 60034
Many years ago, I wrote my own transpose/2, as a part of my IL project. Here it is:
% row/columns transposition
%
transpose_col_row([], []).
transpose_col_row([U], B) :- gen(U, B).
transpose_col_row([H|T], R) :- transpose_col_row(T, TC), splash(H, TC, R).
gen([H|T], [[H]|RT]) :- gen(T,RT).
gen([], []).
splash([], [], []).
splash([H|T], [R|K], [[H|R]|U]) :-
splash(T,K,U).
Despite the code doesn't use anything complicated, it's not too easy to understand what it does, and, like your own, or SWI-Prolog library(clpfd) implementation, it is not 'reversible'.
Your code has many problems you need to solve (note: singletons warnings are errors, really), but assuming you can nail them down, and get a working trans(M,T), you could use a simple 'hack', swapping arguments after checking instantiation:
trans_rev(M,T) :- var(M) -> trans(T,M) ; trans(M,T).
Let's try with my own implementation, that is
transpose_col_row_rev(M,T) :-
var(M) -> transpose_col_row(T,M) ; transpose_col_row(M,T).
?- transpose_col_row_rev([[1,2]],T).
T = [[1], [2]]
?- transpose_col_row_rev(M,$T).
M = [[1, 2]],
T = [[1], [2]]
Upvotes: 1
Reputation: 1316
You can re-assemble the predicate by looking at the publicly available, free (as in beer), open-source SWI-Prolog code. Why people don't do that more often is a mystery to me. It is very easy, but still more difficult than someone just dumping the working code on you I guess.
First, here is the (somewhat cryptic) implementation of transpose/2
in library(clpfd):
lists_transpose([], []).
lists_transpose([L|Ls], Ts) :-
maplist(same_length(L), Ls),
foldl(transpose_, L, Ts, [L|Ls], _).
transpose_(_, Fs, Lists0, Lists) :-
maplist(list_first_rest, Lists0, Fs, Lists).
list_first_rest([L|Ls], L, Ls).
This uses a predicate same_length/2
. It is defined in library(lists) and looks like this:
same_length([], []).
same_length([_|T1], [_|T2]) :-
same_length(T1, T2).
Pretty straight-forward.
Then it uses maplist
and foldl
. Are there allowed or not? If not, you can rewrite maplist(same_length(L), Ls)
as:
all_same_length([], L).
all_same_length([X|Xs], L) :-
same_length(X, L),
all_same_length(Xs, L).
Stupid code that shouldn't be written manually but well.
You can then replace maplist(same_length(L), Ls)
with all_same_length(Ls, L)
.
This leaves you with the foldl(transpose_, L, Ts, [L|Ls], _)
. This is the "cryptic" bit; this qualification was maybe meant as a compliment to the person who wrote it.
Either way, a fold written like this that ignores the last argument (the result) can be re-written as a loop not too different from the maplist above. The transpose_/4
used in the fold has a maplist in its definition, but I showed already how to do that.
Since this looks like homework I will let you figure it out on your own.
Cheat code: if you look far enough into the history of the library (all on github!) you might get super lucky and find a pre-foldl implementation of the same transpose.
Upvotes: 0