A basic depth first maze generator algorithm is fairly simple, and I have recently been re-reading "Adventure in Prolog" by Dennis Merrit, which can be found online or, if you prefer hard-copy, on Amazon, so implementing a maze generator in prolog seemed like a good idea at the time. It might be interesting to develop a simple rogue-like in prolog.

The code below has been developed and tested using GNU Prolog

In pseudo code the maze generator, using a randomized DFS is as follows

Select a starting point, and start generating the maze

PROCEDURE CreateMaze():
  startVertex ← Vertex(0, 0)
  RandomizedDFS(startVertex)
END

PROCEDURE RandomizedDFS(vertex):

Mark the current vertex as visited

  MarkVisited(vertex)

Select a random unvisited neighbor. It is important that this is randomized, otherwise this won't create a branching maze, just a linear path filling the space.

  nextVertex ← RandomUnvisitedNeighbor(vertex)

While there is an available vertex…

  WHILE nextVertex

Connect it to the current vertex

    ConnectCells(vertex, nextVertex)

Recursively continue the maze process with the next vertex

    RandomizedDFS(nextVertex)
  END
END

Because this considers every neighbor at each level of recursion, it is clear that this will visit very available vertex.

Example

This animation shows the DFS maze generation

Example showing DFS maze generation

Implementation

In order implement this we need to be able to find neigboring vertices, and to check if a vertex has been visited. I'm going to store vertices as a set of facts map/3, this will be used to store X and Y coordinates, and a value used to hold other information about the map cell.

The maze is considered as a set of vertices and connections — or nodes and edges when thinking about the maze as a graph. For visualizing this I am using a map, where each node and each edge is a cell in a grid.

I'm going to use two coordinate systems, one for the map, and another for the maze, with \(f(x) = 2x+1\) being used to translate from maze coordinates to map coordinates.

Note: It is convenient to keep all coordinates as integers, so the mapping procedure maze_map/4 does not create a bijection between the two coordinate systems.

maze_map(Xmaze, Ymaze, Xmap, Ymap) :-
  integer(Xmaze), integer(Ymaze),
  Xmap is Xmaze * 2 + 1,
  Ymap is Ymaze * 2 + 1.
maze_map(Xmaze, Ymaze, Xmap, Ymap) :-
  integer(Xmap), integer(Ymap),
  Xmaze is floor( (Xmap - 1) / 2),
  Ymaze is floor( (Ymap - 1) / 2).

I will set the map cell between two adjacent maze vertices to indicate connectivity.

This seems unnecessarily complicated, but makes drawing much easier.

Initializing

The map is initialized by visiting each row recursively, and within each row, each column and setting the maze vertices to empty.

:- dynamic(map/3).

init_map(Width, Height) :-
  clear(map(_, _, _)),
  init_map_row(0, Height, Width).

init_map_row(Y, Y, _).
init_map_row(Y, Height, Width) :-
  init_map_col(0, Width, Y),
  Yn is Y + 1,
  init_map_row(Yn, Height, Width), !.

init_map_col(X, X, _).
init_map_col(X, Width, Y) :-
  maze_map(X, Y, Xmap, Ymap),
  set_map(Xmap, Ymap, empty),
  Xn is X + 1,
  init_map_col(Xn, Width, Y), !.

Drawing the map

The map is drawn in a similar fashion, but using map coordinates rather than maze coordinates.

There are two variations on draw_map, depending on whether it is required to clear the screen first, this reduces flicker if changes have been additive.

draw_map(clear, Width, Height) :-
  clear_screen,
  draw_map(Width, Height).
draw_map(Width, Height) :-
  integer(Width), Width > 0,
  integer(Height), Height > 0,
  set_cursor_pos(0, 0),
  draw_row(0, Height, Width), !.

draw_row(Y, Y,_).
draw_row(Y, Height, Width) :-
  draw_col(0, Width, Y),
  nl,
  Yn is Y + 1,
  draw_row(Yn, Height, Width), !.

draw_col(X, X, _).
draw_col(X, Width, Y) :-
  draw_map_cell(X, Y),
  Xn is X + 1,
  draw_col(Xn, Width, Y).

Each cell is then drawn based on its contents; if no entry is found, then the cell is drawn with two space characters — all cells are draw with two characters to make the aspect ration closer to square.

draw_map_cell(X, Y) :-
  map(X, Y, Fill),
  fill(Fill).
draw_map_cell(_, _) :- write('  ').

If the --ascii command argument was provided, then than specifies the characters to use, otherwise an empty map cell is drawn with two "full block" characters — unicode code point 0x2588 ''

fill(empty) :- option(ascii(X)), write(X).
fill(empty) :- write('██').

Currently only the empty atom is used, so anything else is a bug, lets just print '??' in any other cells.

fill(_) :- write('??').

Drawing procedures

Drawing is assuming an ANSI terminal

csi :- write('\x1b\[').
clear_screen :- csi, write('2J').
cursor(show) :- csi, write('?25h').
cursor(hide) :- csi, write('?25l').

set_cursor_pos/2 allows moving the cursor to an arbitrary position on the screen. set_cursor_map_pos/2 and set_cursor_maze_pos work in the respective coordinate systems to translate to screen coordinates.

set_cursor_pos(X, Y) :- csi, write(Y), write(';'), write(X), write('H').
set_cursor_map_pos(X, Y) :-
  Xmap is X * 2 + 1,
  Ymap is Y + 1,
  set_cursor_pos(Xmap, Ymap).
set_cursor_maze_pos(X, Y) :-
  maze_map(X, Y, Xmap, Ymap),
  set_cursor_map_pos(Xmap, Ymap).

Maze Generation

Now that the grid is populated and the map can be drawn, time to generate the maze.

To keep track of whether a vertex has been visited I'm using visited/2

The first step is to clear any history — there shouldn't be any, but if this is being used interactively it can happen — pick a starting point, and start the search.

Because every cell will be visited, it's not super important where the algorithm starts, by default this starts at 0,0, but can be specified using the --start command line argument.

:- dynamic(visited/2).

create_maze(X, Y) :-
  clear(visited(_, _)),
  randomized_dfs(X, Y).

Core algorithm

The depth first search marks the cell as visited, gets a list of unvisisted neighbors, and visits them.

randomized_dfs(X, Y) :-
  assertz(visited(X, Y)),
  randomized_unvisited_neighbors(X, Y, Neighbors),
  randomized_dfs(X, Y, Neighbors).

There are four patterns for the list of neighbors

  1. The list is empty, so end.
randomized_dfs(_, _, []).
  1. The current neighbor — head of the list — has already been visited, this happens because the neighbor was unvisited when the list was generated, but because this algorithm is depth first that might have changed by the time this neighbor is being considered. Proceed with the rest of the list
randomized_dfs(X, Y, [[Xn, Yn] | T]) :-
  visited(Xn, Yn),
  randomized_dfs(X, Y, T).
  1. If the --eyes argument has been specified, don't descend into the current head of the list if it has no unvisited neighbors of its own. This stops the maze algorithm from creating single step spurs on the maze, at the cost of creating unvisited eyes. This creates a visually distinctive maze.
randomized_dfs(X, Y, [[Xn, Yn] | T]) :-
  option(eyes),
  \+ unvisited_neighbor(Xn, Yn, _, _),
  randomized_dfs(X, Y, T).
  1. The current neighbor is great, connect to it, descend into it — this is what makes this depth first — and then proceed with the rest of the list
randomized_dfs(X, Y, [[Xn, Yn] | T]) :-
  connect(X, Y, Xn, Yn),
  randomized_dfs(Xn, Yn),
  randomized_dfs(X, Y, T).

Getting the list of neighbors

This uses findall/3 to get the list of unvisited neighbors, and then shuffles that list.

randomized_unvisited_neighbors(X, Y, RandomizedList) :-
  findall([Xn, Yn], unvisited_neighbor(X, Y, Xn, Yn), Neighbors),
  randomize_list(Neighbors, RandomizedList).

The neighbor/4 procedure finds adjacent cells in the maze coordinate system, although it has to check for their existence in the map coordinate system.

neighbor(X, Y, X, Yn) :-
  Yn is Y + 1, maze_map(X, Yn, Xmap, Ymap), map(Xmap, Ymap, _).
neighbor(X, Y, X, Yn) :-
  Yn is Y - 1, maze_map(X, Yn, Xmap, Ymap), map(Xmap, Ymap, _).
neighbor(X, Y, Xn, Y) :-
  Xn is X + 1, maze_map(Xn, Y, Xmap, Ymap), map(Xmap, Ymap, _).
neighbor(X, Y, Xn, Y) :-
  Xn is X - 1, maze_map(Xn, Y, Xmap, Ymap), map(Xmap, Ymap, _).

unvisited_neighbor/4 then checks that the neighbor in question has not been visited.

unvisited_neighbor(X, Y, Xn, Yn) :-
  neighbor(X, Y, Xn, Yn),
  \+ visited(Xn, Yn).

Connecting vertices

Connecting two vertices is simply a matter of setting the map cell between them.

Once again we have to convert from maze to map coordinates

connect(Xf, Yf, Xt, Yt) :-
  maze_map(Xf, Yf, Xfm, Yfm),
  maze_map(Xt, Yt, Xtm, Ytm),
  X is floor( (Xfm + Xtm) / 2),
  Y is floor( (Yfm + Ytm) / 2),
  connect_at(X, Y).

If the --visualize command line argument was supplied, then, in addition to setting the map cell to empty, the connect_at/2 procedure waits for a \(1/\mathit{Fps}\) seconds and then directly draws the map cell

connect_at(X, Y) :-
  option(fps(Fps)),
  set_map(X, Y, empty),
  Sleep is 1 / Fps,
  sleep(Sleep),
  set_cursor_map_pos(X, Y),
  fill(empty),
  flush_output(user_output), !.
connect_at(X, Y) :-
  set_map(X, Y, empty), !.

Utility Procedures

Map procedures

Setting a cell

This will clear a map cell if it is set, and set it.

set_map(X, Y, F) :-
  clear(map(X, Y, _)),
  assertz(map(X, Y, F)).

Clearing a predicate

abolish/1 will remove all entries for the provided predicate indicator, but also unsets the dynamic status of the predicate, so we have clear/1 which retracts all matching elements

clear(Pred) :-
  retract(Pred),
  fail.
clear(_).

Random procedures

Shuffling a list

This simply picks a random element from the list, and sets it at the front of the recursively shuffled remainder of the list.

randomize_list([], []).
randomize_list([X], [X]).
randomize_list(Xin, Xout) :-
  random_member(M, Xin),
  delete(Xin, M, Yin),
  randomize_list(Yin, Yout),
  Xout = [M | Yout], !.

Picking a random element from a list

This recursively walks down the list, at each element it has a \(1/n\) chance of selecting that element. This allows selecting an arbitrary element from a list of unknown length, at the cost of having to walk the entire list — and generate a random number for each element in the list after the first.

  1. If the list has a single element simply pick that.
random_member(X, [X]).
  1. Otherwise move the first element of the list into the chosen slot and start checking the rest of the list.
random_member(M, [H|T]) :- random_member(M, H, T, 1).
  1. If were are at the end of the list, unify the chosen slot with the result.
random_member(Chosen, Chosen, [], _).
  1. Increment the counter, and generate a random number between 0 and that count, If the random number is 0 — this is the \(1/n\) probability because random/3 returns an integer in the half open interval — then select this element as the current candidate, and continue, otherwise continue with the existing candidate.
random_member(Member, Chosen, [Head|Tail], Count) :-
  CountN is Count + 1,
  random(0, CountN, R),
  (R =:= 0 -> random_member(Member, Head, Tail, CountN)
            ; random_member(Member, Chosen, Tail, CountN)),
  !.

program entry point

The initialization/1 directive tells prolog to call the supplied query, in this case main.

<<initializing>>
<<drawing>>
<<maze_generation>>
<<utility_procedures>>
<<command_line>>

:- initialization(main).
  1. Parse the command line arguments
main :-
  argument_list(Args),
  read_options(Args),
  1. Lookup the maze dimensions, either from the --size command line argument, or use the default value \(30\times20\), and then initialize the map.
  (option(size(Width, Height)) -> true ; Width = 30, Height = 20),
  init_map(Width, Height),
  1. If the --visualize command line argument was specified, then draw the map. Before doing any drawing operations, hide the cursor, this reduces flicker while updating the terminal
  maze_map(Width, Height, Wmap, Hmap),
  cursor(hide),
  (option(visualize) -> draw_map(clear, Wmap,Hmap); true),
  1. Lookup the maze generation start coordinate, either from the --start command line argument, or use the default value \(0,0\), then create and draw the maze.
  (option(start(X, Y)) -> true ; X = 0, Y = 0),
  create_maze(X, Y),
  (option(visualize) -> draw_map(Wmap, Hmap)
                      ; draw_map(clear, Wmap,Hmap)),
  1. Ensure that the cursor is now visible, then halt execution. halt/0 is not used then the interactive prolog environment will be started after main completes.
  cursor(show),
  halt.

Command line argument parsing

Command line arguments are accessed as a list of atoms using argument_list/1.

Command line options are parsed one at time, each option must begin with -- and, if it contains a = character, then it is split into a name and a , separated list of arguments.

read_options([]).
read_options([Option | Rest]) :-
  atom_chars(Option, OptionList),
  parse_option_list(OptionList, OptionName, OptionParams),
  store_option(OptionName, OptionParams),
  read_options(Rest).
read_options([_|Rest]) :- read_options(Rest).

If the argument starts with -- and contains an = character, then it is split into a name and parameters

parse_option_list(['-', '-' | Tail], Name, AtomParams) :-
  member('=', Tail),
  split_list('=', Tail, 1, [NameList, ParamList]),
  split_list(',', ParamList, all, Params),
  atom_chars(Name, NameList),
  maplist(atom_chars, AtomParams, Params).

If the argument starts with -- and doesn't contain a = character, then it just has a name and no parameters.

parse_option_list(['-', '-' | Tail], Name, []) :-
  atom_chars(Name, Tail).

If the argument doesn't start with --, or on retry, which will happen if store_option/2 fails, then this isn't a valid argument, and that is written to the output.

parse_option_list(List, _, _) :-
  atom_chars(Option, List),
  write(Option), write(' is not a valid argument.'), nl, fail.

List splitting

To split the arguments into their respective parts, this uses a split_list/4 procedure, that can split a list by separator element, and constrain that to only the first Count splits.

For example, when splitting the argument name from arguments, it is split using the first '=' element

  split_list('=', Tail, 1, [NameList, ParamList])

whereas when the comma separated parameters are split, this uses the atom all to split on all ',' elements

  split_list(',', ParamList, all, Params)

This is simply a wrapper around split_list/4 setting the count to -1, so the split_list/5 procedure which is used to limit the number of splits by unifying a decrementing count with 0 is n.ever called.

split_list(Sep, List, all, Parts) :- split_list(Sep, List, -1, Parts).

Only call split_list/5 — the actual implementation — when Count is an integer and the list contains the separator, otherwise simply return the list as a single result.

split_list(Sep, List, Count, Parts) :-
  integer(Count),
  member(Sep, List),
  split_list(Sep, [], List, Count, Parts).
split_list(_, List, _, [List]).

When there is nothing left in the list, then the last part is the elements accumulated so far.

split_list(_, PartAccum, [], _, [PartAccum]).

When the count is 0, at which point the accumulated part should always be empty, then the last part is the remaining elements from the list.

split_list(_, [], Remain, 0, [Remain]).

When the head of the remaining list unifies with the separator, then the accumulated part is prepended onto the parts list, the count is decremented and the split is recursed with the new count and an empty accumulated part.

split_list(Sep, PartAccum, [Sep | Remain], Count, [PartAccum | Parts]) :-
  CountN is Count - 1,
  split_list(Sep, [], Remain, CountN, Parts).

The most basic case, when the current head element in the list doesn't unify with the separator, simply append it to the acucmulator and recurse with the rest of the list. The use of append/3 here makes this \(O(N^2)\), which, could be fixed if critical by prepending the current element and reversing the accumulator when it is prepended onto the result list.

split_list(Sep, PartAccum, [Curr | Remain], Count, Parts) :-
  append(PartAccum, [Curr], NewPartAccum),
  split_list(Sep, NewPartAccum, Remain, Count, Parts).

Individual argument handling

Arguments are stored in the option/1 dynamic predicate. In general argument processing tries to be as flexible as possibe with respect to the number of parameters specified.

For example, --size=10 is equivalent to --size=10,10, and --size=30,20,40,50 is equivlent to --size=30,20.

If arguments are duplicated, or contradictory, then they are ignored, and a warning is written.

:- dynamic(option/1).

store_option(Option, _) :-
  option(Option),
  write('Duplicate argument --'), write(Option), write(' ignored.'), nl.
store_option(Option, _) :-
  Pred =.. [Option, _],
  option(Pred),
  write('Duplicate argument --'), write(Option), write(' ignored.'), nl.
store_option(Option, _) :-
  Pred =.. [Option, _, _],
  option(Pred),
  write('Duplicate argument --'), write(Option), write(' ignored.'), nl.

--visualize[=Fps]

Draws the maze as it generates it, waiting between each connection for \(\frac{1}{\mathit{Fps}}\) seconds. If \(\mathit{Fps}\) defaults to \(20\) if it is not specified.

store_option(visualize, []) :- store_option(visualize, ['20']).
store_option(visualize, [FpsArg | _]) :-
  arg_integer(FpsArg, Fps),
  assertz(option(fps(Fps))),
  assertz(option(visualize)).

--ascii[=Char]

Uses ascii characters to draw map cells, using the supplied character, if any, otherwise X.

Note: cells are draw using doubled characters, this argument will only use the first character supplied

store_option(ascii, []) :- store_option(ascii, ['X']).
store_option(ascii, [Arg|_]) :-
  atom_chars(Arg, [Char | _]),
  atom_chars(X, [Char, Char]),
  assertz(option(ascii(X))).

--eyes

Amends the maze generation algorithm to leave eyes — unvisited neighbors that have no other unvisited neighbors are excluded from the algorithm.

store_option(eyes, []) :-
  assertz(option(eyes)).

--randomize

Picks a random seed for the random number generator. This will then generate a new maze each time it is called.

This will be ignored if the --seed argument has already been specified.

store_option(randomize, _) :-
  option(seed(_)),
  write('Argument --randomize ignored, --seed already specified.'), nl.
store_option(randomize, []) :-
  randomize,
  get_seed(Seed),
  assertz(option(randomize)),
  assertz(option(seed(Seed))).

--seed

Specifies a seed to be used for the random number generator.

This will be ignored if the --randomize argument has already been specified.

store_option(seed, _) :-
  option(randomize),
  write('Argument --seed ignored, --randomize already specified.'), nl.
store_option(seed, [SeedArg | _]) :-
  arg_integer(SeedArg, Seed),
  set_seed(Seed),
  assertz(option(seed(Seed))).

--size=Width[,Height]

Specifies the size of the maze to generate, in the maze coordinate system. If only a single numeric parameter is provided, then this will generate a square maze.

store_option(size, [WidthArg]) :- store_option(size, [WidthArg, WidthArg]).
store_option(size, [WidthArg, HeightArg | _]) :-
  arg_integer(WidthArg, Width),
  arg_integer(HeightArg, Height),
  assertz(option(size(Width, Height))).

--start=X,[Y]

Specifies the zero-based starting coordinate for the maze generation algorithm. If only a single value is provideded, then that will be used for both \(X\) and \(Y\) coordinates.

store_option(start, [XArg]) :- store_option(start, [XArg, XArg]).
store_option(start, [XArg, YArg | _]) :-
  arg_integer(XArg, X),
  arg_integer(YArg, Y),
  assertz(option(start(X, Y))).

If no argument matches then fail.

store_option(_, _) :-
  fail.

Argument type conversion

convert an atom into an integer, or vice versa.

arg_integer(Arg, Integer) :-
  catch(number_atom(Integer, Arg), error(syntax_error(_), _), Integer=Arg),
  integer(Integer).

Code

As mentioned in the first paragraph this literate document produces maze.pl, which compiles and runs with GNU Prolog.