Skip to content

Instantly share code, notes, and snippets.

@vituscze
Created April 3, 2025 22:41
Show Gist options
  • Save vituscze/0cd17ed1e98bdb462cd176050e5f9cae to your computer and use it in GitHub Desktop.
Save vituscze/0cd17ed1e98bdb462cd176050e5f9cae to your computer and use it in GitHub Desktop.
mark_enter(X, enter(X)).
dfs(_, [], Visited, Visited, Time, Time).
dfs(G, [exit(V)|Vs], Visited, FinalVisited, Time, FinalTime) :-
member(V/_/Time, Visited), NewTime is Time + 1,
dfs(G, Vs, Visited, FinalVisited, NewTime, FinalTime).
dfs(G, [enter(V)|Vs], Visited, FinalVisited, Time, FinalTime) :-
( member(V/_/_, Visited) -> dfs(G, Vs, Visited, FinalVisited, Time, FinalTime)
; member(V-Neigh, G), maplist(mark_enter, Neigh, NeighEnter),
NewTime is Time + 1,
append(NeighEnter, [exit(V)|Vs], NewStack),
dfs(G, NewStack, [V/Time/_|Visited], FinalVisited, NewTime, FinalTime)
).
find(Visited, V-N, Result) :- member(V/T1/T2, Visited) -> Result = V/T1/T2-N; Result = V-N.
pruchod(G, Start, NewG) :-
dfs(G, [enter(Start)], [], Visited, 1, _),
maplist(find(Visited), G, NewG).
:- use_module(library(clpfd)).
try_swap([X,Y|R], [Y,X|R]) :- X = 0; Y = 0.
try_swap([X,Y|R], [X|Res]) :- try_swap([Y|R], Res).
swap([R|Rs], [R2|Rs]) :- try_swap(R, R2).
swap([R|Rs], [R|Rs2]) :- swap(Rs, Rs2).
next(M, M2) :- swap(M, M2); transpose(M, MT), swap(MT, MT2), transpose(MT2, M2).
add_list(Xs, X, [X|Xs]).
add_state(S, A1, A2) :- put_assoc(S, A1, s, A2).
bfs1([[State|Path]|_]-_, _, Result) :- State = [[0,1,2],[3,4,5],[6,7,8]], reverse([State|Path], Result).
bfs1([[State|Path]|Rest]-End, Assoc, Result) :-
findall(NewState, (next(State, NewState), \+ get_assoc(NewState, Assoc, _)), NewStates),
foldl(add_state, NewStates, Assoc, NewAssoc),
maplist(add_list([State|Path]), NewStates, NewPaths),
append(NewPaths, NewEnd, End), !,
Rest \== NewEnd, bfs1(Rest-NewEnd, NewAssoc, Result).
bfs(InitState, Result) :-
empty_assoc(A),
add_state(InitState, A, NewA),
bfs1([[InitState]|R]-R, NewA, Result).
write_one(N) :- write(N), write(" ").
write_row(R) :- maplist(write_one, R), nl.
write_matrix(M) :- maplist(write_row, M), nl.
write_path(P) :- maplist(write_matrix, P).
solve(Init, N) :- bfs(Init, Path), !, length(Path, N1), N is N1 - 1, write_path(Path).
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment