-1

I write code in swi-prolog to solve Second End View Pazzles 7*7 (example http://www.funwithpuzzles.com/2009/10/abcd-second-end-view-ev4.html like this 5*5) for numbers 1-6

:- [library(clpfd)].

gen_row(Ls):-length(Ls, 7), Ls ins 0..6.

abc_view :-

maplist(gen_row, [R1,R2,R3,R4,R5,R6,R7]),
transpose([R1,R2,R3,R4,R5,R6,R7], [C1,C2,C3,C4,C5,C6,C7]),
maplist(all_distinct, [R1,R2,R3,R4,R5,R6,R7]),
maplist(all_distinct, [C1,C2,C3,C4,C5,C6,C7]),

start(R1, 4),
start(R2, 2),
start(R3, 3),
start(R4, 5),
start(R5, 3),
finish(R1, 6),
finish(R2, 4),
finish(R3, 2),
finish(R5, 1),
finish(R7, 2),

start(C2, 3),
start(C3, 4),
start(C4, 3),
start(C5, 5),
start(C6, 4),
start(C7, 1),
finish(C1, 3),
finish(C2, 2),
finish(C3, 5),
finish(C4, 5),
finish(C5, 6),
finish(C6, 1),
finish(C7, 4),

    maplist(writeln, [R1,R2,R3,R4,R5,R6,R7]).

How logic i need to write to solve it, maybe on more simple example for 4*4 or 5*5.. i'll be happy for any help. i need to write it for 3 tests but it will be grait for even one.

false
  • 10,264
  • 13
  • 101
  • 209
Oona
  • 3
  • 4
  • 2
    I think you can't use all_distinct on all rows/cols, because 0 (the empty cell, isn't it?) can appear more times... – CapelliC Oct 04 '12 at 06:46
  • i don't understand good in what situations i must use distinct and what will be better for my task, there can be only one empty cell, yes here its 0, in every row and col. it's my first and last lab in university so i'm badly know prolog. – Oona Oct 07 '12 at 22:19
  • you're right. I misunderstood the puzzle, description, as a (deleted) comment from someone else already pointed out. – CapelliC Oct 07 '12 at 22:22
  • i find your answer for another task that looks some like this,but i don't understand it's full code, because it don't wirk in my swi-prolog, it always write false.. ?- abc_view. false. p.s. i'm sorry for my fool( http://stackoverflow.com/questions/10686773/end-view-puzzle-prolog – Oona Oct 07 '12 at 22:25
  • i didn't see deleted comment. what it was about – Oona Oct 07 '12 at 22:27
  • That comment just remarked I'm wrong stating that you can't use all_different here. About this puzzle, it seems a bit more easy than Skyscrapes and Fences (that one I answered) but still rather difficult. – CapelliC Oct 07 '12 at 22:58
  • The problem is rather 'small', maybe CLP(FD) is overkill. – CapelliC Oct 07 '12 at 23:07

1 Answers1

0

I got a solution, effectively the problem is much more simple that the 'SkyScrape & Fences' puzzle I solved previously.

I'm afraid I previously misunderstood the problem and placed a wrong comment, suggesting you to abandon the (right) path you already took.

/*  File:    second_end_view_puzzle.pl
    Author:  Carlo,,,
    Created: Oct  8 2012
    Purpose: help to solve Second End View puzzle as quested at
             https://stackoverflow.com/q/12717609/874024
*/


:- [library(clpfd)].

gen_row(Ls) :-
    length(Ls, 7),
    Ls ins 0..6.

abc_view :-

    Rows = [R1,R2,R3,R4,R5,_R6,R7],
    maplist(gen_row, Rows),
    transpose(Rows, [C1,C2,C3,C4,C5,C6,C7]),
    maplist(all_distinct, Rows),
    maplist(all_distinct, [C1,C2,C3,C4,C5,C6,C7]),

    start(R1, 4),
    start(R2, 2),
    start(R3, 3),
    start(R4, 5),
    start(R5, 3),
    finish(R1, 6),
    finish(R2, 4),
    finish(R3, 2),
    finish(R5, 1),
    finish(R7, 2),

    start(C2, 3),
    start(C3, 4),
    start(C4, 3),
    start(C5, 5),
    start(C6, 4),
    start(C7, 1),
    finish(C1, 3),
    finish(C2, 2),
    finish(C3, 5),
    finish(C4, 5),
    finish(C5, 6),
    finish(C6, 1),
    finish(C7, 4),

    maplist(label, Rows),
    maplist(writeln, Rows).

% place the constraint 'SECOND in that direction' using a reified check
start(Vars, Num) :-
    Vars = [A,B,C|_],
    X #<==> ( A #= 0 #\/ B #= 0 ) #/\ C #= Num,
    Y #<==> A #\= 0 #/\ B #= Num,
    X + Y #= 1 .

finish(Vars, Num) :-
    reverse(Vars, Sarv), start(Sarv, Num).

edit test:

?- abc_view.
[5,4,0,2,1,6,3]
[6,0,2,3,5,4,1]
[1,3,4,6,2,5,0]
[2,5,1,4,0,3,6]
[0,6,3,5,4,1,2]
[3,2,5,1,6,0,4]
[4,1,6,0,3,2,5]
true ;
false.

edit here is the 'porting' to GnuProlog. I've copied from SWI-Prolog CLP(FD) library the transpose/2 code.

/*  File:    second_end_view_puzzle.pl
    Author:  Carlo,,,
    Created: Oct  8 2012
    Purpose: help to solve Second End View puzzle as quested at
             https://stackoverflow.com/q/12717609/874024
*/

gen_row(Ls) :-
    length(Ls, 7),
    fd_domain(Ls, 0, 6).

transpose(Ms, Ts) :-
        %must_be(list(list), Ms),
        (   Ms = [] -> Ts = []
        ;   Ms = [F|_],
            transpose(F, Ms, Ts)
        ).

transpose([], _, []).
transpose([_|Rs], Ms, [Ts|Tss]) :-
        lists_firsts_rests(Ms, Ts, Ms1),
        transpose(Rs, Ms1, Tss).

lists_firsts_rests([], [], []).
lists_firsts_rests([[F|Os]|Rest], [F|Fs], [Os|Oss]) :-
        lists_firsts_rests(Rest, Fs, Oss).

writeln(X) :- write(X), nl.

abc_view :-

    Rows = [R1,R2,R3,R4,R5,_R6,R7],
    maplist(gen_row, Rows),
    transpose(Rows, [C1,C2,C3,C4,C5,C6,C7]),
    maplist(fd_all_different, Rows),
    maplist(fd_all_different, [C1,C2,C3,C4,C5,C6,C7]),

    start(R1, 4),
    start(R2, 2),
    start(R3, 3),
    start(R4, 5),
    start(R5, 3),
    finish(R1, 6),
    finish(R2, 4),
    finish(R3, 2),
    finish(R5, 1),
    finish(R7, 2),

    start(C2, 3),
    start(C3, 4),
    start(C4, 3),
    start(C5, 5),
    start(C6, 4),
    start(C7, 1),
    finish(C1, 3),
    finish(C2, 2),
    finish(C3, 5),
    finish(C4, 5),
    finish(C5, 6),
    finish(C6, 1),
    finish(C7, 4),

    maplist(fd_labeling, Rows),
    maplist(writeln, Rows).

% place the constraint 'SECOND in that direction' using a reified check
start(Vars, Num) :-
    Vars = [A,B,C|_],
    X #<=> ( A #= 0 #\/ B #= 0 ) #/\ C #= Num,
    Y #<=> A #\= 0 #/\ B #= Num,
    X + Y #= 1 .

finish(Vars, Num) :-
    reverse(Vars, Sarv), start(Sarv, Num).
Community
  • 1
  • 1
CapelliC
  • 59,646
  • 5
  • 47
  • 90
  • thanks a lot for the solution. but what to do to get the answer differently than ?- abc_view. false.? Please show how the program gives you the result – Oona Oct 08 '12 at 10:09
  • see the latest edit. While debugging, I take the approach to comment out initially most of constraints, then add a bunch of them. When constraints are ok, this gives many solutions, just 'visually' check the first, second and so on. Then add more, til covering the full set. – CapelliC Oct 08 '12 at 10:45
  • i don't understand this. help me, please, step by step what i doing. at first i create file in swi-prolog .pl with code /* File: second_end_view_puzzle.pl Author: Carlo,,, Created: Oct 8 2012 Purpose: help to solve Second End View puzzle as quested at http://stackoverflow.com/q/12717609/874024 */ :- module(abc_view, [abc_view/0]). :- [library(clpfd)]. gen_row(Ls) :- length(Ls, 7), Ls ins 0..6. ... finish(Vars, Num) :- reverse(Vars, Sarv), start(Sarv, Num). and after compile in main window after ?- i write "question" abc_view. – Oona Oct 08 '12 at 11:29
  • Just doublechecked: copy the program in a new file, compile and run abc_view to get the result. If you are interested in efficiency, this query `?- time(abc_view).` results in `% 1,002,499 inferences, 1,343 CPU in 1,349 seconds (100% CPU, 746670 Lips)` but I'm using a low power machine and a debug versoin of SWI-Prolog – CapelliC Oct 08 '12 at 11:56
  • http://farm9.staticflickr.com/8178/8067194566_a194ea65ec_b.jpg i am doing so, what my mistake? – Oona Oct 08 '12 at 15:20
  • I can't say. I see nothing apparent, apart the old version, but the code doesn't use anything particular. try `?- gtrace, abc_view.`. That will open the graphical debugger. Apart this, I also 'ported' to GnuProlog the code. I could post it. – CapelliC Oct 08 '12 at 15:39
  • post it, please. i would try in GnuProlog – Oona Oct 08 '12 at 16:27
  • Thank you so much!!!! it works in GnuProlog. – Oona Oct 08 '12 at 18:10
  • can u, please, write me what to rewrite in your solve http://stackoverflow.com/questions/10686773/end-view-puzzle-prolog in end-view pazzle for gnuProlog, there are the same problem that was with second end view – Oona Oct 08 '12 at 18:13
  • OMG I didn't remember of that. Then you took from my suggestion from start! Ok, -> means become. Then writeln/1 -> write/1,nl, label/1 -> fd_labeling/1, List ins Low..High -> fd_domain(List, Low, High), all_different/1 -> fd_all_different. Should be enough for that simpler puzzle. You should accept the answer, so you gain some reputation points and we can followup in chat for further details. Bye – CapelliC Oct 08 '12 at 18:32
  • Thanks for your help,but it isn't fully clear to me yet.Should i change the code from endview with this tips?Or the one,that is second view .As a result i want to have endview solver for 8*8 at gnuProlog – Oona Oct 08 '12 at 21:03
  • I remember just another change: reification in SWI is #<==>, in GNU #<=> – CapelliC Oct 08 '12 at 21:07
  • to solve end-view-puzzle, yes, just apply the suggested renaming. GnuProlog will kindly advice you about problems, if any... – CapelliC Oct 08 '12 at 21:15
  • Thanks,but should i commit this changes to the http://stackoverflow.com/questions/10686773/end-view-puzzle-prolog or to code from this page? – Oona Oct 08 '12 at 21:34
  • I corrected code,but it doesn't work either. Can you look at it? http://stackoverflow.com/questions/12797708/endview-game-on-gnu-prolog – Oona Oct 09 '12 at 10:13
  • Will this logic work if in endView i have two emty spaces?Not one? I need this game to work on 8*8 game space with two empty spaces? – Oona Oct 09 '12 at 10:20