Maze generation

From Rosetta Code
(Redirected from Maze)
Task
Maze generation
You are encouraged to solve this task according to the task description, using any language you may know.
This page uses content from Wikipedia. The original article was at Maze generation algorithm. The list of authors can be seen in the page history. As with Rosetta Code, the text of Wikipedia is available under the GNU FDL. (See links for details on variance)
a maze


Task

Generate and show a maze, using the simple Depth-first search algorithm.

  1. Start at a random cell.
  2. Mark the current cell as visited, and get a list of its neighbors. For each neighbor, starting with a randomly selected neighbor:
    If that neighbor hasn't been visited, remove the wall between this cell and that neighbor, and then recurse with that neighbor as the current cell.



Related tasks



11l[edit]

Translation of: Python
F make_maze(w = 16, h = 8)
   V vis = [[0] * w [+] [1]] * h [+] [[1] * (w + 1)]
   V ver = [[‘|  ’] * w [+] [String(‘|’)]] * h [+] [[String]()]
   V hor = [[‘+--’] * w [+] [String(‘+’)]] * (h + 1)

   F walk(Int x, Int y) -> N
      @vis[y][x] = 1
      V d = [(x - 1, y), (x, y + 1), (x + 1, y), (x, y - 1)]
      random:shuffle(&d)
      L(=xx, =yy) d
         I yy == -1
            yy = @vis.len - 1
         I xx == -1
            xx = @vis[0].len - 1
         I @vis[yy][xx]
            L.continue
         I xx == x
            @hor[max(y, yy)][x] = ‘+  ’
         I yy == y
            @ver[y][max(x, xx)] = ‘   ’
         @walk(xx, yy)

   walk(random:(w), random:(h))

   V s = ‘’
   L(a, b) zip(hor, ver)
      s ‘’= (a [+] [String("\n")] + b [+] [String("\n")]).join(‘’)
   R s

print(make_maze())
Output:
+--+--+--+--+--+--+--+--+--+--+--+--+--+--+--+--+
|                                |        |     |
+  +--+--+--+--+--+--+--+--+--+  +  +--+  +  +--+
|              |           |     |     |  |     |
+--+--+--+--+--+--+  +  +--+  +--+  +  +  +  +  +
|           |        |  |     |     |  |  |  |  |
+  +  +--+--+  +  +--+  +  +--+  +--+  +  +--+  +
|  |           |     |  |  |     |     |        |
+  +--+--+--+--+--+  +  +  +  +--+  +  +--+--+--+
|  |        |     |  |  |  |  |     |  |        |
+  +--+--+  +  +  +  +--+  +  +  +--+--+  +--+  +
|     |     |  |     |     |  |  |        |     |
+--+  +  +--+  +--+  +  +--+  +  +  +--+--+  +  +
|  |  |     |     |  |     |  |           |  |  |
+  +  +--+  +--+  +--+--+  +--+--+--+--+--+  +  +
|              |                             |  |
+--+--+--+--+--+--+--+--+--+--+--+--+--+--+--+--+

Action![edit]

Action! language does not support recursion. Therefore an iterative approach with a stack has been proposed.

DEFINE TOP="0"
DEFINE RIGHT="1"
DEFINE BOTTOM="2"
DEFINE LEFT="3"
DEFINE WIDTH="160"
DEFINE HEIGHT="96"

DEFINE STACK_SIZE="5000"
BYTE ARRAY stack(STACK_SIZE)
INT stackSize

PROC InitStack()
  stackSize=0
RETURN

BYTE FUNC IsEmpty()
  IF stackSize=0 THEN
    RETURN (1)
  FI
RETURN (0)

BYTE FUNC IsFull()
  IF stackSize>=STACK_SIZE THEN
    RETURN (1)
  FI
RETURN (0)

PROC Push(BYTE x,y)
  IF IsFull() THEN Break() RETURN FI
  stack(stackSize)=x stackSize==+1
  stack(stackSize)=y stackSize==+1
RETURN

PROC Pop(BYTE POINTER x,y)
  IF IsEmpty() THEN Break() RETURN FI
  stackSize==-1 y^=stack(stackSize)
  stackSize==-1 x^=stack(stackSize)
RETURN

PROC FillScreen()
  BYTE POINTER ptr ;pointer to the screen memory
  INT screenSize=[3840]

  ptr=PeekC(88)
  SetBlock(ptr,screenSize,$55)

  Color=0
  Plot(0,HEIGHT-1) DrawTo(WIDTH-1,HEIGHT-1) DrawTo(WIDTH-1,0)
RETURN

PROC GetNeighbors(BYTE x,y BYTE ARRAY n BYTE POINTER count)
  DEFINE WALL="1"

  count^=0
  IF y>2 AND Locate(x,y-2)=WALL THEN
    n(count^)=TOP count^==+1
  FI
  IF x<WIDTH-3 AND Locate(x+2,y)=WALL THEN
    n(count^)=RIGHT count^==+1
  FI
  IF y<HEIGHT-3 AND Locate(x,y+2)=WALL THEN
    n(count^)=BOTTOM count^==+1
  FI
  IF x>2 AND Locate(x-2,y)=WALL THEN
    n(count^)=LEFT count^==+1
  FI
RETURN

PROC Maze(BYTE x,y)
  BYTE ARRAY stack,neighbors
  BYTE dir,nCount

  FillScreen()

  Color=2
  InitStack()
  Push(x,y)
  WHILE IsEmpty()=0
  DO
    Pop(@x,@y)
    GetNeighbors(x,y,neighbors,@nCount)
    IF nCount>0 THEN
      Push(x,y)
      Plot(x,y)
      dir=neighbors(Rand(nCount))
      IF dir=TOP THEN
        y==-2
      ELSEIF dir=RIGHT THEN
        x==+2
      ELSEIF dir=BOTTOM THEN
        y==+2
      ELSE
        x==-2
      FI
      DrawTo(x,y)
      Push(x,y)
    FI
  OD
RETURN

PROC Main()
  BYTE CH=$02FC,COLOR0=$02C4,COLOR1=$02C5
  BYTE x,y

  Graphics(7+16)
  COLOR0=$0A
  COLOR1=$04

  x=Rand((WIDTH RSH 1)-1) LSH 1+1
  y=Rand((HEIGHT RSH 1)-1) LSH 1+1
  Maze(x,y)

  DO UNTIL CH#$FF OD
  CH=$FF
RETURN
Output:

Screenshot from Atari 8-bit computer

Ada[edit]

Works with: Ada 2005
Works with: GNAT

mazes.ads:

generic
   Height : Positive;
   Width : Positive;
package Mazes is

   type Maze_Grid is private;

   procedure Initialize (Maze : in out Maze_Grid);

   procedure Put (Item : Maze_Grid);

private

   type Directions is (North, South, West, East);

   type Cell_Walls is array (Directions) of Boolean;
   type Cells is record
      Walls   : Cell_Walls := (others => True);
      Visited : Boolean    := False;
   end record;

   subtype Height_Type is Positive range 1 .. Height;
   subtype Width_Type is Positive range 1 .. Width;

   type Maze_Grid is array (Height_Type, Width_Type) of Cells;

end Mazes;

mazes.adb:

with Ada.Numerics.Discrete_Random;
with Ada.Text_IO;
 
package body Mazes is
   package RNG is new Ada.Numerics.Discrete_Random (Positive);
   package Random_Direction is new Ada.Numerics.Discrete_Random (Directions);
 
   Generator     : RNG.Generator;
   Dir_Generator : Random_Direction.Generator;
 
   function "-" (Dir : Directions) return Directions is
   begin
      case Dir is
         when North =>
            return South;
         when South =>
            return North;
         when East =>
            return West;
         when West =>
            return East;
      end case;
   end "-";
 
   procedure Move
     (Row        : in out Height_Type;
      Column     : in out Width_Type;
      Direction  : Directions;
      Valid_Move : out Boolean)
   is
   begin
      Valid_Move := False;
      case Direction is
         when North =>
            if Row > Height_Type'First then
               Valid_Move := True;
               Row        := Row - 1;
            end if;
         when East =>
            if Column < Width_Type'Last then
               Valid_Move := True;
               Column     := Column + 1;
            end if;
         when West =>
            if Column > Width_Type'First then
               Valid_Move := True;
               Column     := Column - 1;
            end if;
         when South =>
            if Row < Height_Type'Last then
               Valid_Move := True;
               Row        := Row + 1;
            end if;
      end case;
   end Move;
 
   procedure Depth_First_Algorithm
     (Maze   : in out Maze_Grid;
      Row    : Height_Type;
      Column : Width_Type)
   is
      Next_Row        : Height_Type;
      Next_Column     : Width_Type;
      Next_Direction  : Directions;
      Valid_Direction : Boolean;
      Tested_Wall     : array (Directions) of Boolean := (others => False);
      All_Tested      : Boolean;
   begin
      -- mark as visited
      Maze (Row, Column).Visited := True;
      loop
         -- use random direction
         loop
            Next_Direction := Random_Direction.Random (Dir_Generator);
            exit when not Tested_Wall (Next_Direction);
         end loop;
         Next_Row       := Row;
         Next_Column    := Column;
         Move (Next_Row, Next_Column, Next_Direction, Valid_Direction);
         if Valid_Direction then
            if not Maze (Next_Row, Next_Column).Visited then
               -- connect the two cells
               Maze (Row, Column).Walls (Next_Direction)              :=
                 False;
               Maze (Next_Row, Next_Column).Walls (-Next_Direction)   :=
                 False;
               Depth_First_Algorithm (Maze, Next_Row, Next_Column);
            end if;
         end if;
         Tested_Wall (Next_Direction) := True;
         -- continue as long as there are unvisited neighbours left
         All_Tested := True;
         for D in Directions loop
            All_Tested := All_Tested and Tested_Wall (D);
         end loop;
         -- all directions are either visited (from here,
         -- or previously visited), or invalid.
         exit when All_Tested;
      end loop;
   end Depth_First_Algorithm;
 
   procedure Initialize (Maze : in out Maze_Grid) is
      Row, Column : Positive;
   begin
      -- initialize random generators
      RNG.Reset (Generator);
      Random_Direction.Reset (Dir_Generator);
      -- choose starting cell
      Row    := RNG.Random (Generator) mod Height + 1;
      Column := RNG.Random (Generator) mod Width + 1;
      Ada.Text_IO.Put_Line
        ("Starting generation at " &
         Positive'Image (Row) &
         " x" &
         Positive'Image (Column));
      Depth_First_Algorithm (Maze, Row, Column);
   end Initialize;
 
   procedure Put (Item : Maze_Grid) is
   begin
      for Row in Item'Range (1) loop
         if Row = Item'First (1) then
            Ada.Text_IO.Put ('+');
            for Col in Item'Range (2) loop
               if Item (Row, Col).Walls (North) then
                  Ada.Text_IO.Put ("---+");
               else
                  Ada.Text_IO.Put ("   +");
               end if;
            end loop;
            Ada.Text_IO.New_Line;
         end if;
         for Col in Item'Range (2) loop
            if Col = Item'First (2) then
               if Item (Row, Col).Walls (West) then
                  Ada.Text_IO.Put ('|');
               else
                  Ada.Text_IO.Put (' ');
               end if;
            elsif Item (Row, Col).Walls (West)
              and then Item (Row, Col - 1).Walls (East)
            then
               Ada.Text_IO.Put ('|');
            elsif Item (Row, Col).Walls (West)
              or else Item (Row, Col - 1).Walls (East)
            then
               Ada.Text_IO.Put ('>');
            else
               Ada.Text_IO.Put (' ');
            end if;
            if Item (Row, Col).Visited then
               Ada.Text_IO.Put ("   ");
            else
               Ada.Text_IO.Put ("???");
            end if;
         end loop;
         if Item (Row, Item'Last (2)).Walls (East) then
            Ada.Text_IO.Put_Line ("|");
         else
            Ada.Text_IO.Put_Line (" ");
         end if;
         Ada.Text_IO.Put ('+');
         for Col in Item'Range (2) loop
            if Item (Row, Col).Walls (South) then
               Ada.Text_IO.Put ("---+");
            else
               Ada.Text_IO.Put ("   +");
            end if;
         end loop;
         Ada.Text_IO.New_Line;
      end loop;
   end Put;
end Mazes;

Example main.adb:

with Mazes;
procedure Main is
   package Small_Mazes is new Mazes (Height => 8, Width => 11);
   My_Maze : Small_Mazes.Maze_Grid;
begin
   Small_Mazes.Initialize (My_Maze);
   Small_Mazes.Put (My_Maze);
end Main;
Output:
Starting generation at  3 x 7
+---+---+---+---+---+---+---+---+---+---+---+
|   |               |   |                   |
+   +   +   +---+   +   +   +---+---+---+   +
|       |       |       |   |       |       |
+   +---+---+   +---+---+   +   +   +   +---+
|           |           |   |   |   |   |   |
+   +---+---+---+---+   +---+   +   +   +   +
|   |           |       |       |       |   |
+   +   +---+   +   +   +   +---+---+---+   +
|   |   |           |   |       |           |
+   +   +---+---+---+---+---+   +---+   +   +
|   |   |                   |           |   |
+---+   +   +---+---+---+   +---+---+---+   +
|       |   |           |                   |
+   +---+   +---+---+   +---+---+---+---+---+
|                                           |
+---+---+---+---+---+---+---+---+---+---+---+

Aime[edit]

grid_maze(data b, integer N)
{
    data d;

    N.times(bb_cast, d, "+---");
    bb_cast(d, "+\n");

    N.times(bb_cast, d, "| * ");
    bb_cast(d, "|\n");

    N.times(bb_copy, b, d);

    b_size(d, N * 4 + 2);

    bb_copy(b, d);
}

void
walk_cell(data b, integer N, line_size, x, y, list x_offsets, y_offsets)
{
    integer i, p, q, r;

    b_replace(b, y + x, ' ');

    r = drand(3);

    i = 0;
    while (i < 4) {
        p = x + x_offsets[q = (r + i) & 3];
        q = y + y_offsets[q];

        if (-1 < p && p < line_size
            && -1 < q && q < line_size * (N * 2 + 1)) {
            if (b[q + p] == '*') {
                walk_cell(b, N, line_size, p, q, x_offsets, y_offsets);
                b[(q + y) / 2 + (p + x) / 2] = ' ';
                if (p == x) {
                    b[(q + y) / 2 + p - 1] = ' ';
                    b[(q + y) / 2 + p + 1] = ' ';
                }
            }
        }

        i += 1;
    }
}

walk_maze(data b, integer N)
{
    integer line_size, x, y;
    list x_offsets, y_offsets;

    line_size = N * 4 + 1 + 1;

    l_bill(x_offsets, 0, 4, 0, -4, 0);
    l_bill(y_offsets, 0, 0, line_size * 2, 0, line_size * -2);

    x = drand(N - 1) * 4 + 2;
    y = line_size * (drand(N - 1) * 2 + 1);

    walk_cell(b, N, line_size, x, y, x_offsets, y_offsets);
}

main(void)
{
    data b;

    grid_maze(b, 10);
    walk_maze(b, 10);

    o_(b);

    0;
}
Output:
+---+---+---+---+---+---+---+---+---+---+
|                       |               |
+   +---+---+---+---+   +   +---+---+   +
|   |       |       |   |   |           |
+   +   +   +   +   +   +   +   +---+   +
|   |   |       |       |   |   |   |   |
+   +---+---+   +---+---+---+   +   +   +
|           |               |   |   |   |
+---+---+---+---+---+---+   +   +   +   +
|                       |   |   |       |
+   +---+---+---+---+   +   +   +---+---+
|   |               |   |   |           |
+   +---+---+---+   +   +   +---+   +   +
|       |       |       |       |   |   |
+   +   +   +   +   +---+---+   +---+   +
|   |       |   |           |       |   |
+---+---+---+   +---+---+---+---+   +   +
|               |       |       |       |
+   +---+---+---+   +   +   +   +---+   +
|                   |       |           |
+---+---+---+---+---+---+---+---+---+---+

APL[edit]

This example shows how to use GNU APL scripting.

#!/usr/local/bin/apl --script --
 ⍝⍝⍝⍝⍝⍝⍝⍝⍝⍝⍝⍝⍝⍝⍝⍝⍝⍝⍝⍝⍝⍝⍝⍝⍝⍝⍝⍝⍝⍝⍝⍝⍝⍝⍝⍝⍝⍝⍝⍝⍝⍝⍝⍝⍝⍝⍝⍝⍝⍝⍝⍝⍝⍝⍝⍝⍝⍝⍝⍝⍝⍝⍝⍝⍝⍝⍝⍝
⍝                                                                    ⍝
⍝ mazeGen.apl                          2022-01-07  19:47:35 (GMT-8)  ⍝
⍝                                                                    ⍝
 ⍝⍝⍝⍝⍝⍝⍝⍝⍝⍝⍝⍝⍝⍝⍝⍝⍝⍝⍝⍝⍝⍝⍝⍝⍝⍝⍝⍝⍝⍝⍝⍝⍝⍝⍝⍝⍝⍝⍝⍝⍝⍝⍝⍝⍝⍝⍝⍝⍝⍝⍝⍝⍝⍝⍝⍝⍝⍝⍝⍝⍝⍝⍝⍝⍝⍝⍝⍝

initPRNG
  ⍝⍝ Seed the internal PRNG used by APL ? operator
  ⎕RL  +/ ⎕TS   ⍝⍝ Not great... but good enough


offs  cellTo dir
  ⍝⍝ Return the offset (row col) to cell which lies in compass (dir)
  offs  ((¯1 0)(0 1)(1 0)(0 ¯1))[('nesw'dir)]


doMaze rc
  ⍝⍝ Main function
  0 0 mazeGen rc      ⍝⍝ Do the maze gen
  m                   ⍝⍝ output result


b  m isVisited coord;mr;mc
  ( / (coord[1] < 1) (coord[2] < 1) )/yes
  ( / (coord > (m)÷2) )/yes
  b  ' '  m[2×coord[1];2×coord[2]]
  0
yes:
  b1


c mazeGen sz ;dirs;c;dir;cell;next
  (c(0 0))/gen
init:
  c  ?sz[1],?sz[2]
  m  mazeInit sz
gen:
  cell  c
  dirs  'nesw'[4?4]
  m[2×c[1];2×c[2]]  ' '  ⍝ mark cell as visited
dir1:
  dir  dirs[1]
  next  cell + cellTo dir
  (m isVisited next)/dir2
  m  m openWall cell dir
  next mazeGen sz
dir2:
  dir  dirs[2]
  next  cell + cellTo dir
  (m isVisited next)/dir3
  m  m openWall cell dir
  next mazeGen sz
dir3:
  dir  dirs[3]
  next  cell + cellTo dir
  (m isVisited next)/dir4
  m  m openWall cell dir
  next mazeGen sz
dir4:
  dir  dirs[4]
  next  cell + cellTo dir
  (m isVisited next)/done
  m  m openWall cell dir
  next mazeGen sz
done:


m  mazeInit sz;rows;cols;r
  ⍝⍝ Init an ASCII grid which
  ⍝⍝ has all closed and unvisited cells:
  ⍝⍝
  ⍝⍝  +-+
  ⍝⍝  |.|
  ⍝⍝  +-+
  ⍝⍝
  ⍝⍝ @param sz - tuple (rows cols)
  ⍝⍝ @return m - ASCII representation of (rows × cols) closed maze cells
  ⍝⍝⍝⍝

  initPRNG
  (rows cols)  sz
  r   (cols  "+-" ),"+"
  r  r,∊ (cols  "|." ),"|"
  r  (rows,(r))r
  r  ((2×rows),(1+2×cols))r
  r  r ( (cols  "+-" ),"+")
  m  r


r  m openWall cellAndDir ;ri;ci;rw;cw;row;col;dir
  (row col dir)  cellAndDir
  ri  2×row
  ci  2×col
  (rw cw)  (ri ci) + cellTo dir
  m[rw;cw]  ' '   ⍝ open wall in (dir)
  r  m


⎕IO1

doMaze 9 9
)OFF
Output:
~/GNUAPL$ workspaces/mazeGen.apl 
+-+-+-+-+-+-+-+-+-+
|   |             |
+ + + +-+ +-+-+-+ +
| |   |   |   |   |
+ +-+ +-+-+ + +-+-+
|   | |     |     |
+ + + + +-+-+-+-+ +
| | | | |         |
+ + + +-+ +-+-+-+-+
| | |   | | |     |
+ + +-+ + + + + + +
| |   | | |   | | |
+ +-+ + + +-+-+ + +
| | | | |       | |
+ + + +-+-+-+-+-+ +
|   |     |       |
+-+ +-+ +-+ +-+-+-+
|     |           |
+-+-+-+-+-+-+-+-+-+

AutoHotkey[edit]

For a challenge, this maze generation is entirely string based. That is to say, all operations including the wall removal and retrieval of cell states are done on the output string.

; Initially build the board
Width	:= 11
Height	:= 8
Loop % height*2+1
{
	Outer := A_Index
	Loop % Width
		maze .= Outer & 1 ? "+-" : "|0"
	maze .= (Outer & 1 ? "+" : "|") "`n"
}
StringTrimRight, maze, maze, 1 ; removes trailing newline
Clipboard := Walk(maze)

Walk(S, x=0, y=0){
	If !x{	; --Start at a random cell...
		StringReplace, junk, S, `n,,UseErrorLevel ; Calculate rows
		Random, y, 1, ErrorLevel//2
		Random, x, 1, InStr(S, "`n")//2-1         ; Calculate height
	}
	
	; --Obtain a list of its neighbors...
	neighbors := x "," y+1 "`n" x "," y-1 "`n" x+1 "," y "`n" x-1 "," y
	; --Randomize the list...
	Sort neighbors, random
	
	; --Then for each neighbor...
	Loop Parse, neighbors, `n
	{
		pC := InStr(A_LoopField, ","), x2 := SubStr(A_LoopField, 1, pC-1), y2 := SubStr(A_LoopField, pC+1)
		; If it has not been visited...
		If GetChar(S, 2*x2, 2*y2) = "0"{
			; Mark it as visited...
			S := ChangeChar(s, 2*x2, 2*y2, " ")
			; Remove the wall between this cell and the neighbor...
			S := ChangeChar(S, x+x2, y+y2, " ")
			; Then recurse with the neighbor as the current cell
			S := Walk(S, x2, y2)
		}
	}
	return S
}
	
; Change a character in a string using x and y coordinates
ChangeChar(s, x, y, c){
	Loop Parse, s, `n
	{
		If (A_Index = Y)
			Loop Parse, A_LoopField
				If (A_Index = x)
					out .= c
				Else	out .= A_LoopField
		Else out .= A_LoopField
		out .= "`n"
	}
	StringTrimRight, out, out, 1
	return out
}

; retrieve a character in a string using x and y coordinates
GetChar(s, x, y, n=1){
	x*=n, y*=n
	Loop Parse, s, `n
		If (A_Index = Y)
			return SubStr(A_LoopField, x, 1)
}
Sample output:
+-+-+-+-+-+-+-+-+-+-+-+
|         |     |     |
+-+ +-+-+ +-+ + + +-+-+
|   |         | |     |
+ +-+ +-+ +-+-+ +-+ + +
| |     | |   |   | | |
+ + +-+-+ + + +-+ +-+ +
| |   |   | |     |   |
+ +-+ + +-+-+-+ +-+ + +
| |   |       |     | |
+ +-+-+-+-+-+ +-+-+-+ +
| |   |       |   |   |
+ + + + +-+-+-+ + + +-+
|   |   |   |   | |   |
+-+-+-+-+ +-+ + +-+-+ +
|             |       |
+-+-+-+-+-+-+-+-+-+-+-+

Alternative Version[edit]

http://rosettacode.org/wiki/Maze_solving#AutoHotkey

Generator and solver combined.

AWK[edit]

#!/usr/bin/awk -f

# Remember: AWK is 1-based, for better or worse.

BEGIN {
    # The maze dimensions.
    width = 20;  # Global
    height = 20; # Global
    resetMaze();

    # Some constants.
    top = 1;
    bottom = 2;
    left = 3;
    right = 4;

    # Randomize the PRNG.
    randomize();

    # Visit all the cells starting at a random point.
    visitCell(getRandX(), getRandY());
    
    # Show the result.
    printMaze();
}

# Wander through the maze removing walls as we go.
function visitCell(x, y,    dirList, dir, nx, ny, ndir, pi) {
    setVisited(x, y);   # This cell has been visited.

    # Visit neighbors in a random order.
    dirList = getRandDirList();
    for (dir = 1; dir <= 4; dir++) {
        # Get coordinates of a random neighbor (next in random direction list).
        ndir = substr(dirList, dir, 1);
        nx = getNextX(x, ndir);
        ny = getNextY(y, ndir);
        
        # Visit an unvisited neighbor, removing the separating walls.
        if (wasVisited(nx, ny) == 0) {
            rmWall(x, y, ndir);
            rmWall(nx, ny, getOppositeDir(ndir));
            visitCell(nx, ny)
        } 
    }
}

# Display the text-mode maze.
function printMaze(    x, y, r, w) {
    for (y = 1; y <= height; y++) {
        for (pass = 1; pass <= 2; pass++) { # Go over each row twice: top, middle
            for (x = 1; x <= width; x++) {
                if (pass == 1) { # top
                    printf("+");
                    printf(hasWall(x, y, top) == 1 ? "---" : "   ");
                    if (x == width) printf("+");
                }
                else if (pass == 2) { # left, right
                    printf(hasWall(x, y, left) == 1 ? "|" : " ");
                    printf("   ");
                    if (x == width) printf(hasWall(x, y, right) == 1 ? "|" : " ");
                }
            }
            print;
        }
    }
    for (x = 1; x <= width; x++) printf("+---"); # bottom row
    print("+"); # bottom right corner
}

# Given a direction, get its opposite.
function getOppositeDir(d) {
    if (d == top) return bottom;
    if (d == bottom) return top;
    if (d == left) return right;
    if (d == right) return left;
}

# Build a list (string) of the four directions in random order.
function getRandDirList(    dirList, randDir, nx, ny, idx) {
    dirList = "";
    while (length(dirList) < 4) {
        randDir = getRandDir();
        if (!index(dirList, randDir)) {
            dirList = dirList randDir;
        }
    }
    return dirList;
}

# Get x coordinate of the neighbor in a given a direction.
function getNextX(x, dir) {
    if (dir == left) x = x - 1;
    if (dir == right) x = x + 1;
    if (!isGoodXY(x, 1)) return -1; # Off the edge.
    return x;
}

# Get y coordinate of the neighbor in a given a direction.
function getNextY(y, dir) {
    if (dir == top) y = y - 1;
    if (dir == bottom) y = y + 1;
    if (!isGoodXY(1, y)) return -1; # Off the edge.
    return y;
}

# Mark a cell as visited.
function setVisited(x, y,    cell) {
    cell = getCell(x, y);
    if (cell == -1) return;
    cell = substr(cell, 1, 4) "1"; # walls plus visited
    setCell(x, y, cell);
}

# Get the visited state of a cell.
function wasVisited(x, y,    cell) {
    cell = getCell(x, y);
    if (cell == -1) return 1; # Off edges already visited.
    return substr(getCell(x,y), 5, 1);
}

# Remove a cell's wall in a given direction.
function rmWall(x, y, d,    i, oldCell, newCell) {
    oldCell = getCell(x, y);
    if (oldCell == -1) return;
    newCell = "";
    for (i = 1; i <= 4; i++) { # Ugly as concat of two substrings and a constant?.
        newCell = newCell (i == d ? "0" : substr(oldCell, i, 1));
    }
    newCell = newCell wasVisited(x, y);
    setCell(x, y, newCell);
}

# Determine if a cell has a wall in a given direction.
function hasWall(x, y, d,    cell) {
    cell = getCell(x, y);
    if (cell == -1) return 1; # Cells off edge always have all walls.
    return substr(getCell(x, y), d, 1);
}

# Plunk a cell into the maze.
function setCell(x, y, cell,    idx) {
    if (!isGoodXY(x, y)) return;
    maze[x, y] = cell
}

# Get a cell from the maze.
function getCell(x, y,    idx) {
    if (!isGoodXY(x, y)) return -1; # Bad cell marker.
    return maze[x, y];
}

# Are the given coordinates in the maze?
function isGoodXY(x, y) {
    if (x < 1 || x > width) return 0;
    if (y < 1 || y > height) return 0;
    return 1;
}

# Build the empty maze.
function resetMaze(    x, y) {
    delete maze;
    for (y = 1; y <= height; y++) {
        for (x = 1; x <= width; x++) {
            maze[x, y] = "11110"; # walls (up, down, left, right) and visited state.
        }
    }
}

# Random things properly scaled.

function getRandX() {
    return 1 + int(rand() * width);
}

function getRandY() {
    return 1 +int(rand() * height);
}

function getRandDir() {
    return 1 + int(rand() * 4);
}

function randomize() {
    "echo $RANDOM" | getline t;
    srand(t);
}

Example output:

+---+---+---+---+---+---+---+---+---+---+---+---+---+---+---+---+---+---+---+---+
|                       |                   |                       |           |
+---+   +---+   +---+---+   +---+   +---+---+   +---+   +---+---+   +   +---+   +
|       |   |   |           |   |           |       |   |   |       |       |   |
+   +---+   +   +   +---+---+   +---+---+   +   +---+   +   +   +---+---+---+   +
|       |       |   |                   |       |       |       |               |
+   +   +   +---+   +---+   +   +---+   +---+---+   +---+---+   +---+   +---+   +
|   |   |   |   |       |   |   |       |       |   |       |           |       |
+---+   +   +   +---+   +---+   +   +---+---+   +   +   +   +---+---+---+   +---+
|       |       |       |       |               |       |   |       |       |   |
+   +   +---+---+   +---+   +---+---+---+---+   +---+---+   +---+   +   +---+   +
|   |   |       |   |           |           |   |       |       |   |   |       |
+   +---+   +   +   +---+---+   +---+   +   +   +   +   +---+   +   +   +   +   +
|   |       |       |       |       |   |   |   |   |       |   |   |       |   |
+   +   +---+---+---+   +   +---+   +   +   +   +---+---+   +   +   +---+---+   +
|   |   |               |           |   |   |               |   |               |
+   +   +---+---+---+   +---+---+---+   +   +---+---+---+   +   +---+---+   +---+
|       |               |   |           |           |       |   |       |       |
+   +---+   +---+---+---+   +   +---+---+---+---+   +   +---+   +   +   +---+   +
|   |       |           |   |   |       |       |   |   |   |       |   |       |
+   +   +   +   +---+   +   +   +   +   +   +   +   +   +   +---+---+   +   +---+
|       |   |       |   |           |   |   |   |   |   |           |   |       |
+   +---+---+---+   +   +---+---+---+   +   +   +   +   +   +---+   +   +---+   +
|   |               |           |   |       |   |           |   |   |       |   |
+---+   +---+---+---+---+---+   +   +---+   +---+---+---+---+   +   +---+   +   +
|   |   |       |           |   |       |   |           |       |       |   |   |
+   +   +   +---+   +---+   +   +---+   +   +   +---+   +---+   +---+   +   +   +
|   |   |           |       |       |       |   |           |           |   |   |
+   +   +   +---+---+   +---+---+   +   +---+   +---+---+   +---+---+   +   +---+
|   |   |   |   |       |           |       |       |   |           |   |       |
+   +   +   +   +   +---+   +---+---+---+---+---+   +   +---+---+   +   +---+   +
|       |   |   |           |                       |               |       |   |
+---+---+   +   +---+---+---+---+   +   +---+---+---+   +---+---+---+---+   +   +
|       |       |               |   |       |       |           |           |   |
+   +   +---+   +---+---+   +   +   +---+   +   +   +---+---+   +---+---+---+   +
|   |       |       |       |   |       |   |   |   |       |           |       |
+   +   +---+---+   +   +---+   +   +---+   +---+   +   +   +---+---+   +   +---+
|   |           |   |   |       |   |       |       |   |           |   |       |
+   +---+   +---+   +   +   +---+---+   +---+   +---+   +---+---+   +   +---+   +
|       |               |               |                       |               |
+---+---+---+---+---+---+---+---+---+---+---+---+---+---+---+---+---+---+---+---+

BASIC[edit]

QB64[edit]

This implementation was written using QB64. It should also be compatible with Qbasic, as it uses no QB64-exclusive features.

OPTION BASE 0
RANDOMIZE TIMER

REM must be even
width% = 40
height% = 20

REM make array and fill
DIM maze$(width%, height%)
FOR x% = 0 TO width%
    FOR y% = 0 TO height%
        maze$(x%, y%) = "#"
    NEXT y%
NEXT x%

REM initial start location
currentx% = INT(RND * (width% - 1))
currenty% = INT(RND * (height% - 1))
REM value must be odd
IF currentx% MOD 2 = 0 THEN currentx% = currentx% + 1
IF currenty% MOD 2 = 0 THEN currenty% = currenty% + 1
maze$(currentx%, currenty%) = " "

REM generate maze
done% = 0
DO WHILE done% = 0
    FOR i% = 0 TO 99
        oldx% = currentx%
        oldy% = currenty%

        REM move in random direction
        SELECT CASE INT(RND * 4)
            CASE 0
                IF currentx% + 2 < width% THEN currentx% = currentx% + 2
            CASE 1
                IF currenty% + 2 < height% THEN currenty% = currenty% + 2
            CASE 2
                IF currentx% - 2 > 0 THEN currentx% = currentx% - 2
            CASE 3
                IF currenty% - 2 > 0 THEN currenty% = currenty% - 2
        END SELECT

        REM if cell is unvisited then connect it
        IF maze$(currentx%, currenty%) = "#" THEN
            maze$(currentx%, currenty%) = " "
            maze$(INT((currentx% + oldx%) / 2), ((currenty% + oldy%) / 2)) = " "
        END IF
    NEXT i%

    REM check if all cells are visited
    done% = 1
    FOR x% = 1 TO width% - 1 STEP 2
        FOR y% = 1 TO height% - 1 STEP 2
            IF maze$(x%, y%) = "#" THEN done% = 0
        NEXT y%
    NEXT x%
LOOP

REM draw maze
FOR y% = 0 TO height%
    FOR x% = 0 TO width%
        PRINT maze$(x%, y%);
    NEXT x%
    PRINT
NEXT y%

REM wait
DO: LOOP WHILE INKEY$ = ""
Output:

This used a slightly modified version that outputs to a text file. (You can't copy from a QB64 window.)

#########################################
# #   #     #     #   #   #       # #   #
# ### # # # # ##### # # ### # # # # # ###
# #   # # #   #   # #     # # # #     # #
# # # ####### # ####### ####### ##### # #
#   #             # #     #     #   #   #
# ##### ### ### # # ### # # ##### ### ###
#     # # # #   #   # # #     # # #     #
### ##### # ##### ### ### # ### # # #####
#       # #   #     #     # # #   # #   #
# # # ### # # ##### ### # # # # ##### ###
# # # #     # #         # #     # #     #
# ### # # ######### ### ####### # ##### #
# #   # # #   # #     #   # # # #   # # #
# ### ####### # ### # ##### # # ### # # #
#   #         # #   # # #     #       # #
##### # ### ### ### ### # # # # # # # # #
#     # #   #     #   #   # #   # # #   #
# # # # ### # ### ### ### # ### ### ### #
# # # #   #   #   #   #   #   #   #   # #
#########################################

BASIC256[edit]

global size_x, size_y
size_x = 25
size_y = 15

global char_wall, char_room
char_wall = "#"
char_room = " "

global directions_permutations
directions_permutations = {{0, 1, 2, 3}, {0, 1, 3, 2}, {0, 2, 1, 3}, {0, 2, 3, 1}, {0, 3, 1, 2}, {0, 3, 2, 1}, {1, 0, 2, 3}, {1, 0, 3, 2}, {1, 2, 0, 3}, {1, 2, 3, 0}, {1, 3, 0, 2}, {1, 3, 2, 0}, {2, 0, 1, 3}, {2, 0, 3, 1}, {2, 1, 0, 3}, {2, 1, 3, 0}, {2, 3, 0, 1}, {2, 3, 1, 0}, {3, 0, 1, 2}, {3, 0, 2, 1}, {3, 1, 0, 2}, {3, 1, 2, 0}, {3, 2, 0, 1}, {3, 2, 1, 0}}

global maze
dim maze[size_x * 2 + 1][size_y * 2 + 1]
for i = 0 to size_x * 2
 for j = 0 to size_y * 2
  maze[i][j] = char_wall
 next j
next i

call make_room(int(rand * size_x), int(rand * size_y))

call draw_maze()

end

subroutine make_room(room_x, room_y)
 maze[1 + room_x * 2][1 + room_y * 2] = char_room
 random_directions_index = rand * 24
 for i = 0 to 3
  random_direction = directions_permutations[random_directions_index][i]
  if ((random_direction / 2) mod 2) < 1 then
   dx = (random_direction mod 2) * 2 - 1
   dy = 0
  else
   dx = 0
   dy = (random_direction mod 2) * 2 - 1
  end if
  if can_dig(room_x + dx, room_y + dy) then
   call make_door(room_x, room_y, dx, dy)
   call make_room(room_x + dx, room_y + dy)
  end if
 next i
end subroutine

function can_dig(room_x, room_y)
 if (room_x < 0) or (room_x >= size_x) or (room_y < 0) or (room_y >= size_y) then
  can_dig = false
 else
  can_dig = (maze[1 + room_x * 2][1 + room_y * 2] = char_wall)
 end if
end function

subroutine make_door(room_x, room_y, dx, dy)
 maze[1 + room_x * 2 + dx][1 + room_y * 2 + dy] = char_room
end subroutine

subroutine draw_maze()
 for i = 0 to size_y * 2
  for j = 0 to size_x * 2
   print maze[j][i];
  next j
  print
 next i
end subroutine
Output:
###################################################
#         #       #       #         #         #   #
# ####### ####### # ##### # ### ##### ##### # # ###
# #     #       #   #     #   # #   # #     # #   #
# ### # ####### ### # ####### # # # # # ##### ### #
#   # #       #   # #         #   # # #   #     # #
# # ##### # ##### ############### # # ### ##### # #
# #     # #     #   #   #       # #     #   #     #
# ##### ####### ### # # # ##### # ##### ### #######
# #   #   #     #   # # # #   # # #   # #   #     #
### # ### # ##### ### # # ### # ### # ### # # ### #
#   #     #       #   #   #   #     #   # # # #   #
# ######### ######### ##### ########### # ### # # #
# #   #   #           #   #       #     #   # # # #
# # # # # ############# ### # # ### ####### # # ###
# # # # #         # #   #   # # #   #     # # #   #
# # # ####### ### # # # # ### ### ##### # # # ### #
#   # #   #   #     # #     # #   #   # # #     # #
####### # # ######### ####### # ### # # # ####### #
#     # #   #         #   #   #   # #   #       # #
# ### # ##### ######### ### ##### # ########### # #
# #     #     #       #   #       # #   #     # # #
# ####### ##### ##### # # ######### # ### ### # # #
#   #   # #     # #   # #       #   #   # #   # # #
### # # # # ##### # ##### ##### # ### # # # ### # #
#   # # #   # #     #     #   # #   # #   # #   # #
# ### # ##### # ##### ##### ### ### # ##### # ### #
# #   #     #   #     # #       #   # #   #   #   #
# # ####### # ####### # # ####### ### ### ####### #
#         #           #           #               #
###################################################

Batch File[edit]

Works with: Windows NT
:amaze Rows Cols [wall char]
:: A stack-less, iterative, depth-first maze generator in native WinNT batch.
:: Rows and Cols must each be >1 and Rows*Cols cannot exceed 2096.
:: Default wall character is #, [wall char] is used if provided.

@ECHO OFF
SETLOCAL EnableDelayedExpansion

:: check for valid input, else GOTO :help
IF /I "%~2" EQU "" GOTO :amaze_help
FOR /F "tokens=* delims=0123456789" %%A IN ("%~1%~2") DO IF "%%~A" NEQ "" GOTO :amaze_help
SET /A "rows=%~1, cols=%~2, mTmp=rows*cols"
IF !rows! LSS 2    GOTO :amaze_help
IF !cols! LSS 2    GOTO :amaze_help
IF !mTmp! GTR 2096 GOTO :amaze_help

:: set map characters and use 1st character of %3 for wall, if defined
SET "wall=#"
SET "hall= "
SET "crumb=."
IF "%~3" NEQ "" SET "wall=%~3"
SET "wall=!wall:~0,1!"

:: assign width, height, cursor position, loop count, and offsets for NSEW
SET /A "cnt=0, wide=cols*2-1, high=rows*2-1, size=wide*high, N=wide*-2, S=wide*2, E=2, W=-2"

:: different random entrance points
:: ...on top
:: SET /A "start=(!RANDOM! %% cols)*2"
:: ...on bottom
:: SET /A "start=size-(!RANDOM! %% cols)*2-1"
:: ...on top or bottom
:: SET /A ch=cols*2, ch=!RANDOM! %% ch
:: IF !ch! GEQ !cols! ( SET /A "start=size-(ch-cols)*2-1"
:: ) ELSE SET /A start=ch*2
:: random entrance inside maze
SET /A "start=(!RANDOM! %% cols*2)+(!RANDOM! %% rows*2)*wide"
SET /A "curPos=start, cTmp=curPos+1, loops=cols*rows*2+1"

:: fill the maze with 8186 wall characters, clip to size, and open 1st cell
SET "mz=!wall!"
FOR /L %%A IN (1,1,6) DO SET mz=!mz!!mz!!mz!!mz!
SET bdr=!mz:~-%wide%!
SET mz=!mz:~3!!mz:~3!
SET mz=!mz:~-%size%!
SET mz=!mz:~0,%curPos%!!hall!!mz:~%cTmp%!

:: iterate #cells*2+1 steps of random depth-first search
FOR /L %%@ IN (1,1,%loops%) DO (
	SET "rand=" & SET "crmPos="
	REM set values for NSEW cell and wall positions
	SET /A "rCnt=rTmp=0, cTmp=curPos+1, np=curPos+N, sp=curPos+S, ep=curPos+E, wp=curPos+W, wChk=curPos/wide*wide, eChk=wChk+wide, nw=curPos-wide, sw=curPos+wide, ew=curPos+1, ww=curPos-1"
	REM examine adjacent cells, build direction list, and find last crumb position
	FOR /F "tokens=1-8" %%A IN ("!np! !sp! !ep! !wp! !nw! !sw! !ew! !ww!") DO (
		IF !np! GEQ 0 IF "!mz:~%%A,1!" EQU "!wall!" ( SET /A rCnt+=1 & SET "rand=n !rand!"
		) ELSE IF "!mz:~%%E,1!" EQU "!crumb!" SET /A crmPos=np, cw=nw
		IF !sp! LEQ !size! IF "!mz:~%%B,1!" EQU "!wall!" ( SET /A rCnt+=1 & SET "rand=s !rand!"
		) ELSE IF "!mz:~%%F,1!" EQU "!crumb!" SET /A crmPos=sp, cw=sw
		IF !ep! LEQ !eChk! IF "!mz:~%%C,1!" EQU "!wall!" ( SET /A rCnt+=1 & SET "rand=e !rand!"
		) ELSE IF "!mz:~%%G,1!" EQU "!crumb!" SET /A crmPos=ep, cw=ew
		IF !wp! GEQ !wChk! IF "!mz:~%%D,1!" EQU "!wall!" ( SET /A rCnt+=1 & SET "rand=w !rand!"
		) ELSE IF "!mz:~%%H,1!" EQU "!crumb!" SET /A crmPos=wp, cw=ww
	)
	IF DEFINED rand ( REM adjacent unvisited cell is available
		SET /A rCnt=!RANDOM! %% rCnt
		FOR %%A IN (!rand!) DO ( REM pick random cell + wall
			IF !rTmp! EQU !rCnt! SET /A "curPos=!%%Ap!, cTmp=curPos+1, mw=!%%Aw!, mTmp=mw+1"
			SET /A rTmp+=1
		)
		REM write the 2 new characters into the maze
		FOR /F "tokens=1-4" %%A IN ("!mw! !mTmp! !curPos! !cTmp!") DO (
			SET "mz=!mz:~0,%%A!!crumb!!mz:~%%B!"
			SET "mz=!mz:~0,%%C!!hall!!mz:~%%D!"
		)
	) ELSE IF DEFINED crmPos ( REM follow the crumbs backward
		SET /A mTmp=cw+1
		REM erase the crumb character and set new cursor position
		FOR /F "tokens=1-2" %%A IN ("!cw! !mTmp!") DO SET "mz=!mz:~0,%%A!!hall!!mz:~%%B!"
		SET "curPos=!crmPos!"
	)
)
SET /A open=cols/2*2, mTmp=open+1
ECHO !wall!!bdr:~0,%open%!!hall!!bdr:~%mTmp%!!wall!
FOR /L %%A IN (0,!wide!,!size!) DO IF %%A LSS !size! ECHO !wall!!mz:~%%A,%wide%!!wall!
ECHO !wall!!bdr:~0,%open%!!hall!!bdr:~%mTmp%!!wall!
ENDLOCAL
EXIT /B 0

:amaze_help
ECHO Usage:   %~0 Rows Cols [wall char]
ECHO          Rows^>1, Cols^>1, and Rows*Cols^<=2096
ECHO Example: %~0 11 39 @
ENDLOCAL
EXIT /B 0

Example output:

@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@ @@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@
@                   @     @   @         @     @     @       @   @         @   @
@ @@@@@@@@@@@ @@@@@@@ @ @ @ @ @ @@@@@ @ @ @ @ @@@ @ @@@ @@@ @ @@@ @ @@@@@ @@@ @
@ @       @   @       @ @ @ @   @     @ @ @ @ @   @     @     @   @ @         @
@ @ @@@@@@@ @@@ @@@@@@@ @ @ @@@@@ @@@@@ @@@ @ @ @@@@@@@@@@@@@@@ @@@ @@@@@@@@@@@
@ @ @     @ @   @   @   @ @ @   @   @       @   @   @         @ @ @     @     @
@ @ @ @@@ @ @ @@@@@ @ @ @@@ @ @ @@@ @@@@@@@ @@@@@ @ @ @@@@@@@ @ @ @@@@@ @ @@@ @
@   @   @ @ @     @ @ @ @   @ @   @   @   @ @     @ @ @ @     @   @   @     @ @
@@@ @@@ @ @ @@@@@ @ @ @ @ @@@ @ @ @@@ @ @ @@@ @@@@@ @ @ @ @@@ @@@ @ @@@@@@@@@ @
@     @ @ @     @   @ @ @   @ @ @   @   @       @   @   @ @   @   @       @   @
@ @@@@@ @ @@@ @ @@@ @ @@@@@ @ @ @@@@@@@@@@@@@@@@@ @@@@@ @ @@@@@ @@@ @@@@@ @ @@@
@   @   @ @   @   @ @ @     @ @ @   @       @   @   @   @ @     @ @ @   @ @   @
@@@@@ @@@ @ @ @@@@@ @ @ @@@@@ @ @ @ @ @@@@@ @ @ @@@ @ @@@ @ @@@@@ @ @ @ @ @@@@@
@     @     @ @     @ @     @ @   @     @   @ @     @ @ @   @       @ @ @   @ @
@ @@@@@@@@@@@ @ @@@@@ @@@@@ @ @@@@@@@ @@@ @ @ @@@@@ @ @ @@@@@@@@@ @@@ @@@ @ @ @
@ @         @ @     @     @ @   @   @ @   @ @     @ @ @         @ @   @   @ @ @
@ @ @@@@@@@ @@@@@@@ @@@ @@@ @@@ @ @ @@@ @@@ @@@@@ @@@ @@@@@@@ @ @ @ @ @ @@@ @ @
@ @     @ @       @ @   @   @   @ @ @   @   @ @   @   @     @ @ @   @ @ @ @ @ @
@ @@@@@ @ @@@ @@@@@ @ @ @ @@@@@@@ @ @ @@@ @@@ @ @@@ @@@ @@@ @ @ @@@@@@@ @ @ @ @
@       @   @       @ @ @   @   @ @   @ @ @   @ @   @   @   @ @ @       @ @   @
@ @@@@@@@ @ @@@@@@@@@ @@@@@ @ @ @ @@@@@ @ @ @ @ @ @@@ @@@ @@@ @ @ @@@@@@@ @@@ @
@         @         @         @   @         @ @       @       @   @           @
@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@ @@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@

BBC BASIC[edit]

      MazeWidth% = 11
      MazeHeight% = 9
      MazeCell% = 50
      
      VDU 23,22,MazeWidth%*MazeCell%/2+3;MazeHeight%*MazeCell%/2+3;8,16,16,128
      VDU 23,23,3;0;0;0; : REM Line thickness
      PROCgeneratemaze(Maze&(), MazeWidth%, MazeHeight%, MazeCell%)
      END
      
      DEF PROCgeneratemaze(RETURN m&(), w%, h%, s%)
      LOCAL x%, y%
      DIM m&(w%, h%)
      FOR y% = 0 TO h%
        LINE 0,y%*s%,w%*s%,y%*s%
      NEXT
      FOR x% = 0 TO w%
        LINE x%*s%,0,x%*s%,h%*s%
      NEXT
      GCOL 15
      PROCcell(m&(), RND(w%)-1, y% = RND(h%)-1, w%, h%, s%)
      ENDPROC
      
      DEF PROCcell(m&(), x%, y%, w%, h%, s%)
      LOCAL i%, p%, q%, r%
      m&(x%,y%) OR= &40 : REM Mark visited
      r% = RND(4)
      FOR i% = r% TO r%+3
        CASE i% MOD 4 OF
          WHEN 0: p% = x%-1 : q% = y%
          WHEN 1: p% = x%+1 : q% = y%
          WHEN 2: p% = x% : q% = y%-1
          WHEN 3: p% = x% : q% = y%+1
        ENDCASE
        IF p% >= 0 IF p% < w% IF q% >= 0 IF q% < h% IF m&(p%,q%) < &40 THEN
          IF p% > x% m&(p%,q%) OR= 1 : LINE p%*s%,y%*s%+4,p%*s%,(y%+1)*s%-4
          IF q% > y% m&(p%,q%) OR= 2 : LINE x%*s%+4,q%*s%,(x%+1)*s%-4,q%*s%
          IF x% > p% m&(x%,y%) OR= 1 : LINE x%*s%,y%*s%+4,x%*s%,(y%+1)*s%-4
          IF y% > q% m&(x%,y%) OR= 2 : LINE x%*s%+4,y%*s%,(x%+1)*s%-4,y%*s%
          PROCcell(m&(), p%, q%, w%, h%, s%)
        ENDIF
      NEXT
      ENDPROC

Sample output:
Maze bbc.gif

Befunge[edit]

Dimensions are specified by the first two values pushed onto the stack - currently 20 (45*) by 16 (28*). Note, however, that the upper limit in a standard Befunge-93 implementation will be around 38 by 40 (1520 cells) due to the constrained page size.

Also note that this requires an interpreter with working read-write memory support, which is suprisingly rare in online implementations. Padding the code page with extra blank lines or spaces can sometimes help. Using smaller dimensions might also be preferable, especially on slower implementations.

45*28*10p00p020p030p006p0>20g30g00g*+::"P"%\"P"/6+gv>$\1v@v1::\+g02+*g00+g03-\<
0_ 1!%4+1\-\0!::\-\2%2:p<pv0<< v0p+6/"P"\%"P":\+4%4<^<v-<$>+2%\1-*20g+\1+4%::v^
#| +2%\1-*30g+\1\40g1-:v0+v2?1#<v>+:00g%!55+*>:#0>#,_^>:!|>\#%"P"v#:*+*g00g0<>1
02!:++`\0\`-1g01:\+`\< !46v3<^$$<^1,g2+1%2/2,g1+1<v%g00:\<*g01,<>:30p\:20p:v^3g
0#$g#<1#<-#<`#<\#<0#<^#_^/>#1+#4<>"P"%\"P"/6+g:2%^!>,1-:#v_$55+^|$$ "JH" $$>#<0
::"P"%\"P"/6+g40p\40g+\:#^"P"%#\<^ ::$_,#!0#:<*"|"<^," _"<:g000 <> /6+g4/2%+#^_
Output:
 _ _ _ _ _ _ _ _ _ _ _ _ _ _ _ _ _ _ _ _
|_  |  _ _  |_     _ _|  _ _   _ _  |_  |
| |_ _|  _|_  |_|_  |  _| |  _|_  |_  | |
|   |_   _  | |   |_ _   _| |  _ _ _|_  |
| |_  |_|  _|_ _|_  |_ _|  _|_  |    _| |
| |_ _ _  |   |  _ _|   |  _  | | | |  _|
|  _ _  |_| | | |  _ _| |_|  _|  _|_ _| |
| | |  _|  _|_ _|_  |_ _  | | | |  _ _  |
|_  |_ _ _|  _ _  |_ _  |_ _| | |_  | | |
| |_ _ _ _ _|   |_ _ _ _| |   |_  | | | |
|_    |  _ _ _|_ _ _ _ _  | |_  |_ _| | |
|  _|_ _|_ _   _    |  _ _|_  |_   _ _| |
| |  _ _ _  | |  _|_|_ _ _  |_  |_ _  | |
|  _|  _  | | |_ _ _ _ _   _ _| | |   | |
|_  |_  |  _|_|   |  _  |_|  _ _ _| | | |
| | | | |_|  _ _| | |  _|  _|   |  _|_| |
|_ _ _|_ _ _ _ _|_ _|_ _ _ _ _|_|_ _ _ _|

C[edit]

Generation/solver in one. Requires UTF8 locale and unicode capable console. If your console font line-drawing chars are single width, define DOUBLE_SPACE to 0.

#include <stdio.h>
#include <stdlib.h>
#include <string.h>
#include <locale.h>

#define DOUBLE_SPACE 1

#if DOUBLE_SPACE
#	define SPC " "
#else
#	define SPC " "
#endif

wchar_t glyph[] = L""SPC"│││─┘┐┤─└┌├─┴┬┼"SPC"┆┆┆┄╯╮ ┄╰╭ ┄";

typedef unsigned char byte;
enum { N = 1, S = 2, W = 4, E = 8, V = 16 };

byte **cell;
int w, h, avail;
#define each(i, x, y) for (i = x; i <= y; i++)

int irand(int n)
{
	int r, rmax = n * (RAND_MAX / n);
	while ((r = rand()) >= rmax);
	return r / (RAND_MAX/n);
}

void show()
{
	int i, j, c;
	each(i, 0, 2 * h) {
		each(j, 0, 2 * w) {
			c = cell[i][j];
			if (c > V) printf("\033[31m");
			printf("%lc", glyph[c]);
			if (c > V) printf("\033[m");
		}
		putchar('\n');
	}
}

inline int max(int a, int b) { return a >= b ? a : b; }
inline int min(int a, int b) { return b >= a ? a : b; }

static int dirs[4][2] = {{-2, 0}, {0, 2}, {2, 0}, {0, -2}};
void walk(int x, int y)
{
	int i, t, x1, y1, d[4] = { 0, 1, 2, 3 };

	cell[y][x] |= V;
	avail--;

	for (x1 = 3; x1; x1--)
		if (x1 != (y1 = irand(x1 + 1)))
			i = d[x1], d[x1] = d[y1], d[y1] = i;

	for (i = 0; avail && i < 4; i++) {
		x1 = x + dirs[ d[i] ][0], y1 = y + dirs[ d[i] ][1];

		if (cell[y1][x1] & V) continue;

		/* break walls */
		if (x1 == x) {
			t = (y + y1) / 2;
			cell[t][x+1] &= ~W, cell[t][x] &= ~(E|W), cell[t][x-1] &= ~E;
		} else if (y1 == y) {
			t = (x + x1)/2;
			cell[y-1][t] &= ~S, cell[y][t] &= ~(N|S), cell[y+1][t] &= ~N;
		}
		walk(x1, y1);
	}
}

int solve(int x, int y, int tox, int toy)
{
	int i, t, x1, y1;

	cell[y][x] |= V;
	if (x == tox && y == toy) return 1;

	each(i, 0, 3) {
		x1 = x + dirs[i][0], y1 = y + dirs[i][1];
		if (cell[y1][x1]) continue;

		/* mark path */
		if (x1 == x) {
			t = (y + y1)/2;
			if (cell[t][x] || !solve(x1, y1, tox, toy)) continue;

			cell[t-1][x] |= S, cell[t][x] |= V|N|S, cell[t+1][x] |= N;
		} else if (y1 == y) {
			t = (x + x1)/2;
			if (cell[y][t] || !solve(x1, y1, tox, toy)) continue;

			cell[y][t-1] |= E, cell[y][t] |= V|E|W, cell[y][t+1] |= W;
		}
		return 1;
	}

	/* backtrack */
	cell[y][x] &= ~V;
	return 0;
}

void make_maze()
{
	int i, j;
	int h2 = 2 * h + 2, w2 = 2 * w + 2;
	byte **p;

	p = calloc(sizeof(byte*) * (h2 + 2) + w2 * h2 + 1, 1);

	p[1] = (byte*)(p + h2 + 2) + 1;
	each(i, 2, h2) p[i] = p[i-1] + w2;
	p[0] = p[h2];
	cell = &p[1];

	each(i, -1, 2 * h + 1) cell[i][-1] = cell[i][w2 - 1] = V;
	each(j, 0, 2 * w) cell[-1][j] = cell[h2 - 1][j] = V;
	each(i, 0, h) each(j, 0, 2 * w) cell[2*i][j] |= E|W;
	each(i, 0, 2 * h) each(j, 0, w) cell[i][2*j] |= N|S;
	each(j, 0, 2 * w) cell[0][j] &= ~N, cell[2*h][j] &= ~S;
	each(i, 0, 2 * h) cell[i][0] &= ~W, cell[i][2*w] &= ~E;

	avail = w * h;
	walk(irand(2) * 2 + 1, irand(h) * 2 + 1);

	/* reset visited marker (it's also used by path finder) */
	each(i, 0, 2 * h) each(j, 0, 2 * w) cell[i][j] &= ~V;
	solve(1, 1, 2 * w - 1, 2 * h - 1);

	show();
}

int main(int c, char **v)
{
	setlocale(LC_ALL, "");
	if (c < 2 || (w = atoi(v[1])) <= 0) w = 16;
	if (c < 3 || (h = atoi(v[2])) <= 0) h = 8;

	make_maze();

	return 0;
}
Sample output:
┌───┬─────┬─────────┬───────┬───┐
│┄┄╮│╭┄┄┄╮│  ╭┄┄┄┄┄╮│  ╭┄┄┄╮│╭┄╮│
│ │┆│┆──┐┆│ │┆──┬─┐┆└──┆┌─┐┆│┆│┆│
│ │┆│╰┄╮│┆│ │╰┄╮│ │╰┄┄┄╯│ │╰┄╯│┆│
│ │┆└──┆│┆└─┼──┆│ └─────┤ └─┬─┘┆│
│ │╰┄┄┄╯│╰┄╮│╭┄╯│       │   │╭┄╯│
│ └─────┴─┐┆│┆┌─┴───┐ │ │ │ │┆──┤
│         │┆│┆│╭┄┄┄╮│ │   │ │╰┄╮│
│ ──────┐ │┆│┆│┆──┐┆└─┤ ┌─┘ └─┐┆│
│       │ │┆│╰┄╯  │╰┄╮│ │     │┆│
│ ┌─────┘ │┆├─────┴─┐┆│ │ ──┬─┘┆│
│ │       │┆│╭┄┄┄┄┄╮│┆│ │   │╭┄╯│
├─┤ ──┬─┬─┘┆│┆┌─┬──┆│┆└─┴─┐ │┆┌─┤
│ │   │ │╭┄╯│┆│ │╭┄╯│╰┄┄┄╮│ │┆│ │
│ └── │ │┆──┘┆│ │┆──┴────┆│ │┆│ │
│     │  ╰┄┄┄╯│  ╰┄┄┄┄┄┄┄╯│  ╰┄┄│
└─────┴───────┴───────────┴─────┘

C#[edit]

using System;
using System.Collections.Generic;
using System.Diagnostics;
using System.Linq;
using System.Text;
using System.Drawing;

namespace MazeGeneration
{
    public static class Extensions
    {
        public static IEnumerable<T> Shuffle<T>(this IEnumerable<T> source, Random rng)
        {
            var e = source.ToArray();
            for (var i = e.Length - 1; i >= 0; i--)
            {
                var swapIndex = rng.Next(i + 1);
                yield return e[swapIndex];
                e[swapIndex] = e[i];
            }
        }

        public static CellState OppositeWall(this CellState orig)
        {
            return (CellState)(((int) orig >> 2) | ((int) orig << 2)) & CellState.Initial;
        }

        public static bool HasFlag(this CellState cs,CellState flag)
        {
            return ((int)cs & (int)flag) != 0;
        }
    }

    [Flags]
    public enum CellState
    {
        Top = 1,
        Right = 2,
        Bottom = 4,
        Left = 8,
        Visited = 128,
        Initial = Top | Right | Bottom | Left,
    }

    public struct RemoveWallAction
    {
        public Point Neighbour;
        public CellState Wall;
    }

    public class Maze
    {
        private readonly CellState[,] _cells;
        private readonly int _width;
        private readonly int _height;
        private readonly Random _rng;

        public Maze(int width, int height)
        {
            _width = width;
            _height = height;
            _cells = new CellState[width, height];
            for(var x=0; x<width; x++)
                for(var y=0; y<height; y++)
                    _cells[x, y] = CellState.Initial;
            _rng = new Random();
            VisitCell(_rng.Next(width), _rng.Next(height));
        }

        public CellState this[int x, int y]
        {
            get { return _cells[x,y]; }
            set { _cells[x,y] = value; }
        }

        public IEnumerable<RemoveWallAction> GetNeighbours(Point p)
        {
            if (p.X > 0) yield return new RemoveWallAction {Neighbour = new Point(p.X - 1, p.Y), Wall = CellState.Left};
            if (p.Y > 0) yield return new RemoveWallAction {Neighbour = new Point(p.X, p.Y - 1), Wall = CellState.Top};
            if (p.X < _width-1) yield return new RemoveWallAction {Neighbour = new Point(p.X + 1, p.Y), Wall = CellState.Right};
            if (p.Y < _height-1) yield return new RemoveWallAction {Neighbour = new Point(p.X, p.Y + 1), Wall = CellState.Bottom};
        }

        public void VisitCell(int x, int y)
        {
            this[x,y] |= CellState.Visited;
            foreach (var p in GetNeighbours(new Point(x, y)).Shuffle(_rng).Where(z => !(this[z.Neighbour.X, z.Neighbour.Y].HasFlag(CellState.Visited))))
            {
                this[x, y] -= p.Wall;
                this[p.Neighbour.X, p.Neighbour.Y] -= p.Wall.OppositeWall();
                VisitCell(p.Neighbour.X, p.Neighbour.Y);
            }
        }

        public void Display()
        {
            var firstLine = string.Empty;
            for (var y = 0; y < _height; y++)
            {
                var sbTop = new StringBuilder();
                var sbMid = new StringBuilder();
                for (var x = 0; x < _width; x++)
                {
                    sbTop.Append(this[x, y].HasFlag(CellState.Top) ? "+---" : "+   ");
                    sbMid.Append(this[x, y].HasFlag(CellState.Left) ? "|   " : "    ");
                }
                if (firstLine == string.Empty)
                    firstLine = "   " + sbTop.ToString();
                Debug.WriteLine("   " + sbTop + "+");
                Debug.WriteLine("   " + sbMid + "|");
            }
            Debug.WriteLine(firstLine);
        }
    }

    class Program
    {
        static void Main(string[] args)
        {
            var maze = new Maze(20, 20);
            maze.Display();
        }
    }
}

Sample output:

   +---+---+---+---+---+---+---+---+---+---+---+---+---+---+---+---+---+---+---+---+
   |           |                   |                       |                       |
   +   +---+   +---+---+   +---+   +   +---+---+   +---+   +---+---+   +---+---+   +
   |   |       |           |   |   |       |       |       |           |       |   |
   +   +   +---+   +---+---+   +   +---+---+   +---+---+   +   +---+---+   +   +   +
   |   |           |   |       |   |           |       |       |           |   |   |
   +   +   +---+---+   +   +   +   +   +---+---+   +   +---+---+   +---+---+   +   +
   |   |   |       |   |   |       |               |           |   |           |   |
   +   +---+   +   +   +   +---+---+   +---+---+---+---+---+   +   +   +---+---+   +
   |           |   |   |           |                   |   |       |   |   |       |
   +---+---+---+   +   +---+---+   +---+---+---+---+   +   +---+---+   +   +   +---+
   |           |   |           |               |           |           |       |   |
   +   +---+---+---+   +   +---+---+---+---+   +   +---+---+   +---+---+   +---+   +
   |       |           |           |       |   |   |           |       |   |       |
   +   +   +   +---+---+---+---+   +   +   +   +   +   +---+---+   +   +   +---+   +
   |   |       |                   |   |       |   |       |       |               |
   +   +---+---+   +---+   +---+---+   +---+---+   +---+   +---+---+   +---+---+---+
   |       |       |   |   |           |       |   |   |   |       |       |       |
   +---+---+   +---+   +   +   +---+---+   +---+   +   +   +   +   +---+---+   +   +
   |           |           |       |   |           |   |       |               |   |
   +   +---+---+   +---+---+---+   +   +   +---+---+   +---+---+---+---+---+---+   +
   |       |       |           |   |   |       |                               |   |
   +   +   +   +---+   +---+   +   +   +---+   +---+---+   +---+---+---+---+---+   +
   |   |   |   |       |   |       |       |   |           |                       |
   +   +   +---+   +---+   +---+---+   +   +   +   +---+---+   +---+---+---+---+   +
   |   |           |                   |   |       |       |   |               |   |
   +   +---+---+---+---+---+   +---+---+   +   +---+   +   +   +   +   +---+---+   +
   |   |       |           |   |       |   |   |       |       |   |   |       |   |
   +   +   +   +---+   +   +   +   +---+   +   +   +---+---+---+   +---+   +   +   +
   |       |       |   |       |   |       |   |           |   |           |       |
   +---+---+---+   +   +---+---+   +   +---+   +---+---+   +   +   +---+---+---+---+
   |           |   |       |           |       |   |       |       |       |       |
   +   +---+   +   +   +   +   +---+---+   +---+   +   +---+   +---+   +---+   +   +
   |   |   |       |   |   |           |   |       |   |   |   |       |       |   |
   +   +   +---+---+---+   +---+---+---+   +   +---+   +   +   +   +   +   +---+   +
   |       |           |               |       |       |   |   |   |           |   |
   +---+   +---+   +   +---+---+---+   +---+   +   +---+   +   +---+---+---+---+   +
   |   |           |   |           |           |   |   |       |                   |
   +   +---+---+---+   +   +---+   +---+---+---+   +   +   +---+   +---+---+---+   +
   |                       |                       |               |               |
   +---+---+---+---+---+---+---+---+---+---+---+---+---+---+---+---+---+---+---+---

C++[edit]

Maze cpp.png

#include <windows.h>
#include <iostream>
#include <string>

//--------------------------------------------------------------------------------------------------
using namespace std;

//--------------------------------------------------------------------------------------------------
const int BMP_SIZE = 512, CELL_SIZE = 8;

//--------------------------------------------------------------------------------------------------
enum directions { NONE, NOR = 1, EAS = 2, SOU = 4, WES = 8 };

//--------------------------------------------------------------------------------------------------
class myBitmap
{
public:
    myBitmap() : pen( NULL ) {}
    ~myBitmap()
    {
	DeleteObject( pen );
	DeleteDC( hdc );
	DeleteObject( bmp );
    }

    bool create( int w, int h )
    {
	BITMAPINFO	bi;
	ZeroMemory( &bi, sizeof( bi ) );
	bi.bmiHeader.biSize	   = sizeof( bi.bmiHeader );
	bi.bmiHeader.biBitCount	   = sizeof( DWORD ) * 8;
	bi.bmiHeader.biCompression = BI_RGB;
	bi.bmiHeader.biPlanes	   = 1;
	bi.bmiHeader.biWidth	   =  w;
	bi.bmiHeader.biHeight	   = -h;

	HDC dc = GetDC( GetConsoleWindow() );
	bmp = CreateDIBSection( dc, &bi, DIB_RGB_COLORS, &pBits, NULL, 0 );
	if( !bmp ) return false;

	hdc = CreateCompatibleDC( dc );
	SelectObject( hdc, bmp );
	ReleaseDC( GetConsoleWindow(), dc ); 
	width = w; height = h;

	return true;
    }

    void clear()
    {
	ZeroMemory( pBits, width * height * sizeof( DWORD ) );
    }

    void setPenColor( DWORD clr )
    {
	if( pen ) DeleteObject( pen );
	pen = CreatePen( PS_SOLID, 1, clr );
	SelectObject( hdc, pen );
    }

    void saveBitmap( string path )
    {
	BITMAPFILEHEADER fileheader;
	BITMAPINFO	 infoheader;
	BITMAP		 bitmap;
	DWORD		 wb;

	GetObject( bmp, sizeof( bitmap ), &bitmap );

	DWORD* dwpBits = new DWORD[bitmap.bmWidth * bitmap.bmHeight];
	ZeroMemory( dwpBits, bitmap.bmWidth * bitmap.bmHeight * sizeof( DWORD ) );
	ZeroMemory( &infoheader, sizeof( BITMAPINFO ) );
	ZeroMemory( &fileheader, sizeof( BITMAPFILEHEADER ) );

	infoheader.bmiHeader.biBitCount = sizeof( DWORD ) * 8;
	infoheader.bmiHeader.biCompression = BI_RGB;
	infoheader.bmiHeader.biPlanes = 1;
	infoheader.bmiHeader.biSize = sizeof( infoheader.bmiHeader );
	infoheader.bmiHeader.biHeight = bitmap.bmHeight;
	infoheader.bmiHeader.biWidth = bitmap.bmWidth;
	infoheader.bmiHeader.biSizeImage = bitmap.bmWidth * bitmap.bmHeight * sizeof( DWORD );

	fileheader.bfType    = 0x4D42;
	fileheader.bfOffBits = sizeof( infoheader.bmiHeader ) + sizeof( BITMAPFILEHEADER );
	fileheader.bfSize    = fileheader.bfOffBits + infoheader.bmiHeader.biSizeImage;

	GetDIBits( hdc, bmp, 0, height, ( LPVOID )dwpBits, &infoheader, DIB_RGB_COLORS );

	HANDLE file = CreateFile( path.c_str(), GENERIC_WRITE, 0, NULL, CREATE_ALWAYS, FILE_ATTRIBUTE_NORMAL, NULL );
	WriteFile( file, &fileheader, sizeof( BITMAPFILEHEADER ), &wb, NULL );
	WriteFile( file, &infoheader.bmiHeader, sizeof( infoheader.bmiHeader ), &wb, NULL );
	WriteFile( file, dwpBits, bitmap.bmWidth * bitmap.bmHeight * 4, &wb, NULL );
	CloseHandle( file );

	delete [] dwpBits;
    }

    HDC getDC() const     { return hdc; }
    int getWidth() const  { return width; }
    int getHeight() const { return height; }

private:
    HBITMAP bmp;
    HDC	    hdc;
    HPEN    pen;
    void    *pBits;
    int	    width, height;
};
//--------------------------------------------------------------------------------------------------
class mazeGenerator
{
public:
    mazeGenerator()
    {
	_world = 0; 
	_bmp.create( BMP_SIZE, BMP_SIZE ); 
	_bmp.setPenColor( RGB( 0, 255, 0 ) ); 
    }

    ~mazeGenerator() { killArray(); }

    void create( int side )
    {
	_s = side;
	generate();
	display();
    }

private:
    void generate()
    {
	killArray();
	_world = new BYTE[_s * _s];
	ZeroMemory( _world, _s * _s );
	_ptX = rand() % _s; _ptY = rand() % _s;
	carve();
    }

    void carve()
    {
	while( true )
	{
	    int d = getDirection();
	    if( d < NOR ) return;

	    switch( d )
	    {
	        case NOR:
	            _world[_ptX + _s * _ptY] |= NOR; _ptY--;
		    _world[_ptX + _s * _ptY] = SOU | SOU << 4;
		break;
	        case EAS:
		    _world[_ptX + _s * _ptY] |= EAS; _ptX++;
		    _world[_ptX + _s * _ptY] = WES | WES << 4;
		break;
		case SOU:
		    _world[_ptX + _s * _ptY] |= SOU; _ptY++;
		    _world[_ptX + _s * _ptY] = NOR | NOR << 4;
		break;
		case WES:
		    _world[_ptX + _s * _ptY] |= WES; _ptX--;
		    _world[_ptX + _s * _ptY] = EAS | EAS << 4;
	    }
	}
    }

    void display()
    {
	_bmp.clear();
	HDC dc = _bmp.getDC();
	for( int y = 0; y < _s; y++ )
	{
	    int yy = y * _s;
	    for( int x = 0; x < _s; x++ )
	    {
		BYTE b = _world[x + yy];
		int nx = x * CELL_SIZE, 
		    ny = y * CELL_SIZE;
				
		if( !( b & NOR ) )
		{
		    MoveToEx( dc, nx, ny, NULL );
		    LineTo( dc, nx + CELL_SIZE + 1, ny );
		}
		if( !( b & EAS ) )
		{
		    MoveToEx( dc, nx + CELL_SIZE, ny, NULL );
		    LineTo( dc, nx + CELL_SIZE, ny + CELL_SIZE + 1 );
		}
		if( !( b & SOU ) )
		{
		    MoveToEx( dc, nx, ny + CELL_SIZE, NULL );
		    LineTo( dc, nx + CELL_SIZE + 1, ny + CELL_SIZE );
		}
		if( !( b & WES ) )
		{
		    MoveToEx( dc, nx, ny, NULL );
		    LineTo( dc, nx, ny + CELL_SIZE + 1 );
		}
	    }
	}

	//_bmp.saveBitmap( "f:\\rc\\maze.bmp" );
	BitBlt( GetDC( GetConsoleWindow() ), 10, 60, BMP_SIZE, BMP_SIZE, _bmp.getDC(), 0, 0, SRCCOPY );
    }

    int getDirection()
    {
	int d = 1 << rand() % 4;
	while( true )
	{
	    for( int x = 0; x < 4; x++ )
	    {
		if( testDir( d ) ) return d;
		d <<= 1;
		if( d > 8 ) d = 1;
	    }
	    d = ( _world[_ptX + _s * _ptY] & 0xf0 ) >> 4;
	    if( !d ) return -1;
	    switch( d )
	    {
		case NOR: _ptY--; break;
		case EAS: _ptX++; break;
		case SOU: _ptY++; break;
		case WES: _ptX--; break;
	    }
            d = 1 << rand() % 4;
	}
    }

    bool testDir( int d )
    {
	switch( d )
	{
	    case NOR: return ( _ptY - 1 > -1 && !_world[_ptX + _s * ( _ptY - 1 )] );
	    case EAS: return ( _ptX + 1 < _s && !_world[_ptX + 1 + _s * _ptY] );
	    case SOU: return ( _ptY + 1 < _s && !_world[_ptX + _s * ( _ptY + 1 )] );
	    case WES: return ( _ptX - 1 > -1 && !_world[_ptX - 1 + _s * _ptY] );
	}
	return false;
    }

    void killArray() { if( _world ) delete [] _world; }

    BYTE*    _world;
    int      _s, _ptX, _ptY;
    myBitmap _bmp;
};
//--------------------------------------------------------------------------------------------------
int main( int argc, char* argv[] )
{
    ShowWindow( GetConsoleWindow(), SW_MAXIMIZE );
    srand( GetTickCount() );

    mazeGenerator mg;
    int s;
    while( true )
    {
	cout << "Enter the maze size, an odd number bigger than 2 ( 0 to QUIT ): "; cin >> s;
	if( !s ) return 0;
	if( !( s & 1 ) ) s++;
	if( s >= 3 ) mg.create( s );
	cout << endl;
	system( "pause" );
	system( "cls" );
    }
    return 0;
}
//--------------------------------------------------------------------------------------------------

Clojure[edit]

(ns maze.core
  (:require [clojure.set :refer [intersection
                                 select]]
            [clojure.string :as str]))

;; Misc functions
(defn neighborhood
  ([] (neighborhood [0 0]))
  ([coord] (neighborhood coord 1))
  ([[y x] r]
   (let [y-- (- y r) y++ (+ y r)
         x-- (- x r) x++ (+ x r)]
     #{[y++ x] [y-- x] [y x--] [y x++]})))

(defn cell-empty? [maze coords]
  (= :empty (get-in maze coords)))

(defn wall? [maze coords]
  (= :wall (get-in maze coords)))

(defn filter-maze
  ([pred maze coords]
   (select (partial pred maze) (set coords)))
  ([pred maze]
   (filter-maze
     pred
     maze
     (for [y (range (count maze))
           x (range (count (nth maze y)))]
       [y x]))))

(defn create-empty-maze [width height]
  (let [width (inc (* 2 width))
        height (inc (* 2 height))]
    (vec (take height
               (interleave
                 (repeat (vec (take width (repeat :wall))))
                 (repeat (vec (take width (cycle [:wall :empty])))))))))

(defn next-step [possible-steps]
  (rand-nth (vec possible-steps)))

;;Algo
(defn create-random-maze [width height]
  (loop [maze (create-empty-maze width height)
         stack []
         nonvisited (filter-maze cell-empty? maze)
         visited #{}
         coords (next-step nonvisited)]
    (if (empty? nonvisited)
      maze
      (let [nonvisited-neighbors (intersection (neighborhood coords 2) nonvisited)]
        (cond
          (seq nonvisited-neighbors)
          (let [next-coords (next-step nonvisited-neighbors)
                wall-coords (map #(+ %1 (/ (- %2 %1) 2)) coords next-coords)]
            (recur (assoc-in maze wall-coords :empty)
                   (conj stack coords)
                   (disj nonvisited next-coords)
                   (conj visited next-coords)
                   next-coords))

          (seq stack)
          (recur maze (pop stack) nonvisited visited (last stack)))))))

;;Conversion to string
(def cell-code->str
  ["  " "  " "  " "  " "· " "╵ " "╴ " "┘ "
   "  " "  " "  " "  " "╶─" "└─" "──" "┴─"
   "  " "  " "  " "  " "╷ " "│ " "┐ " "┤ "
   "  " "  " "  " "  " "┌─" "├─" "┬─" "┼─"])

(defn cell-code [maze coord]
  (transduce
    (comp
      (map (partial wall? maze))
      (keep-indexed (fn [idx el] (when el idx)))
      (map (partial bit-shift-left 1)))
    (completing bit-or)
    0
    (sort (cons coord (neighborhood coord)))))

(defn cell->str [maze coord]
  (get cell-code->str (cell-code maze coord)))

(defn maze->str [maze]
  (->> (for [y (range (count maze))]
         (for [x (range (count (nth maze y)))]
           (cell->str maze [y x])))
       (map str/join)
       (str/join \newline)))

;;Task
(println (maze->str (create-random-maze 10 10)))
Output:
┌───────────┬───────────────┬───────┬───┐ 
│           │               │       │   │ 
├───╴   ╷   ╵   ┌───────────┤   ╷   │   │ 
│       │       │           │   │   │   │ 
│   ╷   └───┐   │   ╶───┐   ╵   │   │   │ 
│   │       │   │       │       │   │   │ 
│   └───┐   └───┴───╴   ├───────┤   │   │ 
│       │               │       │   │   │ 
│   ╷   └───────────────┼───╴   │   ╵   │ 
│   │                   │       │       │ 
├───┴───┐   ┌───────┐   ╵   ╷   ├───╴   │ 
│       │   │       │       │   │       │ 
│   ╷   ╵   │   ╷   ╵   ┌───┴───┘   ┌───┤ 
│   │       │   │       │           │   │ 
│   └───────┴───┴───────┤   ╶───────┤   │ 
│                       │           │   │ 
│   ╶───────┬───────┐   └───┬───╴   │   │ 
│           │       │       │       │   │ 
├───────╴   ╵   ╷   │   ╶───┘   ╶───┘   │ 
│               │   │                   │ 
└───────────────┴───┴───────────────────┘ 

Commodore BASIC[edit]

Written in Commodore BASIC V2 and tested on Commodore 64 and Commodore 128 hardware. (It will also run on the unexpanded Commodore VIC-20 if you reduce the maze size to 8x8.) Due to stack size limitations in the operating systems, this solution eschews recursive subroutine calls. Recursion is accomplished by conditional branching within the maze build routine and the use of an array-based stack for data elements.

100 MS=10:REM MAZE SIZE
110 DIM S(MS+1,MS+1):REM SOUTH WALLS
120 DIM W(MS+1,MS+1):REM WEST WALLS
130 DIM V(MS+1,MS+1):REM VISITED CELLS
140 PRINT "INITIALIZING..."
150 GOSUB 260:REM INITIALIZE MAZE
160 PRINT "BUILDING..."
170 DIM PC(MS*MS+1):DIM PR(MS*MS+1):REM STACK
180 REM PICK RANDOM STARTING CELL
190 X = RND(-TI)
200 C=(INT(RND(1)*MS)+1)
210 R=(INT(RND(1)*MS)+1)
220 GOSUB 400:REM BUILD MAZE
230 GOSUB 540:REM DRAW MAZE
240 END
250 REM -----INITIALIZE MAZE-----
260 REM SET WALLS ON AND VISITED CELLS OFF
270 T=MS+1
280 FOR C=0 TO T:FOR R=0 TO T:
290 S(C,R)=1:W(C,R)=1:V(C,R)=0
300 NEXT R:NEXT C
310 REM SET BORDER CELLS TO VISITED
320 FOR C=0 TO T
330 V(C,0)=1:V(C,T)=1
340 NEXT C
350 FOR R=0 TO T
360 V(0,R)=1:V(T,R)=1
370 NEXT R
380 RETURN
390 REM -----BUILD MAZE-----
400 U=U+1:PC(U)=C:PR(U)=R:REM PUSH
410 V(C,R)=1
420 IF V(C,R+1)=1 AND V(C+1,R)=1 AND V(C,R-1)=1 AND V(C-1,R)=1 THEN GOTO 500
430 Z=INT(RND(1)*4)
440 IF Z=0 AND V(C,R+1)=0 THEN S(C,R)=0:R=R+1:GOTO 400
450 IF Z=1 AND V(C+1,R)=0 THEN W(C+1,R)=0:C=C+1:GOTO 400
460 IF Z=2 AND V(C,R-1)=0 THEN S(C,R-1)=0:R=R-1:GOTO 400
470 IF Z=3 AND V(C-1,R)=0 THEN W(C,R)=0:C=C-1:GOTO 400
480 GOTO 430
500 C=PC(U):R=PR(U):U=U-1:REM POP
510 IF U > 0 THEN GOTO 420
520 RETURN
530 REM -----DRAW MAZE-----
540 REM OPEN 4,4:CMD 4:REM SEND OUTPUT TO PRINTER
550 PRINT "+--+--+--+--+--+--+--+--+--+--+"
560 FOR R = 1 TO MS
570 FOR C = 1 TO MS+1
580 IF W(C,R)=0 THEN PRINT "   ";
590 IF W(C,R)=1 THEN PRINT ":  ";
600 NEXT C
610 PRINT
620 FOR C = 1 TO MS
630 IF S(C,R)=0 THEN PRINT "+  ";
640 IF S(C,R)=1 THEN PRINT "+--";
650 NEXT C
660 PRINT "+"
670 NEXT R
680 REM PRINT#4:CLOSE 4:REM CLOSE PRINTER DEVICE
690 RETURN
Output example (for 10x10 maze):
+--+--+--+--+--+--+--+--+--+--+
:     :        :              :  
+  +  +  +  +--+  +--+--+--+  +
:  :  :  :        :     :     :  
+  +  +  +--+  +--+  +  +  +--+
:  :     :  :  :     :  :     :  
+  +--+--+  +  +  +--+  +--+  +
:     :     :  :  :  :        :  
+--+  +  +--+--+  +  +--+--+  +
:  :  :  :        :  :        :  
+  +  +  +  +--+--+  +  +--+--+
:     :  :        :  :  :     :  
+  +--+  +--+--+  +  +  +  +  +
:     :  :        :     :  :  :  
+  +--+  +  +--+--+  +--+--+  +
:  :     :  :     :        :  :  
+  +  +--+  +  +--+--+--+  +  +
:  :     :  :  :        :  :  :  
+  +--+  +  +  +  +  +--+  +  +
:     :     :     :           :  
+--+--+--+--+--+--+--+--+--+--+

Common Lisp[edit]

The remove-wall function has been written so as to be as close as possible to the specification. The walls are made from a single unicode character, specified by the block keyword, e. g. (maze 20 6 :block #\X). The BOX_DRAWINGS_LIGHT_DIAGONAL_CROSS character is used by default.

(defun shuffle (list)                        ;; Z not uniform
  (sort list '> :key (lambda(x) (random 1.0))))

(defun neighbors (x y maze)
  (remove-if-not
   (lambda (x-y) (and (< -1 (first x-y) (array-dimension maze 0))
                 (< -1 (second x-y) (array-dimension maze 1))))
   `((,x ,(+ y 2)) (,(- x 2) ,y) (,x ,(- y 2)) (,(+ x 2) ,y))))

(defun remove-wall (maze x y &optional visited)
  (labels ((walk (maze x y)
             (push (list x y) visited)
             (loop for (u v) in (shuffle (neighbors x y maze))
                unless (member (list u v) visited :test 'equal)
                do (setf (aref maze u v) #\space
                         (aref maze (/ (+ x u) 2) (/ (+ y v) 2)) #\space)
                   (walk maze u v))))
    (setf (aref maze x y) #\space)
    (walk maze x y)))

(defun draw-maze (width height &key (block #\BOX_DRAWINGS_LIGHT_DIAGONAL_CROSS))
  (let ((maze (make-array (list (1+ (* 2 height)) (1+ (* 2 width)))
                          :element-type 'character :initial-element block)))
    (remove-wall maze (1+ (* 2 (random height))) (1+ (* 2 (random width))))
    (loop for i below (array-dimension maze 0)
          do (fresh-line)
             (loop for j below (array-dimension maze 1)
                   do (princ (aref maze i j))))))

(draw-maze 20 6)
Output:
╳╳╳╳╳╳╳╳╳╳╳╳╳╳╳╳╳╳╳╳╳╳╳╳╳╳╳╳╳╳╳╳╳╳╳╳╳╳╳╳╳
╳         ╳       ╳     ╳         ╳     ╳
╳ ╳╳╳╳╳╳╳ ╳ ╳╳╳ ╳ ╳╳╳ ╳ ╳╳╳╳╳ ╳╳╳ ╳ ╳╳╳╳╳
╳ ╳     ╳   ╳ ╳ ╳     ╳       ╳ ╳ ╳     ╳
╳ ╳╳╳ ╳ ╳╳╳╳╳ ╳ ╳╳╳ ╳╳╳╳╳╳╳╳╳╳╳ ╳ ╳ ╳╳╳ ╳
╳   ╳ ╳ ╳     ╳ ╳   ╳     ╳     ╳ ╳   ╳ ╳
╳╳╳ ╳ ╳ ╳╳╳ ╳ ╳ ╳╳╳ ╳╳╳╳╳ ╳ ╳╳╳ ╳ ╳╳╳ ╳ ╳
╳ ╳ ╳ ╳     ╳ ╳   ╳   ╳   ╳   ╳ ╳   ╳ ╳ ╳
╳ ╳ ╳ ╳╳╳╳╳╳╳ ╳╳╳ ╳╳╳ ╳ ╳╳╳╳╳ ╳╳╳╳╳ ╳╳╳ ╳
╳   ╳   ╳ ╳   ╳ ╳   ╳ ╳     ╳     ╳   ╳ ╳
╳ ╳╳╳╳╳ ╳ ╳ ╳╳╳ ╳╳╳ ╳╳╳╳╳╳╳ ╳ ╳ ╳╳╳╳╳ ╳ ╳
╳       ╳         ╳         ╳ ╳         ╳
╳╳╳╳╳╳╳╳╳╳╳╳╳╳╳╳╳╳╳╳╳╳╳╳╳╳╳╳╳╳╳╳╳╳╳╳╳╳╳╳╳

Another solution using unicode line drawing chars. Assumes they are single width on console. Code pretty horribly unreadable.

(setf *random-state* (make-random-state t))

(defun 2d-array (w h)
  (make-array (list h w) :initial-element 0))

(defmacro or-and (v a b c)
  `(if (or ,a (and ,b (= 1 ,c))) 0 ,v))

(defun make-maze (w h)
  (let ((vis (2d-array w h))
	(ver (2d-array w h))
	(hor (2d-array w h)))
    (labels
      ((walk (y x)
	     (setf (aref vis y x) 1)
	     (loop 
	       (let (x2 y2)
		 (loop for (dx dy) in '((-1 0) (1 0) (0 -1) (0 1))
		       with cnt = 0 do
		       (let ((xx (+ x dx))
			     (yy (+ y dy)))
			 (if (and (array-in-bounds-p vis yy xx)
				  (zerop (aref vis yy xx))
				  (zerop (random (incf cnt))))
			   (setf x2 xx y2 yy))))
		 (if (not x2) (return-from walk))
		 (if (= x x2)
		   (setf (aref hor (min y y2) x) 1)
		   (setf (aref ver y (min x x2)) 1))
		 (walk y2 x2))))

      (show ()
	     (let ((g " │││─┘┐┤─└┌├─┴┬┼"))
	       (loop for i from 0 to h do
		     (loop for j from 0 to w do
			   (format t "~c~a"
			     (char g
			       (+ (or-and 1 (= i 0) (> j 0) (aref ver (1- i) (1- j)))
				  (or-and 2 (= i h) (> j 0) (aref ver i      (1- j)))
				  (or-and 4 (= j 0) (> i 0) (aref hor (1- i) (1- j)))
				  (or-and 8 (= j w) (> i 0) (aref hor (1- i) j    ))))
			     (if (and (< j w)
				      (or (= i 0)
					  (= 0 (aref hor (1- i) j))))
			       "───" "   ")))
		     (terpri)
		     (when (< i h)
		       (loop for j from 0 below w do
			     (format t (if (or (= j 0)
					       (= 0 (aref ver i (1- j))))
					 "│   " "    ")))
		       (format t "│~%"))))))

      (walk (random h) (random w))
      (show))))

(make-maze 20 20)
Output:
┼───┴───┼───┴───┴───┼───┴───┴───┼
│       │           │           │
┼────   │   │   │   │   ┌───┐   ├
│       │   │   │   │   │   │   │
┤   ┌───┘   │   │   │   │   │   ├
│   │       │   │       │   │   │
┤   │   ┌───┘   ├───────┤   │   ├
│   │   │       │       │       │
┤   │   │   ────┤   │   │   ────┼
│       │       │   │   │       │
┤   ────┼───┐   │   │   └───┐   ├
│       │   │       │       │   │
┼───┐   │   └───────┼───┐   └───┼
│   │               │   │       │
┤   └────────────   │   └───┐   ├
│                           │   │
┼───┬───┬───┬───┬───┬───┬───┼───┼

D[edit]

void main() @safe {
    import std.stdio, std.algorithm, std.range, std.random;

    enum uint w = 14, h = 10;
    auto vis = new bool[][](h, w),
         hor = iota(h + 1).map!(_ => ["+---"].replicate(w)).array,
         ver = h.iota.map!(_ => ["|   "].replicate(w) ~ "|").array;

    void walk(in uint x, in uint y) /*nothrow*/ @safe /*@nogc*/ {
        vis[y][x] = true;
        //foreach (immutable p; [[x-1,y], [x,y+1], [x+1,y], [x,y-1]].randomCover) {
        foreach (const p; [[x-1, y], [x, y+1], [x+1, y], [x, y-1]].randomCover) {
            if (p[0] >= w || p[1] >= h || vis[p[1]][p[0]]) continue;
            if (p[0] == x) hor[max(y, p[1])][x] = "+   ";
            if (p[1] == y) ver[y][max(x, p[0])] = "    ";
            walk(p[0], p[1]);
        }
    }
    walk(uniform(0, w), uniform(0, h));
    foreach (const a, const b; hor.zip(ver ~ []))
        join(a ~ "+\n" ~ b).writeln;
}
Output:
+---+---+---+---+---+---+---+---+---+---+---+---+---+---+
|   |               |           |                       |
+   +   +---+---+   +   +---+   +   +---+---+---+   +   +
|               |           |   |       |       |   |   |
+---+---+---+---+---+---+---+   +---+   +---+   +   +---+
|                   |       |       |           |       |
+   +---+---+---+   +   +   +---+   +---+---+   +---+---+
|       |       |   |   |               |   |       |   |
+---+   +   +   +   +   +---+---+---+   +   +---+   +   +
|       |   |   |       |       |           |       |   |
+   +---+   +   +---+---+   +   +---+---+---+   +---+   +
|           |   |           |               |           |
+   +---+---+   +   +---+---+---+---+---+   +---+---+   +
|       |   |       |   |               |           |   |
+---+   +   +---+---+   +   +---+   +   +   +---+---+   +
|   |               |       |       |   |   |           |
+   +---+---+---+   +   +---+   +---+   +   +   +---+---+
|   |               |   |       |   |   |       |       |
+   +   +---+---+---+---+   +---+   +   +---+---+   +   +
|                           |                       |   |
+---+---+---+---+---+---+---+---+---+---+---+---+---+---+

Delphi[edit]

program MazeGen_Rosetta;

{$APPTYPE CONSOLE}

uses System.SysUtils, System.Types, System.Generics.Collections, System.IOUtils;

type
  TMCell = record
    Visited  : Boolean;
    PassTop  : Boolean;
    PassLeft : Boolean;
  end;
  TMaze  = array of array of TMCell;
  TRoute = TStack<TPoint>;

const
  mwidth  = 24;
  mheight = 14;

procedure ClearVisited(var AMaze: TMaze);
var
  x, y: Integer;
begin
  for y := 0 to mheight - 1 do
    for x := 0 to mwidth - 1 do
      AMaze[x, y].Visited := False;
end;

procedure PrepareMaze(var AMaze: TMaze);
var
  Route    : TRoute;
  Position : TPoint;
  d        : Integer;
  Pool     : array of TPoint; // Pool of directions to pick randomly from
begin
  SetLength(AMaze, mwidth, mheight);
  ClearVisited(AMaze);
  Position := Point(Random(mwidth), Random(mheight));
  Route := TStack<TPoint>.Create;
  try
    with Position do
    while True do
    begin
      repeat
        SetLength(Pool, 0);
        if (y > 0)         and not AMaze[x, y-1].Visited then Pool := Pool + [Point(0, -1)];
        if (x < mwidth-1)  and not AMaze[x+1, y].Visited then Pool := Pool + [Point(1,  0)];
        if (y < mheight-1) and not AMaze[x, y+1].Visited then Pool := Pool + [Point(0,  1)];
        if (x > 0)         and not AMaze[x-1, y].Visited then Pool := Pool + [Point(-1, 0)];

        if Length(Pool) = 0 then // no direction to draw from
        begin
          if Route.Count = 0 then Exit; // and we are back at start so this is the end
          Position := Route.Pop;
        end;
      until Length(Pool) > 0;

      d := Random(Length(Pool));
      Offset(Pool[d]);

      AMaze[x, y].Visited := True;
      if Pool[d].y = -1 then AMaze[x, y+1].PassTop  := True; // comes from down to up ( ^ )
      if Pool[d].x =  1 then AMaze[x, y].PassLeft   := True; // comes from left to right ( --> )
      if Pool[d].y =  1 then AMaze[x, y].PassTop    := True; // comes from left to right ( v )
      if Pool[d].x = -1 then AMaze[x+1, y].PassLeft := True; // comes from right to left ( <-- )
      Route.Push(Position);
    end;
  finally
    Route.Free;
  end;
end;

function MazeToString(const AMaze: TMaze; const S, E: TPoint): String; overload;
var
  x, y: Integer;
  v   : Char;
begin
  Result := '';
  for y := 0 to mheight - 1 do
  begin
    for x := 0 to mwidth - 1 do
      if AMaze[x, y].PassTop then Result := Result + '+'#32#32#32 else Result := Result + '+---';
    Result := Result + '+' + sLineBreak;
    for x := 0 to mwidth - 1 do
    begin
      if S = Point(x, y) then v := 'S' else
        if E = Point(x, y) then v := 'E' else
          v := #32'*'[Ord(AMaze[x, y].Visited) + 1];

      Result := Result + '|'#32[Ord(AMaze[x, y].PassLeft) + 1] + #32 + v + #32;
    end;
    Result := Result + '|' + sLineBreak;
  end;
  for x := 0 to mwidth - 1 do Result := Result + '+---';
  Result := Result + '+' + sLineBreak;
end;

procedure Main;
var
  Maze: TMaze;
begin
  Randomize;
  PrepareMaze(Maze);
  ClearVisited(Maze);     // show no route
  Write(MazeToString(Maze, Point(-1, -1), Point(-1, -1)));
  ReadLn;
end;

begin
  Main;

end.
Output:
+---+---+---+---+---+---+---+---+---+---+---+---+---+---+---+---+---+---+---+---+---+---+---+---+---+---+---+---+---+---+---+---+
|   |               |                           |       |                           |               |                   |       |
+   +   +---+---+   +   +   +---+---+---+---+---+   +   +   +---+---+---+   +---+   +   +---+---+   +   +   +---+   +---+---+   +
|       |       |       |                           |       |               |       |   |           |   |   |       |           |
+   +---+   +---+---+---+---+---+---+---+---+---+---+---+   +   +---+---+---+   +---+---+   +---+---+   +   +---+---+   +---+---+
|   |               |               |           |       |   |       |           |       |               |           |   |       |
+   +---+---+   +   +   +   +---+   +---+   +   +   +   +---+---+   +---+---+   +   +   +   +---+---+---+   +---+   +   +   +   +
|       |       |   |   |   |               |   |   |           |           |       |   |   |           |       |   |   |   |   |
+---+   +---+   +   +---+   +---+---+---+---+---+   +---+---+   +---+---+   +---+---+   +---+   +---+   +---+---+   +   +   +   +
|       |       |       |           |           |   |   |       |           |       |   |       |       |       |   |       |   |
+   +---+   +---+---+   +---+---+   +   +---+   +   +   +   +---+   +---+---+   +   +   +   +---+   +---+   +   +   +---+---+   +
|           |   |                   |       |       |   |       |   |           |   |       |   |           |   |   |       |   |
+---+---+---+   +   +---+---+---+---+---+   +---+---+   +---+   +   +---+   +---+   +---+---+   +---+---+---+   +   +   +   +   +
|               |       |               |   |           |       |       |       |   |               |               |   |       |
+   +---+   +---+---+   +   +---+---+   +   +   +   +---+   +---+   +   +---+   +---+   +---+---+   +   +---+---+---+   +---+---+
|   |   |           |   |   |               |   |           |       |       |           |       |       |               |       |
+   +   +---+---+   +   +   +   +---+---+---+   +---+---+---+   +---+---+   +   +---+---+---+   +---+---+   +---+---+---+   +---+
|       |   |       |   |   |   |           |           |       |       |   |                       |       |           |       |
+---+   +   +   +---+   +   +---+   +---+   +---+---+   +---+---+   +   +   +---+---+---+---+---+   +   +---+---+   +   +---+   +
|   |       |   |       |       |   |   |       |                   |       |                   |   |               |           |
+   +---+   +   +   +---+---+   +   +   +---+   +---+---+---+---+---+---+---+   +---+---+---+   +---+---+---+---+---+---+---+   +
|       |   |   |   |       |   |   |       |           |           |       |   |           |                       |           |
+   +   +   +   +   +   +   +   +   +---+   +---+---+   +   +---+   +   +   +   +---+   +   +---+---+---+   +---+---+   +---+---+
|   |       |           |   |                       |           |       |               |               |                       |
+---+---+---+---+---+---+---+---+---+---+---+---+---+---+---+---+---+---+---+---+---+---+---+---+---+---+---+---+---+---+---+---+

EasyLang[edit]

Run it

size = 15
n = 2 * size + 1
f = 100 / (n - 0.5)
len m[] n * n
# 
background 000
proc show_maze . .
   clear
   for i = 1 to len m[]
      if m[i] = 0
         x = (i - 1) mod n
         y = (i - 1) div n
         color 999
         move x * f - f / 2 y * f - f / 2
         rect f * 1.5 f * 1.5
      .
   .
   sleep 0.01
.
offs[] = [ 1 n -1 (-n) ]
# 
proc m_maze pos . .
   m[pos] = 0
   call show_maze
   d[] = [ 1 2 3 4 ]
   for i = 4 downto 1
      d = random i
      dir = offs[d[d]]
      d[d] = d[i]
      if m[pos + dir] = 1 and m[pos + 2 * dir] <> 0
         m[pos + dir] = 0
         call m_maze pos + 2 * dir
      .
   .
.
endpos = n * n - 1
proc make_maze . .
   for i = 1 to len m[]
      m[i] = 1
   .
   for i = 1 to n
      m[i] = 2
      m[n * i] = 2
      m[n * i - n + 1] = 2
      m[n * n - n + i] = 2
   .
   h = 2 * random 15 - n + n * 2 * random 15
   call m_maze h
   m[endpos] = 0
   endpos += n
.
call make_maze
call show_maze

EGL[edit]

program MazeGen

    // First and last columns/rows are "dead" cells. Makes generating
    // a maze with border walls much easier. Therefore, a visible
    // 20x20 maze has a maze size of 22. 	
    mazeSize int = 22;

    south boolean[][];
    west boolean[][];
    visited boolean[][];

    function main()
        initMaze();
        generateMaze();
        drawMaze();
    end

    private function initMaze()

        visited = createBooleanArray(mazeSize, mazeSize, false);

        // Initialize border cells as already visited
        for(col int from 1 to mazeSize)
            visited[col][1] = true;
            visited[col][mazeSize] = true;
        end
        for(row int from 1 to mazeSize)
            visited[1][row] = true;
            visited[mazeSize][row] = true;
        end

        // Initialize all walls as present
        south = createBooleanArray(mazeSize, mazeSize, true);
        west = createBooleanArray(mazeSize, mazeSize, true);

    end

    private function createBooleanArray(col int in, row int in, initialState boolean in) returns(boolean[][])

        newArray boolean[][] = new boolean[0][0];

        for(i int from 1 to col)
            innerArray boolean[] = new boolean[0];
            for(j int from 1 to row)
                innerArray.appendElement(initialState);
            end
            newArray.appendElement(innerArray);
        end

        return(newArray);

    end

    private function createIntegerArray(col int in, row int in, initialValue int in) returns(int[][])

        newArray int[][] = new int[0][0];

        for(i int from 1 to col)
            innerArray int[] = new int[0];
            for(j int from 1 to row)
                innerArray.appendElement(initialValue);
            end
            newArray.appendElement(innerArray);
        end

        return(newArray);

    end

    private function generate(col int in, row int in)

        // Mark cell as visited
        visited[col][row] = true;

        // Keep going as long as there is an unvisited neighbor
        while(!visited[col][row + 1] || !visited[col + 1][row] ||
                !visited[col][row - 1] || !visited[col - 1][row])

            while(true)
                r float = MathLib.random(); // Choose a random direction
                
                case
                    when(r < 0.25 && !visited[col][row + 1]) // Go south
                        south[col][row] = false; // South wall down
                        generate(col, row + 1);
                        exit while;
                    when(r >= 0.25 && r < 0.50 && !visited[col + 1][row]) // Go east 
                        west[col + 1][row] = false; // West wall of neighbor to the east down
                        generate(col + 1, row);
                        exit while;
                    when(r >= 0.5 && r < 0.75 && !visited[col][row - 1]) // Go north
                        south[col][row - 1] = false; // South wall of neighbor to the north down
                        generate(col, row - 1);
                        exit while;
                    when(r >= 0.75 && r < 1.00 && !visited[col - 1][row]) // Go west
                        west[col][row] = false; // West wall down
                        generate(col - 1, row);
                        exit while;
                end
            end
        end

    end

    private function generateMaze()

        // Pick random start position (within the visible maze space)
        randomStartCol int = MathLib.floor((MathLib.random() *(mazeSize - 2)) + 2);
        randomStartRow int = MathLib.floor((MathLib.random() *(mazeSize - 2)) + 2);

        generate(randomStartCol, randomStartRow);

    end

    private function drawMaze()

        line string;

        // Iterate over wall arrays (skipping dead border cells as required). 
        // Construct a line at a time and output to console.
        for(row int from 1 to mazeSize - 1)

            if(row > 1)
                line = "";
                for(col int from 2 to mazeSize)
                    if(west[col][row])
                        line ::= "|   ";
                    else
                        line ::= "    ";
                    end
                end
                Syslib.writeStdout(line);
            end

            line = "";
            for(col int from 2 to mazeSize - 1)
                if(south[col][row])
                    line ::= "+---";
                else
                    line ::= "+   ";
                end
            end
            line ::= "+";
            SysLib.writeStdout(line);

        end

    end

end
Output example (for 10x10 maze):
+---+---+---+---+---+---+---+---+---+---+
|   |                   |           |   |   
+   +   +---+---+---+   +---+   +   +   +
|   |       |   |   |       |   |       |   
+   +---+   +   +   +   +   +   +---+   +
|       |       |   |   |   |   |       |   
+   +   +---+   +   +---+   +   +   +---+
|   |       |   |   |       |   |       |   
+   +---+---+   +   +   +---+   +---+---+
|   |           |   |   |       |       |   
+   +   +---+---+   +   +   +   +   +   +
|   |   |   |       |   |   |       |   |   
+   +   +   +   +---+   +   +---+---+   +
|       |   |           |   |       |   |   
+   +---+   +---+---+---+   +   +   +   +
|   |                   |   |   |       |   
+   +---+   +---+   +   +---+   +---+   +
|       |   |       |           |   |   |   
+---+   +---+   +---+---+---+---+   +   +
|               |                       |   
+---+---+---+---+---+---+---+---+---+---+

Elixir[edit]

Translation of: D
defmodule Maze do
  def generate(w, h) do
    maze = (for i <- 1..w, j <- 1..h, into: Map.new, do: {{:vis, i, j}, true})
           |> walk(:rand.uniform(w), :rand.uniform(h))
    print(maze, w, h)
    maze
  end
  
  defp walk(map, x, y) do
    Enum.shuffle( [[x-1,y], [x,y+1], [x+1,y], [x,y-1]] )
    |> Enum.reduce(Map.put(map, {:vis, x, y}, false), fn [i,j],acc ->
      if acc[{:vis, i, j}] do
        {k, v} = if i == x, do: {{:hor, x, max(y, j)}, "+   "},
                          else: {{:ver, max(x, i), y}, "    "}
        walk(Map.put(acc, k, v), i, j)
      else
        acc
      end
    end)
  end
  
  defp print(map, w, h) do
    Enum.each(1..h, fn j ->
      IO.puts Enum.map_join(1..w, fn i -> Map.get(map, {:hor, i, j}, "+---") end) <> "+"
      IO.puts Enum.map_join(1..w, fn i -> Map.get(map, {:ver, i, j}, "|   ") end) <> "|"
    end)
    IO.puts String.duplicate("+---", w) <> "+"
  end
end

Maze.generate(20, 10)
Output:
+---+---+---+---+---+---+---+---+---+---+---+---+---+---+---+---+---+---+---+---+
|       |               |                           |                   |       |
+   +---+   +   +---+   +---+   +---+---+---+---+   +   +   +---+---+   +   +---+
|   |       |       |           |                   |   |   |       |   |       |
+   +   +---+---+   +---+---+---+---+   +---+---+   +   +   +   +   +   +   +   +
|   |   |       |           |       |   |       |   |   |   |   |   |   |   |   |
+   +   +   +   +---+---+   +   +   +---+   +   +   +---+   +   +---+   +   +   +
|   |   |   |           |       |           |   |           |           |   |   |
+   +   +   +   +---+---+---+---+---+---+---+   +---+---+---+   +---+---+---+   +
|   |   |   |                   |           |       |       |   |           |   |
+   +   +---+---+---+---+   +   +   +   +   +---+   +   +   +   +   +---+   +   +
|   |                   |   |   |   |   |       |   |   |           |   |       |
+   +---+---+---+---+   +   +   +   +   +---+   +   +   +---+---+---+   +---+   +
|                   |   |   |       |   |       |   |   |       |       |       |
+   +---+---+---+---+   +   +---+---+   +---+---+   +   +   +   +   +---+   +---+
|           |           |       |       |           |   |   |   |       |   |   |
+   +---+   +   +---+---+---+---+   +---+   +---+---+---+   +   +---+   +   +   +
|   |   |   |       |               |       |               |       |   |   |   |
+   +   +   +---+   +   +---+---+   +   +---+---+---+---+---+---+   +   +   +   +
|       |               |           |                               |           |
+---+---+---+---+---+---+---+---+---+---+---+---+---+---+---+---+---+---+---+---+

Elm[edit]

import Maybe as M
import Result as R
import Matrix 
import Mouse
import Random exposing (Seed)
import Matrix.Random
import Time exposing (Time, every, second)
import Set exposing (Set, fromList)
import List exposing (..)
import String exposing (join)
import Html exposing (Html, br, input, h1, h2, text, div, button)
import Html.Events as HE 
import Html.Attributes as HA
import Html.App exposing (program)
import Json.Decode  as JD
import Svg 
import Svg.Attributes exposing (version, viewBox, cx, cy, r, x, y, x1, y1, x2, y2, fill,points, style, width, height, preserveAspectRatio)

minSide = 10
maxSide = 40
w = 700
h = 700
dt = 0.001

type alias Direction = Int
down = 0
right = 1

type alias Door = (Matrix.Location, Direction)

type State = Initial | Generating | Generated | Solved

type alias Model =
  { rows : Int
  , cols : Int
  , animate : Bool
  , boxes : Matrix.Matrix Bool
  , doors : Set Door
  , current : List Matrix.Location
  , state : State
  , seedStarter : Int
  , seed : Seed
  }

initdoors : Int -> Int -> Set Door
initdoors rows cols =
  let 
    pairs la lb = List.concatMap (\at -> List.map ((,) at) lb) la
    downs = pairs (pairs [0..rows-2] [0..cols-1]) [down] 
    rights = pairs (pairs [0..rows-1] [0..cols-2]) [right] 
  in downs ++ rights |> fromList

initModel : Int -> Int -> Bool -> State -> Int -> Model
initModel rows cols animate state starter = 
  let rowGenerator = Random.int 0 (rows-1)
      colGenerator = Random.int 0 (cols-1)
      locationGenerator = Random.pair rowGenerator colGenerator
      (c, s)= Random.step locationGenerator (Random.initialSeed starter)
  in { rows = rows
     , cols = cols 
     , animate = animate
     , boxes = Matrix.matrix rows cols (\location -> state == Generating && location == c)
     , doors = initdoors rows cols
     , current = if state == Generating then [c] else []
     , state = state
     , seedStarter = starter -- updated every Tick until maze generated.
     , seed = s
     }

view model =
  let
    borderLineStyle = style "stroke:green;stroke-width:0.3"
    wallLineStyle = style "stroke:green;stroke-width:0.1" 

    x1Min = x1 <| toString 0
    y1Min = y1 <| toString 0
    x1Max = x1 <| toString model.cols
    y1Max = y1 <| toString model.rows
    x2Min = x2 <| toString 0
    y2Min = y2 <| toString 0
    x2Max = x2 <| toString model.cols
    y2Max = y2 <| toString model.rows

    borders = [ Svg.line [ x1Min, y1Min, x2Max, y2Min, borderLineStyle ] []
              , Svg.line [ x1Max, y1Min, x2Max, y2Max, borderLineStyle ] []
              , Svg.line [ x1Max, y1Max, x2Min, y2Max, borderLineStyle ] []
              , Svg.line [ x1Min, y1Max, x2Min, y2Min, borderLineStyle ] []
              ]

    doorToLine door = 
      let (deltaX1, deltaY1) = if (snd door == right) then (1,0) else (0,1)
          (row, column) = fst door
      in Svg.line [ x1 <| toString (column + deltaX1)
                  , y1 <| toString (row    + deltaY1)
                  , x2 <| toString (column + 1)
                  , y2 <| toString (row    + 1)
                  , wallLineStyle ] []

    doors = (List.map doorToLine <| Set.toList model.doors )

    circleInBox (row,col) color = 
      Svg.circle [ r "0.25"
      , fill (color)
      , cx (toString (toFloat col + 0.5))
      , cy (toString (toFloat row + 0.5))
      ] [] 

    showUnvisited location box =
       if box then [] else [ circleInBox location "yellow" ]

    unvisited = model.boxes 
                  |> Matrix.mapWithLocation showUnvisited 
                  |> Matrix.flatten 
                  |> concat

    current = 
      case head model.current of
          Nothing -> []
          Just c -> [circleInBox c "black"]

    maze = 
      if model.animate || model.state /= Generating
      then [ Svg.g [] <| doors ++ borders ++ unvisited ++ current ] 
      else [ Svg.g [] <| borders ]
  in
    div 
      []
      [ h2 [centerTitle] [text "Maze Generator"]
      , div 
          [floatLeft] 
          (  slider "rows" minSide maxSide model.rows SetRows
          ++ [ br [] [] ] 

          ++ slider "cols" minSide maxSide model.cols SetCols
          ++ [ br [] [] ]

          ++ checkbox "Animate" model.animate SetAnimate 
          ++ [ br [] [] ]

          ++ [ button 
                 [ HE.onClick Generate ]
                 [ text "Generate"] 
             ] )
      , div 
          [floatLeft] 
          [ Svg.svg 
              [ version "1.1"
              , width (toString w)
              , height (toString h)
              , viewBox (join " " 
                           [ 0          |> toString
                           , 0          |> toString
                           , model.cols |> toString
                           , model.rows |> toString ])
              ] 
              maze
          ]
      ] 

checkbox label checked msg = 
  [ input
      [ HA.type' "checkbox"
      , HA.checked checked
      , HE.on "change" (JD.map msg HE.targetChecked)
      ]
      []
    , text label
  ]

slider name min max current msg = 
  [ input
    [ HA.value (if current >= min then current |> toString else "")
    , HE.on "input" (JD.map msg HE.targetValue )
    , HA.type' "range"
    , HA.min <| toString min
    , HA.max <| toString max
    ]
    []
  , text <| name ++ "=" ++ (current |> toString)
  ]

floatLeft = HA.style [ ("float", "left") ] 
centerTitle = HA.style [ ( "text-align", "center") ] 

unvisitedNeighbors : Model -> Matrix.Location -> List Matrix.Location
unvisitedNeighbors model (row,col) = 
  [(row, col-1), (row-1, col), (row, col+1), (row+1, col)]
    |> List.filter (\l -> fst l >= 0 && snd l >= 0 && fst l < model.rows && snd l < model.cols)
    |> List.filter (\l -> (Matrix.get l model.boxes) |> M.withDefault False |> not)

updateModel' : Model -> Int -> Model
updateModel' model t = 
  case head model.current of
    Nothing -> {model | state = Generated, seedStarter = t }
    Just prev ->
      let neighbors = unvisitedNeighbors model prev
      in if (length neighbors) > 0 then
           let (neighborIndex, seed) = Random.step (Random.int 0 (length neighbors-1)) model.seed
               next = head (drop neighborIndex neighbors) |> M.withDefault (0,0) 
               boxes = Matrix.set next True model.boxes 
               dir = if fst prev == fst next then right else down
               doorCell = if (  (dir == down)   && (fst prev < fst next))  
                             || (dir == right ) && (snd prev < snd next) then prev else next
               doors = Set.remove (doorCell, dir) model.doors 
           in {model | boxes=boxes, doors=doors, current=next :: model.current, seed=seed, seedStarter = t}
         else
           let tailCurrent = tail model.current |> M.withDefault [] 
           in updateModel' {model | current = tailCurrent} t

updateModel : Msg -> Model -> Model
updateModel msg model = 
  let stringToCellCount s =
    let v' = String.toInt s |> R.withDefault minSide
    in if v' < minSide then minSide else v'
  in case msg of 
       Tick tf -> 
         let t = truncate tf
         in 
           if (model.state == Generating) then updateModel' model t
           else { model | seedStarter = t } 

       Generate -> 
         initModel model.rows model.cols model.animate Generating model.seedStarter

       SetRows countString -> 
         initModel (stringToCellCount countString) model.cols model.animate Initial model.seedStarter

       SetCols countString -> 
         initModel model.rows (stringToCellCount countString) model.animate Initial model.seedStarter

       SetAnimate b -> 
         { model | animate = b } 

       NoOp -> model 

type Msg = NoOp | Tick Time | Generate | SetRows String | SetCols String | SetAnimate Bool

subscriptions model = every (dt * second) Tick

main =
  let 
    update msg model = (updateModel msg model, Cmd.none)
    init = (initModel 21 36 False Initial 0, Cmd.none)
  in program 
       { init = init
       , view = view
       , update = update
       , subscriptions = subscriptions
       }

Link to live demo: http://dc25.github.io/mazeGenerationElm/

Emacs Lisp[edit]

Library: cl-lib
(require 'cl-lib)

(cl-defstruct maze rows cols data)

(defmacro maze-pt (w r c)
  `(+ (* (mod ,r (maze-rows ,w)) (maze-cols ,w))
      (mod ,c (maze-cols ,w))))

(defmacro maze-ref (w r c)
  `(aref (maze-data ,w) (maze-pt ,w ,r ,c)))

(defun new-maze (rows cols)
  (setq rows (1+ rows)
        cols (1+ cols))
  (let ((m (make-maze :rows rows :cols cols :data (make-vector (* rows cols) nil))))

    (dotimes (r rows)
      (dotimes (c cols)
        (setf (maze-ref m r c) (copy-sequence '(wall ceiling)))))

    (dotimes (r rows)
      (maze-set m r (1- cols) 'visited))

    (dotimes (c cols)
      (maze-set m (1- rows) c 'visited))

    (maze-unset m 0 0 'ceiling) ;; Maze Entrance
    (maze-unset m (1- rows) (- cols 2) 'ceiling) ;; Maze Exit

    m))

(defun maze-is-set (maze r c v)
  (member v (maze-ref maze r c)))

(defun maze-set (maze r c v)
  (let ((cell (maze-ref maze r c)))
    (when (not (member v cell))
      (setf (maze-ref maze r c) (cons v cell)))))

(defun maze-unset (maze r c v)
  (setf (maze-ref maze r c) (delete v (maze-ref maze r c))))

(defun print-maze (maze &optional marks)
  (dotimes (r (1- (maze-rows maze)))

    (dotimes (c (1- (maze-cols maze)))
      (princ (if (maze-is-set maze r c 'ceiling) "+---" "+   ")))
    (princ "+")
    (terpri)

    (dotimes (c (1- (maze-cols maze)))
      (princ (if (maze-is-set maze r c 'wall) "|" " "))
      (princ (if (member (cons r c) marks) " * " "   ")))
    (princ "|")
    (terpri))

  (dotimes (c (1- (maze-cols maze)))
    (princ (if (maze-is-set maze (1- (maze-rows maze)) c 'ceiling) "+---" "+   ")))
  (princ "+")
  (terpri))

(defun shuffle (lst)
  (sort lst (lambda (a b) (= 1 (random 2)))))

(defun to-visit (maze row col)
  (let (unvisited)
    (dolist (p '((0 . +1) (0 . -1) (+1 . 0) (-1 . 0)))
      (let ((r (+ row (car p)))
            (c (+ col (cdr p))))
      (unless (maze-is-set maze r c 'visited)
        (push (cons r c) unvisited))))
    unvisited))

(defun make-passage (maze r1 c1 r2 c2)
  (if (= r1 r2)
      (if (< c1 c2)
          (maze-unset maze r2 c2 'wall) ; right
        (maze-unset maze r1 c1 'wall))  ; left
    (if (< r1 r2)
        (maze-unset maze r2 c2 'ceiling)   ; up
      (maze-unset maze r1 c1 'ceiling))))  ; down

(defun dig-maze (maze row col)
  (let (backup
        (run 0))
    (maze-set maze row col 'visited)
    (push (cons row col) backup)
    (while backup
      (setq run (1+ run))
      (when (> run (/ (+ row col) 3))
        (setq run 0)
        (setq backup (shuffle backup)))
      (setq row (caar backup)
            col (cdar backup))
      (let ((p (shuffle (to-visit maze row col))))
        (if p
            (let ((r (caar p))
                  (c (cdar p)))
              (make-passage maze row col r c)
              (maze-set maze r c 'visited)
              (push (cons r c) backup))
          (pop backup)
          (setq backup (shuffle backup))
          (setq run 0))))))

(defun generate (rows cols)
  (let* ((m (new-maze rows cols)))
    (dig-maze m (random rows) (random cols))
    (print-maze m)))

(defun parse-ceilings (line)
  (let (rtn
        (i 1))
    (while (< i (length line))
      (push (eq ?- (elt line i)) rtn)
      (setq i (+ i 4)))
    (nreverse rtn)))

(defun parse-walls (line)
  (let (rtn
        (i 0))
    (while (< i (length line))
      (push (eq ?| (elt line i)) rtn)
      (setq i (+ i 4)))
    (nreverse rtn)))

(defun parse-maze (file-name)
  (let ((rtn)
        (lines (with-temp-buffer
                 (insert-file-contents-literally file-name)
                 (split-string (buffer-string) "\n" t))))
    (while lines
      (push (parse-ceilings (pop lines)) rtn)
      (push (parse-walls (pop lines)) rtn))
    (nreverse rtn)))

(defun read-maze (file-name)
  (let* ((raw (parse-maze file-name))
         (rows (1- (/ (length raw) 2)))
         (cols (length (car raw)))
         (maze (new-maze rows cols)))
    (dotimes (r rows)
      (let ((ceilings (pop raw)))
        (dotimes (c cols)
          (unless (pop ceilings)
            (maze-unset maze r c 'ceiling))))
      (let ((walls (pop raw)))
        (dotimes (c cols)
          (unless (pop walls)
            (maze-unset maze r c 'wall)))))
    maze))

(defun find-exits (maze row col)
  (let (exits)
    (dolist (p '((0 . +1) (0 . -1) (-1 . 0) (+1 . 0)))
      (let ((r (+ row (car p)))
            (c (+ col (cdr p))))
        (unless
            (cond
             ((equal p '(0 . +1)) (maze-is-set maze r   c   'wall))
             ((equal p '(0 . -1)) (maze-is-set maze row col 'wall))
             ((equal p '(+1 . 0)) (maze-is-set maze r   c   'ceiling))
             ((equal p '(-1 . 0)) (maze-is-set maze row col 'ceiling)))
          (push (cons r c) exits))))
    exits))

(defun drop-visited (maze points)
  (let (not-visited)
    (while points
      (unless (maze-is-set maze (caar points) (cdar points) 'visited)
        (push (car points) not-visited))
      (pop points))
    not-visited))

(defun solve-maze (maze)
  (let (solution
        (exit (cons (- (maze-rows maze) 2) (- (maze-cols maze) 2)))
        (pt (cons 0 0)))
    (while (not (equal pt exit))
      (maze-set maze (car pt) (cdr pt) 'visited)
      (let ((exits (drop-visited maze (find-exits maze (car pt) (cdr pt)))))
        (if (null exits)
            (setq pt (pop solution))
          (push pt solution)
          (setq pt (pop exits)))))
    (push pt solution)))

(defun solve (file-name)
  (let* ((maze (read-maze file-name))
         (solution (solve-maze maze)))
    (print-maze maze solution)))

(generate 20 20)
Output:
+   +---+---+---+---+---+---+---+---+---+
|           |   |                   |   |
+---+---+   +   +---+---+   +---+---+   +
|   |       |   |       |   |       |   |
+   +   +   +   +---+   +   +   +---+   +
|       |               |           |   |
+---+---+---+---+---+   +---+---+   +   +
|   |       |   |   |       |   |   |   |
+   +---+   +   +   +---+   +   +   +   +
|   |   |   |   |               |       |
+   +   +   +   +---+   +   +   +---+   +
|   |   |   |           |   |           |
+   +   +   +---+---+---+   +---+---+   +
|   |   |               |   |   |       |
+   +   +---+---+   +   +   +   +   +   +
|       |   |       |       |       |   |
+   +   +   +---+---+---+---+---+   +   +
|   |       |       |               |   |
+   +---+---+   +   +   +---+---+---+   +
|               |       |               |
+---+---+---+---+---+---+---+---+---+   +

Erlang[edit]

Erlang is single assignment. To get mutability I use processes. The code is over-enginered for this task, but the extra is used for Maze_solving. Also, Erlang starts counting at 1, not 0, so the co-ordinate of the lower left corner is 1,1.

Using multiple processes[edit]

-module( maze ).

-export( [cell_accessible_neighbours/1, cell_content/1, cell_content_set/2, cell_pid/3, cell_position/1, display/1, generation/2, stop/1, task/0] ).

-record( maze, {dict, max_x, max_y, start} ).
-record( state, {content=" ", controller, is_dug=false, max_x, max_y, neighbours=[], position, walls=[north, south, east, west], walk_done} ).

cell_accessible_neighbours( Pid ) -> read( Pid, accessible_neighbours ).

cell_content( Pid ) -> read( Pid, content ).

cell_content_set( Pid, Content ) -> Pid ! {content, Content, erlang:self()}.

cell_pid( X, Y, Maze ) -> dict:fetch( {X, Y}, Maze#maze.dict ).

cell_position( Pid ) -> read( Pid, position ).

display( #maze{dict=Dict, max_x=Max_x, max_y=Max_y} ) ->
	Position_pids = dict:to_list( Dict ),
	display( Max_x, Max_y, reads(Position_pids, content), reads(Position_pids, walls) ).

generation( Max_x, Max_y ) ->
       Controller = erlang:self(),
       Position_pids = cells_create( Controller, Max_x, Max_y ),
       Pids = [Y || {_X, Y} <- Position_pids],
       [X ! {position_pids, Position_pids} || X <- Pids],
       {Position, Pid} = lists:nth( random:uniform(Max_x * Max_y), Position_pids ),
       Pid ! {dig, Controller},
       receive
       {dig_done} -> ok
       end,
       #maze{dict=dict:from_list(Position_pids), max_x=Max_x, max_y=Max_y, start=Position}.

stop( #maze{dict=Dict} ) ->
      Controller = erlang:self(),
      Pids = [Y || {_X, Y} <- dict:to_list(Dict)],
      [X ! {stop, Controller} || X <- Pids],
      ok.

task() ->
       Maze = generation( 16, 8 ),
       io:fwrite( "Starting at ~p~n", [Maze#maze.start] ),
       display( Maze ),
       stop( Maze ).



cells_create( Controller, Max_x, Max_y ) -> [{{X, Y}, cell_create(Controller, Max_x, Max_y, {X, Y})} || X <- lists:seq(1, Max_x), Y<- lists:seq(1, Max_y)].

cell_create( Controller, Max_x, Max_y, {X, Y} ) -> erlang:spawn_link( fun() -> random:seed( X*1000, Y*1000, (X+Y)*1000 ), loop( #state{controller=Controller, max_x=Max_x, max_y=Max_y, position={X, Y}} ) end ).

display( Max_x, Max_y, Position_contents, Position_walls ) ->
        All_rows = [display_row( Max_x, Y, Position_contents, Position_walls ) || Y <- lists:seq(Max_y, 1, -1)],
        [io:fwrite("~s+~n~s|~n", [North, West]) || {North, West} <- All_rows],
	io:fwrite("~s+~n", [lists:flatten(lists:duplicate(Max_x, display_row_north(true)))] ).

display_row( Max_x, Y, Position_contents, Position_walls ) ->
	North_wests = [display_row_walls(proplists:get_value({X,Y}, Position_contents), proplists:get_value({X,Y}, Position_walls)) || X <- lists:seq(1, Max_x)],
	North = lists:append( [North || {North, _West} <- North_wests] ),
	West = lists:append( [West || {_X, West} <- North_wests] ),
	{North, West}.

display_row_walls( Content, Walls ) -> {display_row_north( lists:member(north, Walls) ), display_row_west( lists:member(west, Walls), Content )}.

display_row_north( true ) -> "+---";
display_row_north( false ) -> "+   ".

display_row_west( true, Content ) -> "| " ++ Content ++ " ";
display_row_west( false, Content ) -> "  " ++ Content ++ " ".

loop( State ) ->
    receive
    {accessible_neighbours, Pid} ->
    	Pid ! {accessible_neighbours, loop_accessible_neighbours( State#state.neighbours, State#state.walls ), erlang:self()},
        loop( State );
    {content, Pid} ->
    	Pid ! {content, State#state.content, erlang:self()},
        loop( State );
    {content, Content, _Pid} ->
        loop( State#state{content=Content} );
    {dig, Pid} ->
	    Not_dug_neighbours = loop_not_dug( State#state.neighbours ),
	    New_walls = loop_dig( Not_dug_neighbours, lists:delete( loop_wall_from_pid(Pid, State#state.neighbours), State#state.walls), Pid ),
	    loop( State#state{is_dug=true, walls=New_walls, walk_done=Pid} );
    {dig_done} ->
	    Not_dug_neighbours = loop_not_dug( State#state.neighbours ),
	    New_walls = loop_dig( Not_dug_neighbours, State#state.walls, State#state.walk_done ),
	    loop( State#state{walls=New_walls} );
    {is_dug, Pid} ->
    	    Pid ! {is_dug, State#state.is_dug, erlang:self()},
	    loop( State );
    {position, Pid} ->
    	Pid ! {position, State#state.position, erlang:self()},
        loop( State );
    {position_pids, Position_pids} ->
        {_My_position, Neighbours} = lists:foldl( fun loop_neighbours/2, {State#state.position, []}, Position_pids ),
        erlang:garbage_collect(), % Shrink process after using large Pid_positions. For memory starved systems.
        loop( State#state{neighbours=Neighbours} );
    {stop, Controller} when Controller =:= State#state.controller ->
    	   ok;
    {walls, Pid} ->
    	    Pid ! {walls, State#state.walls, erlang:self()},
	    loop( State )
    end.

loop_accessible_neighbours( Neighbours, Walls ) -> [Pid || {Direction, Pid} <- Neighbours, not lists:member(Direction, Walls)].

loop_dig( [], Walls, Pid ) ->
	Pid ! {dig_done},
	Walls;
loop_dig( Not_dug_neighbours, Walls, _Pid ) ->
        {Dig_pid, Dig_direction} = lists:nth( random:uniform(erlang:length(Not_dug_neighbours)), Not_dug_neighbours ),
        Dig_pid ! {dig, erlang:self()},
	lists:delete( Dig_direction, Walls ).

loop_neighbours( {{X, Y}, Pid}, {{X, My_y}, Acc} ) when Y =:= My_y + 1 -> {{X, My_y}, [{north, Pid} | Acc]};
loop_neighbours( {{X, Y}, Pid}, {{X, My_y}, Acc} ) when Y =:= My_y - 1 -> {{X, My_y}, [{south, Pid} | Acc]};
loop_neighbours( {{X, Y}, Pid}, {{My_x, Y}, Acc} ) when X =:= My_x + 1 -> {{My_x, Y}, [{east, Pid} | Acc]};
loop_neighbours( {{X, Y}, Pid}, {{My_x, Y}, Acc} ) when X =:= My_x - 1 -> {{My_x, Y}, [{west, Pid} | Acc]};
loop_neighbours( _Position_pid, Acc ) -> Acc.

loop_not_dug( Neighbours ) ->
	My_pid = erlang:self(),
	[Pid ! {is_dug, My_pid} || {_Direction, Pid} <- Neighbours],
	[{Pid, Direction} || {Direction, Pid} <- Neighbours, not read_receive(Pid, is_dug)].

loop_wall_from_pid( Pid, Neighbours ) -> loop_wall_from_pid_result( lists:keyfind(Pid, 2, Neighbours) ).
loop_wall_from_pid_result( {Direction, _Pid} ) -> Direction;
loop_wall_from_pid_result( false ) -> controller.

read( Pid, Key ) ->
	Pid ! {Key, erlang:self()},
	read_receive( Pid, Key ).

read_receive( Pid, Key ) ->
        receive
        {Key, Value, Pid} -> Value
        end.

reads( Position_pids, Key ) ->
    My_pid = erlang:self(),
    [Pid ! {Key, My_pid} || {_Position, Pid} <- Position_pids],
    [{Position, read_receive(Pid, Key)} || {Position, Pid} <- Position_pids].
Output:
5> maze:task().
Starting at {10,5}
+---+---+---+---+---+---+---+---+---+---+---+---+---+---+---+---+
|                   |       |           |   |                   |
+---+   +---+---+   +   +   +   +---+   +   +   +   +---+---+   +
|       |       |       |   |       |   |       |           |   |
+   +---+   +   +---+   +---+---+   +   +---+---+---+---+   +   +
|   |       |       |   |           |           |           |   |
+   +---+   +---+---+   +   +---+---+---+---+   +   +---+---+   +
|       |   |           |   |           |       |   |   |       |
+   +   +   +   +---+---+   +   +---+---+   +---+   +   +   +---+
|   |   |       |           |           |   |       |       |   |
+---+   +---+---+   +---+---+---+---+   +   +   +---+   +---+   +
|       |       |           |       |   |   |   |       |       |
+   +   +   +   +---+---+   +   +---+   +   +   +---+   +   +   +
|   |   |   |           |   |       |       |       |       |   |
+   +---+   +   +---+---+   +---+   +---+---+---+   +---+---+   +
|           |                                       |           |
+---+---+---+---+---+---+---+---+---+---+---+---+---+---+---+---+

Using 2 digraphs[edit]

Uses 2 digraph "objects": a) the 'matrix', a fully connected digraph of MxN vertices and b) the 'maze', an unconnected digraph, also MxN, that is populated while walking.

Employs a faux Visitor pattern to populate the maze while traversing the matrix in depth-first order.

Vertices: 0 .. MxN - 1

Rows: 0 .. M - 1

Cols: 0 .. N - 1

Usage: start with generate_default/0. Use generate_MxN() to test other maze sizes.

-module(maze).
-record(maze, {g, m, n}).
-export([generate_default/0, generate_MxN/2]).

make_maze(M, N) ->
    Maze = #maze{g = digraph:new(), m = M, n = N},
    lists:foreach(fun(X) -> digraph:add_vertex(Maze#maze.g, X) end, lists:seq(0, M * N - 1)),
    Maze.

row_at(V, Maze) -> trunc(V / Maze#maze.n).
col_at(V, Maze) -> V - row_at(V, Maze) * Maze#maze.n.
vertex_at(Row, Col, Maze) -> Cell_Exists = cell_exists(Row, Col, Maze), if Cell_Exists -> Row * Maze#maze.n + Col; true -> -1 end.
cell_exists(Row, Col, Maze) -> (Row >= 0) and (Row < Maze#maze.m) and (Col >= 0) and (Col < Maze#maze.n).

adjacent_cells(V, Maze) -> % ordered: left, up, right, down
    adjacent_cell(cell_left, V, Maze)++adjacent_cell(cell_up, V, Maze)++adjacent_cell(cell_right, V, Maze)++adjacent_cell(cell_down, V, Maze).

adjacent_cell(cell_left, V, Maze) -> case (col_at(V, Maze) == 0) of true -> []; _Else -> [V - 1] end;
adjacent_cell(cell_up, V, Maze) -> case (row_at(V, Maze) == 0) of true -> []; _Else -> [V - Maze#maze.n] end;
adjacent_cell(cell_right, V, Maze) -> case (col_at(V, Maze) == Maze#maze.n - 1) of true -> []; _Else -> [V + 1] end;
adjacent_cell(cell_down, V, Maze) -> case (row_at(V, Maze) == Maze#maze.m - 1) of true -> []; _Else -> [V + Maze#maze.n] end.

connect_all(V, Maze) ->
    lists:foreach(fun(X) -> digraph:add_edge(Maze#maze.g, V, X) end, adjacent_cells(V, Maze)).

make_maze(M, N, all_connected) ->
    Maze = make_maze(M, N),
    lists:foreach(fun(X) -> connect_all(X, Maze) end, lists:seq(0, M * N - 1)),
    Maze.

maze_parts(Maze) ->
    SPR = Maze#maze.n + 1,      % slots per row is #columns + 1
    NPR = (Maze#maze.m * 2) + 1,    % # part rows is #(rows * 2) + 1
    [make_part(Maze, trunc(Index/SPR), Index - trunc(Index/SPR) * SPR) || Index <- lists:seq(0, (SPR * NPR) - 1)].

draw_part(Part) ->
    case Part of
        {pwall, pclosed} -> io:format("+---");
        {pwall, popen} -> io:format("+   ");
        {pwall, pend} -> io:format("+~n");
        {phall, pclosed} -> io:format("|   ");
        {phall, popen} -> io:format("    ");
        {phall, pend} -> io:format("|~n")
    end.

has_neighbour(Maze, Row, Col, Direction) ->
    V = vertex_at(Row, Col, Maze),
    if
        V >= 0 ->
            Adjacent = adjacent_cell(Direction, V, Maze),
            if 
                length(Adjacent) > 0 ->
                    Neighbours = digraph:out_neighbours(Maze#maze.g, lists:nth(1, Adjacent)),
                    lists:member(V, Neighbours);
                true -> false
            end;
        true -> false
    end.

make_part(Maze, DoubledRow, Col) ->
    if
        trunc(DoubledRow/2) * 2 == DoubledRow -> % --- (even row) making a wall above the cell
            make_part(Maze, trunc(DoubledRow/2), Col, cell_up, pwall);
        true -> % ---otherwise (odd row) making a hall through the cell
            make_part(Maze, trunc(DoubledRow/2), Col, cell_left, phall)
    end.

make_part(Maze, _, Col, _, Part_Type) when Col == Maze#maze.n -> {Part_Type, pend};
make_part(Maze, Row, Col, Direction, Part_Type) ->
    Has_Neighbour = has_neighbour(Maze, Row, Col, Direction),
    if
        Has_Neighbour -> {Part_Type, popen};
        true -> {Part_Type, pclosed}
    end.

shuffle([], Acc) -> Acc;
shuffle(List, Acc) ->
    Elem = lists:nth(random:uniform(length(List)), List),
    shuffle(lists:delete(Elem, List), Acc++[Elem]).

processDepthFirst(Maze) ->
    if
        Maze#maze.m * Maze#maze.n == 0 -> [{pwall, pend}];
        true ->
            Visited = array:new([{size, Maze#maze.m * Maze#maze.n},{fixed,true},{default,false}]),
            {_, Path} = processDepthFirst(Maze, -1, random:uniform(Maze#maze.m * Maze#maze.n) - 1, {Visited, []}),
            Path
    end.

processDepthFirst(Maze, Vfrom, V, VandP) ->
    {Visited, Path} = VandP,
    Was_Visited = array:get(V, Visited),
    if
        not Was_Visited ->
            Walker = fun(X, Acc) -> processDepthFirst(Maze, V, X, Acc) end,
            Random_Neighbours = shuffle(digraph:out_neighbours(Maze#maze.g, V), []),
            lists:foldl(Walker, {array:set(V, true, Visited), Path++[{Vfrom, V}]}, Random_Neighbours);
        true -> VandP
    end.

open_wall(_, {-1, _}) -> ok;
open_wall(Maze, {V, V2}) ->
    case (V2 > V) of true -> digraph:add_edge(Maze#maze.g, V, V2); _Else -> digraph:add_edge(Maze#maze.g, V2, V) end.

generate_MxN(M, N) ->
    Maze = make_maze(M, N),
    Matrix = make_maze(M, N, all_connected),
    Trail = processDepthFirst(Matrix),
    lists:foreach(fun(X) -> open_wall(Maze, X) end, Trail),
    Parts = maze_parts(Maze),
    lists:foreach(fun(X) -> draw_part(X) end, Parts).

generate_default() ->
    generate_MxN(9, 9).
Output:
8> maze:generate_default().
+---+---+---+---+---+---+---+---+---+
|       |                           |
+   +   +---+   +---+---+---+---+   +
|   |       |           |       |   |
+   +---+   +---+---+   +   +   +   +
|   |       |   |       |   |       |
+   +   +   +   +   +---+---+---+   +
|   |   |   |   |       |       |   |
+   +   +---+   +   +   +   +   +---+
|   |           |   |       |       |
+   +---+---+---+---+---+---+---+   +
|   |                           |   |
+   +   +---+---+   +---+---+   +   +
|   |           |   |           |   |
+   +---+---+---+   +---+   +---+   +
|   |           |       |       |   |
+   +   +---+   +---+   +---+   +   +
|       |               |           |
+---+---+---+---+---+---+---+---+---+
ok
9> 

F#[edit]

Using mutable state in the form of 2D arrays:

let rnd : int -> int =
  let gen = new System.Random()
  fun max -> gen.Next(max)

// randomly choose an element of a list
let choose (xs:_ list) = xs.[rnd xs.Length]

type Maze(width, height) =
  // (x,y) -> have we been here before?
  let visited = Array2D.create width height false
  // (x,y) -> is there a wall between (x,y) and (x+1,y)?
  let horizWalls = Array2D.create width height true
  // (x,y) -> is there a wall between (x,y) and (x,y+1)?
  let vertWalls = Array2D.create width height  true
  
  let isLegalPoint (x,y) =
    x >= 0 && x < width && y >= 0 && y < height
  
  let neighbours (x,y) = 
    [(x-1,y);(x+1,y);(x,y-1);(x,y+1)] |> List.filter isLegalPoint
    
  let removeWallBetween (x1,y1) (x2,y2) =
    if x1 <> x2 then
      horizWalls.[min x1 x2, y1] <- false
    else
      vertWalls.[x1, min y1 y2] <- false
 
  let rec visit (x,y as p) = 
    let rec loop ns =
      let (nx,ny) as n = choose ns
      if not visited.[nx,ny] then
        removeWallBetween p n
        visit n
      match List.filter ((<>) n) ns with
      | [] -> ()
      | others -> loop others

    visited.[x,y] <- true
    loop (neighbours p)

  do visit (rnd width, rnd height)

  member x.Print() =
    ("+" + (String.replicate width "-+")) ::
    [for y in 0..(height-1) do
       yield "\n|"
       for x in 0..(width-1) do 
         yield if horizWalls.[x,y] then " |" else "  "
       yield "\n+"
       for x in 0..(width-1) do 
         yield if vertWalls.[x,y] then "-+" else " +"
    ]
    |> String.concat ""
    |> printfn "%s"

let m = new Maze(10,10)
m.Print()
Output example:
+-+-+-+-+-+-+-+-+-+-+
|         |     |   |
+ +-+-+-+-+ +-+ + + +
|       |   |   | | |
+ +-+-+ + +-+-+ +-+ +
|     | |     |     |
+-+ +-+ +-+-+ +-+-+ +
|   |   |     |     |
+ +-+ +-+ +-+-+-+ +-+
| | |   |       |   |
+ + +-+ +-+ +-+ +-+ +
| |   | | |   |   | |
+ + +-+ + +-+-+-+ + +
|   |   |         | |
+-+ + +-+-+-+-+-+-+ +
|   |     |       | |
+ +-+-+ +-+ +-+-+ + +
| |   |   |     |   |
+ +-+ +-+ +-+-+ +-+-+
|       |           |
+-+-+-+-+-+-+-+-+-+-+

Forth[edit]

Works with: gforth version 0.7.3


The solution uses the following library bits.fs, which implements bit-arrays:

\ Bit Arrays

: to-bits ( c -- f f f f f f f f )
    8 0 ?do
        2 /mod 
        swap negate swap
    loop
    drop ;

: from-bits ( f f f f f f f f -- )
    8 0 ?do
        if [char] 1 emit else [char] 0 emit then
    loop ;

: byte-bin. ( c -- )
    to-bits from-bits space ;

: byte. ( c -- )
    dup byte-bin.
    dup 2 ['] u.r 16 base-execute space
    3 u.r space ;

: bytes-for-bits ( u1 -- u2 )
    8 /mod swap
    0> if 1+ then ;

: bits ( u -- bits )
    dup bytes-for-bits cell +  \ u-bits u-bytes
    dup allocate throw         \ u-bits u-bytes addr
    2dup swap erase nip        \ u-bits addr
    swap over ! ;              \ addr

: free-bits ( bits -- )
    free throw ;

: bits. ( bits -- )
    dup @ bytes-for-bits \ addr bytes
    swap cell+ swap      \ addr+cell bytes
    bounds ?do
        i cr 20 ['] u.r 16 base-execute space
        i c@ byte.
    loop
    cr ;

: bit-position ( u -- u-bit u-byte )
    8 /mod ;

: assert-bit ( bits u -- bits u )
    assert( 2dup swap @ < ) ;

: find-bit ( bits u1 -- addr u2 )
    assert-bit
    bit-position       \ addr bit byte
    rot                \ bit byte addr
    cell+ + swap ;     \ addr' bit
    
: set-true ( addr u -- )
    1 swap lshift over \ addr mask addr
    c@ or swap c! ;
    
: set-false ( addr u -- )
    1 swap lshift invert over \ addr mask addr
    c@ and swap c! ;

: set ( addr u f -- )
    if set-true else set-false then ;
    
: set-bit ( bits u f -- )
    { f }
    find-bit f set ;

: set-bits-at-addr ( addr u-start u-stop f -- )
    { f }
    1+ swap u+do
        dup i f set
    loop
    drop ; 

: byte-from-flag ( f -- c )
    if 255 else 0 then ; 

: set-bits { bits u-start u-stop f -- }

    u-start u-stop > if exit then

    bits u-start find-bit { addr-start bit-start }
    bits u-stop  find-bit { addr-stop  bit-stop  }

    addr-start addr-stop = if
        addr-start bit-start bit-stop f set-bits-at-addr
    else
        addr-start bit-start 7 f set-bits-at-addr
        addr-start 1+ addr-stop addr-start - 1- f byte-from-flag fill
        addr-stop 0 bit-stop f set-bits-at-addr
    then ;

: check-bit ( addr u -- f )
    find-bit           \ addr bit
    1 swap lshift swap \ mask addr
    c@ and 0> ;

: resize-bits ( bits u -- bits )
    over @ { old-size }
    tuck bytes-for-bits cell + resize throw \ u-bits bits
    2dup ! swap                             \ bits u-bits
    dup old-size > if
        over swap                           \ bits bits u-bits
        1- old-size swap false set-bits
    else
        drop
    then ;


The solution uses three bit-arrays: one to track whether a cell has been visited, one for "East"-walls (walls to the right of a cell) and one for "South"-walls (walls to the bottom of a cell).

#! /usr/bin/gforth
\ Maze Generation

warnings off

require random.fs
require bits.fs

\ command line

: parse-number      s>number? invert throw drop ;
: parse-width       ." width : " next-arg parse-number dup . cr ;
: parse-height      ." height: " next-arg parse-number dup . cr ;
: parse-args        cr parse-width parse-height ;

parse-args constant HEIGHT constant WIDTH

 2 CONSTANT AISLE-WIDTH
 1 CONSTANT AISLE-HEIGHT

WIDTH HEIGHT * bits    CONSTANT VISITED
WIDTH 1- HEIGHT * bits CONSTANT EAST-WALLS
HEIGHT 1- WIDTH * bits CONSTANT SOUTH-WALLS

0 CONSTANT NORTH
1 CONSTANT EAST
2 CONSTANT SOUTH
3 CONSTANT WEST

: visited-ix            ( x y -- u )                WIDTH * + ;
: east-wall-ix          ( x y -- u )                [ WIDTH 1- ] literal * + ;
: south-wall-ix         ( x y -- u )                WIDTH * + ;
: visited!              ( x y -- )                  visited-ix VISITED swap TRUE set-bit ;
: visited?              ( x y -- f )                visited-ix VISITED swap check-bit ; 
: east-wall?            ( x y -- f )                east-wall-ix EAST-WALLS swap check-bit ;
: south-wall?           ( x y -- f )                south-wall-ix SOUTH-WALLS swap check-bit ;
: remove-east-wall      ( x y -- )                  east-wall-ix EAST-WALLS swap FALSE set-bit ;
: remove-south-wall     ( x y -- )                  south-wall-ix SOUTH-WALLS swap FALSE set-bit ;

: clear-visited         ( -- )                      VISITED 0 WIDTH 1- HEIGHT 1- visited-ix FALSE set-bits ;
: set-east-walls        ( -- )                      EAST-WALLS 0 WIDTH 2 - HEIGHT 1- east-wall-ix TRUE set-bits ;
: set-south-walls       ( -- )                      SOUTH-WALLS 0 WIDTH 1- HEIGHT 2 - south-wall-ix TRUE set-bits ;
: initial-pos           ( -- x y )                  WIDTH random HEIGHT random ;
: init-state            ( -- -1 x y 0 )             clear-visited set-east-walls set-south-walls -1 initial-pos 2dup visited! 0 ;

: north-valid?          ( x y -- f )                nip 0> ;
: east-valid?           ( x y -- f )                drop [ WIDTH 1- ] literal < ;
: south-valid?          ( x y -- f )                nip [ HEIGHT 1- ] literal < ;
: west-valid?           ( x y -- f )                drop 0> ;
: dir-valid?            ( x y d -- f )              case
                                                        NORTH of north-valid? endof
                                                        EAST  of east-valid?  endof
                                                        SOUTH of south-valid? endof
                                                        WEST  of west-valid?  endof
                                                    endcase ;
: move-north            ( x y -- x' y' )            1- ;
: move-east             ( x y -- x' y' )            swap 1+ swap ;
: move-south            ( x y -- x' y' )            1+ ;
: move-west             ( x y -- x' y' )            swap 1- swap ;
: move                  ( x y d -- x' y' )          case
                                                        NORTH of move-north endof
                                                        EAST  of move-east  endof
                                                        SOUTH of move-south endof
                                                        WEST  of move-west  endof
                                                    endcase ;

: remove-north-wall     ( x y -- )                  1- remove-south-wall ;
: remove-west-wall      ( x y -- )                  swap 1- swap remove-east-wall ;
: remove-wall           ( x y d -- )                case
                                                        NORTH of remove-north-wall endof
                                                        EAST  of remove-east-wall  endof
                                                        SOUTH of remove-south-wall endof
                                                        WEST  of remove-west-wall  endof
                                                    endcase ;

: dir?                  ( m d -- f )                1 swap lshift and 0= ;
: dir!                  ( m d -- m' )               1 swap lshift or ;
: pick-dir              ( m -- m' d )               assert( dup $f <> ) begin 4 random 2dup dir? if tuck dir! swap exit then drop again ;

: update-state          ( x y m d -- x' y' m' )     { x y m d }
                                                    x y d dir-valid? if
                                                        x y m
                                                        x y d move
                                                        2dup visited? if
                                                            2drop
                                                        else
                                                            2dup visited!
                                                            x y d remove-wall
                                                            0
                                                        then
                                                    else
                                                        x y m
                                                    then ;   

: step                  ( x y m -- x' y' m' )       dup $f = if
                                                        drop 2drop \ backtracking!
                                                    else
                                                        pick-dir update-state
                                                    then ;

: build-maze            ( -- )                      init-state                                                        
                                                    begin
                                                        dup -1 <> while
                                                            step
                                                    repeat drop ;

: corner                ( -- )                      [char] + emit ;
: h-wall                ( -- )                      [char] - emit ;
: v-wall                ( -- )                      [char] | emit ;
: top-bottom.           ( -- )                      cr corner WIDTH 0 ?do AISLE-WIDTH 0 ?do h-wall loop corner loop ;
: empty                 ( -- )                      AISLE-WIDTH 0 ?do space loop ;
: interior-cell         ( x y -- )                  empty east-wall? if v-wall else space then ;
: last-cell             ( -- )                      empty v-wall ;
: row                   ( y -- )                    cr v-wall [ WIDTH 1- ] literal 0 ?do i over interior-cell loop drop last-cell ;
: last-row              ( y -- )                    cr WIDTH 0 ?do corner i over south-wall? if AISLE-WIDTH 0 ?do h-wall loop else empty then loop drop corner ;
: aisle                 ( y -- )                    AISLE-HEIGHT 0 ?do dup row loop dup [ HEIGHT 1- ] literal < if last-row else drop then ;
: maze.                 ( -- )                      top-bottom.
                                                    HEIGHT 0 ?do i aisle loop
                                                    top-bottom. ;
: maze                  ( width height -- )         build-maze maze. ;

maze cr bye
Output:

./maze-generation.fs 20 10

width : 20 height: 10

+--+--+--+--+--+--+--+--+--+--+--+--+--+--+--+--+--+--+--+--+ | | | | | | | + +--+ + +--+ +--+--+ + +--+ +--+--+ + +--+--+ + + | | | | | | | | | | | +--+--+--+--+ +--+ +--+--+--+ + + +--+--+--+ + +--+ + | | | | | | | | | + +--+--+--+--+--+--+--+ + + + +--+--+--+ +--+--+ +--+ | | | | | | | + +--+--+--+--+--+ + +--+--+--+--+ + + +--+--+ + + + | | | | | | | | | | | | | | + + + + +--+ + + + +--+ +--+ + +--+ + + +--+ + | | | | | | | | | | | | +--+--+--+--+ + + + +--+ +--+--+--+--+--+--+ +--+--+ + | | | | | | | | | + +--+ + +--+--+ +--+--+ + +--+ +--+ +--+--+--+ +--+ | | | | | | | | | | | | | | +--+ + + + + + + +--+--+ + + + + + + + +--+ + | | | | | | | | | | | | | | | | + +--+--+--+--+ + + + + + + + + +--+ +--+--+ + + | | | | | | | +--+--+--+--+--+--+--+--+--+--+--+--+--+--+--+--+--+--+--+--+

./maze-generation.fs 40 20

width : 40 height: 20

+--+--+--+--+--+--+--+--+--+--+--+--+--+--+--+--+--+--+--+--+--+--+--+--+--+--+--+--+--+--+--+--+--+--+--+--+--+--+--+--+ | | | | | | | | | | | | | + +--+ + +--+ +--+--+ + +--+ +--+--+ + + + +--+--+--+ + +--+ +--+ +--+ + + + +--+ + + + + +--+ + | | | | | | | | | | | | | | | | | | | | | | +--+--+--+--+ +--+ +--+--+--+ + + +--+--+--+ + +--+ +--+--+--+ +--+--+--+--+--+ + +--+ + +--+ + +--+--+ + | | | | | | | | | | | | | | | | | | | + + + + +--+--+--+ +--+ + + +--+--+--+ +--+--+ +--+ + + +--+--+--+--+--+ +--+--+ +--+--+ +--+ + +--+ + | | | | | | | | | | | | | | | | | | | + +--+ +--+--+--+--+--+ + +--+--+ +--+ +--+--+ + + +--+ +--+ + +--+ + +--+--+ +--+--+--+--+ + +--+--+--+ | | | | | | | | | | | | | | | | | | + +--+--+ +--+--+--+--+--+ + + +--+ +--+--+ + +--+ + +--+--+--+ + +--+--+ + +--+--+ + + +--+--+--+--+ + | | | | | | | | | | | | | | | | | | | | | + +--+ +--+ +--+--+ + +--+--+--+ + + + + +--+--+--+ +--+ +--+--+--+ + + +--+ + +--+--+--+--+--+--+ + + | | | | | | | | | | | | | | | | | + + +--+--+--+--+--+ +--+ + + +--+--+--+ +--+ + + +--+ +--+--+ +--+--+ +--+--+--+ + + +--+--+--+ +--+ + | | | | | | | | | | | | | | | | | | | | | | +--+ + +--+--+--+ +--+--+--+--+--+ +--+ +--+ +--+ +--+--+ + + +--+--+ + +--+--+ + + + + +--+--+ + + + | | | | | | | | | | | | | | | | | | | | | | | + +--+ + + + +--+ +--+ + +--+--+ +--+ + + + + +--+--+--+--+ + + +--+--+ + + +--+ +--+--+ +--+--+ + | | | | | | | | | | | | | | | | | | | | | | | + +--+--+ + +--+ +--+ + + + + + +--+--+ + +--+ + +--+ + +--+ + + +--+--+ +--+--+--+--+ + + +--+--+ | | | | | | | | | | | | | | | | | | | | | | | | | | + + +--+ + + +--+ +--+ + + + + + +--+--+ + +--+ + +--+--+ + + +--+ + + + + +--+ +--+ +--+ + + | | | | | | | | | | | | | | | | | | | | | | | | | | | + +--+ +--+--+--+ + + +--+--+ + +--+ +--+ + + + +--+ + + +--+ +--+--+--+--+--+--+ + +--+ +--+ + + + | | | | | | | | | | | | | | | | | | | | | +--+ + +--+ + + + +--+--+--+--+--+--+--+--+--+ + + +--+ + +--+--+--+ + + +--+ + +--+ + + +--+ +--+ + | | | | | | | | | | | | | | | | | | | | | | | | + + +--+ +--+--+ + + +--+--+ + +--+--+--+ + + +--+ +--+ + +--+ + + +--+--+--+--+ +--+ +--+ +--+ + + | | | | | | | | | | | | | | | | | | | | | | | | + +--+ + +--+ + + +--+--+ + + + +--+ + +--+ + +--+ + + +--+--+ +--+ +--+--+ +--+ +--+ + +--+--+ + | | | | | | | | | | | | | | | | | | | | | | + +--+ +--+--+ + + + + + +--+--+--+ +--+--+--+--+ + + +--+--+--+--+--+--+--+ +--+--+ +--+ +--+--+ +--+--+ | | | | | | | | | | | | | | | | | | | + + +--+ +--+--+ +--+--+--+--+ + + +--+ +--+--+ +--+ +--+--+ + +--+ + +--+--+ +--+--+ +--+ + +--+--+ + | | | | | | | | | | | | | | | | | | | + +--+--+--+ +--+--+ +--+ +--+--+--+ + + + +--+--+ +--+--+ + + + +--+ +--+ + +--+ + + +--+--+--+--+ + | | | | | | | | | | | | | | | | | | | | | | + +--+--+ +--+--+--+--+ + + +--+ +--+--+--+--+ + + + + +--+--+--+ +--+ + +--+--+ + + +--+ +--+ + + + | | | | | | | | | | | +--+--+--+--+--+--+--+--+--+--+--+--+--+--+--+--+--+--+--+--+--+--+--+--+--+--+--+--+--+--+--+--+--+--+--+--+--+--+--+--+

FreeBASIC[edit]

' version 04-12-2016
' compile with: fbc -s console
' when generating a big maze it's possible to run out of stack space
' increase stack with the -t xxxx (xxxx is the amount you want in Kbytes)

ReDim Shared As String d() ' directions
ReDim Shared As ULong c()  ' cell's

Sub cell(x As ULong, y As ULong, s As ULong)

    Dim As ULong x1, y1, di_n
    c(x,y) = 1 ' mark as visited

    Do
        Dim As String di = d(x, y)
        Dim As Long l = Len(di) -1
        If l < 0 Then Exit Sub ' no directions left then exit
        di_n = di[l] ' get direction
        If l = 0 Then
            d(x,y) = ""
        Else
            d(x,y) = Left(di,l)
        End If

        Select Case di_n ' 0,0 is upper left corner
            Case Asc("N")
                x1 = x    : y1 = y -1
            Case Asc("E")
                x1 = x +1 : y1 = y
            Case Asc("S")
                x1 = x    : y1 = y +1
            Case Asc("W")
                x1 = x -1 : y1 = y
        End Select

        If c(x1,y1) <> 0 Then Continue Do

        Select Case di_n ' 0,0 is upper left corner
            Case Asc("N")
                Line (x * s +1 , y * s) - ((x +1) * s -1, y * s),0
            Case Asc("E")
                Line (x1 * s, y * s +1) - (x1 * s, (y +1) * s -1),0
            Case Asc("S")
                Line (x * s +1, y1 * s) - ((x +1) * s -1, y1 * s),0
            Case Asc("W")
                Line (x * s , y * s +1) - (x * s, (y +1) * s -1),0
        End Select

        cell(x1, y1, s)
    Loop

End Sub

Sub gen_maze(w As ULong, h As ULong, s As ULong)

    ReDim d(w, h)
    ReDim c(w, h)
    Dim As ULong x, y, r, i
    Dim As String di

    d(0, 0) = "SE"       ' cornes
    d(0, h -1) ="NE"
    d(w -1, 0) ="SW"
    d(w -1, h -1) ="NW"

    For x = 1 To w -2  ' sides
        d(x,0) = "EWS"
        d(x,h -1) = "NEW"
    Next

    For y = 1 To h -2
        d(0, y) = "NSE"
        d(w -1, y) ="NSW"
    Next

    For x = 0 To w -1     ' shuffle directions
        For y = 0 To h -1
            di = d(x,y)
            If di = "" Then di = "NEWS"
            i = Len(di)
            Do
                r = Fix(Rnd * i)
                i = i - 1
                Swap di[r], di[i]
            Loop Until i = 0
            d(x,y) = di
        Next
    Next

    ScreenRes w * s +1, h * s +1, 8
    ' draw the grid
    For x = 0 To w
        Line (x * s, 0) - (x * s, h * s), 2 ' green color
    Next

    For y = 0 To h
        Line(0, y * s) - (w* s, y * s),2
    Next
    ' choice the start cell
    x = Fix(Rnd * w)
    y = Fix(Rnd * h)

    cell(x, y, s)

End Sub

' ------=< MAIN >=------

Randomize Timer

Dim As ULong t

Do
    ' gen_maxe(width, height, cell size)
    gen_maze(30, 30, 20)
    WindowTitle " S to save, N for next maze, other key to stop"
    Do
    Var key = Inkey
    key = UCase(key)
    If key = "S" Then
        t = t +1
        BSave("maze" + Str(t) + ".bmp"), 0
        key = ""
    End If
    If key = "N" Then Continue Do, Do
    If key <> "" Then Exit Do, Do 
    Loop
Loop

End

Fōrmulæ[edit]

Fōrmulæ programs are not textual, visualization/edition of programs is done showing/manipulating structures but not text. Moreover, there can be multiple visual representations of the same program. Even though it is possible to have textual representation —i.e. XML, JSON— they are intended for storage and transfer purposes more than visualization and edition.

Programs in Fōrmulæ are created/edited online in its website, However they run on execution servers. By default remote servers are used, but they are limited in memory and processing power, since they are intended for demonstration and casual use. A local server can be downloaded and installed, it has no limitations (it runs in your own computer). Because of that, example programs can be fully visualized and edited, but some of them will not run if they require a moderate or heavy computation/memory resources, and no local server is being used.

In this page you can see the program(s) related to this task and their results.

Go[edit]

package main

import (
    "bytes"
    "fmt"
    "math/rand"
    "time"
)   
    
type maze struct { 
    c  []byte   // cell contents
    h  []byte   // horizontal walls above cells
    v  []byte   // vertical walls to the left of cells
    c2 [][]byte // cells by row
    h2 [][]byte // horizontal walls by row (ignore first row)
    v2 [][]byte // vertical walls by row (ignore first of each column)
}

func newMaze(rows, cols int) *maze {
    c := make([]byte, rows*cols)              // all cells
    h := bytes.Repeat([]byte{'-'}, rows*cols) // all horizontal walls
    v := bytes.Repeat([]byte{'|'}, rows*cols) // all vertical walls
    c2 := make([][]byte, rows)                // cells by row
    h2 := make([][]byte, rows)                // horizontal walls by row
    v2 := make([][]byte, rows)                // vertical walls by row
    for i := range h2 {
        c2[i] = c[i*cols : (i+1)*cols]
        h2[i] = h[i*cols : (i+1)*cols]
        v2[i] = v[i*cols : (i+1)*cols]
    }
    return &maze{c, h, v, c2, h2, v2}
}

func (m *maze) String() string {
    hWall := []byte("+---")
    hOpen := []byte("+   ")
    vWall := []byte("|   ")
    vOpen := []byte("    ")
    rightCorner := []byte("+\n") 
    rightWall := []byte("|\n")
    var b []byte
    // for all rows 
    for r, hw := range m.h2 {
        // draw h walls
        for _, h := range hw { 
            if h == '-' || r == 0 {
                b = append(b, hWall...)
            } else {
                b = append(b, hOpen...)
            }
        }
        b = append(b, rightCorner...)
        // draw v walls
        for c, vw := range m.v2[r] {
            if vw == '|' || c == 0 {
                b = append(b, vWall...)
            } else {
                b = append(b, vOpen...)
            }
            // draw cell contents
            if m.c2[r][c] != 0 {
                b[len(b)-2] = m.c2[r][c]
            }
        }
        b = append(b, rightWall...)
    }
    // draw bottom edge of maze
    for _ = range m.h2[0] {
        b = append(b, hWall...)
    }
    b = append(b, rightCorner...)
    return string(b)
}

func (m *maze) gen() {
    m.g2(rand.Intn(len(m.c2)), rand.Intn(len(m.c2[0])))
}

const (
    up = iota
    dn
    rt
    lf
)

func (m *maze) g2(r, c int) {
    m.c2[r][c] = ' '
    for _, dir := range rand.Perm(4) {
        switch dir {
        case up:
            if r > 0 && m.c2[r-1][c] == 0 {
                m.h2[r][c] = 0
                m.g2(r-1, c)
            }
        case lf:
            if c > 0 && m.c2[r][c-1] == 0 {
                m.v2[r][c] = 0
                m.g2(r, c-1)
            }
        case dn:
            if r < len(m.c2)-1 && m.c2[r+1][c] == 0 {
                m.h2[r+1][c] = 0
                m.g2(r+1, c)
            }
        case rt:
            if c < len(m.c2[0])-1 && m.c2[r][c+1] == 0 {
                m.v2[r][c+1] = 0
                m.g2(r, c+1)
            }
        }
    }
}

func main() {
    rand.Seed(time.Now().UnixNano())
    m := newMaze(4, 6)
    m.gen()
    fmt.Print(m)
}
Output:
+---+---+---+---+---+---+
|   |           |       |
+   +   +   +---+   +---+
|   |   |           |   |
+   +   +---+---+---+   +
|   |   |               |
+   +   +   +---+---+   +
|           |           |
+---+---+---+---+---+---+

Haskell[edit]

{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE TypeFamilies #-}

import Data.Array.ST
       (STArray, freeze, newArray, readArray, writeArray)
import Data.STRef (STRef, newSTRef, readSTRef, writeSTRef)
import System.Random (Random(..), getStdGen, StdGen)
import Control.Monad (forM_, unless)
import Control.Monad.ST (ST, stToIO)
import Data.Array (Array, (!), bounds)
import Data.Bool (bool)

rand
  :: Random a
  => (a, a) -> STRef s StdGen -> ST s a
rand range gen = do
  (a, g) <- randomR range <$> readSTRef gen
  gen `writeSTRef` g
  return a

data Maze = Maze
  { rightWalls, belowWalls :: Array (Int, Int) Bool
  }

maze :: Int -> Int -> StdGen -> ST s Maze
maze width height gen = do
  visited <- mazeArray False
  rWalls <- mazeArray True
  bWalls <- mazeArray True
  gen <- newSTRef gen
  (,) <$> rand (0, maxX) gen <*> rand (0, maxY) gen >>=
    visit gen visited rWalls bWalls
  Maze <$> freeze rWalls <*> freeze bWalls
  where
    visit gen visited rWalls bWalls here = do
      writeArray visited here True
      let ns = neighbors here
      i <- rand (0, length ns - 1) gen
      forM_ (ns !! i : take i ns ++ drop (i + 1) ns) $
        \there -> do
          seen <- readArray visited there
          unless seen $
            do removeWall here there
               visit gen visited rWalls bWalls there
      where
        removeWall (x1, y1) (x2, y2) =
          writeArray (bool rWalls bWalls (x1 == x2)) (min x1 x2, min y1 y2) False
    neighbors (x, y) =
      bool [(x - 1, y)] [] (0 == x) ++
      bool [(x + 1, y)] [] (maxX == x) ++
      bool [(x, y - 1)] [] (0 == y) ++ bool [(x, y + 1)] [] (maxY == y)
    maxX = width - 1
    maxY = height - 1
    mazeArray =
      newArray ((0, 0), (maxX, maxY)) :: Bool -> ST s (STArray s (Int, Int) Bool)

printMaze :: Maze -> IO ()
printMaze (Maze rWalls bWalls) = do
  putStrLn $ '+' : concat (replicate (maxX + 1) "---+")
  forM_ [0 .. maxY] $
    \y -> do
      putStr "|"
      forM_ [0 .. maxX] $
        \x -> do
          putStr "   "
          putStr $ bool " " "|" (rWalls ! (x, y))
      putStrLn ""
      forM_ [0 .. maxX] $
        \x -> do
          putStr "+"
          putStr $ bool "   " "---" (bWalls ! (x, y))
      putStrLn "+"
  where
    maxX = fst (snd $ bounds rWalls)
    maxY = snd (snd $ bounds rWalls)

main :: IO ()
main = getStdGen >>= stToIO . maze 11 8 >>= printMaze
Sample output:
 +---+---+---+---+---+---+---+---+---+---+---+
 |               |                           |
 +   +---+---+---+   +---+---+---+---+---+   +
 |               |           |   |       |   |
 +   +---+---+   +---+---+   +   +   +   +   +
 |   |   |       |           |       |   |   |
 +   +   +   +---+---+---+---+   +---+   +   +
 |       |   |                   |   |       |
 +---+---+   +   +---+---+---+---+   +---+---+
 |       |   |   |                       |   |
 +   +   +   +   +---+---+---+   +---+   +   +
 |   |       |   |               |       |   |
 +   +---+---+   +   +---+---+---+   +---+   +
 |               |       |           |       |
 +   +---+---+---+---+   +   +---+---+   +   +
 |                       |               |   |
 +---+---+---+---+---+---+---+---+---+---+---+

Huginn[edit]

import Algorithms as algo;
import Mathematics as math;
import Terminal as term;

class Maze {
	_rows = none;
	_cols = none;
	_data = none;
	constructor( rows_, cols_ ) {
		_rows = ( rows_ / 2 ) * 2 - 1;
		_cols = ( cols_ / 2 ) * 2 - 1;
		_data = [].resize( _rows + 2, [].resize( _cols + 2, false ) );
		x = 0;
		y = 0;
		path = [];
		rng = math.Randomizer( math.Randomizer.DISTRIBUTION.DISCRETE, 0, integer( $2 ^ $63 - $1 ) );
		for ( _ : algo.range( _rows * _cols / 3 ) ) {
			_data[y + 1][x + 1] = true;
			while ( true ) {
				n = neighbours( y, x );
				ns = size( n );
				if ( ns == 0 ) {
					if ( size( path ) == 0 ) {
						break;
					}
					y, x = path[-1];
					path.pop();
					continue;
				}
				oy, ox = ( y, x );
				y, x = n[rng.next() % ns];
				_data[(y + oy) / 2 + 1][(x + ox) / 2 + 1] = true;
				path.push( ( y, x ) );
				break;
			}
		}
		_data[0][1] = true;
		_data[-1][-2] = true;
	}
	neighbours( y_, x_ ) {
		n = [];
		if ( ( x_ > 1 ) && ! _data[y_ + 1][x_ - 1] ) {
			n.push( ( y_, x_ - 2 ) );
		}
		if ( ( y_ > 1 ) && ! _data[y_ - 1][x_ + 1] ) {
			n.push( ( y_ - 2, x_ ) );
		}
		if ( ( x_ < ( _cols - 2 ) ) && ! _data[y_ + 1][x_ + 3] ) {
			n.push( ( y_, x_ + 2 ) );
		}
		if ( ( y_ < ( _rows - 2 ) ) && ! _data[y_ + 3][x_ + 1] ) {
			n.push( ( y_ + 2, x_ ) );
		}
		return ( n );
	}
	to_string() {
		s = "";
		for ( r : _data ) {
			s += ∑( algo.map( r, @( b ) { b ? " " : "#"; } ) );
			s += "\n";
		}
		return ( s );
	}
}

main() {
	rows = term.lines() - 2;
	cols = term.columns() - 1;
	maze = Maze( rows, cols );
	print( "{}".format( maze ) );
}

Icon and Unicon[edit]

20x30 with two random openings
20x30 with opposite openings
link printf

procedure main(A)                               # generate rows x col maze
   /mh := \A[1] | 12                            # or take defaults 12 x 16
   /mw := \A[2] | 16
   mz := DisplayMaze(GenerateMaze(mh,mw))
   WriteImage(mz.filename)                      # save file
   WAttrib(mz.window,"canvas=normal")           # show maze in hidden window
   until Event() == &lpress                     # wait for left mouse press
   close(mz.window)                            
end

$define FINISH 64 # exit
$define START  32 # entrance
$define PATH  128 
$define SEEN   16 # bread crumbs for generator
$define NORTH   8 # sides ...
$define EAST    4
$define SOUTH   2
$define WEST    1
$define EMPTY   0 # like new

procedure GenerateMaze(r,c)                     #: Depth First Maze Generation
static maze,h,w,rd 
   if /maze then {                              # BEGING - No maze yet
      /h := integer(1 < r) | runerr(r,205)      # valid size 2x2 or better
      /w := integer(1 < c) | runerr(r,205)
      every !(maze := list(h)) := list(w,EMPTY) # shinny new empty maze
      start  := [?h,?w,?4-1,START]              # random [r,c] start & finish                 
      finish := [?h,?w,(start[3]+2)%4,FINISH]   # w/ opposite side exponent
      every x := start | finish do {
         case x[3] := 2 ^ x[3] of {             # get side from exponent and 
            NORTH : x[1] := 1                   # project r,c to selected edge
            EAST  : x[2] := w
            SOUTH : x[1] := h         
            WEST  : x[2] := 1
            }   
         maze[x[1],x[2]] +:= x[3] + x[4]        # transcribe s/f to maze
         }
      rd := [NORTH, EAST, SOUTH, WEST]          # initial list of directions     
      GenerateMaze(start[1],start[2])           # recurse through maze     
      return 1(.maze,maze := &null)             # return maze, reset for next
   }
   else {         # ----------------------- recursed to clear insize of maze
      if iand(maze[r,c],SEEN) = 0 then {        # in bounds and not SEEN yet?
         maze[r,c] +:= SEEN                     # Mark current cell as visited   
         every !rd :=: ?rd                      # randomize list of directions
         every d := !rd do
            case d of {                         # try all, succeed & clear wall
               NORTH :  maze[r,c] +:= ( GenerateMaze(r-1,c), NORTH)
               EAST  :  maze[r,c] +:= ( GenerateMaze(r,c+1),  EAST)
               SOUTH :  maze[r,c] +:= ( GenerateMaze(r+1,c), SOUTH)
               WEST  :  maze[r,c] +:= ( GenerateMaze(r,c-1),  WEST)   
               }
         return                                 # signal success to caller
         }
   }
end

$define CELL   20                                   # cell size in pixels
$define BORDER 30                                   # border size in pixels

record mazeinfo(window,maze,filename)               # keepers

procedure DisplayMaze(maze)                         #: show it off
if CELL < 8 then runerr(205,CELL)                   # too small

wh := (ch := (mh := *maze  ) * CELL) + 2 * BORDER   # win, cell, maze height
ww := (cw := (mw := *maze[1]) * CELL) + 2 * BORDER  # win, cell, maze width

wparms := [ sprintf("Maze %dx%d",*maze,*maze[1]),   # window parameters
            "g","bg=white","canvas=hidden",      
            sprintf("size=%d,%d",ww,wh),
            sprintf("dx=%d",BORDER),
            sprintf("dy=%d",BORDER)]

&window := open!wparms | stop("Unable to open Window")

Fg("black")                                         # Draw full grid
every DrawLine(x := 0 to cw by CELL,0,x,ch+1)       # . verticals
every DrawLine(0,y := 0 to ch by CELL,cw+1,y)       # . horizontals

Fg("white")                                         # Set to erase lines
every y := CELL*((r := 1 to mh)-1) & x := CELL*((c := 1 to mw)-1) do {
   WAttrib("dx="||x+BORDER,"dy="||y+BORDER)         # position @ cell r,c
   if iand(maze[r,c],NORTH) > 0 then DrawLine(2,0,CELL-1,0)            
   if iand(maze[r,c],EAST)  > 0 then DrawLine(CELL,2,CELL,CELL-1)        
   if iand(maze[r,c],SOUTH) > 0 then DrawLine(2,CELL,CELL-1,CELL)                
   if iand(maze[r,c],WEST)  > 0 then DrawLine(0,2,0,CELL-1)            
   }   

return mazeinfo(&window,maze,sprintf("maze-%dx%d-%d.gif",r,c,&now))
end

Note: The underlying maze structure (matrix) is uni-directional from the start

printf.icn provides formatting

J[edit]

This algorithm allows almost no parallelism. So, while it might be "simple", generating very large mazes this way will not be necessarily efficient to implement on future (highly parallel) systems. That said, perhaps mazes with millions of cells are not very likely to be needed to be generated quickly.

Translation of: PicoLisp

But without any relevant grid library:

maze=:4 :0
  assert.0<:n=.<:x*y
  horiz=. 0$~x,y-1
  verti=. 0$~(x-1),y
  path=.,:here=. ?x,y
  unvisited=.0 (<here+1)} 0,0,~|:0,0,~1$~y,x
  while.n do.
    neighbors=. here+"1 (,-)=0 1
    neighbors=. neighbors #~ (<"1 neighbors+1) {unvisited
    if.#neighbors do.
      n=.n-1
      next=. ({~ ?@#) neighbors
      unvisited=.0 (<next+1)} unvisited
      if.{.next=here
      do. horiz=.1 (<-:here+next-0 1)} horiz
      else. verti=. 1 (<-:here+next-1 0)} verti end.
      path=.path,here=.next
    else.
      here=.{:path
      path=.}:path
    end.
  end.
  horiz;verti
)

display=:3 :0
  size=. >.&$&>/y
  text=. (}:1 3$~2*1+{:size)#"1":size$<' '
  'hdoor vdoor'=. 2 4&*&.>&.> (#&,{@;&i./@$)&.> y
  ' ' (a:-.~0 1;0 2; 0 3;(2 1-~$text);(1 4&+&.> hdoor),,vdoor+&.>"0/2 1;2 2;2 3)} text
)

The result of maze is a pair of arrays: one for open "doors" in the horizontal direction and the other for open "doors" in the vertical direction. The entry and exit doors are not represented by maze -- they are implicitly defined and are implemented in display. (The sequences of coordinates in display are the relative coordinates for the doors. For example, 2 1;2 2;2 3 are where we put spaces for each vertical door. The variable text is an ascii representation of the maze grid before the doors are placed.)

Example use (with ascii box drawing enabled):
   display 8 maze 11
+   +---+---+---+---+---+---+---+---+---+---+
|       |           |                   |   |
+   +   +   +   +---+   +   +---+---+   +   +
|   |       |   |       |           |   |   |
+   +---+---+   +   +---+---+---+   +   +   +
|   |           |   |           |   |       |
+---+   +---+   +   +   +---+   +   +---+---+
|       |       |   |       |   |           |
+   +   +---+---+   +---+   +   +---+---+   +
|   |   |       |   |   |   |           |   |
+   +---+   +   +   +   +   +---+---+   +   +
|           |           |           |       |
+   +---+---+---+---+---+---+---+   +---+   +
|   |   |   |       |       |       |   |   |
+   +   +   +   +   +   +   +   +---+   +   +
|       |       |       |       |            
+---+---+---+---+---+---+---+---+---+---+---+

Java[edit]

Works with: Java version 1.5+
package org.rosettacode;

import java.util.Collections;
import java.util.Arrays;

/*
 * recursive backtracking algorithm
 * shamelessly borrowed from the ruby at
 * http://weblog.jamisbuck.org/2010/12/27/maze-generation-recursive-backtracking
 */
public class MazeGenerator {
	private final int x;
	private final int y;
	private final int[][] maze;

	public MazeGenerator(int x, int y) {
		this.x = x;
		this.y = y;
		maze = new int[this.x][this.y];
		generateMaze(0, 0);
	}

	public void display() {
		for (int i = 0; i < y; i++) {
			// draw the north edge
			for (int j = 0; j < x; j++) {
				System.out.print((maze[j][i] & 1) == 0 ? "+---" : "+   ");
			}
			System.out.println("+");
			// draw the west edge
			for (int j = 0; j < x; j++) {
				System.out.print((maze[j][i] & 8) == 0 ? "|   " : "    ");
			}
			System.out.println("|");
		}
		// draw the bottom line
		for (int j = 0; j < x; j++) {
			System.out.print("+---");
		}
		System.out.println("+");
	}

	private void generateMaze(int cx, int cy) {
		DIR[] dirs = DIR.values();
		Collections.shuffle(Arrays.asList(dirs));
		for (DIR dir : dirs) {
			int nx = cx + dir.dx;
			int ny = cy + dir.dy;
			if (between(nx, x) && between(ny, y)
					&& (maze[nx][ny] == 0)) {
				maze[cx][cy] |= dir.bit;
				maze[nx][ny] |= dir.opposite.bit;
				generateMaze(nx, ny);
			}
		}
	}

	private static boolean between(int v, int upper) {
		return (v >= 0) && (v < upper);
	}

	private enum DIR {
		N(1, 0, -1), S(2, 0, 1), E(4, 1, 0), W(8, -1, 0);
		private final int bit;
		private final int dx;
		private final int dy;
		private DIR opposite;

		// use the static initializer to resolve forward references
		static {
			N.opposite = S;
			S.opposite = N;
			E.opposite = W;
			W.opposite = E;
		}

		private DIR(int bit, int dx, int dy) {
			this.bit = bit;
			this.dx = dx;
			this.dy = dy;
		}
	};

	public static void main(String[] args) {
		int x = args.length >= 1 ? (Integer.parseInt(args[0])) : 8;
		int y = args.length == 2 ? (Integer.parseInt(args[1])) : 8;
		MazeGenerator maze = new MazeGenerator(x, y);
		maze.display();
	}

}
Output:
+---+---+---+---+---+---+---+---+---+---+
|   |                           |       |
+   +---+---+   +---+---+   +   +   +---+
|           |   |   |       |   |       |
+---+---+   +   +   +   +---+   +---+   +
|           |       |   |   |       |   |
+   +---+---+   +---+   +   +---+   +   +
|   |       |   |       |           |   |
+   +   +   +---+   +---+---+---+   +   +
|   |   |       |               |       |
+   +   +---+   +   +---+---+   +---+---+
|   |       |   |   |           |       |
+   +---+   +   +---+   +---+---+   +   +
|       |   |       |               |   |
+---+   +   +---+   +   +---+---+---+   +
|   |   |       |   |       |           |
+   +   +---+   +   +---+---+   +---+   +
|   |       |   |           |   |   |   |
+   +---+   +   +---+---+   +   +   +   +
|               |               |       |
+---+---+---+---+---+---+---+---+---+---+

JavaScript[edit]

Translation of: J
function maze(x,y) {
	var n=x*y-1;
	if (n<0) {alert("illegal maze dimensions");return;}
	var horiz =[]; for (var j= 0; j<x+1; j++) horiz[j]= [],
	    verti =[]; for (var j= 0; j<x+1; j++) verti[j]= [],
	    here = [Math.floor(Math.random()*x), Math.floor(Math.random()*y)],
	    path = [here],
	    unvisited = [];
	for (var j = 0; j<x+2; j++) {
		unvisited[j] = [];
		for (var k= 0; k<y+1; k++)
			unvisited[j].push(j>0 && j<x+1 && k>0 && (j != here[0]+1 || k != here[1]+1));
	}
	while (0<n) {
		var potential = [[here[0]+1, here[1]], [here[0],here[1]+1],
		    [here[0]-1, here[1]], [here[0],here[1]-1]];
		var neighbors = [];
		for (var j = 0; j < 4; j++)
			if (unvisited[potential[j][0]+1][potential[j][1]+1])
				neighbors.push(potential[j]);
		if (neighbors.length) {
			n = n-1;
			next= neighbors[Math.floor(Math.random()*neighbors.length)];
			unvisited[next[0]+1][next[1]+1]= false;
			if (next[0] == here[0])
				horiz[next[0]][(next[1]+here[1]-1)/2]= true;
			else 
				verti[(next[0]+here[0]-1)/2][next[1]]= true;
			path.push(here = next);
		} else 
			here = path.pop();
	}
	return {x: x, y: y, horiz: horiz, verti: verti};
}

function display(m) {
	var text= [];
	for (var j= 0; j<m.x*2+1; j++) {
		var line= [];
		if (0 == j%2)
			for (var k=0; k<m.y*4+1; k++)
				if (0 == k%4) 
					line[k]= '+';
				else
					if (j>0 && m.verti[j/2-1][Math.floor(k/4)])
						line[k]= ' ';
					else
						line[k]= '-';
		else
			for (var k=0; k<m.y*4+1; k++)
				if (0 == k%4)
					if (k>0 && m.horiz[(j-1)/2][k/4-1])
						line[k]= ' ';
					else
						line[k]= '|';
				else
					line[k]= ' ';
		if (0 == j) line[1]= line[2]= line[3]= ' ';
		if (m.x*2-1 == j) line[4*m.y]= ' ';
		text.push(line.join('')+'\r\n');
	}
	return text.join('');
}

Variable meanings in function maze:

  1. x,y — dimensions of maze
  2. n — number of openings to be generated
  3. horiz — two dimensional array of locations of horizontal openings (true means wall is open)
  4. verti — two dimensional array of locations of vertical openings (true means wall is open)
  5. here — current location under consideration
  6. path — history (stack) of locations that might need to be revisited
  7. unvisited — two dimensional array of locations that have not been visited, padded to avoid need for boundary tests (true means location needs to be visited)
  8. potential — locations adjacent to here
  9. neighbors — unvisited locations adjacent to here

Variable meanings in function display:

  1. m — maze to be drawn
  2. text — lines of text representing maze
  3. line — characters of current line

Note that this implementation relies on javascript arrays being treatable as infinite in size with false (null) values springing into existence as needed, to support referenced array locations. (This significantly reduces the bulk of the necessary initialization code.)

Example use:
<html><head><title></title></head><body><pre id="out"></pre></body></html>
<script type="text/javascript">
/* ABOVE CODE GOES HERE */
document.getElementById('out').innerHTML= display(maze(8,11)); 
</script>

produced output:

+   +---+---+---+---+---+---+---+---+---+---+
|                   |                   |   |
+---+---+   +   +---+   +   +---+---+   +   +
|       |   |   |       |   |           |   |
+   +   +   +---+   +---+   +---+---+   +   +
|   |   |               |           |   |   |
+   +---+   +---+---+---+---+---+   +   +   +
|       |   |               |       |       |
+---+   +---+   +---+---+   +   +---+---+   +
|   |   |       |               |       |   |
+   +   +   +---+---+---+---+---+   +   +   +
|       |                   |       |   |   |
+   +---+---+   +---+---+   +   +---+---+   +
|   |       |   |           |       |       |
+   +   +   +---+   +---+---+   +   +   +---+
|       |           |           |            
+---+---+---+---+---+---+---+---+---+---+---+

For an animated presentation of the progress of this maze creation process, you can use display in each iteration of the main loop. You would also need to take steps to make sure you could see each intermediate result.

For example, change replace the line while (0<n) { with:

	function step() {
		if (0<n) {

And replace the closing brace for this while loop with:

			document.getElementById('out').innerHTML= display({x: x, y: y, horiz: horiz, verti: verti, here: here});
			setTimeout(step, 100);
		}
	}
	step();

To better see the progress, you might want a marker in place, showing the position being considered. To do that, replace the line which reads if (0 == k%4) { with

				if (m.here && m.here[0]*2+1 == j && m.here[1]*4+2 == k) 
					line[k]= '#'
				else if (0 == k%4) {

Note however that this leaves the final '#' in place on maze completion, and that the function maze no longer returns a result which represents a generated maze.

Note also that this display suggests an optimization. You can replace the line reading path.push(here= next); with:

			here= next;
			if (1 < neighbors.length) 
				path.push(here);

And this does indeed save a negligible bit of processing, but the maze algorithm will still be forced to backtrack through a number of locations which have no unvisited neighbors.

HTML Table[edit]

Using HTML, CSS and table cells for maze.

<html><head><title>Maze maker</title>
<style type="text/css">
table { border-collapse: collapse }
td { width: 1em; height: 1em; border: 1px solid }
td.s { border-bottom: none }
td.n { border-top: none }
td.w { border-left: none }
td.e { border-right: none }
td.v { background: skyblue}
</style>
<script type="application/javascript">
Node.prototype.add = function(tag, cnt, txt) {
	for (var i = 0; i < cnt; i++)
		this.appendChild(ce(tag, txt));
}
Node.prototype.ins = function(tag) {
	this.insertBefore(ce(tag), this.firstChild)
}
Node.prototype.kid = function(i) { return this.childNodes[i] }
Node.prototype.cls = function(t) { this.className += ' ' + t }

NodeList.prototype.map = function(g) {
	for (var i = 0; i < this.length; i++) g(this[i]);
}

function ce(tag, txt) {
	var x = document.createElement(tag);
	if (txt !== undefined) x.innerHTML = txt;
	return x
}

function gid(e) { return document.getElementById(e) }
function irand(x) { return Math.floor(Math.random() * x) }

function make_maze() {
	var w = parseInt(gid('rows').value || 8, 10);
	var h = parseInt(gid('cols').value || 8, 10);
	var tbl = gid('maze');
	tbl.innerHTML = '';
	tbl.add('tr', h);
	tbl.childNodes.map(function(x) {
			x.add('th', 1);
			x.add('td', w, '*');
			x.add('th', 1)});
	tbl.ins('tr');
	tbl.add('tr', 1);
	tbl.firstChild.add('th', w + 2);
	tbl.lastChild.add('th', w + 2);
	for (var i = 1; i <= h; i++) {
		for (var j = 1; j <= w; j++) {
			tbl.kid(i).kid(j).neighbors = [
				tbl.kid(i + 1).kid(j),
				tbl.kid(i).kid(j + 1),
				tbl.kid(i).kid(j - 1),
				tbl.kid(i - 1).kid(j)
			];
		}
	}
	walk(tbl.kid(irand(h) + 1).kid(irand(w) + 1));
	gid('solve').style.display='inline';
}

function shuffle(x) {
	for (var i = 3; i > 0; i--) {
		j = irand(i + 1);
		if (j == i) continue;
		var t = x[j]; x[j] = x[i]; x[i] = t;
	}
	return x;
}

var dirs = ['s', 'e', 'w', 'n'];
function walk(c) {
	c.innerHTML = '&nbsp;';
	var idx = shuffle([0, 1, 2, 3]);
	for (var j = 0; j < 4; j++) {
		var i = idx[j];
		var x = c.neighbors[i];
		if (x.textContent != '*') continue;
		c.cls(dirs[i]), x.cls(dirs[3 - i]);
		walk(x);
	}
}

function solve(c, t) {
	if (c === undefined) {
		c = gid('maze').kid(1).kid(1);
		c.cls('v');
	}
	if (t === undefined)
		t = gid('maze')	.lastChild.previousSibling
				.lastChild.previousSibling;

	if (c === t) return 1;
	c.vis = 1;
	for (var i = 0; i < 4; i++) {
		var x = c.neighbors[i];
		if (x.tagName.toLowerCase() == 'th') continue;
		if (x.vis || !c.className.match(dirs[i]) || !solve(x, t))
			continue;

		x.cls('v');
		return 1;
	}
	c.vis = null;
	return 0;
}

</script></head>
<body><form><fieldset>
<label>rows </label><input id='rows' size="3"/>
<label>colums </label><input id='cols' size="3"/>
<a href="javascript:make_maze()">Generate</a>
<a id='solve' style='display:none' href='javascript:solve(); void(0)'>Solve</a>
</fieldset></form><table id='maze'/></body></html>

Julia[edit]

Works with: Julia version >0.6

Generating functions

using Random
check(bound::Vector) = cell -> all([1, 1] .≤ cell .≤ bound)
neighbors(cell::Vector, bound::Vector, step::Int=2) =
    filter(check(bound), map(dir -> cell + step * dir, [[0, 1], [-1, 0], [0, -1], [1, 0]]))

function walk(maze::Matrix, nxtcell::Vector, visited::Vector=[])
    push!(visited, nxtcell)
    for neigh in shuffle(neighbors(nxtcell, collect(size(maze))))
        if neigh  visited
            maze[round.(Int, (nxtcell + neigh) / 2)...] = 0
            walk(maze, neigh, visited)
        end
    end
    maze
end
function maze(w::Int, h::Int)
    maze = collect(i % 2 | j % 2 for i in 1:2w+1, j in 1:2h+1)
    firstcell = 2 * [rand(1:w), rand(1:h)]
    return walk(maze, firstcell)
end

Printing functions

pprint(matrix) = for i = 1:size(matrix, 1) println(join(matrix[i, :])) end
function printmaze(maze)
    walls = split("╹ ╸ ┛ ╺ ┗ ━ ┻ ╻ ┃ ┓ ┫ ┏ ┣ ┳ ╋")
    h, w = size(maze)
    f = cell -> 2 ^ ((3cell[1] + cell[2] + 3) / 2)
    wall(i, j) = if maze[i,j] == 0 " " else
        walls[Int(sum(f, filter(x -> maze[x...] != 0, neighbors([i, j], [h, w], 1)) .- [[i, j]]))]
    end
    mazewalls = collect(wall(i, j) for i in 1:2:h, j in 1:w)
    pprint(mazewalls)
end

printmaze(maze(10, 10))
Output:
┏━━━━━┳━━━━━┳━━━━━━━┓
┃ ╻ ╻ ┃ ╺━┓ ╹ ┏━━━┓ ┃
┣━┛ ┃ ┗━┓ ┗━━━┛ ╻ ┃ ┃
┃ ╺━┻━┓ ┃ ╺━┳━━━┛ ┃ ┃
┃ ╺━┓ ┃ ┗━━━┛ ┏━━━┛ ┃
┣━━━┛ ┣━━━━━┳━┛ ┏━━━┫
┃ ┏━━━┛ ┏━╸ ┃ ╺━┛ ╻ ┃
┣━┛ ┏━━━┛ ╻ ┣━━━━━┛ ┃
┃ ┏━┛ ┏━━━┻━┛ ┏━━━┳━┫
┃ ┃ ╺━┛ ╺━━━━━┛ ╻ ╹ ┃
┗━┻━━━━━━━━━━━━━┻━━━┛

Kotlin[edit]

Translation of: Java
import java.util.*

class MazeGenerator(val x: Int, val y: Int) {
    private val maze = Array(x) { IntArray(y) }

    fun generate(cx: Int, cy: Int) {
        Direction.values().shuffle().forEach {
            val nx = cx + it.dx
            val ny = cy + it.dy
            if (between(nx, x) && between(ny, y) && maze[nx][ny] == 0) {
                maze[cx][cy] = maze[cx][cy] or it.bit
                maze[nx][ny] = maze[nx][ny] or it.opposite!!.bit
                generate(nx, ny)
            }
        }
    }

    fun display() {
        for (i in 0..y - 1) {
            // draw the north edge
            for (j in 0..x - 1)
                print(if (maze[j][i] and 1 == 0) "+---" else "+   ")
            println('+')

            // draw the west edge
            for (j in 0..x - 1)
                print(if (maze[j][i] and 8 == 0) "|   " else "    ")
            println('|')
        }

        // draw the bottom line
        for (j in 0..x - 1) print("+---")
        println('+')
    }

    inline private fun <reified T> Array<T>.shuffle(): Array<T> {
        val list = toMutableList()
        Collections.shuffle(list)
        return list.toTypedArray()
    }

    private enum class Direction(val bit: Int, val dx: Int, val dy: Int) {
        N(1, 0, -1), S(2, 0, 1), E(4, 1, 0),W(8, -1, 0);

        var opposite: Direction? = null

        companion object {
            init {
                N.opposite = S
                S.opposite = N
                E.opposite = W
                W.opposite = E
            }
        }
    }

    private fun between(v: Int, upper: Int) = v >= 0 && v < upper
}

fun main(args: Array<String>) {
    val x = if (args.size >= 1) args[0].toInt() else 8
    val y = if (args.size == 2) args[1].toInt() else 8
    with(MazeGenerator(x, y)) {
        generate(0, 0)
        display()
    }
}

Lua[edit]

Works with: Lua version 5.1
math.randomseed( os.time() )

-- Fisher-Yates shuffle from http://santos.nfshost.com/shuffling.html
function shuffle(t)
  for i = 1, #t - 1 do
    local r = math.random(i, #t)
    t[i], t[r] = t[r], t[i]
  end
end

-- builds a width-by-height grid of trues
function initialize_grid(w, h)
  local a = {}
  for i = 1, h do
    table.insert(a, {})
    for j = 1, w do
      table.insert(a[i], true)
    end
  end
  return a
end

-- average of a and b
function avg(a, b)
  return (a + b) / 2
end


dirs = {
  {x = 0, y = -2}, -- north
  {x = 2, y = 0}, -- east
  {x = -2, y = 0}, -- west
  {x = 0, y = 2}, -- south
}

function make_maze(w, h)
  w = w or 16
  h = h or 8

  local map = initialize_grid(w*2+1, h*2+1)

  function walk(x, y)
    map[y][x] = false

    local d = { 1, 2, 3, 4 }
    shuffle(d)
    for i, dirnum in ipairs(d) do
      local xx = x + dirs[dirnum].x
      local yy = y + dirs[dirnum].y
      if map[yy] and map[yy][xx] then
        map[avg(y, yy)][avg(x, xx)] = false
        walk(xx, yy)
      end
    end
  end

  walk(math.random(1, w)*2, math.random(1, h)*2)

  local s = {}
  for i = 1, h*2+1 do
    for j = 1, w*2+1 do
      if map[i][j] then
        table.insert(s, '#')
      else
        table.insert(s, ' ')
      end
    end
    table.insert(s, '\n')
  end
  return table.concat(s)
end

print(make_maze())
Output:
#################################
# #     # #         #         # #
# # ### # # ### ##### # ##### # #
# # # # #     #       # #   #   #
# # # # ########### ### # # #####
#   # #     #     # # #   #     #
# ### ##### # ### # # ####### # #
# #     # # # # # #       # # # #
# # ### # # # # # ######### ### #
# #   #   # #   #   #       #   #
# ### ### # ### ### # ####### # #
# #   # # #     # #   #   #   # #
# # ### # ####### ##### # # ### #
# #   # #       #   #   # # # # #
# ### # ####### # # # ### # # # #
#     #           #   #     #   #
#################################

M2000 Interpreter[edit]

Random Generation[edit]

Translation of: BASIC

For Next is not the same as basic. In M2000 always a loop perform once. Step converted to absolute value if start<>end. To go down we have to place start>end. If start=end then the value after the loop is equal to start+step and here step used as is (with no conversion to absolute value).

We can use the for loop as in basic using a software swit