Sudoku

From Rosetta Code
Task
Sudoku
You are encouraged to solve this task according to the task description, using any language you may know.

Solve a partially filled-in normal 9x9 Sudoku grid and display the result in a human-readable format. Algorithmics of Sudoku may help implement this.

Ada

<lang Ada>with Ada.Text_IO; procedure Sudoku is

  subtype Number is Natural range 0 .. 9;
  subtype Valid_Number is Number range 1 .. 9;
  type Board is array (Valid_Number, Valid_Number) of Number;
  function Check_Row (Data : in Board; Row : in Valid_Number) return Boolean is
     Seen       : array (Valid_Number) of Boolean := (others => False);
     The_Number : Number;
  begin
     for Column in Data'Range (2) loop
        The_Number := Data (Row, Column);
        if The_Number in Valid_Number then
           if Seen (The_Number) then
              return False;
           end if;
           Seen (The_Number) := True;
        end if;
     end loop;
     return True;
  end Check_Row;
  function Check_Column (Data : in Board; Column : in Valid_Number) return Boolean is
     Seen       : array (Valid_Number) of Boolean := (others => False);
     The_Number : Number;
  begin
     for Row in Data'Range (1) loop
        The_Number := Data (Row, Column);
        if The_Number in Valid_Number then
           if Seen (The_Number) then
              return False;
           end if;
           Seen (The_Number) := True;
        end if;
     end loop;
     return True;
  end Check_Column;
  function Check_Square (Data : in Board; Row, Column : in Valid_Number) return Boolean is
     Seen          : array (Valid_Number) of Boolean := (others => False);
     The_Number    : Number;
     Row_Offset    : constant Number := ((Row - 1) / 3) * 3;
     Column_Offset : constant Number := ((Column - 1) / 3) * 3;
  begin
     for Sub_Row in 1 .. 3 loop
        for Sub_Column in 1 .. 3 loop
           The_Number := Data (Row_Offset + Sub_Row, Column_Offset + Sub_Column);
           if The_Number in Valid_Number then
              if Seen (The_Number) then
                 return False;
              end if;
              Seen (The_Number) := True;
           end if;
        end loop;
     end loop;
     return True;
  end Check_Square;
  function Is_Valid (Data : in Board) return Boolean is
     Result : Boolean := True;
  begin
     for Row in Data'Range (1) loop
        Result := Result and Check_Row (Data, Row);
     end loop;
     for Column in Data'Range (2) loop
        Result := Result and Check_Column (Data, Column);
     end loop;
     for Square_Row in 1 .. 3 loop
        for Square_Column in 1 .. 3 loop
           Result := Result and Check_Square (Data, Square_Row * 3, Square_Column * 3);
        end loop;
     end loop;
     return Result;
  end Is_Valid;
  Unsolvable : Exception;
  procedure Solve (Data : in out Board) is
     Solved : Boolean := False;
     -- Try all possible values for given cell and continue with next cell.
     procedure Place_Number (Row, Column : Valid_Number) is
        Next_Row    : Valid_Number := Row;
        Next_Column : Valid_Number := Column;
        Last        : Boolean := False;
     begin
        -- determine if this is the last cell or else the next cell coordinates
        if Row = Data'Last (1) and then Column = Data'Last (2) then
           Last := True;
        elsif Row = Data'Last (1) then
           Next_Row := Data'First (1);
           Next_Column := Column + 1;
        else
           Next_Row := Row + 1;
        end if;
        -- only need to try values for nonvalid cell entries (0)
        if Data (Row, Column) not in Valid_Number then
           -- try all possible values
           for Test in Valid_Number loop
              -- set the cell
              Data (Row, Column) := Test;
              if Is_Valid (Data) then
                 -- the last cell was processed and lead to a valid sudoku
                 -- this means all cells have valid entries -> solved.
                 if Last then
                    Solved := True;
                    return;
                 else
                    -- try next cells
                    Place_Number (Next_Row, Next_Column);
                    -- if we have a solved sudoku, exit procedure.
                    if Solved then
                       return;
                    end if;
                 end if;
              end if;
              -- reset the cell, it will be tried later again
              Data (Row, Column) := 0;
           end loop;
        elsif Last then
           -- last cell, already valid, it is solved and there is nothing to do
           Solved := True;
        else
           -- this cell already has a value, continue to next
           Place_Number (Next_Row, Next_Column);
        end if;
     end Place_Number;
  begin
     -- only accept sudokus without inconsistencies
     if not Is_Valid (Data) then
        raise Constraint_Error;
     end if;
     -- start with first cell
     Place_Number (Data'First (1), Data'First (2));
     -- tried all combinations without success -> unsolvable.
     if not Solved then
        raise Unsolvable;
     end if;
  end Solve;
  procedure Print_Board (Data : in Board) is
     package Number_IO is new Ada.Text_IO.Integer_IO (Number);
  begin
     for X in Data'Range (1) loop
        for Y in Data'Range (2) loop
           Number_IO.Put (Data (X, Y));
        end loop;
        Ada.Text_IO.New_Line;
     end loop;
  end Print_Board;
  Sample_Board : Board := (1 => (3, 9, 4, 0, 0, 2, 6, 7, 0),
                           2 => (0, 0, 0, 3, 0, 0, 4, 0, 0),
                           3 => (5, 0, 0, 6, 9, 0, 0, 2, 0),
                           4 => (0, 4, 5, 0, 0, 0, 9, 0, 0),
                           5 => (6, 0, 0, 0, 0, 0, 0, 0, 7),
                           6 => (0, 0, 7, 0, 0, 0, 5, 8, 0),
                           7 => (0, 1, 0, 0, 6, 7, 0, 0, 8),
                           8 => (0, 0, 9, 0, 0, 8, 0, 0, 0),
                           9 => (0, 2, 6, 4, 0, 0, 7, 3, 5));

begin

  Ada.Text_IO.Put_Line ("Unsolved:");
  Print_Board (Sample_Board);
  Solve (Sample_Board);
  Ada.Text_IO.Put_Line ("Solved:");
  Print_Board (Sample_Board);

end Sudoku;</lang> Output:

Unsolved:
 3 9 4 0 0 2 6 7 0
 0 0 0 3 0 0 4 0 0
 5 0 0 6 9 0 0 2 0
 0 4 5 0 0 0 9 0 0
 6 0 0 0 0 0 0 0 7
 0 0 7 0 0 0 5 8 0
 0 1 0 0 6 7 0 0 8
 0 0 9 0 0 8 0 0 0
 0 2 6 4 0 0 7 3 5
Solved:
 3 9 4 8 5 2 6 7 1
 2 6 8 3 7 1 4 5 9
 5 7 1 6 9 4 8 2 3
 1 4 5 7 8 3 9 6 2
 6 8 2 9 4 5 3 1 7
 9 3 7 1 2 6 5 8 4
 4 1 3 5 6 7 2 9 8
 7 5 9 2 3 8 1 4 6
 8 2 6 4 1 9 7 3 5

ALGOL 68

Translation of: D

Note: This specimen retains the original D coding style.

Works with: ALGOL 68 version Revision 1 - no extensions to language used.
Works with: ALGOL 68G version Any - tested with release 1.18.0-9h.tiny.

<lang algol68>MODE AVAIL = [9]BOOL; MODE BOX = [3, 3]CHAR;

FORMAT row fmt = $"|"3(" "3(g" ")"|")l$; FORMAT line = $"+"3(7"-","+")l$; FORMAT puzzle fmt = $f(line)3(3(f(row fmt))f(line))$;

AVAIL gen full = (TRUE, TRUE, TRUE, TRUE, TRUE, TRUE, TRUE, TRUE, TRUE);

OP REPR = (AVAIL avail)STRING: (

 STRING out := "";
 FOR i FROM LWB avail TO UPB avail DO
   IF avail[i] THEN out +:= REPR(ABS "0" + i) FI
 OD;
 out

);

CHAR empty = "_";

OP -:= = (REF AVAIL set, CHAR index)VOID: (

 set[ABS index - ABS "0"]:=FALSE

);

  1. these two functions assume that the number has not already been found #

PROC avail slice = (REF[]CHAR slice, REF AVAIL available)REF AVAIL:(

       FOR ele FROM LWB slice TO UPB slice DO
               IF slice[ele] /= empty THEN available-:=slice[ele] FI
       OD;
       available

);

PROC avail box = (INT x, y, REF AVAIL available)REF AVAIL:(

       #  x designates row, y designates column #
       #  get a base index for the boxes #
       INT bx := x - (x-1) MOD 3;
       INT by := y - (y-1) MOD 3;
       REF BOX box = puzzle[bx:bx+2, by:by+2];
       FOR i FROM LWB box TO UPB box DO
         FOR j FROM 2 LWB box TO 2 UPB box DO
               IF box[i, j] /= empty THEN available-:=box[i, j] FI
         OD
       OD;
       available

);

[9, 9]CHAR puzzle; PROC solve = ([,]CHAR in puzzle)VOID:(

       puzzle := in puzzle;
       TO UPB puzzle UP 2 DO
               BOOL done := TRUE;
               FOR i FROM LWB puzzle TO UPB puzzle DO
                 FOR j FROM 2 LWB puzzle TO 2 UPB puzzle DO 
                   CHAR ele := puzzle[i, j];
                   IF ele = empty THEN
                       #  poke at the elements that are "_" #
                       AVAIL remaining := avail box(i, j, 
                                          avail slice(puzzle[i, ], 
                                          avail slice(puzzle[, j], 
                                          LOC AVAIL := gen full)));
                       STRING s = REPR remaining;
                       IF UPB s = 1 THEN puzzle[i, j] := s[LWB s]
                       ELSE done := FALSE
                       FI
                   FI
                 OD
               OD;
               IF done THEN break FI
       OD;

break:

       #  write out completed puzzle #
       printf(($gl$, "Completed puzzle:"));
       printf((puzzle fmt, puzzle))

); main:(

  solve(("394__267_",
         "___3__4__",
         "5__69__2_",
         "_45___9__",
         "6_______7",
         "__7___58_",
         "_1__67__8",
         "__9__8___",
         "_264__735"))

CO # note: This codes/algorithm does not [yet] solve: #

  solve(("9__2__5__",
         "_4__6__3_",
         "__3_____6",
         "___9__2__",
         "____5__8_",
         "__7__4__3",
         "7_____1__",
         "_5__2__4_",
         "__1__6__9"))

END CO )</lang> Output:

Completed puzzle:
+-------+-------+-------+
| 3 9 4 | 8 5 2 | 6 7 1 |
| 2 6 8 | 3 7 1 | 4 5 9 |
| 5 7 1 | 6 9 4 | 8 2 3 |
+-------+-------+-------+
| 1 4 5 | 7 8 3 | 9 6 2 |
| 6 8 2 | 9 4 5 | 3 1 7 |
| 9 3 7 | 1 2 6 | 5 8 4 |
+-------+-------+-------+
| 4 1 3 | 5 6 7 | 2 9 8 |
| 7 5 9 | 2 3 8 | 1 4 6 |
| 8 2 6 | 4 1 9 | 7 3 5 |
+-------+-------+-------+

AutoHotkey

<lang AutoHotkey>#SingleInstance, Force SetBatchLines, -1 SetTitleMatchMode, 3

   Loop 9 {
      r := A_Index, y := r*17-8 + (A_Index >= 7 ? 4 : A_Index >= 4 ? 2 : 0)
      Loop 9 {
         c := A_Index, x := c*17+5 + (A_Index >= 7 ? 4 : A_Index >= 4 ? 2 : 0)
         Gui, Add, Edit, x%x% y%y% w17 h17 v%r%_%c% Center Number Limit1 gNext
      }
   }
   Gui, Add, Button, vButton gSolve w175 x10 Center, Solve
   Gui, Add, Text, vMsg r3, Enter Sudoku puzzle and click Solve
   Gui, Show,, Sudoku Solver

Return

Solve:

   Gui, Submit, NoHide
   Loop 9
   {
      r := A_Index
      Loop 9
         If (%r%_%A_Index% = "")
            puzzle .= "@"
         Else
            puzzle .= %r%_%A_Index%
   }
   s := A_TickCount
   answer := Sudoku(puzzle)
   iterations := ErrorLevel
   e := A_TickCount
   seconds := (e-s)/1000
   StringSplit, a, answer, |
   Loop 9
   {
      r := A_Index
      Loop 9
      {
         b := (r*9)+A_Index-9
         GuiControl,, %r%_%A_Index%, % a%b%
         GuiControl, +ReadOnly, %r%_%A_Index%
       }
   }
   if answer
       GuiControl,, Msg, Solved!`nTime: %seconds%s`nIterations: %iterations%
   else
       GuiControl,, Msg, Failed! :(`nTime: %seconds%s`nIterations: %iterations%
   GuiControl,, Button, Again!
   GuiControl, +gAgain, Button

return

GuiClose:

   ExitApp

Again:

   Reload
  1. IfWinActive, Sudoku Solver

~*Enter::GoSub % GetKeyState( "Shift", "P" ) ? "~Up" : "~Down" ~Up::

   GuiControlGet, f, focus
   StringTrimLeft, f, f, 4
   f := ((f >= 1 && f <= 9) ? f+72 : f-9)
   GuiControl, Focus, Edit%f%

return ~Down::

   GuiControlGet, f, focus
   StringTrimLeft, f, f, 4
   f := ((f >= 73 && f <= 81) ? f-72 : f + 9)
   GuiControl, Focus, Edit%f%

return ~Left::

   GuiControlGet, f, focus
   StringTrimLeft, f, f, 4
   f := Mod(f + 79, 81) + 1
   GuiControl, Focus, Edit%f%

return Next: ~Right::

   GuiControlGet, f, focus
   StringTrimLeft, f, f, 4
   f := Mod(f, 81) + 1
   GuiControl, Focus, Edit%f%

return

  1. IfWinActive
Functions Start here

Sudoku( p ) { ;ErrorLevel contains the number of iterations

  p := RegExReplace(p, "[^1-9@]"), ErrorLevel := 0 ;format puzzle as single line string
  return Sudoku_Display(Sudoku_Solve(p))

}

Sudoku_Solve( p, d = 0 ) { ;d is 0-based

http://www.autohotkey.com/forum/topic46679.html
p
81 character puzzle string
(concat all 9 rows of 9 chars each)
givens represented as chars 1-9
fill-ins as any non-null, non 1-9 char
d
used internally. omit on initial call
returns
81 char string with non-givens replaced with valid solution
  If (d >= 81), ErrorLevel++
     return p  ;this is 82nd iteration, so it has successfully finished iteration 81
  If InStr( "123456789", SubStr(p, d+1, 1) ) ;this depth is a given, skip through
     return Sudoku_Solve(p, d+1)
  m := Sudoku_Constraints(p,d) ;a string of this level's constraints. 
  ; (these will not change for all 9 loops)
  Loop 9
  {
     If InStr(m, A_Index)
        Continue
     NumPut(Asc(A_Index), p, d, "Char")
     If r := Sudoku_Solve(p, d+1)
        return r
  }
  return 0

}

Sudoku_Constraints( ByRef p, d ) {

returns a string of the constraints for a particular position
    c := Mod(d,9)
  , r := (d - c) // 9
  , b := r//3*27 + c//3*3 + 1
  ;convert to 1-based
  , c++
  return ""
  ; row:
     . SubStr(p, r * 9 + 1, 9)
  ; column: 
     . SubStr(p,c   ,1) SubStr(p,c+9 ,1) SubStr(p,c+18,1)
     . SubStr(p,c+27,1) SubStr(p,c+36,1) SubStr(p,c+45,1)
     . SubStr(p,c+54,1) SubStr(p,c+63,1) SubStr(p,c+72,1)
  ;box
     . SubStr(p, b, 3) SubStr(p, b+9, 3) SubStr(p, b+18, 3) 

}

Sudoku_Display( p ) {

  If StrLen(p) = 81
     loop 81
        r .= SubStr(p, A_Index, 1) . "|"
  return r

}</lang>

BBC BASIC

<lang bbcbasic> VDU 23,22,453;453;8,20,16,128

     *FONT Arial,28
     
     DIM Board%(8,8)
     Board%() = %111111111
     
     FOR L% = 0 TO 9:P% = L%*100
       LINE 2,P%+2,902,P%+2
       IF (L% MOD 3)=0 LINE 2,P%,902,P% : LINE 2,P%+4,902,P%+4
       LINE P%+2,2,P%+2,902
       IF (L% MOD 3)=0 LINE P%,2,P%,902 : LINE P%+4,2,P%+4,902
     NEXT
     
     DATA "  4 5  6 "
     DATA " 6 1  8 9"
     DATA "3    7   "
     DATA " 8    5  "
     DATA "   4 3   "
     DATA "  6    7 "
     DATA "   2    6"
     DATA "1 5  4 3 "
     DATA " 2  7 1  "
     
     FOR R% = 8 TO 0 STEP -1
       READ A$
       FOR C% = 0 TO 8
         A% = ASCMID$(A$,C%+1) AND 15
         IF A% Board%(R%,C%) = 1 << (A%-1)
       NEXT
     NEXT R%
     
     GCOL 4
     PROCshow
     WAIT 200
     dummy% = FNsolve(Board%(), TRUE)
     GCOL 2
     PROCshow
     REPEAT WAIT 1 : UNTIL FALSE
     END
     
     DEF PROCshow
     LOCAL C%,P%,R%
     FOR C% = 0 TO 8
       FOR R% = 0 TO 8
         P% = Board%(R%,C%)
         IF (P% AND (P%-1)) = 0 THEN
           IF P% P% = LOGP%/LOG2+1.5
           MOVE C%*100+30,R%*100+90
           VDU 5,P%+48,4
         ENDIF
       NEXT
     NEXT
     ENDPROC
     
     DEF FNsolve(P%(),F%)
     LOCAL C%,D%,M%,N%,R%,X%,Y%,Q%()
     DIM Q%(8,8)
     REPEAT
       Q%() = P%()
       FOR R% = 0 TO 8
         FOR C% = 0 TO 8
           D% = P%(R%,C%)
           IF (D% AND (D%-1))=0 THEN
             M% = NOT D%
             FOR X% = 0 TO 8
               IF X%<>C% P%(R%,X%) AND= M%
               IF X%<>R% P%(X%,C%) AND= M%
             NEXT
             FOR X% = C%DIV3*3 TO C%DIV3*3+2
               FOR Y% = R%DIV3*3 TO R%DIV3*3+2
                 IF X%<>C% IF Y%<>R% P%(Y%,X%) AND= M%
               NEXT
             NEXT
           ENDIF
         NEXT
       NEXT
       Q%() -= P%()
     UNTIL SUMQ%()=0
     M% = 10
     FOR R% = 0 TO 8
       FOR C% = 0 TO 8
         D% = P%(R%,C%)
         IF D%=0 M% = 0
         IF D% AND (D%-1) THEN
           N% = 0
           REPEAT N% += D% AND 1
             D% DIV= 2
           UNTIL D% = 0
           IF N%<M% M% = N% : X% = C% : Y% = R%
         ENDIF
       NEXT
     NEXT
     IF M%=0 THEN = 0
     IF M%=10 THEN = 1
     D% = 0
     FOR M% = 0 TO 8
       IF P%(Y%,X%) AND (2^M%) THEN
         Q%() = P%()
         Q%(Y%,X%) = 2^M%
         C% = FNsolve(Q%(),F%)
         D% += C%
         IF C% IF F% P%() = Q%() : = D%
       ENDIF
     NEXT
     = D%</lang>

BCPL

<lang BCPL>// This can be run using Cintcode BCPL freely available from www.cl.cam.ac.uk/users/mr10.

// This is a really naive program to solve Su Doku problems. Even so it is usually quite fast.

// SuDoku consists of a 9x9 grid of cells. Each cell should contain // a digit in the range 1..9. Every row, column and major 3x3 // square should contain all the digits 1..9. Some cells have // given values. The problem is to find digits to place in // the unspecified cells satisfying the constraints.

// A typical problem is:

// - - - 6 3 8 - - - // 7 - 6 - - - 3 - 5 // - 1 - - - - - 4 -

// - - 8 7 1 2 4 - - // - 9 - - - - - 5 - // - - 2 5 6 9 1 - -

// - 3 - - - - - 1 - // 1 - 5 - - - 6 - 8 // - - - 1 8 4 - - -

SECTION "sudoku"

GET "libhdr"

GLOBAL { count:ug

// The 9x9 board

a1; a2; a3; a4; a5; a6; a7; a8; a9 b1; b2; b3; b4; b5; b6; b7; b8; b9 c1; c2; c3; c4; c5; c6; c7; c8; c9 d1; d2; d3; d4; d5; d6; d7; d8; d9 e1; e2; e3; e4; e5; e6; e7; e8; e9 f1; f2; f3; f4; f5; f6; f7; f8; f9 g1; g2; g3; g4; g5; g6; g7; g8; g9 h1; h2; h3; h4; h5; h6; h7; h8; h9 i1; i2; i3; i4; i5; i6; i7; i8; i9 }

MANIFEST { N1=1<<0; N2=1<<1; N3=1<<2; N4=1<<3; N5=1<<4; N6=1<<5; N7=1<<6; N8=1<<7; N9=1<<8 }

LET start() = VALOF { count := 0

 initboard()
 prboard()
 ta1()
 writef("*n*nTotal number of solutions: %n*n", count)
 RESULTIS 0

}

AND initboard() BE { a1, a2, a3, a4, a5, a6, a7, a8, a9 := 0, 0, 0, N6,N3,N8, 0, 0, 0 b1, b2, b3, b4, b5, b6, b7, b8, b9 := N7, 0,N6, 0, 0, 0, N3, 0,N5 c1, c2, c3, c4, c5, c6, c7, c8, c9 := 0,N1, 0, 0, 0, 0, 0,N4, 0 d1, d2, d3, d4, d5, d6, d7, d8, d9 := 0, 0,N8, N7,N1,N2, N4, 0, 0 e1, e2, e3, e4, e5, e6, e7, e8, e9 := 0,N9, 0, 0, 0, 0, 0,N5, 0 f1, f2, f3, f4, f5, f6, f7, f8, f9 := 0, 0,N2, N5,N6,N9, N1, 0, 0 g1, g2, g3, g4, g5, g6, g7, g8, g9 := 0,N3, 0, 0, 0, 0, 0,N1, 0 h1, h2, h3, h4, h5, h6, h7, h8, h9 := N1, 0,N5, 0, 0, 0, N6, 0,N8 i1, i2, i3, i4, i5, i6, i7, i8, i9 := 0, 0, 0, N1,N8,N4, 0, 0, 0

// Un-comment the following to test that the backtracking works // giving 184 solutions. //h1, h2, h3, h4, h5, h6, h7, h8, h9 := N1, 0,N5, 0, 0, 0, N6, 0, 0 //i1, i2, i3, i4, i5, i6, i7, i8, i9 := 0, 0, 0, 0, 0, 0, 0, 0, 0 }

AND c(n) = VALOF SWITCHON n INTO { DEFAULT: RESULTIS '?'

 CASE  0:    RESULTIS '-'
 CASE N1:    RESULTIS '1'
 CASE N2:    RESULTIS '2'
 CASE N3:    RESULTIS '3'
 CASE N4:    RESULTIS '4'
 CASE N5:    RESULTIS '5'
 CASE N6:    RESULTIS '6'
 CASE N7:    RESULTIS '7'
 CASE N8:    RESULTIS '8'
 CASE N9:    RESULTIS '9'

}

AND prboard() BE { LET form = "%c %c %c %c %c %c %c %c %c*n"

 writef("*ncount = %n*n", count)
 newline()
 writef(form, c(a1),c(a2),c(a3),c(a4),c(a5),c(a6),c(a7),c(a8),c(a9))
 writef(form, c(b1),c(b2),c(b3),c(b4),c(b5),c(b6),c(b7),c(b8),c(b9))
 writef(form, c(c1),c(c2),c(c3),c(c4),c(c5),c(c6),c(c7),c(c8),c(c9))
 newline()
 writef(form, c(d1),c(d2),c(d3),c(d4),c(d5),c(d6),c(d7),c(d8),c(d9))
 writef(form, c(e1),c(e2),c(e3),c(e4),c(e5),c(e6),c(e7),c(e8),c(e9))
 writef(form, c(f1),c(f2),c(f3),c(f4),c(f5),c(f6),c(f7),c(f8),c(f9))
 newline()
 writef(form, c(g1),c(g2),c(g3),c(g4),c(g5),c(g6),c(g7),c(g8),c(g9))
 writef(form, c(h1),c(h2),c(h3),c(h4),c(h5),c(h6),c(h7),c(h8),c(h9))
 writef(form, c(i1),c(i2),c(i3),c(i4),c(i5),c(i6),c(i7),c(i8),c(i9))
 newline()

//abort(1000) }

AND try(p, f, row, col, sq) BE { LET x = !p

 TEST x
 THEN f()
 ELSE { LET bits = row|col|sq

//prboard() // writef("x=%n %b9*n", x, bits) //abort(1000)

        IF (N1&bits)=0 DO { !p:=N1; f() }
        IF (N2&bits)=0 DO { !p:=N2; f() }
        IF (N3&bits)=0 DO { !p:=N3; f() }
        IF (N4&bits)=0 DO { !p:=N4; f() }
        IF (N5&bits)=0 DO { !p:=N5; f() }
        IF (N6&bits)=0 DO { !p:=N6; f() }
        IF (N7&bits)=0 DO { !p:=N7; f() }
        IF (N8&bits)=0 DO { !p:=N8; f() }
        IF (N9&bits)=0 DO { !p:=N9; f() }
        !p := 0
      }

}

AND ta1() BE try(@a1, ta2, a1+a2+a3+a4+a5+a6+a7+a8+a9,

                          a1+b1+c1+d1+e1+f1+g1+h1+i1,
                          a1+a2+a3+b1+b2+b3+c1+c2+c3)

AND ta2() BE try(@a2, ta3, a1+a2+a3+a4+a5+a6+a7+a8+a9,

                          a2+b2+c2+d2+e2+f2+g2+h2+i2,
                          a1+a2+a3+b1+b2+b3+c1+c2+c3)

AND ta3() BE try(@a3, ta4, a1+a2+a3+a4+a5+a6+a7+a8+a9,

                          a3+b3+c3+d3+e3+f3+g3+h3+i3,
                          a1+a2+a3+b1+b2+b3+c1+c2+c3)

AND ta4() BE try(@a4, ta5, a1+a2+a3+a4+a5+a6+a7+a8+a9,

                          a4+b4+c4+d4+e4+f4+g4+h4+i4,
                          a4+a5+a6+b4+b5+b6+c4+c5+c6)

AND ta5() BE try(@a5, ta6, a1+a2+a3+a4+a5+a6+a7+a8+a9,

                          a5+b5+c5+d5+e5+f5+g5+h5+i5,
                          a4+a5+a6+b4+b5+b6+c4+c5+c6)

AND ta6() BE try(@a6, ta7, a1+a2+a3+a4+a5+a6+a7+a8+a9,

                          a6+b6+c6+d6+e6+f6+g6+h6+i6,
                          a4+a5+a6+b4+b5+b6+c4+c5+c6)

AND ta7() BE try(@a7, ta8, a1+a2+a3+a4+a5+a6+a7+a8+a9,

                          a7+b7+c7+d7+e7+f7+g7+h7+i7,
                          a7+a8+a9+b7+b8+b9+c7+c8+c9)

AND ta8() BE try(@a8, ta9, a1+a2+a3+a4+a5+a6+a7+a8+a9,

                          a8+b8+c8+d8+e8+f8+g8+h8+i8,
                          a7+a8+a9+b7+b8+b9+c7+c8+c9)

AND ta9() BE try(@a9, tb1, a1+a2+a3+a4+a5+a6+a7+a8+a9,

                          a9+b9+c9+d9+e9+f9+g9+h9+i9,
                          a7+a8+a9+b7+b8+b9+c7+c8+c9)

AND tb1() BE try(@b1, tb2, b1+b2+b3+b4+b5+b6+b7+b8+b9,

                          a1+b1+c1+d1+e1+f1+g1+h1+i1,
                          a1+a2+a3+b1+b2+b3+c1+c2+c3)

AND tb2() BE try(@b2, tb3, b1+b2+b3+b4+b5+b6+b7+b8+b9,

                          a2+b2+c2+d2+e2+f2+g2+h2+i2,
                          a1+a2+a3+b1+b2+b3+c1+c2+c3)

AND tb3() BE try(@b3, tb4, b1+b2+b3+b4+b5+b6+b7+b8+b9,

                          a3+b3+c3+d3+e3+f3+g3+h3+i3,
                          a1+a2+a3+b1+b2+b3+c1+c2+c3)

AND tb4() BE try(@b4, tb5, b1+b2+b3+b4+b5+b6+b7+b8+b9,

                          a4+b4+c4+d4+e4+f4+g4+h4+i4,
                          a4+a5+a6+b4+b5+b6+c4+c5+c6)

AND tb5() BE try(@b5, tb6, b1+b2+b3+b4+b5+b6+b7+b8+b9,

                          a5+b5+c5+d5+e5+f5+g5+h5+i5,
                          a4+a5+a6+b4+b5+b6+c4+c5+c6)

AND tb6() BE try(@b6, tb7, b1+b2+b3+b4+b5+b6+b7+b8+b9,

                          a6+b6+c6+d6+e6+f6+g6+h6+i6,
                          a4+a5+a6+b4+b5+b6+c4+c5+c6)

AND tb7() BE try(@b7, tb8, b1+b2+b3+b4+b5+b6+b7+b8+b9,

                          a7+b7+c7+d7+e7+f7+g7+h7+i7,
                          a7+a8+a9+b7+b8+b9+c7+c8+c9)

AND tb8() BE try(@b8, tb9, b1+b2+b3+b4+b5+b6+b7+b8+b9,

                          a8+b8+c8+d8+e8+f8+g8+h8+i8,
                          a7+a8+a9+b7+b8+b9+c7+c8+c9)

AND tb9() BE try(@b9, tc1, b1+b2+b3+b4+b5+b6+b7+b8+b9,

                          a9+b9+c9+d9+e9+f9+g9+h9+i9,
                          a7+a8+a9+b7+b8+b9+c7+c8+c9)

AND tc1() BE try(@c1, tc2, c1+c2+c3+c4+c5+c6+c7+c8+c9,

                          a1+b1+c1+d1+e1+f1+g1+h1+i1,
                          a1+a2+a3+b1+b2+b3+c1+c2+c3)

AND tc2() BE try(@c2, tc3, c1+c2+c3+c4+c5+c6+c7+c8+c9,

                          a2+b2+c2+d2+e2+f2+g2+h2+i2,
                          a1+a2+a3+b1+b2+b3+c1+c2+c3)

AND tc3() BE try(@c3, tc4, c1+c2+c3+c4+c5+c6+c7+c8+c9,

                          a3+b3+c3+d3+e3+f3+g3+h3+i3,
                          a1+a2+a3+b1+b2+b3+c1+c2+c3)

AND tc4() BE try(@c4, tc5, c1+c2+c3+c4+c5+c6+c7+c8+c9,

                          a4+b4+c4+d4+e4+f4+g4+h4+i4,
                          a4+a5+a6+b4+b5+b6+c4+c5+c6)

AND tc5() BE try(@c5, tc6, c1+c2+c3+c4+c5+c6+c7+c8+c9,

                          a5+b5+c5+d5+e5+f5+g5+h5+i5,
                          a4+a5+a6+b4+b5+b6+c4+c5+c6)

AND tc6() BE try(@c6, tc7, c1+c2+c3+c4+c5+c6+c7+c8+c9,

                          a6+b6+c6+d6+e6+f6+g6+h6+i6,
                          a4+a5+a6+b4+b5+b6+c4+c5+c6)

AND tc7() BE try(@c7, tc8, c1+c2+c3+c4+c5+c6+c7+c8+c9,

                          a7+b7+c7+d7+e7+f7+g7+h7+i7,
                          a7+a8+a9+b7+b8+b9+c7+c8+c9)

AND tc8() BE try(@c8, tc9, c1+c2+c3+c4+c5+c6+c7+c8+c9,

                          a8+b8+c8+d8+e8+f8+g8+h8+i8,
                          a7+a8+a9+b7+b8+b9+c7+c8+c9)

AND tc9() BE try(@c9, td1, c1+c2+c3+c4+c5+c6+c7+c8+c9,

                          a9+b9+c9+d9+e9+f9+g9+h9+i9,
                          a7+a8+a9+b7+b8+b9+c7+c8+c9)

AND td1() BE try(@d1, td2, d1+d2+d3+d4+d5+d6+d7+d8+d9,

                          a1+b1+c1+d1+e1+f1+g1+h1+i1,
                          d1+d2+d3+e1+e2+e3+f1+f2+f3)

AND td2() BE try(@d2, td3, d1+d2+d3+d4+d5+d6+d7+d8+d9,

                          a2+b2+c2+d2+e2+f2+g2+h2+i2,
                          d1+d2+d3+e1+e2+e3+f1+f2+f3)

AND td3() BE try(@d3, td4, d1+d2+d3+d4+d5+d6+d7+d8+d9,

                          a3+b3+c3+d3+e3+f3+g3+h3+i3,
                          d1+d2+d3+e1+e2+e3+f1+f2+f3)

AND td4() BE try(@d4, td5, d1+d2+d3+d4+d5+d6+d7+d8+d9,

                          a4+b4+c4+d4+e4+f4+g4+h4+i4,
                          d4+d5+d6+e4+e5+e6+f4+f5+f6)

AND td5() BE try(@d5, td6, d1+d2+d3+d4+d5+d6+d7+d8+d9,

                          a5+b5+c5+d5+e5+f5+g5+h5+i5,
                          d4+d5+d6+e4+e5+e6+f4+f5+f6)

AND td6() BE try(@d6, td7, d1+d2+d3+d4+d5+d6+d7+d8+d9,

                          a6+b6+c6+d6+e6+f6+g6+h6+i6,
                          d4+d5+d6+e4+e5+e6+f4+f5+f6)

AND td7() BE try(@d7, td8, d1+d2+d3+d4+d5+d6+d7+d8+d9,

                          a7+b7+c7+d7+e7+f7+g7+h7+i7,
                          d7+d8+d9+e7+e8+e9+f7+f8+f9)

AND td8() BE try(@d8, td9, d1+d2+d3+d4+d5+d6+d7+d8+d9,

                          a8+b8+c8+d8+e8+f8+g8+h8+i8,
                          d7+d8+d9+e7+e8+e9+f7+f8+f9)

AND td9() BE try(@d9, te1, d1+d2+d3+d4+d5+d6+d7+d8+d9,

                          a9+b9+c9+d9+e9+f9+g9+h9+i9,
                          d7+d8+d9+e7+e8+e9+f7+f8+f9)

AND te1() BE try(@e1, te2, e1+e2+e3+e4+e5+e6+e7+e8+e9,

                          a1+b1+c1+d1+e1+f1+g1+h1+i1,
                          d1+d2+d3+e1+e2+e3+f1+f2+f3)

AND te2() BE try(@e2, te3, e1+e2+e3+e4+e5+e6+e7+e8+e9,

                          a2+b2+c2+d2+e2+f2+g2+h2+i2,
                          d1+d2+d3+e1+e2+e3+f1+f2+f3)

AND te3() BE try(@e3, te4, e1+e2+e3+e4+e5+e6+e7+e8+e9,

                          a3+b3+c3+d3+e3+f3+g3+h3+i3,
                          d1+d2+d3+e1+e2+e3+f1+f2+f3)

AND te4() BE try(@e4, te5, e1+e2+e3+e4+e5+e6+e7+e8+e9,

                          a4+b4+c4+d4+e4+f4+g4+h4+i4,
                          d4+d5+d6+e4+e5+e6+f4+f5+f6)

AND te5() BE try(@e5, te6, e1+e2+e3+e4+e5+e6+e7+e8+e9,

                          a5+b5+c5+d5+e5+f5+g5+h5+i5,
                          d4+d5+d6+e4+e5+e6+f4+f5+f6)

AND te6() BE try(@e6, te7, e1+e2+e3+e4+e5+e6+e7+e8+e9,

                          a6+b6+c6+d6+e6+f6+g6+h6+i6,
                          d4+d5+d6+e4+e5+e6+f4+f5+f6)

AND te7() BE try(@e7, te8, e1+e2+e3+e4+e5+e6+e7+e8+e9,

                          a7+b7+c7+d7+e7+f7+g7+h7+i7,
                          d7+d8+d9+e7+e8+e9+f7+f8+f9)

AND te8() BE try(@e8, te9, e1+e2+e3+e4+e5+e6+e7+e8+e9,

                          a8+b8+c8+d8+e8+f8+g8+h8+i8,
                          d7+d8+d9+e7+e8+e9+f7+f8+f9)

AND te9() BE try(@e9, tf1, e1+e2+e3+e4+e5+e6+e7+e8+e9,

                          a9+b9+c9+d9+e9+f9+g9+h9+i9,
                          d7+d8+d9+e7+e8+e9+f7+f8+f9)

AND tf1() BE try(@f1, tf2, f1+f2+f3+f4+f5+f6+f7+f8+f9,

                          a1+b1+c1+d1+e1+f1+g1+h1+i1,
                          d1+d2+d3+e1+e2+e3+f1+f2+f3)

AND tf2() BE try(@f2, tf3, f1+f2+f3+f4+f5+f6+f7+f8+f9,

                          a2+b2+c2+d2+e2+f2+g2+h2+i2,
                          d1+d2+d3+e1+e2+e3+f1+f2+f3)

AND tf3() BE try(@f3, tf4, f1+f2+f3+f4+f5+f6+f7+f8+f9,

                          a3+b3+c3+d3+e3+f3+g3+h3+i3,
                          d1+d2+d3+e1+e2+e3+f1+f2+f3)

AND tf4() BE try(@f4, tf5, f1+f2+f3+f4+f5+f6+f7+f8+f9,

                          a4+b4+c4+d4+e4+f4+g4+h4+i4,
                          d4+d5+d6+e4+e5+e6+f4+f5+f6)

AND tf5() BE try(@f5, tf6, f1+f2+f3+f4+f5+f6+f7+f8+f9,

                          a5+b5+c5+d5+e5+f5+g5+h5+i5,
                          d4+d5+d6+e4+e5+e6+f4+f5+f6)

AND tf6() BE try(@f6, tf7, f1+f2+f3+f4+f5+f6+f7+f8+f9,

                          a6+b6+c6+d6+e6+f6+g6+h6+i6,
                          d4+d5+d6+e4+e5+e6+f4+f5+f6)

AND tf7() BE try(@f7, tf8, f1+f2+f3+f4+f5+f6+f7+f8+f9,

                          a7+b7+c7+d7+e7+f7+g7+h7+i7,
                          d7+d8+d9+e7+e8+e9+f7+f8+f9)

AND tf8() BE try(@f8, tf9, f1+f2+f3+f4+f5+f6+f7+f8+f9,

                          a8+b8+c8+d8+e8+f8+g8+h8+i8,
                          d7+d8+d9+e7+e8+e9+f7+f8+f9)

AND tf9() BE try(@f9, tg1, f1+f2+f3+f4+f5+f6+f7+f8+f9,

                          a9+b9+c9+d9+e9+f9+g9+h9+i9,
                          d7+d8+d9+e7+e8+e9+f7+f8+f9)

AND tg1() BE try(@g1, tg2, g1+g2+g3+g4+g5+g6+g7+g8+g9,

                          a1+b1+c1+d1+e1+f1+g1+h1+i1,
                          g1+g2+g3+h1+h2+h3+i1+i2+i3)

AND tg2() BE try(@g2, tg3, g1+g2+g3+g4+g5+g6+g7+g8+g9,

                          a2+b2+c2+d2+e2+f2+g2+h2+i2,
                          g1+g2+g3+h1+h2+h3+i1+i2+i3)

AND tg3() BE try(@g3, tg4, g1+g2+g3+g4+g5+g6+g7+g8+g9,

                          a3+b3+c3+d3+e3+f3+g3+h3+i3,
                          g1+g2+g3+h1+h2+h3+i1+i2+i3)

AND tg4() BE try(@g4, tg5, g1+g2+g3+g4+g5+g6+g7+g8+g9,

                          a4+b4+c4+d4+e4+f4+g4+h4+i4,
                          g4+g5+g6+h4+h5+h6+i4+i5+i6)

AND tg5() BE try(@g5, tg6, g1+g2+g3+g4+g5+g6+g7+g8+g9,

                          a5+b5+c5+d5+e5+f5+g5+h5+i5,
                          g4+g5+g6+h4+h5+h6+i4+i5+i6)

AND tg6() BE try(@g6, tg7, g1+g2+g3+g4+g5+g6+g7+g8+g9,

                          a6+b6+c6+d6+e6+f6+g6+h6+i6,
                          g4+g5+g6+h4+h5+h6+i4+i5+i6)

AND tg7() BE try(@g7, tg8, g1+g2+g3+g4+g5+g6+g7+g8+g9,

                          a7+b7+c7+d7+e7+f7+g7+h7+i7,
                          g7+g8+g9+h7+h8+h9+i7+i8+i9)

AND tg8() BE try(@g8, tg9, g1+g2+g3+g4+g5+g6+g7+g8+g9,

                          a8+b8+c8+d8+e8+f8+g8+h8+i8,
                          g7+g8+g9+h7+h8+h9+i7+i8+i9)

AND tg9() BE try(@g9, th1, g1+g2+g3+g4+g5+g6+g7+g8+g9,

                          a9+b9+c9+d9+e9+f9+g9+h9+i9,
                          g7+g8+g9+h7+h8+h9+i7+i8+i9)

AND th1() BE try(@h1, th2, h1+h2+h3+h4+h5+h6+h7+h8+h9,

                          a1+b1+c1+d1+e1+f1+g1+h1+i1,
                          g1+g2+g3+h1+h2+h3+i1+i2+i3)

AND th2() BE try(@h2, th3, h1+h2+h3+h4+h5+h6+h7+h8+h9,

                          a2+b2+c2+d2+e2+f2+g2+h2+i2,
                          g1+g2+g3+h1+h2+h3+i1+i2+i3)

AND th3() BE try(@h3, th4, h1+h2+h3+h4+h5+h6+h7+h8+h9,

                          a3+b3+c3+d3+e3+f3+g3+h3+i3,
                          g1+g2+g3+h1+h2+h3+i1+i2+i3)

AND th4() BE try(@h4, th5, h1+h2+h3+h4+h5+h6+h7+h8+h9,

                          a4+b4+c4+d4+e4+f4+g4+h4+i4,
                          g4+g5+g6+h4+h5+h6+i4+i5+i6)

AND th5() BE try(@h5, th6, h1+h2+h3+h4+h5+h6+h7+h8+h9,

                          a5+b5+c5+d5+e5+f5+g5+h5+i5,
                          g4+g5+g6+h4+h5+h6+i4+i5+i6)

AND th6() BE try(@h6, th7, h1+h2+h3+h4+h5+h6+h7+h8+h9,

                          a6+b6+c6+d6+e6+f6+g6+h6+i6,
                          g4+g5+g6+h4+h5+h6+i4+i5+i6)

AND th7() BE try(@h7, th8, h1+h2+h3+h4+h5+h6+h7+h8+h9,

                          a7+b7+c7+d7+e7+f7+g7+h7+i7,
                          g7+g8+g9+h7+h8+h9+i7+i8+i9)

AND th8() BE try(@h8, th9, h1+h2+h3+h4+h5+h6+h7+h8+h9,

                          a8+b8+c8+d8+e8+f8+g8+h8+i8,
                          g7+g8+g9+h7+h8+h9+i7+i8+i9)

AND th9() BE try(@h9, ti1, h1+h2+h3+h4+h5+h6+h7+h8+h9,

                          a9+b9+c9+d9+e9+f9+g9+h9+i9,
                          g7+g8+g9+h7+h8+h9+i7+i8+i9)

AND ti1() BE try(@i1, ti2, i1+i2+i3+i4+i5+i6+i7+i8+i9,

                          a1+b1+c1+d1+e1+f1+g1+h1+i1,
                          g1+g2+g3+h1+h2+h3+i1+i2+i3)

AND ti2() BE try(@i2, ti3, i1+i2+i3+i4+i5+i6+i7+i8+i9,

                          a2+b2+c2+d2+e2+f2+g2+h2+i2,
                          g1+g2+g3+h1+h2+h3+i1+i2+i3)

AND ti3() BE try(@i3, ti4, i1+i2+i3+i4+i5+i6+i7+i8+i9,

                          a3+b3+c3+d3+e3+f3+g3+h3+i3,
                          g1+g2+g3+h1+h2+h3+i1+i2+i3)

AND ti4() BE try(@i4, ti5, i1+i2+i3+i4+i5+i6+i7+i8+i9,

                          a4+b4+c4+d4+e4+f4+g4+h4+i4,
                          g4+g5+g6+h4+h5+h6+i4+i5+i6)

AND ti5() BE try(@i5, ti6, i1+i2+i3+i4+i5+i6+i7+i8+i9,

                          a5+b5+c5+d5+e5+f5+g5+h5+i5,
                          g4+g5+g6+h4+h5+h6+i4+i5+i6)

AND ti6() BE try(@i6, ti7, i1+i2+i3+i4+i5+i6+i7+i8+i9,

                          a6+b6+c6+d6+e6+f6+g6+h6+i6,
                          g4+g5+g6+h4+h5+h6+i4+i5+i6)

AND ti7() BE try(@i7, ti8, i1+i2+i3+i4+i5+i6+i7+i8+i9,

                          a7+b7+c7+d7+e7+f7+g7+h7+i7,
                          g7+g8+g9+h7+h8+h9+i7+i8+i9)

AND ti8() BE try(@i8, ti9, i1+i2+i3+i4+i5+i6+i7+i8+i9,

                          a8+b8+c8+d8+e8+f8+g8+h8+i8,
                          g7+g8+g9+h7+h8+h9+i7+i8+i9)

AND ti9() BE try(@i9, suc, i1+i2+i3+i4+i5+i6+i7+i8+i9,

                          a9+b9+c9+d9+e9+f9+g9+h9+i9,
                          g7+g8+g9+h7+h8+h9+i7+i8+i9)

AND suc() BE { count := count + 1

 prboard()

}</lang>

Bracmat

The program: <lang bracmat>{sudokuSolver.bra

Solves any 9x9 sudoku, using backtracking. Not a simple brute force algorithm!}

sudokuSolver=

 ( sudoku
 =   ( new
     =   create
       .   ( create
           =   a
             .     !arg:%(<3:?a) ?arg
                 &   ( !a
                     .     !arg:
                         & 1 2 3 4 5 6 7 8 9
                       | create$!arg
                     )
                     create$(!a+1 !arg)
               | 
           )
         & create$(0 0 0 0):?(its.Tree)
         & ( init
           =   cell remainingCells remainingRows x y
             .       !arg
                   : ( ?y
                     . ?x
                     . (.%?cell ?remainingCells) ?remainingRows
                     )
                 &   (   !cell:#
                       & ( !cell
                         .   mod$(!x,3)
                             div$(!x,3)
                             mod$(!y,3)
                             div$(!y,3)
                         )
                     | 
                     )
                     (   !remainingCells:
                       & init$(!y+1.0.!remainingRows)
                     |   init
                       $ ( !y
                         . !x+1
                         . (.!remainingCells) !remainingRows
                         )
                     )
               | 
           )
         & out$!arg
         &   (its.Set)$(!(its.Tree).init$(0.0.!arg))
           : ?(its.Tree)
     )
     ( Display
     =   val
       .     put$(str$("|~~~|~~~|~~~|" \n))
           &   !(its.Tree)
             :   ?
                 ( ?
                 .     ?
                       ( ?&put$"|"
                       .     ?
                             ( ?
                             .     ?
                                   ( ( ?
                                     .     ?val
                                         & !val:% %
                                         & put$"-"
                                       |   !val:
                                         & put$" "
                                       | put$!val
                                     )
                                   & ~
                                   )
                                   ?
                               | ?&put$"|"&~
                             )
                             ?
                         | ?&put$\n&~
                       )
                       ?
                   |   ?
                     & put$(str$("|~~~|~~~|~~~|" \n))
                     & ~
                 )
                 ?
         | 
     )
     ( Set
     =     update certainValue a b c d
         , tree branch todo DOING loop dcba minlen len minp
       .   ( update
           =     path rempath value tr
               , k z x y trc p v branch s n
             .   !arg:(?path.?value.?tr.?trc)
               & (   !path:%?path ?rempath
                   & `(     !tr
                          : ?k (!path:?p.?branch) ?z
                        & `(   update$(!rempath.!value.!branch.!p !trc)
                             : ?s
                           &     update
                               $ (!path !rempath.!value.!z.!trc)
                             : ?n
                           & !k (!p.!s) !n
                           )
                      | !tr
                      )
                 | !DOING:(?.!trc)&!value
                 |   !tr:?x !value ?y
                   & `( !x !y
                      : (   ~:@
                          & (   !todo:? (?v.!trc) ?
                              & ( !v:!x !y
                                |     out
                                    $ (mismatch v !v "<>" x y !x !y)
                                  & get'
                                )
                            | (!x !y.!trc) !todo:?todo
                            )
                        | % %
                        | &!DOING:(?.!trc)
                        )
                      )
                 | !tr
                 )
           )
         & !arg:(?tree.?todo)
         & ( loop
           =   !todo:
             |     !todo
                 : ((?certainValue.%?d %?c %?b %?a):?DOING) ?todo
               &   update$(!a ? !c ?.!certainValue.!tree.)
                 : ?tree
               &   update$(!a !b <>!c ?.!certainValue.!tree.)
                 : ?tree
               &   update$(<>!a ? !c !d.!certainValue.!tree.)
                 : ?tree
               & !loop
           )
         & !loop
         & ( ~( !tree
              :   ?
                  (?.? (?.? (?.? (?.% %) ?) ?) ?)
                  ?
              )
           |   9:?minlen
             & :?minp
             & ( len
               =   
                 .   !arg:% %?arg&1+len$!arg
                   | 1
               )
             & (   !tree
                 :   ?
                     ( ?a
                     .   ?
                         ( ?b
                         .   ?
                             ( ?c
                             .   ?
                                 ( ?d
                                 .   % %:?p
                                   & len$!p:<!minlen:?minlen
                                   & !d !c !b !a:?dcba
                                   & !p:?:?minp
                                   & ~
                                 )
                                 ?
                             )
                             ?
                         )
                         ?
                     )
                     ?
               |   !minp
                 :   ?
                     ( %@?n
                     & (its.Set)$(!tree.!n.!dcba):?tree
                     )
                     ?
               )
           )
         & !tree
     )
     (Tree=)
 )
 ( new
 =   puzzle
   .   new$((its.sudoku),!arg):?puzzle
     & (puzzle..Display)$
 );</lang>

Solve a sudoku that is hard for a brute force solver: <lang bracmat>new'( sudokuSolver

   , (.- - - - - - - - -)
     (.- - - - - 3 - 8 5)
     (.- - 1 - 2 - - - -)
     (.- - - 5 - 7 - - -)
     (.- - 4 - - - 1 - -)
     (.- 9 - - - - - - -)
     (.5 - - - - - - 7 3)
     (.- - 2 - 1 - - - -)
     (.- - - - 4 - - - 9)
   );</lang>

Solution:

|~~~|~~~|~~~|
|987|654|321|
|246|173|985|
|351|928|746|
|~~~|~~~|~~~|
|128|537|694|
|634|892|157|
|795|461|832|
|~~~|~~~|~~~|
|519|286|473|
|472|319|568|
|863|745|219|
|~~~|~~~|~~~|

C

See e.g. this GPLed solver written in C.

The following code is really only good for size 3 puzzles. A longer, even less readable version here could handle size 4s. <lang c>#include <stdio.h>

void show(int *x) { int i, j; for (i = 0; i < 9; i++) { if (!(i % 3)) putchar('\n'); for (j = 0; j < 9; j++) printf(j % 3 ? "%2d" : "%3d", *x++); putchar('\n'); } }

int trycell(int *x, int pos) { int row = pos / 9; int col = pos % 9; int i, j, used = 0;

if (pos == 81) return 1; if (x[pos]) return trycell(x, pos + 1);

for (i = 0; i < 9; i++) used |= 1 << (x[i * 9 + col] - 1);

for (j = 0; j < 9; j++) used |= 1 << (x[row * 9 + j] - 1);

row = row / 3 * 3; col = col / 3 * 3; for (i = row; i < row + 3; i++) for (j = col; j < col + 3; j++) used |= 1 << (x[i * 9 + j] - 1);

for (x[pos] = 1; x[pos] <= 9; x[pos]++, used >>= 1) if (!(used & 1) && trycell(x, pos + 1)) return 1;

x[pos] = 0; return 0; }

void solve(const char *s) { int i, x[81]; for (i = 0; i < 81; i++) x[i] = s[i] >= '1' && s[i] <= '9' ? s[i] - '0' : 0;

if (trycell(x, 0)) show(x); else puts("no solution"); }

int main(void) { solve( "5x..7...." "6..195..." ".98....6." "8...6...3" "4..8.3..1" "7...2...6" ".6....28." "...419..5" "....8..79" );

return 0; }</lang>

C_sharp

“Manual” Solution

Translation of: Java

<lang csharp>using System;

class SudokuSolver {

   private int[] grid;
   public SudokuSolver(String s)
   {
       grid = new int[81];
       for (int i = 0; i < s.Length; i++)
       {
           grid[i] = int.Parse(s[i].ToString());
       }
   }
   public void solve()
   {
       try
       {
           placeNumber(0);
           Console.WriteLine("Unsolvable!");
       }
       catch (Exception ex)
       {
           Console.WriteLine(ex.Message);
           Console.WriteLine(this);
       }
   }
   public void placeNumber(int pos)
   {
       if (pos == 81)
       {
           throw new Exception("Finished!");
       }
       if (grid[pos] > 0)
       {
           placeNumber(pos + 1);
           return;
       }
       for (int n = 1; n <= 9; n++)
       {
           if (checkValidity(n, pos % 9, pos / 9))
           {
               grid[pos] = n;
               placeNumber(pos + 1);
               grid[pos] = 0;
           }
       }
   }
   public bool checkValidity(int val, int x, int y)
   {
       for (int i = 0; i < 9; i++)
       {
           if (grid[y * 9 + i] == val || grid[i * 9 + x] == val)
               return false;
       }
       int startX = (x / 3) * 3;
       int startY = (y / 3) * 3;
       for (int i = startY; i < startY + 3; i++)
       {
           for (int j = startX; j < startX + 3; j++)
           {
               if (grid[i * 9 + j] == val)
                   return false;
           }
       }
       return true;
   }
   public override string ToString()
   {
       string sb = "";
       for (int i = 0; i < 9; i++)
       {
           for (int j = 0; j < 9; j++)
           {
               sb += (grid[i * 9 + j] + " ");
               if (j == 2 || j == 5)
                   sb += ("| ");
           }
           sb += ('\n');
           if (i == 2 || i == 5)
               sb += ("------+-------+------\n");
       }
       return sb;
   }
   public static void Main(String[] args)
   {
       new SudokuSolver("850002400" +
                        "720000009" +
                        "004000000" +
                        "000107002" +
                        "305000900" +
                        "040000000" +
                        "000080070" +
                        "017000000" +
                        "000036040").solve();
       Console.Read();
   }

}</lang>

“Automatic” Solution

<lang csharp>using Microsoft.SolverFoundation.Solvers;

namespace Sudoku {

   class Program
   {
       private static int[,] B = new int[,] {{9,7,0, 3,0,0, 0,6,0},
                                             {0,6,0, 7,5,0, 0,0,0},
                                             {0,0,0, 0,0,8, 0,5,0},
                                             {0,0,0, 0,0,0, 6,7,0},
                                             {0,0,0, 0,3,0, 0,0,0},
                                             {0,5,3, 9,0,0, 2,0,0},
                                             {7,0,0, 0,2,5, 0,0,0},
                                             {0,0,2, 0,1,0, 0,0,8},
                                             {0,4,0, 0,0,7, 3,0,0}};
       private static CspTerm[] GetSlice(CspTerm[][] sudoku, int Ra, int Rb, int Ca, int Cb)
       {
           CspTerm[] slice = new CspTerm[9];
           int i = 0;
           for (int row = Ra; row < Rb + 1; row++)
               for (int col = Ca; col < Cb + 1; col++)
               {
                   {
                       slice[i++] = sudoku[row][col];
                   }
               }
           return slice;
       }
       static void Main(string[] args)
       {
           ConstraintSystem S = ConstraintSystem.CreateSolver();
           CspDomain Z = S.CreateIntegerInterval(1, 9);
           CspTerm[][] sudoku = S.CreateVariableArray(Z, "cell", 9, 9);
           for (int row = 0; row < 9; row++)
           {
               for (int col = 0; col < 9; col++)
               {
                   if (B[row, col] > 0)
                   {
                       S.AddConstraints(S.Equal(B[row, col], sudoku[row][col]));
                   }
               }
               S.AddConstraints(S.Unequal(GetSlice(sudoku, row, row, 0, 8)));
           }
           for (int col = 0; col < 9; col++)
           {
               S.AddConstraints(S.Unequal(GetSlice(sudoku, 0, 8, col, col)));
           }
           for (int a = 0; a < 3; a++)
           {
               for (int b = 0; b < 3; b++)
               {
                   S.AddConstraints(S.Unequal(GetSlice(sudoku, a * 3, a * 3 + 2, b * 3, b * 3 + 2)));
               }
           }
           ConstraintSolverSolution soln = S.Solve();
           object[] h = new object[9];
           for (int row = 0; row < 9; row++)
           {
               if ((row % 3) == 0) System.Console.WriteLine();
               for (int col = 0; col < 9; col++)
               {
                   soln.TryGetValue(sudoku[row][col], out h [col]);
               }
               System.Console.WriteLine("{0}{1}{2} {3}{4}{5} {6}{7}{8}", h[0],h[1],h[2],h[3],h[4],h[5],h[6],h[7],h[8]);
           }
       }
   }

}</lang> Produces:

975 342 861
861 759 432
324 168 957

219 584 673
487 236 519
653 971 284

738 425 196
592 613 748
146 897 325

C++

Translation of: Java

<lang cpp>#include <iostream> using namespace std;

class SudokuSolver { private:

   int grid[81];

public:

   SudokuSolver(string s) {
       for (unsigned int i = 0; i < s.length(); i++) {
           grid[i] = (int) (s[i] - '0');
       }
   }
   void solve() {
       try {
           placeNumber(0);
           cout << "Unsolvable!" << endl;
       } catch (char* ex) {
           cout << ex << endl;
           cout << this->toString() << endl;
       }
   }
   void placeNumber(int pos) {
       if (pos == 81) {
           throw (char*) "Finished!";
       }
       if (grid[pos] > 0) {
           placeNumber(pos + 1);
           return;
       }
       for (int n = 1; n <= 9; n++) {
           if (checkValidity(n, pos % 9, pos / 9)) {
               grid[pos] = n;
               placeNumber(pos + 1);
               grid[pos] = 0;
           }
       }
   }
   bool checkValidity(int val, int x, int y) {
       for (int i = 0; i < 9; i++) {
           if (grid[y * 9 + i] == val || grid[i * 9 + x] == val)
               return false;
       }
       int startX = (x / 3) * 3;
       int startY = (y / 3) * 3;
       for (int i = startY; i < startY + 3; i++) {
           for (int j = startX; j < startX + 3; j++) {
               if (grid[i * 9 + j] == val)
                   return false;
           }
       }
       return true;
   }
   string toString() {
       string sb;
       for (int i = 0; i < 9; i++) {
           for (int j = 0; j < 9; j++) {
               char c[2];
               c[0] = grid[i * 9 + j] + '0';
               c[1] = '\0';
               sb.append(c);
               sb.append(" ");
               if (j == 2 || j == 5)
                   sb.append("| ");
           }
           sb.append("\n");
           if (i == 2 || i == 5)
               sb.append("------+-------+------\n");
       }
       return sb;
   }

};

int main() {

   SudokuSolver ss(
           (string) "850002400" +
           (string) "720000009" +
           (string) "004000000" +
           (string) "000107002" +
           (string) "305000900" +
           (string) "040000000" +
           (string) "000080070" +
           (string) "017000000" +
           (string) "000036040"
           );
   ss.solve();

}</lang>

Clojure

<lang clojure>(ns sudoku

 (:use [clojure.contrib.math :only (sqrt)]))

(defn print-grid [grid]

 (doseq [y (range (count grid))]
   (doseq [x (range (count grid))]
     (print (retrieve grid x y) " "))
   (println))
 (println))

(defn retrieve [grid x y]

 (get (get grid y) x))

(defn store [grid x y n]

 (assoc grid y (assoc (get grid y) x n)))

(defn coordinates [grid x y]

 (let [n (sqrt (count grid))
       zx (* n (quot x n))
       zy (* n (quot y n))]
   (for [x (range zx (+ zx n)) y (range zy (+ zy n))]
     [x y])))

(defn compatible? [grid x y n]

 (or
  (= n (retrieve grid x y))
  (and
   (zero? (retrieve grid x y))
   (every? #(and (not= n (retrieve grid % y)) (not= n (retrieve grid x %))) (range (count grid)))
   (every? #(not= n (retrieve grid (first %) (second %))) (coordinates grid x y)))))

(defn solve [grid x y]

 (let [m (count grid)]
   (if (= y m)
     (print-grid grid)
     (doseq [n (range 1 (inc m))]
       (when (compatible? grid x y n)
         (let [new-grid (store grid x y n)]
           (if (= x (dec m))
             (solve new-grid 0 (inc y))
             (solve new-grid (inc x) y))))))))</lang>

<lang clojure>sudoku> (solve [[3 9 4 0 0 2 6 7 0]

              [0 0 0 3 0 0 4 0 0]
              [5 0 0 6 9 0 0 2 0]
              [0 4 5 0 0 0 9 0 0]
              [6 0 0 0 0 0 0 0 7]
              [0 0 7 0 0 0 5 8 0]
              [0 1 0 0 6 7 0 0 8]
              [0 0 9 0 0 8 0 0 0]
              [0 2 6 4 0 0 7 3 5]]
              0 0)

3 9 4 8 5 2 6 7 1 2 6 8 3 7 1 4 5 9 5 7 1 6 9 4 8 2 3 1 4 5 7 8 3 9 6 2 6 8 2 9 4 5 3 1 7 9 3 7 1 2 6 5 8 4 4 1 3 5 6 7 2 9 8 7 5 9 2 3 8 1 4 6 8 2 6 4 1 9 7 3 5

nil</lang>

Common Lisp

A simple solver without optimizations (except for pre-computing the possible entries of a cell). <lang lisp>(defun row-neighbors (row column grid &aux (neighbors '()))

 (dotimes (i 9 neighbors)
   (let ((x (aref grid row i)))
     (unless (or (eq '_ x) (= i column))
       (push x neighbors)))))

(defun column-neighbors (row column grid &aux (neighbors '()))

 (dotimes (i 9 neighbors)
   (let ((x (aref grid i column)))
     (unless (or (eq x '_) (= i row))
       (push x neighbors)))))

(defun square-neighbors (row column grid &aux (neighbors '()))

 (let* ((rmin (* 3 (floor row 3)))    (rmax (+ rmin 3))
        (cmin (* 3 (floor column 3))) (cmax (+ cmin 3)))
   (do ((r rmin (1+ r))) ((= r rmax) neighbors)
     (do ((c cmin (1+ c))) ((= c cmax))
       (let ((x (aref grid r c)))
         (unless (or (eq x '_) (= r row) (= c column))
           (push x neighbors)))))))

(defun choices (row column grid)

 (nset-difference
  (list 1 2 3 4 5 6 7 8 9)
  (nconc (row-neighbors row column grid)
         (column-neighbors row column grid)
         (square-neighbors row column grid))))

(defun solve (grid &optional (row 0) (column 0))

 (cond
  ((= row 9)
   grid)
  ((= column 9)
   (solve grid (1+ row) 0))
  ((not (eq '_ (aref grid row column)))
   (solve grid row (1+ column)))
  (t (dolist (choice (choices row column grid) (setf (aref grid row column) '_))
       (setf (aref grid row column) choice)
       (when (eq grid (solve grid row (1+ column)))
         (return grid))))))</lang>

Example:

> (defparameter *puzzle*
  #2A((3 9 4    _ _ 2    6 7 _)
      (_ _ _    3 _ _    4 _ _)
      (5 _ _    6 9 _    _ 2 _)
    
      (_ 4 5    _ _ _    9 _ _)
      (6 _ _    _ _ _    _ _ 7)
      (_ _ 7    _ _ _    5 8 _)
    
      (_ 1 _    _ 6 7    _ _ 8)
      (_ _ 9    _ _ 8    _ _ _)
      (_ 2 6    4 _ _    7 3 5)))
*PUZZLE*

> (pprint (solve *puzzle*))

#2A((3 9 4 8 5 2 6 7 1)
    (2 6 8 3 7 1 4 5 9)
    (5 7 1 6 9 4 8 2 3)
    (1 4 5 7 8 3 9 6 2)
    (6 8 2 9 4 5 3 1 7)
    (9 3 7 1 2 6 5 8 4)
    (4 1 3 5 6 7 2 9 8)
    (7 5 9 2 3 8 1 4 6)
    (8 2 6 4 1 9 7 3 5))

Curry

Copied from Curry: Example Programs. <lang curry>----------------------------------------------------------------------------- --- Solving Su Doku puzzles in Curry with FD constraints --- --- @author Michael Hanus --- @version December 2005


import CLPFD import List

-- Solving a Su Doku puzzle represented as a matrix of numbers (possibly free -- variables): sudoku :: Int -> Success sudoku m =

domain (concat m) 1 9 &                         -- define domain of all digits
foldr1 (&) (map allDifferent m)  &             -- all rows contain different digits
foldr1 (&) (map allDifferent (transpose m))  & -- all columns have different digits
foldr1 (&) (map allDifferent (squaresOfNine m)) & -- all 3x3 squares are different
labeling [FirstFailConstrained] (concat m)

-- translate a matrix into a list of small 3x3 squares squaresOfNine :: a -> a squaresOfNine [] = [] squaresOfNine (l1:l2:l3:ls) = group3Rows [l1,l2,l3] ++ squaresOfNine ls

group3Rows l123 = if null (head l123) then [] else

concatMap (take 3) l123 : group3Rows (map (drop 3) l123)

-- read a Su Doku specification written as a list of strings containing digits -- and spaces readSudoku :: [String] -> Int readSudoku s = map (map transDigit) s

where
  transDigit c = if c==' ' then x else ord c - ord '0'
     where x free

-- show a solved Su Doku matrix showSudoku :: Int -> String showSudoku = unlines . map (concatMap (\i->[chr (i + ord '0'),' ']))

-- the main function, e.g., evaluate (main s1): main s | sudoku m = putStrLn (showSudoku m)

where m = readSudoku s

s1 = ["9 2 5 ",

     " 4  6  3 ",
     "  3     6",
     "   9  2  ",
     "    5  8 ",
     "  7  4  3",
     "7     1  ",
     " 5  2  4 ",
     "  1  6  9"]

s2 = ["819 5 ",

     "  2   75 ",
     " 371 4 6 ",
     "4  59 1  ",
     "7  3 8  2",
     "  3 62  7",
     " 5 7 921 ",
     " 64   9  ",
     "   2  438"]</lang>

D

Translation of: C++

A little over-engineered solution, that shows some strong static typing useful in larger programs. <lang d>import std.stdio, std.range, std.string, std.algorithm, std.array,

      std.typetuple, std.ascii, std.typecons;

template Range(size_t stop) { // For loop unrolling.

   static if (stop == 0)
       alias TypeTuple!() Range;
   else
       alias TypeTuple!(Range!(stop - 1), stop - 1) Range;

}


enum size_t sudokuUnitSide = 3; enum size_t sudokuSide = sudokuUnitSide ^^ 2; // Sudoku grid side.


struct Digit {

   immutable char d;
   this(in char d_) pure nothrow
   in { assert(d_ >= '0' && d_ <= '9'); }
   body { this.d = d_; }
   this(in int d_) pure nothrow
   in { assert(d_ >= '0' && d_ <= '9'); }
   body { this.d = cast(char)d_; } // Required cast.
   alias d this;

}

alias SudokuTable = Digit[sudokuSide ^^ 2];


Nullable!SudokuTable sudokuSolver(in ref SudokuTable problem) /*pure nothrow*/ {

   alias Tgrid = uint;
   Tgrid[SudokuTable.length] grid = void;
   problem[].map!(c => c - '0')().copy(grid[]); // Not pure.
   // DMD doesn't inline this function. Performance loss.
   Tgrid access(in size_t x, in size_t y) nothrow {
       return grid[y * sudokuSide + x];
   }
   // DMD doesn't inline this function. If you want to retain
   // the same performance as the C++ entry and you use the DMD
   // compiler then this function must be manually inlined.
   bool checkValidity(in Tgrid val, in size_t x, in size_t y) nothrow {
       /*static*/ foreach (immutable i; Range!sudokuSide)
           if (access(i, y) == val || access(x, i) == val)
               return false;
       immutable startX = (x / sudokuUnitSide) * sudokuUnitSide;
       immutable startY = (y / sudokuUnitSide) * sudokuUnitSide;
       /*static*/ foreach (immutable i; Range!sudokuUnitSide)
           /*static*/ foreach (immutable j; Range!sudokuUnitSide)
               if (access(startX + j, startY + i) == val)
                   return false;
       return true;
   }
   bool canPlaceNumbers(in size_t pos=0) nothrow {
       if (pos == SudokuTable.length)
           return true;
       if (grid[pos] > 0)
           return canPlaceNumbers(pos + 1);
       foreach (immutable n; 1 .. sudokuSide + 1)
           if (checkValidity(n, pos % sudokuSide, pos / sudokuSide)) {
               grid[pos] = n;
               if (canPlaceNumbers(pos + 1))
                   return true;
               grid[pos] = 0;
           }
       return false;
   }
   if (canPlaceNumbers()) {
       //return typeof(return)(grid[]
       //                      .map!(c => Digit(c + '0'))()
       //                      .array());
       Digit[] aux;
       foreach (c; grid)
           aux ~= Digit(c + '0');
       immutable SudokuTable result = aux;
       return typeof(return)(result);
   } else
       return typeof(return)();

}


string representSudoku(in ref SudokuTable sudo) pure nothrow out(result) {

   // assert(result.countchars("1-9") == sudo.countchars("^0"));
   uint nPosDigits;
   foreach (c; sudo)
       if (c >= '1' && c <= '9')
           nPosDigits++;
   assert(result.countchars("1-9") == nPosDigits);

} body {

   static assert(sudo.length == 81,
       "representSudoku works only with a 9x9 Sudoku.");
   string result;
   foreach (immutable i; 0 .. sudokuSide) {
       foreach (immutable j; 0 .. sudokuSide) {
           // immutable digit = sudo[i * sudokuSide + j];
           immutable char digit = sudo[i * sudokuSide + j];
           result ~= (digit == '0') ? '.' : digit;
           result ~= ' ';
           if (j == 2 || j == 5)
               result ~= "| ";
       }
       result ~= "\n";
       if (i == 2 || i == 5)
           result ~= "------+-------+------\n";
   }
   //return result.replace("0", "."); // Not pure, not nothrow.
   return result;

}


U[] validator(U, T)(in T[] items) pure nothrow {

   typeof(return) result;
   foreach (immutable item; items)
       result ~= U(item);
   return result;

}

template ValidateCells(string s) {

   enum ValidateCells = validator!Digit(s);

}


void main() {

   immutable SudokuTable problem = ValidateCells!("
       850002400
       720000009
       004000000
       000107002
       305000900
       040000000
       000080070
       017000000
       000036040".removechars(std.ascii.whitespace));
   problem.representSudoku().writeln();
   immutable solution = sudokuSolver(problem);
   if (solution.isNull)
       writeln("Unsolvable!");
   else
       solution.get().representSudoku().writeln();

}</lang>

Output:
8 5 . | . . 2 | 4 . .
7 2 . | . . . | . . 9
. . 4 | . . . | . . .
------+-------+------
. . . | 1 . 7 | . . 2
3 . 5 | . . . | 9 . .
. 4 . | . . . | . . .
------+-------+------
. . . | . 8 . | . 7 .
. 1 7 | . . . | . . .
. . . | . 3 6 | . 4 . 

8 5 9 | 6 1 2 | 4 3 7 
7 2 3 | 8 5 4 | 1 6 9 
1 6 4 | 3 7 9 | 5 2 8 
------+-------+------
9 8 6 | 1 4 7 | 3 5 2 
3 7 5 | 2 6 8 | 9 1 4 
2 4 1 | 5 9 3 | 7 8 6 
------+-------+------
4 3 2 | 9 8 1 | 6 7 5 
6 1 7 | 4 2 5 | 8 9 3 
5 9 8 | 7 3 6 | 2 4 1 

Delphi

Example taken from C++ <lang delphi>type

 TIntArray = array of Integer;
 { TSudokuSolver }
 TSudokuSolver = class
 private
   FGrid: TIntArray;
   function CheckValidity(val: Integer; x: Integer; y: Integer): Boolean;
   function ToString: string; reintroduce;
   procedure PlaceNumber(pos: Integer);
 public
   constructor Create(s: string);
   procedure Solve;
 end;

implementation

uses

 Dialogs;

{ TSudokuSolver }

function TSudokuSolver.CheckValidity(val: Integer; x: Integer; y: Integer

 ): Boolean;

var

 i: Integer;
 j: Integer;
 StartX: Integer;
 StartY: Integer;

begin

 for i := 0 to 8 do
 begin
   if (FGrid[y * 9 + i] = val) or
      (FGrid[i * 9 + x] = val) then
   begin
     Result := False;
     Exit;
   end;
 end;
 StartX := (x div 3) * 3;
 StartY := (y div 3) * 3;
 for i := StartY to Pred(StartY + 3) do
 begin
   for j := StartX to Pred(StartX + 3) do
   begin
     if FGrid[i * 9 + j] = val then
     begin
       Result := False;
       Exit;
     end;
   end;
 end;
 Result := True;

end;

function TSudokuSolver.ToString: string; var

 sb: string;
 i: Integer;
 j: Integer;
 c: char;

begin

 sb := ;
 for i := 0 to 8 do
 begin
   for j := 0 to 8 do
   begin
     c := (IntToStr(FGrid[i * 9 + j]) + '0')[1];
     sb := sb + c + ' ';
     if (j = 2) or (j = 5) then sb := sb + '| ';
   end;
   sb := sb + #13#10;
   if (i = 2) or (i = 5) then
     sb := sb + '-----+-----+-----' + #13#10;
 end;
 Result := sb;

end;

procedure TSudokuSolver.PlaceNumber(pos: Integer); var

 n: Integer;

begin

 if Pos = 81 then
   raise Exception.Create('Finished!');
 if FGrid[pos] > 0 then
 begin
   PlaceNumber(Succ(pos));
   Exit;
 end;
 for n := 1 to 9 do
 begin
   if CheckValidity(n, pos mod 9, pos div 9) then
   begin
     FGrid[pos] := n;
     PlaceNumber(Succ(pos));
     FGrid[pos] := 0;
   end;
 end;

end;

constructor TSudokuSolver.Create(s: string); var

 lcv: Cardinal;

begin

 SetLength(FGrid, 81);
 for lcv := 0 to Pred(Length(s)) do
   FGrid[lcv] := StrToInt(s[Succ(lcv)]);

end;

procedure TSudokuSolver.Solve; begin

 try
   PlaceNumber(0);
   ShowMessage('Unsolvable');
 except
   ShowMessage((ExceptObject as Exception).Message);
   ShowMessage(ToString);
 end;

end;</lang> Usage: <lang delphi>var

 SudokuSolver: TSudokuSolver;

begin

 SudokuSolver := TSudokuSolver.Create('850002400' +
                                      '720000009' +
                                      '004000000' +
                                      '000107002' +
                                      '305000900' +
                                      '040000000' +
                                      '000080070' +
                                      '017000000' +
                                      '000036040');
 try
   SudokuSolver.Solve;
 finally
   FreeAndNil(SudokuSolver);
 end;

end;</lang>

Forth

Works with: 4tH version 3.60.0

<lang forth>include lib/interprt.4th include lib/istype.4th include lib/argopen.4th

\ --------------------- \ Variables \ ---------------------

81 string sudokugrid 9 array sudoku_row 9 array sudoku_col 9 array sudoku_box

\ ------------- \ 4tH interface \ -------------

>grid ( n2 a1 n1 -- n3)
 rot dup >r 9 chars * sudokugrid + dup >r swap
 0 do                                 ( a1 a2)
   over i chars + c@ dup is-digit     ( a1 a2 c f)
   if [char] 0 - over c! char+ else drop then
 loop                                 ( a1 a2)
 nip r> - 9 /  r> +                   ( n3)

0 s" 090004007" >grid s" 000007900" >grid s" 800000000" >grid s" 405800000" >grid s" 300000002" >grid s" 000009706" >grid s" 000000004" >grid s" 003500000" >grid s" 200600080" >grid drop

\ --------------------- \ Logic \ --------------------- \ Basically : \ Grid is parsed. All numbers are put into sets, which are \ implemented as bitmaps (sudoku_row, sudoku_col, sudoku_box) \ which represent sets of numbers in each row, column, box. \ only one specific instance of a number can exist in a \ particular set.

\ SOLVER is recursively called \ SOLVER looks for the next best guess using FINDNEXTSPACE \ tries this trail down... if fails, backtracks... and tries \ again.


\ Grid Related

xy 9 * + ; \ x y -- offset ;
getrow 9 / ;
getcol 9 mod ;
getbox dup getrow 3 / 3 * swap getcol 3 / + ;

\ Puts and gets numbers from/to grid only

setnumber sudokugrid + c! ; \ n position --
getnumber sudokugrid + c@ ;
cleargrid sudokugrid 81 bounds do 0 i c! loop ;

\ -------------- \ Set related: sets are sudoku_row, sudoku_col, sudoku_box

\ ie x y --  ; adds x into bitmap y

addbits_row cells sudoku_row + dup @ rot 1 swap lshift or swap ! ;
addbits_col cells sudoku_col + dup @ rot 1 swap lshift or swap ! ;
addbits_box cells sudoku_box + dup @ rot 1 swap lshift or swap ! ;

\ ie x y --  ; remove number x from bitmap y

removebits_row cells sudoku_row + dup @ rot 1 swap lshift invert and swap ! ;
removebits_col cells sudoku_col + dup @ rot 1 swap lshift invert and swap ! ;
removebits_box cells sudoku_box + dup @ rot 1 swap lshift invert and swap ! ;

\ clears all bitsmaps to 0

clearbitmaps 9 0 do i cells
                    0 over sudoku_row + !
                    0 over sudoku_col + !
                    0 swap sudoku_box + !
          loop ;

\ Adds number to grid and sets

addnumber \ number position --
   2dup setnumber
   2dup getrow addbits_row
   2dup getcol addbits_col
        getbox addbits_box

\ Remove number from grid, and sets

removenumber \ position --
   dup getnumber swap    
   2dup getrow removebits_row
   2dup getcol removebits_col
   2dup getbox removebits_box
   nip 0 swap setnumber

\ gets bitmap at position, ie \ position -- bitmap

getrow_bits getrow cells sudoku_row + @ ;
getcol_bits getcol cells sudoku_col + @ ;
getbox_bits getbox cells sudoku_box + @ ;

\ position -- composite bitmap (or'ed)

getbits
   dup getrow_bits
   over getcol_bits
   rot getbox_bits or or

\ algorithm from c.l.f circa 1995 ? Will Baden

countbits ( number -- bits )
       [HEX] DUP  55555555 AND  SWAP  1 RSHIFT  55555555 AND  +
             DUP  33333333 AND  SWAP  2 RSHIFT  33333333 AND  +
             DUP  0F0F0F0F AND  SWAP  4 RSHIFT  0F0F0F0F AND  +
       [DECIMAL] 255 MOD

\ Try tests a number in a said position of grid \ Returns true if it's possible, else false.

try \ number position -- true/false
     getbits 1 rot lshift and 0=

\ --------------

parsegrid \ Parses Grid to fill sets.. Run before solver.
  sudokugrid                          \ to ensure all numbers are parsed into sets/bitmaps
  81 0 do
    dup i + c@                            
      dup if                              
        dup i try if                    
          i addnumber                          
        else
          unloop drop drop FALSE exit      
        then  
      else
        drop
      then
  loop
  drop
  TRUE

\ Morespaces? manually checks for spaces ... \ Obviously this can be optimised to a count var, done initially \ Any additions/subtractions made to the grid could decrement \ a 'spaces' variable.

morespaces?
    0  sudokugrid 81 bounds do i c@  0= if 1+ then loop ;
findnextmove \ -- n ; n = index next item, if -1 finished.
  -1  10                              \  index  prev_possibilities  --
                                      \  err... yeah... local variables, kind of...
  81 0 do
     i sudokugrid + c@ 0= IF
            i getbits countbits 9 swap -
            \ get bitmap and see how many possibilities
            \ stack diagram:
            \ index prev_possibilities  new_possiblities --
            2dup > if          
                                      \ if new_possibilities < prev_possibilities...
                nip nip i swap  
                                      \ new_index new_possibilies --
            else                      \ else prev_possibilities < new possibilities, so:
                drop                  \ new_index new_possibilies --        
            then                
     THEN
  loop
  drop

\ findnextmove returns index of best next guess OR returns -1 \ if no more guesses. You then have to check to see if there are \ spaces left on the board unoccupied. If this is the case, you \ need to back up the recursion and try again.

solver
    findnextmove
        dup 0< if
            morespaces? if
               drop false exit
            else
               drop true exit
            then
        then
    10 1 do
       i over try if          
          i over addnumber
          recurse  if
               drop unloop TRUE EXIT
          else
               dup removenumber
          then
       then
    loop
    drop FALSE

\ SOLVER

startsolving
  clearbitmaps                        \ reparse bitmaps and reparse grid
  parsegrid                           \ just in case..
  solver
  AND

\ --------------------- \ Display Grid \ ---------------------

\ Prints grid nicely

.sudokugrid
 CR CR
 sudokugrid
 81 0 do
   dup i + c@ .
   i 1+
     dup 3 mod 0= if
        dup 9 mod 0= if
           CR
           dup 27 mod 0= if
             dup 81 < if ." ------+-------+------" CR then
           then
        else
          ." | "
        then      
     then
   drop
 loop
 drop
 CR

\ --------------------- \ Higher Level Words \ ---------------------

checkifoccupied ( offset -- t/f)
   sudokugrid + c@
add ( n x y --)
   xy 2dup
     dup checkifoccupied if
       dup removenumber
     then
   try if
     addnumber
     .sudokugrid
   else
     CR ." Not a valid move. " CR
     2drop
   then
rm
   xy removenumber
   .sudokugrid
clearit
   cleargrid
   clearbitmaps
   .sudokugrid
solveit
 CR 
 startsolving
 if
   ." Solution found!" CR .sudokugrid
 else
   ." No solution found!" CR CR
 then
showit .sudokugrid ;

\ Print help menu

help
 CR
 ." Type clearit     ; to clear grid " CR
 ."      1-9 x y add ; to add 1-9 to grid at x y (0 based) " CR
 ."      x y rm      ; to remove number at x y " CR
 ."      showit      ; redisplay grid " CR
 ."      solveit     ; to solve " CR
 ."      help        ; for help " CR
 CR

\ --------------------- \ Execution starts here \ ---------------------

godoit
   clearbitmaps
   parsegrid if
     CR ." Grid valid!"
   else
     CR ." Warning: grid invalid!"
   then
   .sudokugrid
   help

\ ------------- \ 4tH interface \ -------------

read-sudoku
 input 1 arg-open 0
 begin dup 9 < while refill while 0 parse >grid repeat
 drop close
bye quit ;

create wordlist \ dictionary

 ," clearit" ' clearit ,
 ," add"     ' add ,
 ," rm"      ' rm ,
 ," showit"  ' showit ,
 ," solveit" ' solveit ,
 ," quit"    ' bye ,
 ," exit"    ' bye ,
 ," bye"     ' bye ,
 ," q"       ' bye ,
 ," help"    ' help ,
 NULL ,

wordlist to dictionary

noname ." Unknown command '" type ." '" cr ; is NotFound
                                      \ sudoku interpreter
sudoku
 argn 1 > if read-sudoku then
 godoit
 begin
   ." OK" cr
   refill drop ['] interpret
   catch if ." Error" cr then
 again

sudoku</lang>

Fortran

Works with: Fortran version 90 and later

This implementation uses a brute force method. The subroutine solve recursively checks valid entries using the rules defined in the function is_safe. When solve is called beyond the end of the sudoku, we know that all the currently entered values are valid. Then the result is displayed. <lang fortran>program sudoku

 implicit none
 integer, dimension (9, 9) :: grid
 integer, dimension (9, 9) :: grid_solved
 grid = reshape ((/               &
   & 0, 0, 3, 0, 2, 0, 6, 0, 0,   &
   & 9, 0, 0, 3, 0, 5, 0, 0, 1,   &
   & 0, 0, 1, 8, 0, 6, 4, 0, 0,   &
   & 0, 0, 8, 1, 0, 2, 9, 0, 0,   &
   & 7, 0, 0, 0, 0, 0, 0, 0, 8,   &
   & 0, 0, 6, 7, 0, 8, 2, 0, 0,   &
   & 0, 0, 2, 6, 0, 9, 5, 0, 0,   &
   & 8, 0, 0, 2, 0, 3, 0, 0, 9,   &
   & 0, 0, 5, 0, 1, 0, 3, 0, 0/), &
   & shape = (/9, 9/),            &
   & order = (/2, 1/))
 call pretty_print (grid)
 call solve (1, 1)
 write (*, *)
 call pretty_print (grid_solved)

contains

 recursive subroutine solve (i, j)
   implicit none
   integer, intent (in) :: i
   integer, intent (in) :: j
   integer :: n
   integer :: n_tmp
   if (i > 9) then
     grid_solved = grid
   else
     do n = 1, 9
       if (is_safe (i, j, n)) then
         n_tmp = grid (i, j)
         grid (i, j) = n
         if (j == 9) then
           call solve (i + 1, 1)
         else
           call solve (i, j + 1)
         end if
         grid (i, j) = n_tmp
       end if
     end do
   end if
 end subroutine solve
 function is_safe (i, j, n) result (res)
   implicit none
   integer, intent (in) :: i
   integer, intent (in) :: j
   integer, intent (in) :: n
   logical :: res
   integer :: i_min
   integer :: j_min
   if (grid (i, j) == n) then
     res = .true.
     return
   end if
   if (grid (i, j) /= 0) then
     res = .false.
     return
   end if
   if (any (grid (i, :) == n)) then
     res = .false.
     return
   end if
   if (any (grid (:, j) == n)) then
     res = .false.
     return
   end if
   i_min = 1 + 3 * ((i - 1) / 3)
   j_min = 1 + 3 * ((j - 1) / 3)
   if (any (grid (i_min : i_min + 2, j_min : j_min + 2) == n)) then
     res = .false.
     return
   end if
   res = .true.
 end function is_safe
 subroutine pretty_print (grid)
   implicit none
   integer, dimension (9, 9), intent (in) :: grid
   integer :: i
   integer :: j
   character (*), parameter :: bar = '+-----+-----+-----+'
   character (*), parameter :: fmt = '(3 ("|", i0, 1x, i0, 1x, i0), "|")'
   write (*, '(a)') bar
   do j = 0, 6, 3
     do i = j + 1, j + 3
       write (*, fmt) grid (i, :)
     end do
     write (*, '(a)') bar
   end do
 end subroutine pretty_print

end program sudoku</lang> Output:

+-----+-----+-----+
|0 0 3|0 2 0|6 0 0|
|9 0 0|3 0 5|0 0 1|
|0 0 1|8 0 6|4 0 0|
+-----+-----+-----+
|0 0 8|1 0 2|9 0 0|
|7 0 0|0 0 0|0 0 8|
|0 0 6|7 0 8|2 0 0|
+-----+-----+-----+
|0 0 2|6 0 9|5 0 0|
|8 0 0|2 0 3|0 0 9|
|0 0 5|0 1 0|3 0 0|
+-----+-----+-----+

+-----+-----+-----+
|4 8 3|9 2 1|6 5 7|
|9 6 7|3 4 5|8 2 1|
|2 5 1|8 7 6|4 9 3|
+-----+-----+-----+
|5 4 8|1 3 2|9 7 6|
|7 2 9|5 6 4|1 3 8|
|1 3 6|7 9 8|2 4 5|
+-----+-----+-----+
|3 7 2|6 8 9|5 1 4|
|8 1 4|2 5 3|7 6 9|
|6 9 5|4 1 7|3 8 2|
+-----+-----+-----+

Go

Solution using Knuth's DLX. This code follows his paper fairly closely. Input to function solve is an 81 character string. This seems to be a conventional computer representation for Sudoku puzzles. <lang go>package main

import "fmt"

// sudoku puzzle representation is an 81 character string var puzzle = "" +

   "394  267 " +
   "   3  4  " +
   "5  69  2 " +
   " 45   9  " +
   "6       7" +
   "  7   58 " +
   " 1  67  8" +
   "  9  8   " +
   " 264  735"

func main() {

   printGrid("puzzle:", puzzle)
   if s := solve(puzzle); s == "" {
       fmt.Println("no solution")
   } else {
       printGrid("solved:", s)
   }

}

// print grid (with title) from 81 character string func printGrid(title, s string) {

   fmt.Println(title)
   for r, i := 0, 0; r < 9; r, i = r+1, i+9 {
       fmt.Printf("%c %c %c | %c %c %c | %c %c %c\n", s[i], s[i+1], s[i+2],
           s[i+3], s[i+4], s[i+5], s[i+6], s[i+7], s[i+8])
       if r == 2 || r == 5 {
           fmt.Println("------+-------+------")
       }
   }

}

// solve puzzle in 81 character string format. // if solved, result is 81 character string. // if not solved, result is the empty string. func solve(u string) string {

   // construct an dlx object with 324 constraint columns.
   // other than the number 324, this is not specific to sudoku.
   d := newDlxObject(324)
   // now add constraints that define sudoku rules.
   for r, i := 0, 0; r < 9; r++ {
       for c := 0; c < 9; c, i = c+1, i+1 {
           b := r/3*3 + c/3
           n := int(u[i] - '1')
           if n >= 0 && n < 9 {
               d.addRow([]int{i, 81 + r*9 + n, 162 + c*9 + n,
                   243 + b*9 + n})
           } else {
               for n = 0; n < 9; n++ {
                   d.addRow([]int{i, 81 + r*9 + n, 162 + c*9 + n,
                       243 + b*9 + n})
               }
           }
       }
   }
   // run dlx.  not sudoku specific.
   d.search()
   // extract the sudoku-specific 81 character result from the dlx solution.
   return d.text()

}

// Knuth's data object type x struct {

   c          *y
   u, d, l, r *x
   // except x0 is not Knuth's.  it's pointer to first constraint in row,
   // so that the sudoku string can be constructed from the dlx solution.
   x0 *x

}

// Knuth's column object type y struct {

   x
   s int // size
   n int // name

}

// an object to hold the matrix and solution type dlx struct {

   ch []y  // all column headers
   h  *y   // ch[0], the root node
   o  []*x // solution

}

// constructor creates the column headers but no rows. func newDlxObject(nCols int) *dlx {

   ch := make([]y, nCols+1)
   h := &ch[0]
   d := &dlx{ch, h, nil}
   h.c = h
   h.l = &ch[nCols].x
   ch[nCols].r = &h.x
   nh := ch[1:]
   for i := range ch[1:] {
       hi := &nh[i]
       ix := &hi.x
       hi.n = i
       hi.c = hi
       hi.u = ix
       hi.d = ix
       hi.l = &h.x
       h.r = ix
       h = hi
   }
   return d

}

// rows define constraints func (d *dlx) addRow(nr []int) {

   if len(nr) == 0 {
       return
   }
   r := make([]x, len(nr))
   x0 := &r[0]
   for x, j := range nr {
       ch := &d.ch[j+1]
       ch.s++
       np := &r[x]
       np.c = ch
       np.u = ch.u
       np.d = &ch.x
       np.l = &r[(x+len(r)-1)%len(r)]
       np.r = &r[(x+1)%len(r)]
       np.u.d, np.d.u, np.l.r, np.r.l = np, np, np, np
       np.x0 = x0
   }

}

// extracts 81 character sudoku string func (d *dlx) text() string {

   b := make([]byte, len(d.o))
   for _, r := range d.o {
       x0 := r.x0
       b[x0.c.n] = byte(x0.r.c.n%9) + '1'
   }
   return string(b)

}

// the dlx algorithm func (d *dlx) search() bool {

   h := d.h
   j := h.r.c
   if j == h {
       return true
   }
   c := j 
   for minS := j.s; ; {
       j = j.r.c
       if j == h {
           break
       }
       if j.s < minS {
           c, minS = j, j.s
       }
   }
   cover(c)
   k := len(d.o)
   d.o = append(d.o, nil)
   for r := c.d; r != &c.x; r = r.d {
       d.o[k] = r
       for j := r.r; j != r; j = j.r {
           cover(j.c)
       }
       if d.search() {
           return true
       }
       r = d.o[k]
       c = r.c
       for j := r.l; j != r; j = j.l {
           uncover(j.c)
       }
   }
   d.o = d.o[:len(d.o)-1]
   uncover(c)
   return false

}

func cover(c *y) {

   c.r.l, c.l.r = c.l, c.r
   for i := c.d; i != &c.x; i = i.d {
       for j := i.r; j != i; j = j.r {
           j.d.u, j.u.d = j.u, j.d
           j.c.s--
       }
   }

}

func uncover(c *y) {

   for i := c.u; i != &c.x; i = i.u {
       for j := i.l; j != i; j = j.l {
           j.c.s++
           j.d.u, j.u.d = j, j
       }
   }
   c.r.l, c.l.r = &c.x, &c.x

}</lang> Output:

puzzle:
3 9 4 |     2 | 6 7  
      | 3     | 4    
5     | 6 9   |   2  
------+-------+------
  4 5 |       | 9    
6     |       |     7
    7 |       | 5 8  
------+-------+------
  1   |   6 7 |     8
    9 |     8 |      
  2 6 | 4     | 7 3 5
solved:
3 9 4 | 8 5 2 | 6 7 1
2 6 8 | 3 7 1 | 4 5 9
5 7 1 | 6 9 4 | 8 2 3
------+-------+------
1 4 5 | 7 8 3 | 9 6 2
6 8 2 | 9 4 5 | 3 1 7
9 3 7 | 1 2 6 | 5 8 4
------+-------+------
4 1 3 | 5 6 7 | 2 9 8
7 5 9 | 2 3 8 | 1 4 6
8 2 6 | 4 1 9 | 7 3 5

Groovy

Adaptive "Non-guessing Then Guessing" Solution

Non-guessing part is iterative. Guessing part is recursive. Implementation uses exception handling to back out of bad guesses. <lang groovy>final CELL_VALUES = ('1'..'9')

class GridException extends Exception {

   GridException(String message) { super(message) }

}

def string2grid = { string ->

   assert string.size() == 81
   (0..8).collect { i -> (0..8).collect { j -> string[9*i+j] } }

}

def gridRow = { grid, slot -> grid[slot.i] as Set }

def gridCol = { grid, slot -> grid.collect { it[slot.j] } as Set }

def gridBox = { grid, slot ->

   def t, l; (t, l) = [slot.i.intdiv(3)*3, slot.j.intdiv(3)*3]
   (0..2).collect { row -> (0..2).collect { col -> grid[t+row][l+col] } }.flatten() as Set

}

def slotList = { grid ->

   def slots = (0..8).collect { i -> (0..8).findAll { j -> grid[i][j] == '.' } \
           .collect {j -> [i: i, j: j] } }.flatten()

}

def assignCandidates = { grid, slots = slotList(grid) ->

   slots.each { slot ->
       def unavailable = [gridRow, gridCol, gridBox].collect { it(grid, slot) }.sum() as Set
       slot.candidates = CELL_VALUES - unavailable
   }
   slots.sort { - it.candidates.size() }
   if (slots && ! slots[-1].candidates) {
       throw new GridException('Invalid Sudoku Grid, overdetermined slot: ' + slots[-1])
   }
   slots

}

def isSolved = { grid -> ! (grid.flatten().find { it == '.' }) }

def solve solve = { grid ->

   def slots = assignCandidates(grid)
   if (! slots) { return grid }
   while (slots[-1].candidates.size() == 1) {
       def slot = slots.pop()
       grid[slot.i][slot.j] = slot.candidates[0]
       if (! slots) { return grid }
       slots = assignCandidates(grid, slots)
   }
   if (! slots) { return grid } 
   def slot = slots.pop()
   slot.candidates.each {
       if (! isSolved(grid)) {
           try {
               def sGrid = grid.collect { row -> row.collect { cell -> cell } }
               sGrid[slot.i][slot.j] = it
               grid = solve(sGrid)
           } catch (GridException ge) {
               grid[slot.i][slot.j] = '.'
           }
       }
   }
   if (!isSolved(grid)) {
       slots = assignCandidates(grid)
       throw new GridException('Invalid Sudoku Grid, underdetermined slots: ' + slots)
   }
   grid

}</lang> Test/Benchmark Cases

Mentions of "exceptionally difficult" example in Wikipedia refer to this page: Exceptionally difficult Sudokus <lang groovy>def sudokus = [

 //Used in Curry solution:                             ~ 0.1 seconds
   '819..5.....2...75..371.4.6.4..59.1..7..3.8..2..3.62..7.5.7.921..64...9.....2..438',

 //Used in Perl and PicoLisp solutions:                ~ 0.1 seconds
   '53..247....2...8..1..7.39.2..8.72.49.2.98..7.79.....8.....3.5.696..1.3...5.69..1.',

 //Used in Fortran solution:                           ~ 0.1 seconds
   '..3.2.6..9..3.5..1..18.64....81.29..7.......8..67.82....26.95..8..2.3..9..5.1.3..',

 //Used in many other solutions, notably Ada:          ~ 0.1 seconds
   '394..267....3..4..5..69..2..45...9..6.......7..7...58..1..67..8..9..8....264..735',

 //Used in C# solution:                                ~ 0.2 seconds
   '97.3...6..6.75.........8.5.......67.....3.....539..2..7...25.....2.1...8.4...73..',

 //Used in Oz solution:                                ~ 0.2 seconds
   '4......6.5...8.9..3....1....2.7....1.9.....4.8....3.5....2....7..6.5...8.1......6',

 //Used in many other solutions, notably C++:          ~ 0.3 seconds
   '85...24..72......9..4.........1.7..23.5...9...4...........8..7..17..........36.4.',

 //Used in VBA solution:                               ~ 0.3 seconds
   '..1..5.7.92.6.......8...6...9..2.4.1.........3.4.8..9...7...3.......7.69.1.8..7..',

 //Used in Forth solution:                             ~ 0.8 seconds
   '.9...4..7.....79..8........4.58.....3.......2.....97.6........4..35.....2..6...8.',

 //3rd "exceptionally difficult" example in Wikipedia: ~ 2.3 seconds
   '12.3....435....1....4........54..2..6...7.........8.9...31..5.......9.7.....6...8',

 //Used in Curry solution:                             ~ 2.4 seconds
   '9..2..5...4..6..3...3.....6...9..2......5..8...7..4..37.....1...5..2..4...1..6..9',

 //"AL Escargot", so-called "hardest sudoku" (HA!):    ~ 3.0 seconds
   '1....7.9..3..2...8..96..5....53..9...1..8...26....4...3......1..4......7..7...3..',

 //1st "exceptionally difficult" example in Wikipedia: ~ 6.5 seconds
   '12.4..3..3...1..5...6...1..7...9.....4.6.3.....3..2...5...8.7....7.....5.......98',

 //Used in Bracmat and Scala solutions:                ~ 6.7 seconds
   '..............3.85..1.2.......5.7.....4...1...9.......5......73..2.1........4...9',

 //2nd "exceptionally difficult" example in Wikipedia: ~ 8.8 seconds
   '.......39.....1..5..3.5.8....8.9...6.7...2...1..4.......9.8..5..2....6..4..7.....',

 //Used in MATLAB solution:                            ~15   seconds
   '....839..1......3...4....7..42.3....6.......4....7..1..2........8...92.....25...6',

 //4th "exceptionally difficult" example in Wikipedia: ~29   seconds
   '..3......4...8..36..8...1...4..6..73...9..........2..5..4.7..686........7..6..5..']

sudokus.each { sudoku ->

   def grid = string2grid(sudoku)
   println '\nPUZZLE'
   grid.each { println it }

   println '\nSOLUTION'
   def start = System.currentTimeMillis()
   def solution = solve(grid)
   def elapsed = (System.currentTimeMillis() - start)/1000
   solution.each { println it }
   println "\nELAPSED: ${elapsed} seconds"

}</lang>

Output (last only):

PUZZLE
[., ., 3, ., ., ., ., ., .]
[4, ., ., ., 8, ., ., 3, 6]
[., ., 8, ., ., ., 1, ., .]
[., 4, ., ., 6, ., ., 7, 3]
[., ., ., 9, ., ., ., ., .]
[., ., ., ., ., 2, ., ., 5]
[., ., 4, ., 7, ., ., 6, 8]
[6, ., ., ., ., ., ., ., .]
[7, ., ., 6, ., ., 5, ., .]

SOLUTION
[1, 2, 3, 4, 5, 6, 7, 8, 9]
[4, 5, 7, 1, 8, 9, 2, 3, 6]
[9, 6, 8, 3, 2, 7, 1, 5, 4]
[2, 4, 9, 5, 6, 1, 8, 7, 3]
[5, 7, 6, 9, 3, 8, 4, 1, 2]
[8, 3, 1, 7, 4, 2, 6, 9, 5]
[3, 1, 4, 2, 7, 5, 9, 6, 8]
[6, 9, 5, 8, 1, 4, 3, 2, 7]
[7, 8, 2, 6, 9, 3, 5, 4, 1]

ELAPSED: 28.978 seconds

Haskell

Visit the Haskell wiki Sudoku

J

See Solving Sudoku in J.

Java

<lang java>public class Sudoku {

   private int mBoard[][];
   private int mBoardSize;
   private int mBoxSize;
   private boolean mRowSubset[][];
   private boolean mColSubset[][];
   private boolean mBoxSubset[][];
   public Sudoku(int board[][]) {
       mBoard = board;
       mBoardSize = mBoard.length;
       mBoxSize = (int)Math.sqrt(mBoardSize);
   }
   public void initSubsets() {
       mRowSubset = new boolean[mBoardSize][mBoardSize];
       mColSubset = new boolean[mBoardSize][mBoardSize];
       mBoxSubset = new boolean[mBoardSize][mBoardSize];
       for(int i = 0; i < mBoard.length; i++) {
           for(int j = 0; j < mBoard.length; j++) {
               int value = mBoard[i][j];
               if(value != 0)
                   setSubsetValue(i, j, value, true);
           }
       }
   }
   private void setSubsetValue(int i, int j, int value, boolean present) {
       mRowSubset[i][value - 1] = present;
       mColSubset[j][value - 1] = present;
       mBoxSubset[computeBoxNo(i, j)][value - 1] = present;
   }
   public boolean solve() {
       return solve(0, 0);
   }
   public boolean solve(int i, int j) {
       if(i == mBoardSize) {
           i = 0;
           if(++j == mBoardSize)
               return true;
       }
       if(mBoard[i][j] != 0)
           return solve(i + 1, j);
       for(int value = 1; value <= mBoardSize; value++)
           if(isValid(i, j, value)) {
               mBoard[i][j] = value;
               setSubsetValue(i, j, value, true);
               if(solve(i + 1, j))
                   return true;
               setSubsetValue(i, j, value, false);
           }
       mBoard[i][j] = 0;
       return false;
   }
   private boolean isValid(int i, int j, int val) {
       val--;
       boolean isPresent = mRowSubset[i][val] || mColSubset[j][val] || mBoxSubset[computeBoxNo(i, j)][val];
       return !isPresent;
   }
   private int computeBoxNo(int i, int j) {
       int boxRow = i / mBoxSize;
       int boxCol = j / mBoxSize;
       return boxRow * mBoxSize + boxCol;
   }
   public void print() {
       for(int i = 0; i < mBoardSize; i++) {
           if(i % mBoxSize == 0)
               System.out.println(" -----------------------");
           for(int j = 0; j < mBoardSize; j++) {
               if(j % mBoxSize == 0)
                   System.out.print("| ");
               System.out.print(mBoard[i][j] != 0 ? ((Object) (Integer.valueOf(mBoard[i][j]))) : " ");
               System.out.print(' ');
           }
           System.out.println("|");
       }
       System.out.println(" -----------------------");
   }

}</lang>

Mathematica

<lang mathematica>solve[array_] :=

NestWhile[
 Join @@ Function[newarray, 
     Function[{i, j}, 
       Table[ReplacePart[newarray, 
         Position[newarray, 0, {2}, 1]1 -> n], {n, 
         Select[Range@9, 
          FreeQ[newarrayi, #] && FreeQ[newarrayAll, j, #] && 
            FreeQ[Partition[
               newarray, {3, 3}][[Sequence @@ 
                Quotient[{i, j}, 3, -2]]], #] &]}]] @@ 
      Position[newarray, 0, {2}, 1]1] /@ # &, {array}, ! 
   FreeQ[#, 0] &]</lang>

Example: <lang>solve[{{9, 7, 0, 3, 0, 0, 0, 6, 0},

 {0, 6, 0, 7, 5, 0, 0, 0, 0},
 {0, 0, 0, 0, 0, 8, 0, 5, 0},
 {0, 0, 0, 0, 0, 0, 6, 7, 0},
 {0, 0, 0, 0, 3, 0, 0, 0, 0},
 {0, 5, 3, 9, 0, 0, 2, 0, 0},
 {7, 0, 0, 0, 2, 5, 0, 0, 0},
 {0, 0, 2, 0, 1, 0, 0, 0, 8},
 {0, 4, 0, 0, 0, 7, 3, 0, 0}}]</lang>

Output:

{{{9, 7, 5, 3, 4, 2, 8, 6, 1}, {8, 6, 1, 7, 5, 9, 4, 3, 2}, {3, 2, 4, 
   1, 6, 8, 9, 5, 7}, {2, 1, 9, 5, 8, 4, 6, 7, 3}, {4, 8, 7, 2, 3, 6, 
   5, 1, 9}, {6, 5, 3, 9, 7, 1, 2, 8, 4}, {7, 3, 8, 4, 2, 5, 1, 9, 
   6}, {5, 9, 2, 6, 1, 3, 7, 4, 8}, {1, 4, 6, 8, 9, 7, 3, 2, 5}}}

MATLAB

This solution impliments a recursive, depth-first search of the possible values unfilled sudoku cells can take. The search tree is pruned using logical deduction rules and takes about a minute to solve some of the more difficult puzzles. This code can be cleaned by making the main code blocks, denoted by "%% [Block Title]," into their own separate functions. This can also be further improved by implementing a Sudoku class and making this solver a member function. There are also several lines of code that can be vectorized to improve efficiency, but at the expense of readability.

For this to work, this code must be placed in a file named "sudokuSolver.m" <lang MATLAB>function solution = sudokuSolver(sudokuGrid)

   %Define what each of the sub-boxes of the sudoku grid are by defining
   %the start and end coordinates of each sub-box. The indecies represent
   %the column and row of a grid coordinate on the actual sudoku grid.
   %The contents of each cell with the same grid coordinates contain the
   %information to determine which sub-box that grid coordinate is
   %contained in on the sudoku grid. The array in position 1, i.e.
   %subBoxes{row,column}(1), represents the row indecies of the subbox.
   %The array in position 2, i.e. subBoxes{row,column}(2),represents the
   %column indecies of the subbox.
   
   subBoxes(1:9,1:9) = Template:(1:3),(1:3);
   subBoxes(4:6,:)= Template:(4:6),(1:3);
   subBoxes(7:9,:)= Template:(7:9),(1:3);
   
   for column = (4:6)
       for row = (1:9) 
           subBoxes{row,column}(2)= {4:6};
       end
   end
   for column = (7:9)
       for row = (1:9) 
           subBoxes{row,column}(2)= {7:9};
       end
   end
   %Generate a cell of arrays which contain the possible values of the
   %sudoku grid for each cell in the grid. The possible values a specific
   %grid coordinate can take share the same indices as the sudoku grid
   %coordinate they represent.
   %For example sudokuGrid(m,n) can be possibly filled in by the
   %values stored in the array at possibleValues(m,n).
   possibleValues(1:9,1:9) = { (1:9) };
   
   %Filter the possibleValues so that no entry exists for coordinates that
   %have already been filled in. This will replace any array with an empty
   %array in the possibleValues cell matrix at the coordinates of a grid
   %already filled in the sudoku grid.
   possibleValues( ~isnan(sudokuGrid) )={[]};
   
   %Iterate through each grid coordinate and filter out the possible
   %values for that grid point that aren't alowed by the rules given the
   %current values that are filled in. Or, if there is only one possible
   %value for the current coordinate, fill it in.
   
   solution = sudokuGrid; %so the original sudoku input isn't modified
   memory = 0; %contains the previous iterations possibleValues
   dontStop = true; %stops the while loop when nothing else can be reasoned about the sudoku
   
   while( dontStop )

%% Process of elimination deduction method

       while( ~isequal(possibleValues,memory) ) %Stops using the process of elimination deduction method when this deduction rule stops working
           memory = possibleValues; %Copies the current possibleValues into memory, for the above conditional on the next iteration.
           %Iterate through everything
           for row = (1:9) 
               for column = (1:9)
                   if isnan( solution(row,column) ) %If grid coordinate hasn't been filled in, try to determine it's value.
                       %Look at column to see what values have already
                       %been filled in and thus the current grid
                       %coordinate can't be
                       removableValues = solution( ~isnan(solution(:,column)),column );
                       %If there are any values that have been assigned to
                       %other cells in the same column, filter those out
                       %of the current cell's possiblValues
                       if ~isempty(removableValues)
                           for m = ( 1:numel(removableValues) )
                               possibleValues{row,column}( possibleValues{row,column}==removableValues(m) )=[];
                           end
                       end
                       %If the current grid coordinate can only atain one
                       %possible value, assign it that value
                       if numel( possibleValues{row,column} ) == 1
                           solution(row,column) = possibleValues{row,column};
                           possibleValues(row,column)={[]};
                       end
                   end  %end if
                   if isnan( solution(row,column) ) %If grid coordinate hasn't been filled in, try to determine it's value. 
                       %Look at row to see what values have already
                       %been filled in and thus the current grid
                       %coordinate can't be
                       removableValues = solution( row,~isnan(solution(row,:)) );
                       %If there are any values that have been assigned to
                       %other cells in the same row, filter those out
                       %of the current cell's possiblValues
                       if ~isempty(removableValues)
                           for m = ( 1:numel(removableValues) )
                               possibleValues{row,column}( possibleValues{row,column}==removableValues(m) )=[];
                           end
                       end
                       
                       %If the current grid coordinate can only atain one
                       %possible value, assign it that value
                       if numel( possibleValues{row,column} ) == 1
                           solution(row,column) = possibleValues{row,column};
                           possibleValues(row,column)={[]};
                       end
                   end %end if
                   if isnan( solution(row,column) ) %If grid coordinate hasn't been filled in, try to determine it's value. 
                       
                       %Look at sub-box to see if any possible values can be
                       %filtered out. First pull the boundaries of the sub-box
                       %containing the current array coordinate           
                       currentBoxBoundaries=subBoxes{row,column};
                       %Then pull the sub-boxes values out of the solution
                       box = solution(currentBoxBoundaries{:});
                       %Look at sub-box to see what values have already
                       %been filled in and thus the current grid
                       %coordinate can't be
                       removableValues = box( ~isnan(box) );
                       %If there are any values that have been assigned to
                       %other cells in the same sub-box, filter those out
                       %of the current cell's possiblValues
                       if ~isempty(removableValues)
                           for m = ( 1:numel(removableValues) )
                               possibleValues{row,column}( possibleValues{row,column}==removableValues(m) )=[];
                           end
                       end
                       
                       %If the current grid coordinate can only atain one
                       %possible value, assign it that value
                       if numel( possibleValues{row,column} ) == 1
                           solution(row,column) = possibleValues{row,column};
                           possibleValues(row,column)={[]};
                       end
                   end %end if
                   
               end %end for column
           end %end for row
       end %stop process of elimination
       

%% Check that there are no contradictions in the solved grid coordinates.

       %Check that each row at most contains one of each of the integers
       %from 1 to 9
       if ~isempty( find( histc( solution,(1:9),1 )>1 ) )
           solution = false;
           return
       end
       
       %Check that each column at most contains one of each of the integers
       %from 1 to 9
       if ~isempty( find( histc( solution,(1:9),2 )>1 ) )
           solution = false;
           return
       end
       
       %Check that each sub-box at most contains one of each of the integers
       %from 1 to 9
       subBoxBins = zeros(9,9);
       counter = 0;
       for row = [2 5 8]
           for column = [2 5 8]
               counter = counter +1;
               
               %because the sub-boxes are extracted as square matricies,
               %we need to reshape them into row vectors so all of the 
               %boxes can be input into histc simultaneously
               subBoxBins(counter,:) = reshape( solution(subBoxes{row,column}{:}),1,9 ); 
           end
       end
       if ~isempty( find( histc( subBoxBins,(1:9),2 )>1 ) )
           solution = false;
           return
       end
               
       %Check to make sure there are no grid coordinates that are not
       %filled in and have no possible values.
       
       [rowStack,columnStack] = find(isnan(solution)); %extracts the indicies of the unsolved grid coordinates
       if (numel(rowStack) > 0)
           
           for counter = (1:numel(rowStack))
               if isempty(possibleValues{rowStack(counter),columnStack(counter)})
                   solution = false;
                   return
               end  
           end
       
       %if there are no more grid coordinates to be filed in then the
       %sudoku is solved and we can return the solution without further 
       %computation
       elseif (numel(rowStack) == 0)
           return
       end   
       

%% Use the unique relative compliment of sets deduction method

       %Because no more information can be determined by the process of
       %ellimination we have to try a new method of reasoning. Now we will
       %look at the possible values a cell can take. If there is a value that
       %that grid coordinate can take but no other coordinates in the same row,
       %column or sub-box can take that value then we assign that coordinate
       %that value.
       keepGoing = true; %signals to keep applying rules to the current grid-coordinate because it hasn't been solved using previous rules
       dontStop = false; %if this method doesn't figure anything out, this will terminate the top level while loop
       
       [rowStack,columnStack] = find(isnan(solution)); %This will also take care of the case where the sudoku is solved
       counter = 0; %makes sure the loop terminates when there are no more cells to consider
       
       while( keepGoing && (counter < numel(rowStack)) ) %stop this method of reasoning when the value of one of the cells has been determined and return to the process of elimination method
       
           counter = counter + 1;
           
           row = rowStack(counter);
           column = columnStack(counter);
           
           gridPossibles = [possibleValues{row,column}];
           
           coords = (1:9);
           coords(column) = [];
           rowPossibles = [possibleValues{row,coords}]; %extract possible values for everything in the same row except the current grid coordinate
           
           totalMatches = zeros( numel(gridPossibles),1 ); %preallocate for speed
           
           %count how many times a possible value for the current cell
           %appears as a possible value for the cells in the same row
           for n = ( 1:numel(gridPossibles) )
               totalMatches(n) = sum( (rowPossibles == gridPossibles(n)) ); 
           end
           
           %remove any possible values for the current cell that have
           %matches in other cells
           gridPossibles = gridPossibles(totalMatches==0);
           
           %if there is only one possible value that the current cell can
           %take that aren't shared by other cells, assign that value to
           %the current cell.
           if numel(gridPossibles) == 1
               
               solution(row,column) = gridPossibles;
               possibleValues(row,column)={[]};
               keepGoing = false; %stop this method of deduction and return to the process of elimination
               dontStop = true; %keep the top level loop going
               
           end
           
           if(keepGoing) %do the same as above but for the current cell's column
               gridPossibles = [possibleValues{row,column}];
               
               coords = (1:9);
               coords(row) = [];
               columnPossibles = [possibleValues{coords,column}];
               totalMatches = zeros( numel(gridPossibles),1 );
               for n = ( 1:numel(gridPossibles) )
                   totalMatches(n) = sum( (columnPossibles == gridPossibles(n)) );
               end
               gridPossibles = gridPossibles(totalMatches==0);
               if numel(gridPossibles) == 1
                   solution(row,column) = gridPossibles;
                   possibleValues(row,column)={[]};
                   keepGoing = false;
                   dontStop = true;
               end
           end
           
           if(keepGoing) %do the same as above but for the current cell's sub-box
               gridPossibles = [possibleValues{row,column}];
               
               currentBoxBoundaries = subBoxes{row,column};
               subBoxPossibles = [];
               for m = currentBoxBoundaries{1}
                   for n = currentBoxBoundaries{2}
                       if ~((m == row) && (n == column))
                           subBoxPossibles = [subBoxPossibles possibleValues{m,n}];
                       end
                   end
               end
               totalMatches = zeros( numel(gridPossibles),1 );
               for n = ( 1:numel(gridPossibles) )
                   totalMatches(n) = sum( (subBoxPossibles == gridPossibles(n)) );
               end
               gridPossibles = gridPossibles(totalMatches==0);
               if numel(gridPossibles) == 1
                   solution(row,column) = gridPossibles;
                   possibleValues(row,column)={[]};
                   keepGoing = false;
                   dontStop = true;
               end
           end %end 
           
       end %end  set comliment rule while loop 
   end %end top-level while loop

%% Depth-first search of the solution tree

   %There is no more reasoning that can solve the puzzle so now it is time
   %for a depth-first search of the possible answers, basically
   %guess-and-check. This is implimented recursively.
   
   [rowStack,columnStack] = find(isnan(solution)); %Get all of the unsolved cells
   
   if (numel(rowStack) > 0) %If all of the above stuff terminates then there will be at least one grid coordinate not filled in
               
       %Treat the rowStack and columnStack like stacks, and pop the top
       %value off the stack to act as the current node whose
       %possibleValues to search through, then assign the possible values
       %of that grid coordinate to a variable that holds that values to
       %search through
       searchTreeNodes = possibleValues{rowStack(1),columnStack(1)}; 
       
       keepSearching = true; %used to continue the search
       counter = 0; %counts the amount of possible values searched for the current node
       tempSolution = solution; %used so that the solution is not overriden until a solution hase been found
       
       while( keepSearching && (counter < numel(searchTreeNodes)) ) %stop recursing if we run out of possible values for the current node
       
           counter = counter + 1;
           tempSolution(rowStack(1),columnStack(1)) = searchTreeNodes(counter); %assign a possible value to the current node in the tree
           tempSolution = sudokuSolver(tempSolution); %recursively call the solver with the current guess value for the current grid coordinate           
           
           if ~islogical(tempSolution) %if tempSolution is not a boolean but a valid sudoku stop recursing and set solution to tempSolution
              keepSearching = false;
              solution = tempSolution;
           elseif counter == numel(searchTreeNodes) %if we have run out of guesses for the current node, stop recursing and return a value of "false" for the solution
              solution = false;
           else %reset tempSolution to the current state of the board and try the next guess for the possible value of the current cell
              tempSolution = solution;
           end
           
       end %end recursion
   end  %end if 
   

%% End of program end %end sudokuSolver</lang> Test Input: All empty cells must have a value of NaN. <lang MATLAB>sudoku = [NaN NaN NaN NaN 8 3 9 NaN NaN

    1   NaN   NaN   NaN   NaN   NaN   NaN     3   NaN
  NaN   NaN     4   NaN   NaN   NaN   NaN     7   NaN
  NaN     4     2   NaN     3   NaN   NaN   NaN   NaN
    6   NaN   NaN   NaN   NaN   NaN   NaN   NaN     4
  NaN   NaN   NaN   NaN     7   NaN   NaN     1   NaN
  NaN     2   NaN   NaN   NaN   NaN   NaN   NaN   NaN
  NaN     8   NaN   NaN   NaN     9     2   NaN   NaN
  NaN   NaN   NaN     2     5   NaN   NaN   NaN     6]</lang>

Output: <lang MATLAB>solution =

    7     6     5     4     8     3     9     2     1
    1     9     8     7     2     6     4     3     5
    2     3     4     9     1     5     6     7     8
    8     4     2     5     3     1     7     6     9
    6     1     7     8     9     2     3     5     4
    3     5     9     6     7     4     8     1     2
    9     2     6     1     4     7     5     8     3
    5     8     1     3     6     9     2     4     7
    4     7     3     2     5     8     1     9     6</lang>

OCaml

uses the library ocamlgraph <lang ocaml>(* Ocamlgraph demo program: solving the Sudoku puzzle using graph coloring

  Copyright 2004-2007 Sylvain Conchon, Jean-Christophe Filliatre, Julien Signoles
  This software is free software; you can redistribute it and/or modify 
  it under the terms of the GNU Library General Public License version 2,
  with the special exception on linking described in file LICENSE.
  This software is distributed in the hope that it will be useful,
  but WITHOUT ANY WARRANTY; without even the implied warranty of
  MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. *)

open Format open Graph

(* We use undirected graphs with nodes containing a pair of integers

  (the cell coordinates in 0..8 x 0..8).
  The integer marks of the nodes will store the colors. *)

module G = Imperative.Graph.Abstract(struct type t = int * int end)

(* The Sudoku grid = a graph with 9x9 nodes *) let g = G.create ()

(* We create the 9x9 nodes, add them to the graph and keep them in a matrix

  for later access *)

let nodes =

 let new_node i j = let v = G.V.create (i, j) in G.add_vertex g v; v in
 Array.init 9 (fun i -> Array.init 9 (new_node i))

let node i j = nodes.(i).(j) (* shortcut for easier access *)

(* We add the edges:

  two nodes are connected whenever they can't have the same value,
  i.e. they belong to the same line, the same column or the same 3x3 group *)

let () =

 for i = 0 to 8 do for j = 0 to 8 do
   for k = 0 to 8 do
     if k <> i then G.add_edge g (node i j) (node k j);
     if k <> j then G.add_edge g (node i j) (node i k);
   done;
   let gi = 3 * (i / 3) and gj = 3 * (j / 3) in
   for di = 0 to 2 do for dj = 0 to 2 do
     let i' = gi + di and j' = gj + dj in
     if i' <> i || j' <> j then G.add_edge g (node i j) (node i' j')
   done done
 done done

(* Displaying the current state of the graph *) let display () =

 for i = 0 to 8 do
   for j = 0 to 8 do printf "%d" (G.Mark.get (node i j)) done;
   printf "\n";
 done;
 printf "@?"

(* We read the initial constraints from standard input and we display g *) let () =

 for i = 0 to 8 do
   let s = read_line () in
   for j = 0 to 8 do match s.[j] with
     | '1'..'9' as ch -> G.Mark.set (node i j) (Char.code ch - Char.code '0')
     | _ -> ()
   done
 done;
 display ();
 printf "---------@."

(* We solve the Sudoku by 9-coloring the graph g and we display the solution *) module C = Coloring.Mark(G)

let () = C.coloring g 9; display ()</lang>

Oz

Using built-in constraint propagation and search. <lang oz>declare

 %% a puzzle is a function that returns an initial board configuration
 fun {Puzzle1}
    %% a board is a list of 9 rows
    [[4 _ _  _ _ _  _ 6 _]
     [5 _ _  _ 8 _  9 _ _]
     [3 _ _  _ _ 1  _ _ _]
   
     [_ 2 _  7 _ _  _ _ 1]
     [_ 9 _  _ _ _  _ 4 _]
     [8 _ _  _ _ 3  _ 5 _]
   
     [_ _ _  2 _ _  _ _ 7]
     [_ _ 6  _ 5 _  _ _ 8] 
     [_ 1 _  _ _ _  _ _ 6]]
 end
 %% Returns a list of solutions for the given puzzle.
 fun {Solve Puzzle}
    {SearchAll {GetScript Puzzle}}
 end
 %% Creates a solver script for a puzzle.
 fun {GetScript Puzzle}
    proc {$ Board}
       %% Every row is a list of nine finite domain vars
       %% with the domain 1..9.
       Board = {MapRange fun {$ _} {FD.list 9 1#9} end}
       %% Post initial configuration.
       Board = {Puzzle}
       
       %% The core constraints:
       {ForAll {Rows Board} FD.distinct}
       {ForAll {Columns Board} FD.distinct}
       {ForAll {Boxes Board} FD.distinct}
       %% Search if necessary.
       {FD.distribute ff {Flatten Board}}
    end
 end

 %% Returns the board as a list of rows.
 fun {Rows Board}
    Board %% This is already the representation we have chosen.
 end

 %% Returns the board as a list of columns.
 fun {Columns Board}
    {MapRange fun {$ I} {Column Board I} end}
 end

 %% Returns the board as a list of boxes (sub-grids).
 fun {Boxes Board}
    {MapRange fun {$ I} {Box Board I} end}
 end

 %% Helper function: map the range 1..9 to something.
 fun {MapRange F}
    {Map [1 2 3 4 5 6 7 8 9] F}
 end

 %% Returns a column of the board as a list of fields.
 fun {Column Board Index}
    {Map Board
     fun {$ Row}
        {Nth Row Index}
     end
    }
 end

 %% Returns a box of the board as a list of fields.
 fun {Box Board Index}
    Index0 = Index-1
    Fields = {Flatten Board}
    Start = (Index0 div 3) * 27 + (Index0 mod 3)*3   
 in
    {Flatten
     for I in 0..2 collect:C do
        {C {List.take {List.drop Fields Start+I*9} 3}}
     end
    }
 end

in

 {Inspect {Solve Puzzle1}.1}</lang>

Perl

<lang Perl>#!/usr/bin/perl use integer; use strict;

my @A = qw(

   5 3 0  0 2 4  7 0 0 
   0 0 2  0 0 0  8 0 0 
   1 0 0  7 0 3  9 0 2 
   0 0 8  0 7 2  0 4 9 
   0 2 0  9 8 0  0 7 0 
   7 9 0  0 0 0  0 8 0 
   0 0 0  0 3 0  5 0 6 
   9 6 0  0 1 0  3 0 0 
   0 5 0  6 9 0  0 1 0

);

sub solve {

   my $i;
   foreach $i ( 0 .. 80 ) {

next if $A[$i]; my %t = map { $_ / 9 == $i / 9 || $_ % 9 == $i % 9 || $_ / 27 == $i / 27 && $_ % 9 / 3 == $i % 9 / 3 ? $A[$_] : 0, 1; } 0 .. 80; solve( $A[$i] = $_ ) for grep !$t{$_}, 1 .. 9; return $A[$i] = 0;

   }
   $i = 0;
   foreach (@A) {

print "-----+-----+-----\n" if !($i%27) && $i; print !($i%9) ? : $i%3 ? ' ' : '|', $_; print "\n" unless ++$i%9;

   }

} solve();</lang> Output:

5 3 9|8 2 4|7 6 1
6 7 2|1 5 9|8 3 4
1 8 4|7 6 3|9 5 2
-----+-----+-----
3 1 8|5 7 2|6 4 9
4 2 5|9 8 6|1 7 3
7 9 6|3 4 1|2 8 5
-----+-----+-----
8 4 1|2 3 7|5 9 6
9 6 7|4 1 5|3 2 8
2 5 3|6 9 8|4 1 7

Perl 6

(Translation of Perl)

<lang perl6>use v6; my @A = <

   5 3 0  0 2 4  7 0 0 
   0 0 2  0 0 0  8 0 0 
   1 0 0  7 0 3  9 0 2 

   0 0 8  0 7 2  0 4 9 
   0 2 0  9 8 0  0 7 0 
   7 9 0  0 0 0  0 8 0 

   0 0 0  0 3 0  5 0 6 
   9 6 0  0 1 0  3 0 0 
   0 5 0  6 9 0  0 1 0

>;

my &I = * div 9; # line number my &J = * % 9; # column number my &K = { ($_ div 27) * 3 + $_ % 9 div 3 }; # bloc number

sub solve {

   for ^@A -> $i {

next if @A[$i]; my @taken-values = @A[ grep { I($_) == I($i) || J($_) == J($i) || K($_) == K($i) }, ^@A ]; for grep none(@taken-values), 1..9 { @A[$i] = $_; solve; } return @A[$i] = 0;

   }
   my $i = 1;
   for ^@A {

print "@A[$_] "; print " " if $i %% 3; print "\n" if $i %% 9; print "\n" if $i++ %% 27;

   }

} solve;</lang>

Output:
5 3 9  8 2 4  7 6 1  
6 7 2  1 5 9  8 3 4  
1 8 4  7 6 3  9 5 2  

3 1 8  5 7 2  6 4 9  
4 2 5  9 8 6  1 7 3  
7 9 6  3 4 1  2 8 5  

8 4 1  2 3 7  5 9 6  
9 6 7  4 1 5  3 2 8  
2 5 3  6 9 8  4 1 7

Prolog

<lang Prolog>:- use_module(library(clpfd)).

sudoku(Rows) :-

       length(Rows, 9), maplist(length_(9), Rows),
       append(Rows, Vs), Vs ins 1..9,
       maplist(all_distinct, Rows),
       transpose(Rows, Columns), maplist(all_distinct, Columns),
       Rows = [A,B,C,D,E,F,G,H,I],
       blocks(A, B, C), blocks(D, E, F), blocks(G, H, I).

length_(L, Ls) :- length(Ls, L).

blocks([], [], []). blocks([A,B,C|Bs1], [D,E,F|Bs2], [G,H,I|Bs3]) :-

       all_distinct([A,B,C,D,E,F,G,H,I]),
       blocks(Bs1, Bs2, Bs3).

problem(1, [[_,_,_,_,_,_,_,_,_],

           [_,_,_,_,_,3,_,8,5],
           [_,_,1,_,2,_,_,_,_],
           [_,_,_,5,_,7,_,_,_],
           [_,_,4,_,_,_,1,_,_],
           [_,9,_,_,_,_,_,_,_],
           [5,_,_,_,_,_,_,7,3],
           [_,_,2,_,1,_,_,_,_],
           [_,_,_,_,4,_,_,_,9]]).</lang>

PicoLisp

<lang PicoLisp>(load "lib/simul.l")

      1. Fields/Board ###
  1. val lst

(setq

  *Board (grid 9 9)
  *Fields (apply append *Board) )
  1. Init values to zero (empty)

(for L *Board

  (for This L
     (=: val 0) ) )
  1. Build lookup lists

(for (X . L) *Board

  (for (Y . This) L
     (=: lst
        (make
           (let A (* 3 (/ (dec X) 3))
              (do 3
                 (inc 'A)
                 (let B (* 3 (/ (dec Y) 3))
                    (do 3
                       (inc 'B)
                       (unless (and (= A X) (= B Y))
                          (link
                             (prop (get *Board A B) 'val) ) ) ) ) ) )
           (for Dir '(`west `east `south `north)
              (for (This (Dir This)  This  (Dir This))
                 (unless (memq (:: val) (made))
                    (link (:: val)) ) ) ) ) ) ) )
  1. Cut connections (for display only)

(for (X . L) *Board

  (for (Y . This) L
     (when (member X (3 6))
        (con (car (val This))) )
     (when (member Y (4 7))
        (set (cdr (val This))) ) ) )
  1. Display board

(de display ()

  (disp *Board 0
     '((This)
        (if (=0 (: val))
           "   "
           (pack " " (: val) " ") ) ) ) )
  1. Initialize board

(de main (Lst)

  (for (Y . L) Lst
     (for (X . N) L
        (put *Board X (- 10 Y) 'val N) ) )
  (display) )
  1. Find solution

(de go ()

  (unless
     (recur (*Fields)
        (with (car *Fields)
           (if (=0 (: val))
              (loop
                 (NIL
                    (or
                       (assoc (inc (:: val)) (: lst))
                       (recurse (cdr *Fields)) ) )
                 (T (= 9 (: val)) (=: val 0)) )
              (recurse (cdr *Fields)) ) ) )
     (display) ) )

(main

  (quote
     (5 3 0 0 7 0 0 0 0)
     (6 0 0 1 9 5 0 0 0)
     (0 9 8 0 0 0 0 6 0)
     (8 0 0 0 6 0 0 0 3)
     (4 0 0 8 0 3 0 0 1)
     (7 0 0 0 2 0 0 0 6)
     (0 6 0 0 0 0 2 8 0)
     (0 0 0 4 1 9 0 0 5)
     (0 0 0 0 8 0 0 7 9) ) )</lang>

Output:

   +---+---+---+---+---+---+---+---+---+
 9 | 5   3     |     7     |           |
   +   +   +   +   +   +   +   +   +   +
 8 | 6         | 1   9   5 |           |
   +   +   +   +   +   +   +   +   +   +
 7 |     9   8 |           |     6     |
   +---+---+---+---+---+---+---+---+---+
 6 | 8         |     6     |         3 |
   +   +   +   +   +   +   +   +   +   +
 5 | 4         | 8       3 |         1 |
   +   +   +   +   +   +   +   +   +   +
 4 | 7         |     2     |         6 |
   +---+---+---+---+---+---+---+---+---+
 3 |     6     |           | 2   8     |
   +   +   +   +   +   +   +   +   +   +
 2 |           | 4   1   9 |         5 |
   +   +   +   +   +   +   +   +   +   +
 1 |           |     8     |     7   9 |
   +---+---+---+---+---+---+---+---+---+
     a   b   c   d   e   f   g   h   i

<lang PicoLisp>(go)</lang> Output:

   +---+---+---+---+---+---+---+---+---+
 9 | 5   3   4 | 6   7   8 | 9   1   2 |
   +   +   +   +   +   +   +   +   +   +
 8 | 6   7   2 | 1   9   5 | 3   4   8 |
   +   +   +   +   +   +   +   +   +   +
 7 | 1   9   8 | 3   4   2 | 5   6   7 |
   +---+---+---+---+---+---+---+---+---+
 6 | 8   5   9 | 7   6   1 | 4   2   3 |
   +   +   +   +   +   +   +   +   +   +
 5 | 4   2   6 | 8   5   3 | 7   9   1 |
   +   +   +   +   +   +   +   +   +   +
 4 | 7   1   3 | 9   2   4 | 8   5   6 |
   +---+---+---+---+---+---+---+---+---+
 3 | 9   6   1 | 5   3   7 | 2   8   4 |
   +   +   +   +   +   +   +   +   +   +
 2 | 2   8   7 | 4   1   9 | 6   3   5 |
   +   +   +   +   +   +   +   +   +   +
 1 | 3   4   5 | 2   8   6 | 1   7   9 |
   +---+---+---+---+---+---+---+---+---+
     a   b   c   d   e   f   g   h   i

PureBasic

A brute force method is used, it seemed the fastest as well as the simplest. <lang PureBasic>DataSection

 puzzle:
 Data.s "394002670"
 Data.s "000300400"
 Data.s "500690020"
 Data.s "045000900"
 Data.s "600000007"
 Data.s "007000580"
 Data.s "010067008"
 Data.s "009008000"
 Data.s "026400735"

EndDataSection

  1. IsPossible = 0
  2. IsNotPossible = 1
  3. Unknown = 0

Global Dim sudoku(8, 8)

-declarations

Declare readSudoku() Declare displaySudoku() Declare.s buildpossible(x, y, Array possible.b(1)) Declare solvePuzzle(x = 0, y = 0)

-procedures

Procedure readSudoku()

 Protected a$, row, column
 
 Restore puzzle
 For row = 0 To 8 
   Read.s a$  
   For column = 0 To 8
     sudoku(column, row) = Val(Mid(a$, column + 1, 1))
   Next
 Next

EndProcedure

Procedure displaySudoku()

 Protected row, column 
 Static border.s = "+-----+-----+-----+"
 For row = 0 To 8
   If row % 3 = 0: PrintN(border): EndIf
   For column = 0 To 8
     If column % 3 = 0: Print("|"): Else: Print(" "): EndIf
     If sudoku(column, row): Print(Str(sudoku(column, row))): Else: Print("."): EndIf
   Next
   PrintN("|")
 Next
 PrintN(border)

EndProcedure

Procedure.s buildpossible(x, y, Array possible.b(1))

 Protected index, column, row, boxColumn = (x / 3) * 3, boxRow = (y / 3) * 3
 Dim possible.b(9)
 For index = 0 To 8 
   possible(sudoku(index, y)) = #IsNotPossible ;record possibles in column
   possible(sudoku(x, index)) = #IsNotPossible ;record possibles in row
 Next
 
 ;record possibles in box
 For row = boxRow To boxRow + 2
   For column = boxColumn To boxColumn + 2 
     possible(sudoku(column, row)) = #IsNotPossible
   Next 
 Next

EndProcedure

Procedure solvePuzzle(x = 0, y = 0)

 Protected row, column, spot, digit
 Dim possible.b(9)
 
 For row = y To 8
   For column = x To 8
     If sudoku(column, row) = #Unknown
       buildpossible(column, row, possible())
       
       For digit =  1 To 9                                   
         If possible(digit) = #IsPossible
           sudoku(column, row) = digit
           spot = row * 9 + column + 1
           If solvePuzzle(spot % 9, spot / 9)
             Break 3
           EndIf   
         EndIf
       Next
       If digit = 10
         sudoku(column, row) = #Unknown
         ProcedureReturn #False
       EndIf 
     EndIf 
   Next 
   x = 0 ;reset column start point
 Next 
 ProcedureReturn #True

EndProcedure

If OpenConsole()

 readSudoku()
 displaySudoku()
 If solvePuzzle()
   PrintN("Solved.")
   displaySudoku()
 Else
   PrintN("Unable to solve puzzle") ;due to bad starting data
 EndIf 
 
 Print(#CRLF$ + #CRLF$ + "Press ENTER to exit")
 Input()
 CloseConsole()

EndIf</lang> Sample output:

+-----+-----+-----+
|3 9 4|. . 2|6 7 .|
|. . .|3 . .|4 . .|
|5 . .|6 9 .|. 2 .|
+-----+-----+-----+
|. 4 5|. . .|9 . .|
|6 . .|. . .|. . 7|
|. . 7|. . .|5 8 .|
+-----+-----+-----+
|. 1 .|. 6 7|. . 8|
|. . 9|. . 8|. . .|
|. 2 6|4 . .|7 3 5|
+-----+-----+-----+
Solved.
+-----+-----+-----+
|3 9 4|8 5 2|6 7 1|
|2 6 8|3 7 1|4 5 9|
|5 7 1|6 9 4|8 2 3|
+-----+-----+-----+
|1 4 5|7 8 3|9 6 2|
|6 8 2|9 4 5|3 1 7|
|9 3 7|1 2 6|5 8 4|
+-----+-----+-----+
|4 1 3|5 6 7|2 9 8|
|7 5 9|2 3 8|1 4 6|
|8 2 6|4 1 9|7 3 5|
+-----+-----+-----+

Python

See Solving Sudoku puzzles with Python for GPL'd solvers of increasing complexity of algorithm.

A simple backtrack algorithm -- Quick but may take longer if the grid had been more than 9 x 9 <lang python> def initiate():

   box.append([0, 1, 2, 9, 10, 11, 18, 19, 20])
   box.append([3, 4, 5, 12, 13, 14, 21, 22, 23])
   box.append([6, 7, 8, 15, 16, 17, 24, 25, 26])
   box.append([27, 28, 29, 36, 37, 38, 45, 46, 47])
   box.append([30, 31, 32, 39, 40, 41, 48, 49, 50])
   box.append([33, 34, 35, 42, 43, 44, 51, 52, 53])
   box.append([54, 55, 56, 63, 64, 65, 72, 73, 74])
   box.append([57, 58, 59, 66, 67, 68, 75, 76, 77])
   box.append([60, 61, 62, 69, 70, 71, 78, 79, 80])
   for i in range(0, 81, 9):
       row.append(range(i, i+9))
   for i in range(9):
       column.append(range(i, 80+i, 9))

def valid(n, pos):

   current_row = pos/9
   current_col = pos%9
   current_box = (current_row/3)*3 + (current_col/3)
   for i in row[current_row]:
       if (grid[i] == n):
           return False
   for i in column[current_col]:
       if (grid[i] == n):
           return False
   for i in box[current_box]:
       if (grid[i] == n):
           return False
   return True

def solve():

   i = 0
   proceed = 1
   while(i < 81):
       if given[i]:
           if proceed:
                   i += 1
           else:
               i -= 1
       else:
           n = grid[i]
           prev = grid[i]
           while(n < 9):
             if (n < 9):
                 n += 1
             if valid(n, i):
                 grid[i] = n
                 proceed = 1
                 break
           if (grid[i] == prev):
              grid[i] = 0
              proceed = 0
           if proceed:
              i += 1
           else:
              i -=1

def inputs():

   nextt = 'T'
   number = 0
   pos = 0
   while(not(nextt == 'N' or nextt == 'n')):
       print "Enter the position:",
       pos = int(raw_input())
       given[pos - 1] = True
       print "Enter the numerical:",
       number = int(raw_input())
       grid[pos - 1] = number
       print "Do you want to enter another given?(Y, for yes: N, for no)"
       nextt = raw_input()


grid = [0]*81 given = [False]*81 box = [] row = [] column = [] initiate() inputs() solve() for i in range(9):

   print grid[i*9:i*9+9]

raw_input() </lang>

Rascal

A sudoku is represented as a matrix, see Rascal solutions to matrix related problems for examples.

<lang Rascal>import Prelude; import vis::Figure; import vis::Render;

public rel[int,int,int] sudoku(rel[int x, int y, int v] sudoku){ annotated= annotateGrid(sudoku); solved = {<0,0,0,0,{0}>};

while(!isEmpty(solved)){ for (n <- [0 ..8]){ column = domainR(annotated, {n}); annotated -= column; annotated += reduceOptions(column);

row = {<x,y,v,g,p> | <x,y,v,g,p> <- annotated, y==n}; annotated -= row; annotated += reduceOptions(row);

grid1 = {<x,y,v,g,p> | <x,y,v,g,p> <- annotated, g==n}; annotated -= grid1; annotated += reduceOptions(grid1); }

solved = {<x,y,v,g,p> | <x,y,v,g,p> <- annotated, size(p)==1}; annotated -= solved; annotated += {<x,y,getOneFrom(p),g,{*[1 .. 9]}> | <x,y,v,g,p> <- solved}; }

result = {<x,y,v> | <x,y,v,g,p> <- annotated}; return result; }


//adds gridnumber and default set of options public rel[int,int,int,int,set[int]] annotateGrid(rel[int x, int y, int v] sudoku){ result = {}; for (<x, y, v> <- sudoku){ g = 0; if (x<3 && y<3) g = 0; if (2<x && x<6 && y<3) g = 1; if (x>5 && y<3) g = 2;

if (x<3 && 2<y && y<6) g = 3; if (2<x && x<6 && 2<y && y<6) g = 4; if (x>5 && 2<y && y<6) g = 5;

if (x<3 && y>5) g=6; if (2<x && x<6 && y>5) g=7; if (x>5 && y>5) g=8;

result += <x,y,v,g,{*[1 .. 9]}>; } return result; }

//reduces set of options public rel[int,int,int,int,set[int]] reduceOptions(rel[int x, int y, int v, int g, set[int] p] subSudoku){ solved = {<x,y,v,g,p> | <x,y,v,g,p> <- subSudoku, v!=0}; numbers = {*[1 .. 9]} - {v | <x,y,v,g,p> <- solved}; remaining = {<x,y,v,g,numbers&p> | <x,y,v,g,p> <- subSudoku-solved}; result = remaining + solved; return result; }

//a function to visualize the result public void displaySudoku(rel[int x, int y, int v] sudoku){ points = [box(text("<v>"), align(0.111111*(x+1),0.111111*(y+1)),shrink(0.1)) | <x,y,v> <- sudoku]; print(points); render(overlay([*points], aspectRatio(1.0))); }

//a sudoku public rel[int, int, int] sudokuA = { <0,0,3>, <1,0,9>, <2,0,4>, <3,0,0>, <4,0,0>, <5,0,2>, <6,0,6>, <7,0,7>, <8,0,0>, <0,1,0>, <1,1,0>, <2,1,0>, <3,1,3>, <4,1,0>, <5,1,0>, <6,1,4>, <7,1,0>, <8,1,0>, <0,2,5>, <1,2,0>, <2,2,0>, <3,2,6>, <4,2,9>, <5,2,0>, <6,2,0>, <7,2,2>, <8,2,0>, <0,3,0>, <1,3,4>, <2,3,5>, <3,3,0>, <4,3,0>, <5,3,0>, <6,3,9>, <7,3,0>, <8,3,0>, <0,4,6>, <1,4,0>, <2,4,0>, <3,4,0>, <4,4,0>, <5,4,0>, <6,4,0>, <7,4,0>, <8,4,7>, <0,5,0>, <1,5,0>, <2,5,7>, <3,5,0>, <4,5,0>, <5,5,0>, <6,5,5>, <7,5,8>, <8,5,0>, <0,6,0>, <1,6,1>, <2,6,0>, <3,6,0>, <4,6,6>, <5,6,7>, <6,6,0>, <7,6,0>, <8,6,8>, <0,7,0>, <1,7,0>, <2,7,9>, <3,7,0>, <4,7,0>, <5,7,8>, <6,7,0>, <7,7,0>, <8,7,0>, <0,8,0>, <1,8,2>, <2,8,6>, <3,8,4>, <4,8,0>, <5,8,0>, <6,8,7>, <7,8,3>, <8,8,5> };</lang>

Example

rascal>displaySudoku(sudoku(sudokuA))

See picture

REXX

The REXX program was original written to assist in sudoku puzzle solving, not to solve the puzzle outright.
The REXX code was written to give hints and also show the possibilities (of what is possible solution for any cell),
and to partially solve the puzzle using distinct strategies (separately or in combination).

REXX programs not included are $T which is only used when specific options are used (used when TOPS is specified),
the $ERR program which issues errors, and $H which shows help and other documentation. <lang rexx>/**/trace o;parse arg !;if !all(arg()) then exit;if !cms then address ;signal on halt;signal on novalue;signal on syntax

ops=! /*remove extraneous blanks.*/ numeric digits 20 combos=1 @.=' ' /*initialize grid to blanks*/ !.= /*nullify valid empty# list*/ @abc='abcdefghijklmnopqrstuvwxyz'; @abcU=@abc; upper @abcU colors=!cms | !pcrexx | !r4 | !roo /*Are colors supported ? */ clear=1 /*option: clear the screen.*/ highlight=0 /*option: highlight singles*/ pruneall=0 /*option: prune all. */ prunemats=0 /*option: prune matches. */ prunesing=0 /*option: prune singles. */ pruneexcl=0 /*option: prune exclusives.*/ pruneline=0 /*option: prune lines. */ pruneonly=0 /*option: prune onlys. */ simple=0 /*option: show simple boxes*/ showoneline=0 /*option: show grid as1line*/ showgrid=1 /*option: show the grid. */ showinfo=1 /*option: show informatiion*/ showposs=0 /*option: show possible val*/ showcomb=0 /*option: show combinations*/ showrow= /*option: SHOWPOSS for rowN*/ showcol= /*option: SHOWPOSS for colN*/ showbox= /*option: SHOWPOSS for boxN*/ showcell= /*option: SHOWPOSS cellRC */ short=0 solve=0 /*option: solve the puzzle.*/ sod=lower(translate(!fn,,'$')) /*name of the puzzle. */ tellinvalid=1 /*tell err msg if invalid X*/ tops= /*option: used for $T opts.*/

gridindents=3 /*# spaces grid is indented*/ gridindent=left(,gridindents) /*spaces indented for grid.*/ gridwidth=7 /*grid cell interior width.*/ gridbar='b3'x /*bar for the grid (cells).*/ gridlt='da'x /*grid cell left top. */ gridrt='bf'x /*grid cell right top. */ gridlb='c0'x /*grid cell left bottom. */ gridrb='d9'x /*grid cell right bottom. */ gridline='c4'x /*grid cell line (hyphen). */ gridlin=copies(gridline,gridwidth) /*grid cell total line. */ gridemp=left(,gridwidth) /*grid cell empty (spaces).*/ griddj='c2'x /*grid cell down junction.*/ griduj='c1'x /*grid cell up junction.*/ gridlj='c3'x /*grid cell left junction.*/ gridrj='b4'x /*grid cell right junction.*/ gridcross='c5'x /*grid cell cross junction.*/

 do  while ops\==                         /*parse any and all options*/
 parse var ops _1 2 1 _ . 1 _o ops; upper _
   select
   when _==','                    then nop
   when _1=='.' & pos("=",_)\==0  then tops=tops _o
   when left(_,4)=='PUZZ'         then      /*do PUZZ (whole) placement*/
        do
        parse var _ '=' y; if y== then call er 35,'PUZZ'rc
        if length(y)>81  then call er 30,y 'PUZZ 1--->81'
                        do j=1
                        q=substr(y,j,1);  if q==' '  then leave
                        if q=='.'  then iterate
                        call vern q,'PUZZLE_digit'
                        c=j//9
                        if c==0 then c=9
                        r=(j-1)%9+1
                        @.r.c=q
                        end   /*j*/
        end
   when left(_,4)=='CELL'  then             /*do CELL (grid) placement.*/
        do
        parse var _ 'CELL' rc '=' y;  if y==  then call er 35,'CELL'rc
        if length(rc)\==2                   then call er 30,y 'CELL'rc 2
        r=left(rc,1);c=right(rc,1)
        call vern r,'CELLrow'
        call vern c,'CELLcol'
        if length(y)>1                      then call er 30,y 'CELL'rc 1
        call vern y,'CELLdigit'
        @.r.c=y
        end
   when left(_,3)=='COL' then               /*do COL (grid) placement. */
        do
        parse var _ 'COL' n '=' y;  if y==  then call er 35,'COL'n
        call vern n,'COL'
        ly=length(y); if ly>9           then call er 30,y 'COL'n '1--->8'
                        do j=1 to  ly
                        x=substr(y,j,1)
                        if x== | x=="_" | x=='*' | x=="."  then iterate
                        @.j.n=x
                        end   /*j*/
        end
   when left(_,3)=='ROW' then               /*do ROW (grid) placement. */
        do
        parse var _ 'ROW' n '=' y; if y== then call er 35,'ROW'n
        call vern n,'ROW'
        ly=length(y); if ly>9           then call er 30,y 'ROW'n '1--->8'
                        do j=1  to ly
                        x=substr(y,j,1)
                        if x== | x=="_" | x=='*' | x=="."  then iterate
                        if \isint(x)  then call er 92,x 'ROWn'
                        @.n.j=x
                        end   /*j*/
        end
   when abbn('CLearscreen')        then clear=no()
   when abbn('HIGHLightsingles')   then highlight=no()
   when abbn('PRUNEALL')           then pruneall=no()
   when abbn('PRUNEONLYs')         then pruneonly=no()
   when abbn('PRUNEEXclusives')    then pruneexcl=no()
   when abbn('PRUNELINEs')         then pruneline=no()
   when abbn('PRUNEMATches')       then prunemats=no()
   when abbn('PRUNESINGles')       then prunesing=no()
   when abbn('SIMPle')             then simple=no()
   when  abb('SHOWBOXes')|,
         abb('SHOWBOXs')           then showbox=nai()
   when  abb('SHOWCELLs')          then showcell=translate(na(),,',')
   when  abb('SHOWCOLs')           then showcol=nai()
   when abbn('SHOWCOMBinations')   then showcomb=no()
   when abbn('SHOWGrid')           then showgrid=no()
   when abbn('SHOWINFOrmation')    then showinfo=no()
   when abbn('SHOWONELINE')        then showoneline=no()
   when abbn('SHOWPOSSibles') then showposs=no()
   when  abb('SHOWROWs')           then showrow=nai()
   when abbn('SHortgrid')          then short=no()
   when abbn('SOLvepuzzle')        then solve=no()
   otherwise                       call er 55,_o
   end   /*select*/
 end     /*while ops¬==*/

if pruneall then do /*if pruneAll, set ON other*/

                pruneexcl=1
                pruneonly=1
                pruneline=1
                prunemats=1
                prunesing=1
                end

aprune = , /*is there a PRUNExxx on ? */

            pruneexcl |,
            pruneonly |,
            pruneline |,
            prunemats |,
            prunesing

if highlight then do /*HIGHLIGHTSINGLES opt on? */

                  hll='-'
                  hlr='-'
                  if colors  then do
                                  hll='('
                                  hlr=')'
                                  tops='.H=yell' tops
                                  end
                  end

tops=space(tops) box.=

 do j=1  for 9                              /*build the box bounds.    */
 rr=(((j*3)%10)+1)*3-2                      /*compute row lower bound. */
 cc=(((j-1)//3)+1)*3-2                      /*compute col lower bound. */
 boxr.j=rr
 boxc.j=cc
                       do   r=rr  to rr+2   /*build boxes with cell #s.*/
                         do c=cc  to cc+2
                         rc=r || c
                         box.j=box.j rc
                         box.rc=j
                         end   /*c*/
                       end     /*r*/
 box.j=strip(box.j)
 end   /*j*/

rowlb.=10 /*row R, low box number=b.*/ collb.=10 /*col R, low box number=b.*/ boxlr.=10 /*box B, low row number=r.*/ boxlc.=10 /*box B, low col number=c.*/

 do   r=1  for 9
   do c=1  for 9
   rc=r || c
   b=box.rc                                 /*what box is this R,C in ?*/
   rowlb.r=min(rowlb.r,b)                   /*find min box # for row R.*/
   collb.c=min(collb.c,b)                   /*find min box # for col C.*/
   boxlr.b=min(boxlr.b,r)                   /*find min row # for box B.*/
   boxlc.b=min(boxlc.b,c)                   /*find min col # for box B.*/
   end   /*c*/
 end     /*r*/
do j=1  to 9                                /*for each box, row, col...*/
rowhb.j=rowlb.j+2                           /*compute row's high box #.*/
colhb.j=collb.j+6                           /*compute col's high box #.*/
boxhr.j=boxlr.j+2                           /*compute box's high row #.*/
boxhc.j=boxlc.j+6                           /*compute box's high col #.*/
end   /*j*/

if showgrid then call showgrid 'the puzzle' /*show the grid to screen ?*/ if \validall() then exit /*validate specified digits*/ tellinvalid=0 /*don't tell err messages. */ !.= /*nullify valid empty# list*/ call buildposs /*build possible values. */ if showposs then call showgrid 'puzzle possibles' /*show 1st possibles?*/ if \validate(1) then exit /*validate the puzzle. */

if showoneline then do /*show grid as line line ? */

                    _=                      /*start with a clean slate.*/
                          do   r=1 for 9
                            do c=1 for 9
                            _=_ || @.r.c    /*build the string ...     */
                            end   /*c*/
                          end     /*r*/
                    _=translate(strip(_,'T'),".",' ')
                    if showinfo  then call $T 'one-line grid:'
                    call $T _
                    end

if aprune |,

  showposs then do
                call pruneposs              /*go build poss, then prune*/
                if showposs then call showgrid 'possibles' /*show grid.*/
                if \validate(1) then exit   /*validate the puzzle.     */
                end

if combos==1 then call $t sod 'puzzle solved.'

            else if showcomb then call $t 'combinations='comma(combos)

exit /*stick a fork in it, we're done.*/

/*─────────────────────────────vern subroutine──────────────────────────*/

vern: parse arg v,w /*verify a digit for an opt*/ if v== then call er 35,w if \isint(v) then call er 92,w if v<1 | v>9 then call er 81,1 9 v w return

/*─────────────────────────────buildposs subroutine─────────────────────*/ buildposs: !.= /*nullify possibilities. */ combos=1

 do   rp=1  for 9                           /*build table of valid #s. */
   do cp=1  for 9                           /*step through each column.*/
   if @.rp.cp\==' '  then iterate           /*not blank?  Keep looking.*/
                         do jd=1  for 9     /*try each digit.          */
                         @.rp.cp=jd
                         if validx(rp,cp) then !.rp.cp=!.rp.cp || jd
                         end   /*jd*/
   combos=combos*length(!.rp.cp)            /*calculate # combinations.*/
   @.rp.cp=' '                              /*restore the point (blank)*/
   end      /*cp*/
 end        /*rp*/

return

/*─────────────────────────────showgrid subroutine──────────────────────*/ showgrid: parse arg title if clear then !cls /*clear the screen ? */ if title\== & showinfo then call $t !fn 'is showing' title gtail=copies3(gridlb || gridlin || copies2(griduj || gridlin) || gridrb) ghead=copies3(gridlt || gridlin || copies2(griddj || gridlin) || gridrt) call tg ghead gemp=copies3(copies3(gridbar || gridemp)gridbar) grid=copies3(gridlj || gridlin || copies2(gridcross || gridlin)gridrj) anyshow= \ ((showcell || showcol || showrow || showbox)\==)

 do jr=1  for 9
 if \short  then call tg gemp
 gnum=
   do jc=1  for 9
   _=@.jr.jc
   if _\==' ' & highlight  then _=hll || _ || hlr
   if _==' ' & ,
      showposs  then do
                     jrjc=jr || jc
                     showit=anyshow
                     if showcell\== then if wordpos(jrjc,showcell)\==0 then showit=1
                     if showcol\== then if pos(jc,showcol)\==0 then showit=1
                     if showrow\== then if pos(jr,showrow)\==0 then showit=1
                            do jb=1 while showbox\==
                            b=substr(showbox,jb,1); if b==' ' then leave
                            if wordpos(jrjc,box.b)\==0 then showit=1
                            end   /*jb*/
                     if showit then _=strip(left(!.jr.jc,gridwidth),'T')
                     end
   gnum=gnum || gridbar || centre(_,gridwidth)
   if jc//3==0 then gnum=gnum || gridbar
   end   /*jc*/
 call tg gnum
 if \short  then call tg gemp
 if jr//3==0 then do
                  call tg gtail
                  if jr\==9 then call tg ghead
                  end
             else call tg grid
 end   /*jr*/

call $t return

/*─────────────────────────────validate subroutine──────────────────────*/ validate: /*are all empties possible?*/

 do   r=1  for 9                            /*step through each row.   */
   do c=1  for 9                            /*step through each column.*/
   if @.r.c==' ' & !.r.c== then do        /*no legal digit here.     */
                                  if arg(1)==1 then call $t sod "puzzle isn't valid !"
                                  return 0
                                  end
   end   /*c*/
 end     /*r*/                              /*sub requires possibles.  */

return 1 /*indicate puzzle is valid.*/

/*─────────────────────────────validall subroutine──────────────────────*/ validall: /*validate all Q specified.*/

 do   r=1  for 9                            /*step through each row.   */
   do c=1  for 9                            /*step through each column.*/
   if @.r.c==' '  then iterate              /*if blank, then it's ok.  */
   y=                                       /*the rest of the row.     */
   rc=r||c
               do kc=1  for 9               /*compare to #s in column. */
               if kc\==c  then y=y|| @.r.kc /*build the rest of the row*/
               end   /*kc*/
   q=@.r.c
   if pos(q,y)\==0  then return tem(r,c,'row')    /*same # in same row?*/
   y=                                       /*the rest of the column.  */
               do kr=1 for 9                /*compare to #s in column. */
               if kr\==r then y=y || @.kr.c /*build the rest of the col*/
               end      /*kr*/
   if pos(q,y)\==0  then return tem(r,c,'col')    /*same # in same col?*/
   y=                                       /*the rest of the box.     */
   b=box.rc
     do   br=boxr.b  to boxr.b+2            /*compare to #s of the box.*/
       do bc=boxc.b  to boxc.b+2            /*build the rest of the box*/
       if br\==r & bc\==c  then y=y || @.br.bc
       end  /*bc*/
     end    /*br*/
   if pos(q,y)\==0  then return tem(r,c,'box')    /*same # in same box?*/
   end   /*c*/
 end     /*r*/

return 1 /*indicate all are valid.*/

/*─────────────────────────────validx subroutine────────────────────────*/ validx: arg r,c rc=r || c y= /*the rest of the row. */

          do kc=1  for 9                    /*compare to #s in column. */
          if kc\==c  then y=y || @.r.kc     /*build the rest of the row*/
          end   /*kc*/

q=@.r.c /*get the digit at r,c */ if pos(q,y)\==0 then return tem(r,c,'row') /*same number in same row ?*/ y= /*the rest of the column. */

     do kr=1  for 9                         /*compare to #s in column. */
     if kr\==r  then y=y || @.kr.c          /*build the rest of the col*/
     end   /*kr*/

if pos(q,y)\==0 then return tem(r,c,'col') /*same # in same col ?*/ y= /*the rest of the box. */ b=box.rc

          do   br=boxr.b  to boxr.b+2       /*compare to #s of the box.*/
            do bc=boxc.b  to boxc.b+2       /*build the rest of the box*/
            if br==r & bc==c  then iterate
            y=y || @.br.bc
            end   /*br*/
          end     /*bc*/

if pos(q,y)\==0 then return tem(r,c,'box') /*same # in same box ? */ return 1 /*indicate X (r,c) is valid*/

/*─────────────────────────────pruneposs subroutine─────────────────────*/ pruneposs: if \(prunesing | pruneexcl | prunemats | pruneline) then return call buildposs

 do prunes=1
 call $t !fn 'is starting prune pass #' prunes
 found=0                                    /*indicate no prunes so far*/
 if prunesing then do                       /*prune puzzle for singles.*/
                   _=prunesing()            /*find any singles ?       */
                   found=found | _          /*track if anything found. */
                   if _ then if showgrid then call showgrid /*show grid?*/
                   end
 if pruneexcl then do                       /*prune puzzle for singles.*/
                   _=pruneexcl()            /*find any excluives ?     */
                   found=found | _          /*track if anything found. */
                   if _ then if showgrid then call showgrid /*show grid?*/
                   end
 if pruneonly then do                       /*prune puzzle for onlys.  */
                   _=pruneonly()            /*find any onlys ?         */
                   found=found | _          /*track if anything found. */
                   if _ then if showgrid then call showgrid /*show grid?*/
                   end
 if prunemats then do jpm=2 to 8            /*prune puzzle for matches.*/
                   _=prunemats(jpm)         /*find any matches (len=j)?*/
                   found=found | _          /*track if anything found. */
                   if _ then if showgrid then call showgrid /*show grid?*/
                   end
 if pruneline then do                       /*prune puzzle for lines.  */
                   _=pruneline()            /*find 2 or more on a line?*/
                   found=found | _          /*track if anything found. */
                   if _ then if showgrid then call showgrid /*show grid?*/
                   end
 if \found then leave                       /*nothing found this time ?*/
 end    /*prunes*/

return

/*─────────────────────────────prunesing subroutine─────────────────────*/ prunesing: foundsing=0

   do   r=1  for 9
     do c=1  for 9;         _=length(!.r.c) /*get length of possible.  */
     if _==0   then iterate                 /*if null, then ignore it. */
     if _\==1  then iterate                 /*if not one digit, ignore.*/
     @.r.c=!.r.c                            /*it's 1 digit, a solution.*/
     !.r.c=                                 /*erase the old possible.  */
     foundsing=1
     call $t !fn 'found a single digit at cell' drc(r,c,@.r.c)
     end   /*c*/
   end     /*r*/

if foundsing then call buildposs /*re-build the possibles. */ return foundsing

/*─────────────────────────────pruneexcl subroutine─────────────────────*/ pruneexcl: foundexcl=0

 do exclusives=1                            /*keep building possibles. */
   do   r=1  for 9
     do c=1  for 9;   z=!.r.c
     lz=length(z)                           /*get length of possible.  */
     if lz==0  then iterate                 /*if null, then ignore it. */
     y=
     rc=r || c
     b=box.rc
               do   br=boxr.b  to boxr.b+2  /*compare to #s of the box.*/
                 do bc=boxc.b  to boxc.b+2  /*build the rest of the box*/
                 if br==r & bc==c  then iterate
                 y=y || @.br.bc || !.br.bc
                 end   /*bc*/
               end     /*br*/
                                            /*test for reduction.      */
      do t=1  for lz;   q=substr(z,t,1)
      if pos(q,y)==0 then do
                          foundexcl=1
                          @.r.c=q           /*it's a singularity, a sol*/
                          !.r.c=            /*erase old possibleity.   */
                          call $t !fn 'found the digit' q,
                                 "by exclusiveness at cell" drc(r,c,z)
                          call buildposs    /*re-build the possibles.  */
                          iterate exclusives
                          end
      end  /*t*/
     end   /*c*/
   end     /*r*/
 leave
 end       /*exclusives*/

return foundexcl

/*─────────────────────────────prunemats subroutine─────────────────────*/ prunemats: foundmatch=0 /*no matches found so far. */ parse arg L /*length of match, L=2,pair*/

 do matches=1
   do   r=1  for 9
     do c=1  for 9;         _=length(!.r.c) /*get length of possible.  */
     if _==0   then iterate                 /*if null, then ignore it. */
     if _\==L  then iterate                 /*not right length, ignore.*/
     qq=!.r.c
     m=0                                    /*count of matches so far. */
            do _c=1  for 9                  /*nother match in same row?*/
            if qq==!.r._c  then m=m+1       /*up count if it's a match.*/
            end  /*_c*/
     if m>=L then do pc=1  for 9            /*squish other possibles.  */
                  old=!.r.pc                /*save the "old" value.    */
                  if old==qq   then iterate /*if match, then ignore it.*/
                  if old==   then iterate /*if null poss, then ignore*/
                  new=squish(old,qq)        /*remove mat's digs from X.*/
                  if new==old  then iterate /*if no change,keep looking*/
                  !.r.pc=new                /*store new value into old.*/
                  foundmatch=1              /*indicate match was found.*/
                  call $t !fn 'is removing a' L "from" drc(r,pc,old),
                              'because of a match at' drc(r,c,qq)
                  if length(new)==1 then do             /*reduce if L=1*/
                                         @.r.pc=new     /*store single.*/
                                         !.r.pc=        /*delete poss. */
                                         call buildposs /*re-build poss*/
                                         iterate matches  /*start over.*/
                                         end
                  end    /*pc*/
     m=0                                    /*count of matches so far. */
            do _r=1  for 9                  /*nother match in same col?*/
            if qq==!._r.c  then m=m+1       /*up count if it's a match.*/
            end   /*_r*/
     if m>=L then do pr=1 for 9             /*squish other possibles.  */
                  old=!.pr.c                /*save the "old" value.    */
                  if old==qq then iterate   /*if match, then ignore it.*/
                  if old== then iterate   /*if null poss, then ignore*/
                  new=squish(old,qq)        /*remove mat's digs from X.*/
                  if new==old then iterate  /*if no change,keep looking*/
                  !.pr.c=new                /*store new value into old.*/
                  foundmatch=1              /*indicate match was found.*/
                  call $t !fn 'is removing a' L "from" drc(pr,c,old),
                              'because of a match at' drc(r,c,qq)
                  if length(new)==1 then do             /*reduce if L=1*/
                                         @.pr.c=new     /*store single.*/
                                         !.pr.c=        /*delete poss. */
                                         call buildposs /*re-build poss*/
                                         iterate matches  /*start over.*/
                                         end
                  end   /*pr*/
     end                /*c*/
   end                  /*r*/
 leave
 end                    /*matches*/

return foundmatch

/*─────────────────────────────pruneonly subroutine─────────────────────*/ pruneonly: foundmatch=0 /*no matches found so far. */

 do findonlys=1                             /*keep searching ...       */
 _row.=                                     /*build str for each row . */
          do   r=1  for 9
            do c=1  for 9;   if !.r.c\==  then _row.r=_row.r !.r.c
            end   /*c*/
          end     /*r*/
 _col.=                                     /*build str for each boxcol*/
          do   c=1  for 9
            do r=1  for 9;   if !.r.c\==  then _col.c=_col.c !.r.c
            end   /*r*/
          end     /*c*/
   do   r=1  for 9
     do c=1  for 9;          q=!.r.c
     if q==  then iterate                 /*if empty, then ignore it.*/
       do j=1  to length(q)                 /*step through each digit. */
       k=substr(q,j,1)
       if kount1(k,_row.r) |,               /*is this the ONLY digit K?*/
          kount1(k,_col.c) then do i=1  to length(q)    /*prune others.*/
                                foundmatch=1
                                _=substr(q,i,1)
                                if _==k  then iterate   /*if=K, ignore.*/
                                o=squish(q,_)           /*remove others*/
                                !.r.c=o
                                call $t !fn 'removed part of an only',
                                            _ "from cell" drc(r,c,q)
                                if length(o)==1  then   /*reduce if L=1*/
                                  do
                                  @.r.c=o               /*store single.*/
                                  !.r.c=                /*delete poss. */
                                  call buildposs        /*re-build poss*/
                                  iterate findonlys     /*start over.  */
                                  end
                                end   /*i*/
       end   /*j*/
     end     /*c*/
   end       /*r*/
 leave
 end     /*findonlys*/

return foundmatch

/*─────────────────────────────pruneline subroutine─────────────────────*/ pruneline: foundmatch=0 /*no matches found so far. */

do findlines=1                              /*keep searching ...       */
_boxr.=                                     /*build str for each boxrow*/
          do   r=1  for 9
            do c=1  for 9;    rc=r || c;    b=box.rc
            if !.r.c\==  then _boxr.r.b=strip(_boxr.r.b !.r.c)
            end   /*c*/
          end     /*r*/
 _boxc.=                                    /*build str for each boxcol*/
          do   c=1  for 9
            do r=1  for 9;    rc=r || c;    b=box.rc
            if !.r.c\==  then _boxc.c.b=strip(_boxc.c.b !.r.c)
            end   /*r*/
          end     /*c*/
 do r=1  for 9                              /*search all rows for twins*/
   do b=rowlb.r  to rowhb.r                 /*for each row, search box.*/
   aline=_boxr.r.b; if aline== then iterate   /*if empty, ignore line*/
   w=words(aline);  if w<2  then iterate    /*if < 2 words, ignore line*/
     do k=1  for 9                          /*search for each digit.   */
     f=pos(k,aline)                         /*pos of the 1st digit:  k */
     if f==0 then  iterate                  /*no dig k, so keep looking*/
     s=pos(k,aline,f+1)                     /*pos of the 2nd digit:  k */
     if s==0 then  iterate                  /*no 2nd k, so keep looking*/
       do jr=rowlb.r  to rowhb.r            /*look at the other 2 rows.*/
       if jr==r then  iterate               /*if the same row, ignore. */
       if pos(k,_boxr.jr.b)\==0  then iterate k /*if no digit K, ignore*/
       end   /*jr*/
                                            /*found 2 Ks in row R box B*/
        do jb=rowlb.r  to rowhb.r           /*search boxes row R for K.*/
        if jb==b then iterate               /*ignore if in the same box*/
        if pos(k,_boxr.r.jb)==0  then iterate
        foundmatch=1                        /*found a K in col C box JB*/
          do kc=1  for 9                    /*find which cell  K is in.*/
          rc=r || kc
          if box.rc==b        then iterate  /*ignore if in the same box*/
          _=!.r.kc; if _==  then iterate  /*ignore if no possible.   */
          if pos(k,_)==0      then iterate  /*if no digit  K,  ignore. */
          call $t !fn 'is row-line pruning digit' k,
                      'from cell' drc(r,kc,!.r.kc)
          !.r.kc=squish(_,k)                /*remove mat's digs from X.*/
          if length(!.r.kc)==1 then do      /*pruned down to one digit?*/
                                    @.r.kc=!.r.kc   /*make a true digit*/
                                    !.r.kc=         /*erase possibility*/
                                    call buildposs  /*rebuild possibles*/.
                                    iterate findlines
                                    end
          end   /*kc*/
        end     /*jb*/
     end        /*k*/
   end          /*b*/
 end            /*r*/
 do c=1  for 9                              /*search all cols for twins*/
   do b=collb.c  to colhb.c  by 3           /*for each col, search box.*/
   aline=_boxc.c.b;  if aline== then iterate  /*if empty, ignore line*/
   w=words(aline);   if w<2  then iterate   /*if < 2 words, ignore line*/
     do k=1  for 9                          /*search for each digit.   */
     f=pos(k,aline)                         /*pos of the 1st digit:  k */
     if f==0  then iterate                  /*no dig k, so keep looking*/
     s=pos(k,aline,f+1)                     /*pos of the 2nd digit:  k */
     if s==0  then iterate                  /*no 2nd k, so keep looking*/
       do jc=boxlc.b  to boxhc.b            /*look at the other 2 cols.*/
       if jc==c  then iterate               /*if the same col, ignore. */
       if pos(k,_boxc.jc.b)\==0  then iterate k /*if no digit K, ignore*/
       end   /*jc*/
                                            /*found 2 Ks in col C box B*/
        do jb=collb.c  to colhb.c by 3      /*search boxes col C for K.*/
        if jb==b  then iterate              /*ignore if in the same box*/
        if pos(k,_boxc.c.jb)==0  then iterate
        foundmatch=1                        /*found a K in col C box JB*/
          do kr=1  for 9                    /*find which cell  K is in.*/
          rc=kr || c
          if box.rc==b       then iterate   /*ignore if in the same box*/
          _=!.kr.c;if _==  then iterate   /*ignore if no possible.   */
          if pos(k,_)==0     then iterate   /*if no digit  K,  ignore. */
          call $t !fn 'is col-line pruning digit' k,
                      'from cell' drc(kr,c,!.kr.c)
          !.kr.c=squish(_,k)                /*remove mat's digs from X.*/
          if length(!.kr.c)==1 then do      /*pruned down to one digit?*/
                                    @.kr.c=!.kr.c   /*make a true digit*/
                                    !.kr.c=         /*erase possibility*/
                                    call buildposs  /*rebuild possibles*/.
                                    iterate findlines
                                    end
          end   /*kr*/
        end     /*jb*/
     end        /*k*/
   end          /*b*/
 end            /*c*/
leave
end     /*findlines*/

return foundmatch

/*═════════════════════════════general 1-line subs══════════════════════*/ !all:!!=!;!=space(!);upper !;call !fid;!nt=right(!var('OS'),2)=='NT';!cls=word('CLS VMFCLEAR CLRSCREEN',1+!cms+!tso*2);if arg(1)\==1 then return 0;if wordpos(!,'? ?SAMPLES ?AUTHOR ?FLOW')==0 then return 0;!call=']$H';call '$H' !fn !;!call=;return 1 !cal:if symbol('!CALL')\=="VAR" then !call=;return !call !env:!env='ENVIRONMENT';if !sys=='MSDOS'|!brexx|!r4|!roo then !env='SYSTEM';if !os2 then !env='OS2'!env;!ebcdic=1=='f0'x;return !fid:parse upper source !sys !fun !fid . 1 . . !fn !ft !fm .;call !sys;if !dos then do;_=lastpos('\',!fn);!fm=left(!fn,_);!fn=substr(!fn,_+1);parse var !fn !fn '.' !ft;end;return word(0 !fn !ft !fm,1+('0'arg(1))) !rex:parse upper version !ver !vernum !verdate .;!brexx='BY'==!vernum;!kexx='KEXX'==!ver;!pcrexx='REXX/PERSONAL'==!ver|'REXX/PC'==!ver;!r4='REXX-R4'==!ver;!regina='REXX-REGINA'==left(!ver,11);!roo='REXX-ROO'==!ver;call !env;return !sys:!cms=!sys=='CMS';!os2=!sys=='OS2';!tso=!sys=='TSO'|!sys=='MVS';!vse=!sys=='VSE';!dos=pos('DOS',!sys)\==0|pos('WIN',!sys)\==0|!sys=='CMD';call !rex;return !var:call !fid;if !kexx then return space(dosenv(arg(1)));return space(value(arg(1),,!env)) $fact!:procedure;parse arg x _ .;l=length(x);n=l-length(strip(x,'T',"!"));if n<=-n|_\==|arg()\==1 then return x;z=left(x,l-n);if z<0|\isint(z) then return x;return $fact(z,n) $fact:procedure;parse arg x _ .;arg ,n ! .;n=p(n 1);if \isint(n) then n=0;if x<-n|\isint(x)|n<1|_||!\==|arg()>2 then return x||copies("!",max(1,n));!=1;s=x//n;if s==0 then s=n;do j=s to x by n;!=!*j;end;return ! $sfxa:parse arg ,s,m;arg u,c;if pos(left(s,2),u)\==0 then do j=length(s) to compare(s,c)-1 by -1;if right(u,j)\==left(c,j) then iterate;_=left(u,length(u)-j);if isnum(_) then return m*_;leave;end;return arg(1) $sfxf:parse arg y;if right(y,1)=='!' then y=$fact!(y);if \isnum(y) then y=$sfxz();if isnum(y) then return y;return $sfxm(y) $sfxm:parse arg z;arg w;b=1000;if right(w,1)=='I' then do;z=shorten(z);w=z;upper w;b=1024;end;p=pos(right(w,1),'KMGTPEZYXWVU');if p==0 then return arg(1);n=shorten(z);r=num(n,f,1);if isnum(r) then return r*b**p;return arg(1) $sfxz:return $sfxa($sfxa($sfxa($sfxa($sfxa($sfxa(y,'PAIRs',2),'DOZens',12),'SCore',20),'GREATGRoss',1728),'GRoss',144),'GOOGOLs',1e100) $t:if tops== then say arg(1);else do;!call=']$T';call "$T" tops arg(1);!call=;end;return ab: arg ab,abl;return abbrev(ab,_,abl) abb: arg abbu;parse arg abb;return abbrev(abbu,_,abbl(abb)) abbl: return verify(arg(1)'a',@abc,'M')-1 abbn: parse arg abbn;return abb(abbn)|abb('NO'abbn) abn: arg ab,abl;return abbrev(ab,_,abl)|abbrev('NO'ab,_,abl+2) changestr:procedure;parse arg o,h,n;r=;w=length(o);if w==0 then return n||h;do forever;parse var h y (o) _ +(w) h;if _== then return r||y;r=r||y||n;end comma:procedure;parse arg _,c,p,t;c=pickblank(c,",");o=p(p 3);p=abs(o);t=p(t 999999999);if \isint(p)|\isint(t)|p==0|arg()>4 then return _;n=_'.9';#=123456789;k=0;return comma_() comma_:if o<0 then do;b=verify(_,' ');if b==0 then return _;e=length(_)-verify(reverse(_),' ')+1;end;else do;b=verify(n,#,"M");e=verify(n,#'0',,verify(n,#"0.",'M'))-p-1;end;do j=e to b by -p while k<t;_=insert(c,_,j);k=k+1;end;return _ copies2:return copies(arg(1),2) copies3:return copies(arg(1),3) drc:procedure;parse arg r,c,p;_=r","c;if p\== then _=_ "("p')';return _ er:parse arg _1,_2;call '$ERR' "14"p(_1) p(word(_1,2) !fid(1)) _2;if _1<0 then return _1;exit result err: call er '-'arg(1),arg(2);return erx: call er '-'arg(1),arg(2);exit halt: call er .1 int:int=num(arg(1),arg(2));if \isint(int) then call er 92,arg(1) arg(2);return int/1 isint: return datatype(arg(1),'W') isnum: return datatype(arg(1),'N') kount1:parse arg qd,string;k1=pos(qd,string);if k1==0 then return 0;return pos(qd,string,k1+1)==0 lower: return translate(arg(1),@abc,translate(@abc)) na:if arg(1)\== then call er 01,arg(2);parse var ops na ops;if na== then call er 35,_o;return na nai: return int(na(),_o) nail: return squish(int(translate(na(),0,','),_o)) nan: return num(na(),_o) no: if arg(1)\== then call er 01,arg(2);return left(_,2)\=='NO' novalue:!sigl=sigl;call er 17,!fid(2) !fid(3) !sigl condition('D') sourceline(!sigl) num:procedure;parse arg x .,f,q;if x== then return x;if isnum(x) then return x/1;x=space(translate(x,,','),0);if \isnum(x) then x=$sfxf(x);if isnum(x) then return x/1;if q==1 then return x;if q== then call er 53,x f;call erx 53,x f p: return word(arg(1),1) pickblank:procedure;parse arg x,y;arg xu;if xu=='BLANK' then return ' ';return p(x y) shorten:procedure;parse arg a,n;return left(a,max(0,length(a)-p(n 1))) simple:return translate(arg(1),'.||--%<>AV'copies('+',25),"·│║─═☼◄►↑↓┤┐└┴┬├┼┘┌╔╗╚╝╟╢╞╡╫╪╤╧╥╨╠╣") squish:return space(translate(arg(1),,word(arg(2) ',',1)),0) syntax:!sigl=sigl;call er 13,!fid(2) !fid(3) !sigl !cal() condition('D') sourceline(!sigl) tem:parse arg r,c,w;if tellinvalid then say '***error!*** row' r", col" c '('@.r.c") is a duplicate of another in the same" w'.';return 0 tg:arg tg; if simple then tg=simple(tg); call $t gridindent || tg; return</lang> output when using the input of:
row1=.5..7.89 row2=9...3 row3=1...89.4 row4=..9.....1 row5=..13.52 row6=6.....5 row7=.6.89...3 row8=....5...7 row9=.98.2..5 pruneALL

$SUDOKU is showing the puzzle
   ┌───────┬───────┬───────┐┌───────┬───────┬───────┐┌───────┬───────┬───────┐
   │       │       │       ││       │       │       ││       │       │       │
   │       │   5   │       ││       │   7   │       ││   8   │   9   │       │
   │       │       │       ││       │       │       ││       │       │       │
   ├───────┼───────┼───────┤├───────┼───────┼───────┤├───────┼───────┼───────┤
   │       │       │       ││       │       │       ││       │       │       │
   │   9   │       │       ││       │   3   │       ││       │       │       │
   │       │       │       ││       │       │       ││       │       │       │
   ├───────┼───────┼───────┤├───────┼───────┼───────┤├───────┼───────┼───────┤
   │       │       │       ││       │       │       ││       │       │       │
   │   1   │       │       ││       │   8   │   9   ││       │   4   │       │
   │       │       │       ││       │       │       ││       │       │       │
   └───────┴───────┴───────┘└───────┴───────┴───────┘└───────┴───────┴───────┘
   ┌───────┬───────┬───────┐┌───────┬───────┬───────┐┌───────┬───────┬───────┐
   │       │       │       ││       │       │       ││       │       │       │
   │       │       │   9   ││       │       │       ││       │       │   1   │
   │       │       │       ││       │       │       ││       │       │       │
   ├───────┼───────┼───────┤├───────┼───────┼───────┤├───────┼───────┼───────┤
   │       │       │       ││       │       │       ││       │       │       │
   │       │       │   1   ││   3   │       │   5   ││   2   │       │       │
   │       │       │       ││       │       │       ││       │       │       │
   ├───────┼───────┼───────┤├───────┼───────┼───────┤├───────┼───────┼───────┤
   │       │       │       ││       │       │       ││       │       │       │
   │   6   │       │       ││       │       │       ││   5   │       │       │
   │       │       │       ││       │       │       ││       │       │       │
   └───────┴───────┴───────┘└───────┴───────┴───────┘└───────┴───────┴───────┘
   ┌───────┬───────┬───────┐┌───────┬───────┬───────┐┌───────┬───────┬───────┐
   │       │       │       ││       │       │       ││       │       │       │
   │       │   6   │       ││   8   │   9   │       ││       │       │   3   │
   │       │       │       ││       │       │       ││       │       │       │
   ├───────┼───────┼───────┤├───────┼───────┼───────┤├───────┼───────┼───────┤
   │       │       │       ││       │       │       ││       │       │       │
   │       │       │       ││       │   5   │       ││       │       │   7   │
   │       │       │       ││       │       │       ││       │       │       │
   ├───────┼───────┼───────┤├───────┼───────┼───────┤├───────┼───────┼───────┤
   │       │       │       ││       │       │       ││       │       │       │
   │       │   9   │   8   ││       │   2   │       ││       │   5   │       │
   │       │       │       ││       │       │       ││       │       │       │
   └───────┴───────┴───────┘└───────┴───────┴───────┘└───────┴───────┴───────┘

$SUDOKU is starting prune pass # 1
$SUDOKU found the digit 8 by exclusiveness at cell 2,2 (2478)
$SUDOKU found the digit 3 by exclusiveness at cell 3,7 (367)
$SUDOKU found the digit 5 by exclusiveness at cell 4,1 (234578)
$SUDOKU found the digit 8 by exclusiveness at cell 5,1 (478)
$SUDOKU found the digit 9 by exclusiveness at cell 6,4 (12479)
$SUDOKU found the digit 9 by exclusiveness at cell 5,9 (469)
$SUDOKU found the digit 5 by exclusiveness at cell 7,3 (2457)
$SUDOKU found the digit 1 by exclusiveness at cell 8,2 (1234)
$SUDOKU found the digit 9 by exclusiveness at cell 8,7 (469)
$SUDOKU found the digit 8 by exclusiveness at cell 8,8 (268)
$SUDOKU found the digit 8 by exclusiveness at cell 6,9 (48)
$SUDOKU found the digit 8 by exclusiveness at cell 4,6 (24678)
$SUDOKU found the digit 4 by exclusiveness at cell 4,7 (467)
$SUDOKU found the digit 2 by exclusiveness at cell 7,8 (12)
$SUDOKU found the digit 4 by exclusiveness at cell 9,9 (46)
$SUDOKU found the digit 6 by exclusiveness at cell 9,7 (16)
$SUDOKU found the digit 1 by exclusiveness at cell 7,7 (1)
$SUDOKU found the digit 1 by exclusiveness at cell 2,8 (167)
$SUDOKU found the digit 7 by exclusiveness at cell 2,7 (7)
 ∙
 ∙
 ∙
   some output elided ∙∙∙
 ∙
 ∙
 ∙ 
   ┌───────┬───────┬───────┐┌───────┬───────┬───────┐┌───────┬───────┬───────┐
   │       │       │       ││       │       │       ││       │       │       │
   │   4   │   5   │   3   ││   1   │   7   │   6   ││   8   │   9   │   2   │
   │       │       │       ││       │       │       ││       │       │       │
   ├───────┼───────┼───────┤├───────┼───────┼───────┤├───────┼───────┼───────┤
   │       │       │       ││       │       │       ││       │       │       │
   │   9   │   8   │   6   ││   4   │   3   │   2   ││   7   │   1   │   5   │
   │       │       │       ││       │       │       ││       │       │       │
   ├───────┼───────┼───────┤├───────┼───────┼───────┤├───────┼───────┼───────┤
   │       │       │       ││       │       │       ││       │       │       │
   │   1   │   2   │   7   ││   5   │   8   │   9   ││   3   │   4   │   6   │
   │       │       │       ││       │       │       ││       │       │       │
   └───────┴───────┴───────┘└───────┴───────┴───────┘└───────┴───────┴───────┘
   ┌───────┬───────┬───────┐┌───────┬───────┬───────┐┌───────┬───────┬───────┐
   │       │       │       ││       │       │       ││       │       │       │
   │   5   │   3   │   9   ││   2   │   6   │   8   ││   4   │   7   │   1   │
   │       │       │       ││       │       │       ││       │       │       │
   ├───────┼───────┼───────┤├───────┼───────┼───────┤├───────┼───────┼───────┤
   │       │       │       ││       │       │       ││       │       │       │
   │   8   │   7   │   1   ││   3   │   4   │   5   ││   2   │   6   │   9   │
   │       │       │       ││       │       │       ││       │       │       │
   ├───────┼───────┼───────┤├───────┼───────┼───────┤├───────┼───────┼───────┤
   │       │       │       ││       │       │       ││       │       │       │
   │   6   │   4   │   2   ││   9   │   1   │   7   ││   5   │   3   │   8   │
   │       │       │       ││       │       │       ││       │       │       │
   └───────┴───────┴───────┘└───────┴───────┴───────┘└───────┴───────┴───────┘
   ┌───────┬───────┬───────┐┌───────┬───────┬───────┐┌───────┬───────┬───────┐
   │       │       │       ││       │       │       ││       │       │       │
   │   7   │   6   │   5   ││   8   │   9   │   4   ││   1   │   2   │   3   │
   │       │       │       ││       │       │       ││       │       │       │
   ├───────┼───────┼───────┤├───────┼───────┼───────┤├───────┼───────┼───────┤
   │       │       │       ││       │       │       ││       │       │       │
   │   2   │   1   │   4   ││   6   │   5   │   3   ││   9   │   8   │   7   │
   │       │       │       ││       │       │       ││       │       │       │
   ├───────┼───────┼───────┤├───────┼───────┼───────┤├───────┼───────┼───────┤
   │       │       │       ││       │       │       ││       │       │       │
   │   3   │   9   │   8   ││   7   │   2   │   1   ││   6   │   5   │   4   │
   │       │       │       ││       │       │       ││       │       │       │
   └───────┴───────┴───────┘└───────┴───────┴───────┘└───────┴───────┴───────┘

$SUDOKU is starting prune pass # 4
 sudoku puzzle solved.

Ruby

Example of a back-tracking solver, from wp:Algorithmics of sudoku

Works with: Ruby version 1.8.7+

<lang ruby>def read_matrix(fh)

 matrix = []

 (0..8).each { |i|
   l = fh.readline
   matrix[i] = []
   (0..8).each { |j|
     matrix[i][j] = l[j..j].to_i
   }
 }
 matrix

end

def permissible(matrix, i, j)

 ok = [true] * 9
 # Same as another in the column isn't permissible...
 (0..8).each { |i2|
   next if matrix[i2][j] == 0
   ok[matrix[i2][j] - 1] = false
 }
 # Same as another in the row isn't permissible...
 (0..8).each { |j2|
   next if matrix[i][j2] == 0
   ok[matrix[i][j2] - 1] = false
 }
 # Same as another in the 3x3 block isn't permissible...
 igroup = (i / 3) * 3
 jgroup = (j / 3) * 3
 (igroup..(igroup + 2)).each { |i2|
   (jgroup..(jgroup + 2)).each { |j2|
     next if matrix[i2][j2] == 0
     ok[matrix[i2][j2] - 1] = false
   }
 }
 # Convert to the array format...
 (1..9).select { |i2| ok[i2-1] }

end

def deep_copy_sudoku(matrix)

 matrix.collect { |row| row.dup }

end

def solve_sudoku(matrix)

 loop do
   options = []
   (0..8).each { |i|
     (0..8).each { |j|
       next if matrix[i][j] != 0
       p = permissible(matrix, i, j)
       # If nothing is permissible, there is no solution at this level.
       return nil if p.length == 0
       options.push({:i => i, :j => j, :permissible => p})
     }
   }
   # If the matrix is complete, we have a solution...
   return matrix if options.length == 0

   omin = options.min_by { |x| x[:permissible].length }

   # If there is an option with only one solution, set it and re-check permissibility
   if omin[:permissible].length == 1
     matrix[omin[:i]][omin[:j]] = omin[:permissible][0]
     next
   end

   # We have two or more choices. We need to search both...
   omin[:permissible].each { |v|
     mtmp = deep_copy_sudoku(matrix)
     mtmp[omin[:i]][omin[:j]] = v
     ret = solve_sudoku(mtmp)
     return ret if ret
   }

   # We did an exhaustive search on this branch and nothing worked out.
   return nil
 end

end

def print_matrix(matrix)

 if not matrix
   puts "Impossible"
   return
 end

 border = "+-----+-----+-----+"
 (0..8).each { |i|
   puts border if i%3 == 0
   (0..8).each { |j|
     print(j%3 == 0 ? "|" : " ")
     print(matrix[i][j] == 0 ? "." : matrix[i][j])
   }
   print "|\n"
 }
 puts border

end

matrix = read_matrix(DATA) print_matrix(matrix) puts print_matrix(solve_sudoku(matrix))

__END__ 394__267_ ___3__4__ 5__69__2_ _45___9__ 6_______7 __7___58_ _1__67__8 __9__8___ _264__735</lang> Output:

+-----+-----+-----+
|3 9 4|. . 2|6 7 .|
|. . .|3 . .|4 . .|
|5 . .|6 9 .|. 2 .|
+-----+-----+-----+
|. 4 5|. . .|9 . .|
|6 . .|. . .|. . 7|
|. . 7|. . .|5 8 .|
+-----+-----+-----+
|. 1 .|. 6 7|. . 8|
|. . 9|. . 8|. . .|
|. 2 6|4 . .|7 3 5|
+-----+-----+-----+

+-----+-----+-----+
|3 9 4|8 5 2|6 7 1|
|2 6 8|3 7 1|4 5 9|
|5 7 1|6 9 4|8 2 3|
+-----+-----+-----+
|1 4 5|7 8 3|9 6 2|
|6 8 2|9 4 5|3 1 7|
|9 3 7|1 2 6|5 8 4|
+-----+-----+-----+
|4 1 3|5 6 7|2 9 8|
|7 5 9|2 3 8|1 4 6|
|8 2 6|4 1 9|7 3 5|
+-----+-----+-----+

Scala

I use the following slightly modified code for creating new sudokus and it seems to me usable for solving given sudokus. It doesn't look like elegant and functional programming - so what! it works! This solver works with normally 9x9 sudokus as well as with sudokus of jigsaw type or sudokus with additional condition like diagonal constraint.

Works with: Scala version 2.9.1

<lang scala>object SudokuSolver extends App {

 class Solver {
   var solution = new Array[Int](81)   //listOfFields toArray
   val fp2m: Int => Tuple2[Int,Int] = pos => Pair(pos/9+1,pos%9+1) //get row, col from array position
   val setAll = (1 to 9) toSet //all possibilities
   val arrayGroups = new Array[List[List[Int]]](81)
   val sv: Int => Int = (row: Int) => (row-1)*9 //start value group row
   val ev: Int => Int = (row: Int) => sv(row)+8 //end value group row
   val fgc: (Int,Int) => Int = (i,col) => i*9+col-1 //get group col
   val fgs: Int => (Int,Int) = p => Pair(p, p/(27)*3+p%9/3) //get group square box
   for (pos <- 0 to 80) {
     val (row,col) = fp2m(pos)
     val gRow = (sv(row) to ev(row)).toList
     val gCol = ((0 to 8) toList) map (fgc(_,col))
     val gSquare = (0 to 80 toList) map fgs filter (_._2==(fgs(pos))._2) map (_._1)
     arrayGroups(pos) = List(gRow,gCol,gSquare)
   }
   val listGroups = arrayGroups toList 
   
   val fpv4s: (Int) => List[Int] = pos => {   //get possible values for solving
     val setRow = (listGroups(pos)(0) map (solution(_))).toSet
     val setCol = listGroups(pos)(1).map(solution(_)).toSet
     val setSquare = listGroups(pos)(2).map(solution(_)).toSet
     val setG = setRow++setCol++setSquare--Set(0)
     val setPossible = setAll--setG
     setPossible.toList.sortWith(_<_)
   }
   
   
   //solve the riddle: Nil ==> solution does not exist
   def solve(listOfFields: List[Int]): List[Int] = {
     solution = listOfFields toArray
     def checkSol(uncheckedSol: List[Int]): List[Int] = {
       if (uncheckedSol == Nil) return Nil
       solution = uncheckedSol toArray
       val check = (0 to 80).map(fpv4s(_)).filter(_.size>0)
       if (check == Nil) return uncheckedSol
       return Nil
     }
   
     val f1: Int => Pair[Int,Int] = p => Pair(p,listOfFields(p))
     val numFields = (0 to 80 toList) map f1 filter (_._2==0)
     val iter = numFields map ((_: (Int,Int))._1)
     var p_iter = 0
     val first: () => Int = () => {
       val ret = numFields match {
         case Nil => -1
         case _   => numFields(0)._1
       }
       ret
     }
 
     val last: () => Int = () => {
       val ret = numFields match {
         case Nil => -1
         case _   => numFields(numFields.size-1)._1
       }
       ret
     }
 
     val hasPrev: () => Boolean = () => p_iter > 0
     val prev: () => Int = () => {p_iter -= 1; iter(p_iter)}
     val hasNext: () => Boolean = () => p_iter < iter.size-1
     val next: () => Int = () => {p_iter += 1; iter(p_iter)}
     val fixed: Int => Boolean = pos => listOfFields(pos) != 0  
     val possiArray = new Array[List[Int]](numFields.size)
     val firstUF = first() //first unfixed
     if (firstUF < 0) return checkSol(solution.toList) //that is it!
     var pif = iter(p_iter) //pos in fields
     val lastUF = last() //last unfixed
     val (row,col) = fp2m(pif)
     possiArray(p_iter) = fpv4s(pif).toList.sortWith(_<_)
     while(pif <= lastUF) {
       val (row,col) = fp2m(pif)
       if (possiArray(p_iter) == null) possiArray(p_iter) = fpv4s(pif).toList.sortWith(_<_)
       val possis = possiArray(p_iter)
       if (possis.isEmpty) {
         if (hasPrev()) {
           possiArray(p_iter) = null
           solution(pif) = 0
           pif = prev()
         } else {
           return Nil
         }
       } else {
         solution(pif) = possis(0)
         possiArray(p_iter) = (possis.toSet - possis(0)).toList.sortWith(_<_)
         if (hasNext()) {
           pif = next()
         } else {
           return checkSol(solution.toList)
         }
       }
     }
     checkSol(solution.toList)
   }
 }  
 val f2Str: List[Int] => String = fields => {
   val sepLine = "+---+---+---+"
   val sepPoints = Set(2,5,8)
   val fs: (Int, Int) => String = (i, v) => v.toString.replace("0"," ")+(if (sepPoints.contains(i%9)) "|" else "")
   sepLine+"\n"+(0 to fields.size-1).map(i => (if (i%9==0) "|" else "")+fs(i,fields(i))+(if (i%9==8) if (sepPoints.contains(i/9)) "\n"+sepLine+"\n" else "\n" else "")).foldRight("")(_+_)
 }
 
 val solver = new Solver()
 val riddle = List(3,9,4,0,0,2,6,7,0,
                   0,0,0,3,0,0,4,0,0,
                   5,0,0,6,9,0,0,2,0,
                   0,4,5,0,0,0,9,0,0,
                   6,0,0,0,0,0,0,0,7,
                   0,0,7,0,0,0,5,8,0,
                   0,1,0,0,6,7,0,0,8,
                   0,0,9,0,0,8,0,0,0,
                   0,2,6,4,0,0,7,3,5)
 println("riddle:")
 println(f2Str(riddle))
 var solution = solver.solve(riddle)
 println("solution:")
 println(solution match {case Nil => "no solution!!!" case _ => f2Str(solution)})

}</lang> Output:

riddle:
+---+---+---+
|394|  2|67 |
|   |3  |4  |
|5  |69 | 2 |
+---+---+---+
| 45|   |9  |
|6  |   |  7|
|  7|   |58 |
+---+---+---+
| 1 | 67|  8|
|  9|  8|   |
| 26|4  |735|
+---+---+---+

solution:
+---+---+---+
|394|852|671|
|268|371|459|
|571|694|823|
+---+---+---+
|145|783|962|
|682|945|317|
|937|126|584|
+---+---+---+
|413|567|298|
|759|238|146|
|826|419|735|
+---+---+---+

The implementation above doesn't work so effective for sudokus like Bracmat version, therefore I implemented a second version inspired by Java section:

Works with: Scala version 2.9.1

<lang scala>object SudokuSolver extends App {

 object Solver {
   var solution = new Array[Int](81)
   val fap: (Int, Int) => Int = (row, col) => (row)*9+col //function array position
   def solve(listOfFields: List[Int]): List[Int] = {
     solution = listOfFields toArray
     
     val mRowSubset = new Array[Boolean](81)
     val mColSubset = new Array[Boolean](81)
     val mBoxSubset = new Array[Boolean](81)
     def initSubsets: Unit = {
       for (row <- 0 to 8) {
         for (col <- 0 to 8) {
           val value = solution(fap(row, col))
           if (value != 0)
             setSubsetValue(row, col, value, true)
         }
       }
     }
     
     def setSubsetValue(r: Int, c: Int, value: Int, present: Boolean): Unit = {
       mRowSubset(fap(r, value - 1)) = present
       mColSubset(fap(c, value - 1)) = present
       mBoxSubset(fap(computeBoxNo(r, c), value - 1)) = present
     }
     def computeBoxNo(r: Int, c: Int): Int = {
       val boxRow = r / 3
       val boxCol = c / 3
       return boxRow * 3 + boxCol 
     }
     def isValid(r: Int, c: Int, value: Int): Boolean = {
       val vVal = value - 1
       val isPresent = mRowSubset(fap(r, vVal)) || mColSubset(fap(c, vVal)) || mBoxSubset(fap(computeBoxNo(r, c), vVal))
       return !isPresent
     }
     def solve(row: Int, col: Int): Boolean = {
       var r = row
       var c = col
       if (r == 9) {
         r = 0
         c += 1
         if (c == 9)
           return true
       }
       
       if(solution(fap(r,c)) != 0)
         return solve(r+1,c)
       for(value <- 1 to 9) 
         if(isValid(r, c, value)) {
           solution(fap(r,c)) = value
           setSubsetValue(r, c, value, true)
           if(solve(r+1,c))
             return true
           setSubsetValue(r, c, value, false)
         }
       solution(fap(r,c)) = 0
       return false
     }

     def checkSol: Boolean = {
       initSubsets
       if ((mRowSubset.exists(_==false)) || (mColSubset.exists(_==false)) || (mBoxSubset.exists(_==false))) return false
       true
     }
     initSubsets
     val ret = solve(0,0)
     if (ret) 
       if (checkSol) return solution.toList else Nil
     else
       return Nil
   }
 }
 
 val f2Str: List[Int] => String = fields => {
   val f2Stri: List[Int] => String = fields => {
     val sepLine = "+---+---+---+"
     val sepPoints = Set(2,5,8)
     val fs: (Int, Int) => String = (i, v) => v.toString.replace("0"," ")+(if (sepPoints.contains(i%9)) "|" else "")
     val s = sepLine+"\n"+(0 to fields.size-1).map(i => (if (i%9==0) "|" else "")+fs(i,fields(i))+(if (i%9==8) if (sepPoints.contains(i/9)) "\n"+sepLine+"\n" else "\n" else "")).foldRight("")(_+_)
     s
   }
   val s = fields match {case Nil => "no solution!!!" case _ => f2Stri(fields)}
   s
 }
 val elapsedtime: (=> Unit) => Long = f => {val s = System.currentTimeMillis; f; (System.currentTimeMillis - s)/1000}
 var sol = List[Int]()
 
 val sudokus = List(
     ("riddle used in Ada section:",
      "394..267....3..4..5..69..2..45...9..6.......7..7...58..1..67..8..9..8....264..735"),
     ("riddle used in Bracmat section:",
      "..............3.85..1.2.......5.7.....4...1...9.......5......73..2.1........4...9"),
     ("riddle from Groovy section: 4th exceptionally difficult example in Wikipedia: ~80 seconds",
      "..3......4...8..36..8...1...4..6..73...9..........2..5..4.7..686........7..6..5.."),
     ("riddle used in Ada section with incorrect modifactions - it should fail:",
      "3943.267....3..4..5..69..2..45...9..6.......7..7...58..1..67..8..9..8....264..735"),       
     ("riddle constructed with mess - it should fail too:",
      "123456789456789123789123456.45..89..6.......72.7...58.31..67..8..9..8....264..735"))
 for (sudoku <- sudokus) {
   val desc = sudoku._1
   val riddle = sudoku._2.replace(".","0").toList.map(_.toString.toInt)
   println(desc+"\n"+f2Str(riddle)+"\n"
     +"elapsed time: "+elapsedtime(sol = Solver.solve(riddle))+" sec"+"\n"+"solution:"+"\n"+f2Str(sol)
     +("\n"*2))
 }

}</lang> Output:

riddle used in Ada section:
+---+---+---+
|394|  2|67 |
|   |3  |4  |
|5  |69 | 2 |
+---+---+---+
| 45|   |9  |
|6  |   |  7|
|  7|   |58 |
+---+---+---+
| 1 | 67|  8|
|  9|  8|   |
| 26|4  |735|
+---+---+---+
elapsed time: 0 sec
solution:
+---+---+---+
|394|852|671|
|268|371|459|
|571|694|823|
+---+---+---+
|145|783|962|
|682|945|317|
|937|126|584|
+---+---+---+
|413|567|298|
|759|238|146|
|826|419|735|
+---+---+---+

riddle used in Bracmat section:
+---+---+---+
|   |   |   |
|   |  3| 85|
|  1| 2 |   |
+---+---+---+
|   |5 7|   |
|  4|   |1  |
| 9 |   |   |
+---+---+---+
|5  |   | 73|
|  2| 1 |   |
|   | 4 |  9|
+---+---+---+
elapsed time: 43 sec
solution:
+---+---+---+
|987|654|321|
|246|173|985|
|351|928|746|
+---+---+---+
|128|537|694|
|634|892|157|
|795|461|832|
+---+---+---+
|519|286|473|
|472|319|568|
|863|745|219|
+---+---+---+

riddle from Groovy section: 4th exceptionally difficult example in Wikipedia: ~80 seconds
+---+---+---+
|  3|   |   |
|4  | 8 | 36|
|  8|   |1  |
+---+---+---+
| 4 | 6 | 73|
|   |9  |   |
|   |  2|  5|
+---+---+---+
|  4| 7 | 68|
|6  |   |   |
|7  |6  |5  |
+---+---+---+
elapsed time: 3 sec
solution:
+---+---+---+
|123|456|789|
|457|189|236|
|968|327|154|
+---+---+---+
|249|561|873|
|576|938|412|
|831|742|695|
+---+---+---+
|314|275|968|
|695|814|327|
|782|693|541|
+---+---+---+

riddle used in Ada section with incorrect modifactions - it should fail:
+---+---+---+
|394|3 2|67 |
|   |3  |4  |
|5  |69 | 2 |
+---+---+---+
| 45|   |9  |
|6  |   |  7|
|  7|   |58 |
+---+---+---+
| 1 | 67|  8|
|  9|  8|   |
| 26|4  |735|
+---+---+---+
elapsed time: 0 sec
solution:
no solution!!!

riddle constructed with mess - it should fail too:
+---+---+---+
|123|456|789|
|456|789|123|
|789|123|456|
+---+---+---+
| 45|  8|9  |
|6  |   |  7|
|2 7|   |58 |
+---+---+---+
|31 | 67|  8|
|  9|  8|   |
| 26|4  |735|
+---+---+---+
elapsed time: 0 sec
solution:
no solution!!!

Tcl

Adapted from a page on the Tcler's Wiki to use a standard object system.

Note that you can implement more rules if you want. Just make another subclass of Rule and the solver will pick it up and use it automatically.

Works with: Tcl version 8.6

or

Library: TclOO

<lang tcl>package require Tcl 8.6 oo::class create Sudoku {

   variable idata
   method clear {} {

for {set y 0} {$y < 9} {incr y} { for {set x 0} {$x < 9} {incr x} { my set $x $y {} } }

   }
   method load {data} {

set error "data must be a 9-element list, each element also being a\ list of 9 numbers from 1 to 9 or blank or an @ symbol." if {[llength $data] != 9} { error $error } for {set y 0} {$y<9} {incr y} { set row [lindex $data $y] if {[llength $row] != 9} { error $error } for {set x 0} {$x<9} {incr x} { set d [lindex $row $x] if {![regexp {^[@1-9]?$} $d]} { error $d-$error } if {$d eq "@"} {set d ""} my set $x $y $d } }

   }
   method dump {} {

set rows {} for {set y 0} {$y < 9} {incr y} { lappend rows [my getRow 0 $y] } return $rows

   }
   method Log msg {

# Chance to print message

   }
   method set {x y value} {

if {[catch {set value [format %d $value]}]} {set value 0} if {$value<1 || $value>9} { set idata(sq$x$y) {} } else { set idata(sq$x$y) $value }

   }
   method get {x y} {

if {![info exists idata(sq$x$y)]} { return {} } return $idata(sq$x$y)

   }
   method getRow {x y} {

set row {} for {set x 0} {$x<9} {incr x} { lappend row [my get $x $y] } return $row

   }
   method getCol {x y} {

set col {} for {set y 0} {$y<9} {incr y} { lappend col [my get $x $y] } return $col

   }
   method getRegion {x y} {

set xR [expr {($x/3)*3}] set yR [expr {($y/3)*3}] set regn {} for {set x $xR} {$x < $xR+3} {incr x} { for {set y $yR} {$y < $yR+3} {incr y} { lappend regn [my get $x $y] } } return $regn

   }

}

  1. SudokuSolver inherits from Sudoku, and adds the ability to filter
  2. possibilities for a square by looking at all the squares in the row, column,
  3. and region that the square is a part of. The method 'solve' contains a list
  4. of rule-objects to use, and iterates over each square on the board, applying
  5. each rule sequentially until the square is allocated.

oo::class create SudokuSolver {

   superclass Sudoku
   method validchoices {x y} {

if {[my get $x $y] ne {}} { return [my get $x $y] }

set row [my getRow $x $y] set col [my getCol $x $y] set regn [my getRegion $x $y] set eliminate [list {*}$row {*}$col {*}$regn] set eliminate [lsearch -all -inline -not $eliminate {}] set eliminate [lsort -unique $eliminate]

set choices {} for {set c 1} {$c < 10} {incr c} { if {$c ni $eliminate} { lappend choices $c } } if {[llength $choices]==0} { error "No choices left for square $x,$y" } return $choices

   }
   method completion {} {

return [expr { 81-[llength [lsearch -all -inline [join [my dump]] {}]] }]

   }
   method solve {} {

foreach ruleClass [info class subclass Rule] { lappend rules [$ruleClass new] }

while {1} { set begin [my completion] for {set y 0} {$y < 9} {incr y} { for {set x 0} {$x < 9} {incr x} { if {[my get $x $y] eq ""} { foreach rule $rules { set c [$rule solve [self] $x $y] if {$c} { my set $x $y $c my Log "[info object class $rule] solved [self] at $x,$y for $c" break } } } } } set end [my completion] if {$end==81} { my Log "Finished solving!" break } elseif {$begin==$end} { my Log "A round finished without solving any squares, giving up." break } } foreach rule $rules { $rule destroy }

   }

}

  1. Rule is the template for the rules used in Solver. The other rule-objects
  2. apply their logic to the values passed in and return either '0' or a number
  3. to allocate to the requested square.

oo::class create Rule {

   method solve {hSudoku x y} {

if {![info object isa typeof $hSudoku SudokuSolver]} { error "hSudoku must be an instance of class SudokuSolver." }

tailcall my Solve $hSudoku $x $y [$hSudoku validchoices $x $y]

   }

}

  1. Get all the allocated numbers for each square in the the row, column, and
  2. region containing $x,$y. If there is only one unallocated number among all
  3. three groups, it must be allocated at $x,$y

oo::class create RuleOnlyChoice {

   superclass Rule
   method Solve {hSudoku x y choices} {

if {[llength $choices]==1} { return $choices } else { return 0 }

   }

}

  1. Test each column to determine if $choice is an invalid choice for all other
  2. columns in row $X. If it is, it must only go in square $x,$y.

oo::class create RuleColumnChoice {

   superclass Rule
   method Solve {hSudoku x y choices} {

foreach choice $choices { set failed 0 for {set x2 0} {$x2<9} {incr x2} { if {$x2 != $x && $choice in [$hSudoku validchoices $x2 $y]} { set failed 1 break } } if {!$failed} {return $choice} } return 0

   }

}

  1. Test each row to determine if $choice is an invalid choice for all other
  2. rows in column $y. If it is, it must only go in square $x,$y.

oo::class create RuleRowChoice {

   superclass Rule
   method Solve {hSudoku x y choices} {

foreach choice $choices { set failed 0 for {set y2 0} {$y2<9} {incr y2} { if {$y2 != $y && $choice in [$hSudoku validchoices $x $y2]} { set failed 1 break } } if {!$failed} {return $choice} } return 0

   }

}

  1. Test each square in the region occupied by $x,$y to determine if $choice is
  2. an invalid choice for all other squares in that region. If it is, it must
  3. only go in square $x,$y.

oo::class create RuleRegionChoice {

   superclass Rule
   method Solve {hSudoku x y choices} {

foreach choice $choices { set failed 0 set regnX [expr {($x/3)*3}] set regnY [expr {($y/3)*3}] for {set y2 $regnY} {$y2 < $regnY+3} {incr y2} { for {set x2 $regnX} {$x2 < $regnX+3} {incr x2} { if { ($x2!=$x || $y2!=$y) && $choice in [$hSudoku validchoices $x2 $y2] } then { set failed 1 break } } } if {!$failed} {return $choice} } return 0

   }

}</lang> Demonstration code: <lang tcl>SudokuSolver create sudoku sudoku load {

   {3 9 4    @ @ 2    6 7 @}
   {@ @ @    3 @ @    4 @ @}
   {5 @ @    6 9 @    @ 2 @}
   {@ 4 5    @ @ @    9 @ @}
   {6 @ @    @ @ @    @ @ 7}
   {@ @ 7    @ @ @    5 8 @}
   {@ 1 @    @ 6 7    @ @ 8}
   {@ @ 9    @ @ 8    @ @ @}
   {@ 2 6    4 @ @    7 3 5}

} sudoku solve

  1. Simple pretty-printer for completed sudokus

puts +-----+-----+-----+ foreach line [sudoku dump] postline {0 0 1 0 0 1 0 0 1} {

   puts |[lrange $line 0 2]|[lrange $line 3 5]|[lrange $line 6 8]|
   if {$postline} {

puts +-----+-----+-----+

   }

} sudoku destroy</lang> Sample output:

+-----+-----+-----+
|3 9 4|8 5 2|6 7 1|
|2 6 8|3 7 1|4 5 9|
|5 7 1|6 9 4|8 2 3|
+-----+-----+-----+
|1 4 5|7 8 3|9 6 2|
|6 8 2|9 4 5|3 1 7|
|9 3 7|1 2 6|5 8 4|
+-----+-----+-----+
|4 1 3|5 6 7|2 9 8|
|7 5 9|2 3 8|1 4 6|
|8 2 6|4 1 9|7 3 5|
+-----+-----+-----+

If we'd added a logger method (after creating the sudoku object but before running the solver) like this: <lang tcl>oo::objdefine sudoku method Log msg {puts $msg}</lang> Then this additional logging output would have been produced prior to the result being printed:

::RuleOnlyChoice solved ::sudoku at 8,0 for 1
::RuleColumnChoice solved ::sudoku at 1,1 for 6
::RuleRegionChoice solved ::sudoku at 4,1 for 7
::RuleRowChoice solved ::sudoku at 7,1 for 5
::RuleOnlyChoice solved ::sudoku at 8,1 for 9
::RuleColumnChoice solved ::sudoku at 1,2 for 7
::RuleColumnChoice solved ::sudoku at 5,2 for 4
::RuleRowChoice solved ::sudoku at 6,2 for 8
::RuleOnlyChoice solved ::sudoku at 8,2 for 3
::RuleColumnChoice solved ::sudoku at 3,3 for 7
::RuleRowChoice solved ::sudoku at 1,4 for 8
::RuleRowChoice solved ::sudoku at 5,4 for 5
::RuleRowChoice solved ::sudoku at 6,4 for 3
::RuleRowChoice solved ::sudoku at 0,5 for 9
::RuleOnlyChoice solved ::sudoku at 1,5 for 3
::RuleOnlyChoice solved ::sudoku at 0,6 for 4
::RuleOnlyChoice solved ::sudoku at 2,6 for 3
::RuleColumnChoice solved ::sudoku at 3,6 for 5
::RuleOnlyChoice solved ::sudoku at 6,6 for 2
::RuleOnlyChoice solved ::sudoku at 7,6 for 9
::RuleOnlyChoice solved ::sudoku at 0,7 for 7
::RuleOnlyChoice solved ::sudoku at 1,7 for 5
::RuleColumnChoice solved ::sudoku at 4,7 for 3
::RuleOnlyChoice solved ::sudoku at 6,7 for 1
::RuleOnlyChoice solved ::sudoku at 0,8 for 8
::RuleOnlyChoice solved ::sudoku at 4,8 for 1
::RuleOnlyChoice solved ::sudoku at 5,8 for 9
::RuleOnlyChoice solved ::sudoku at 3,0 for 8
::RuleOnlyChoice solved ::sudoku at 4,0 for 5
::RuleColumnChoice solved ::sudoku at 2,1 for 8
::RuleOnlyChoice solved ::sudoku at 5,1 for 1
::RuleOnlyChoice solved ::sudoku at 2,2 for 1
::RuleRowChoice solved ::sudoku at 0,3 for 1
::RuleColumnChoice solved ::sudoku at 4,3 for 8
::RuleColumnChoice solved ::sudoku at 5,3 for 3
::RuleOnlyChoice solved ::sudoku at 7,3 for 6
::RuleOnlyChoice solved ::sudoku at 8,3 for 2
::RuleOnlyChoice solved ::sudoku at 2,4 for 2
::RuleColumnChoice solved ::sudoku at 3,4 for 9
::RuleOnlyChoice solved ::sudoku at 4,4 for 4
::RuleOnlyChoice solved ::sudoku at 7,4 for 1
::RuleColumnChoice solved ::sudoku at 3,5 for 1
::RuleOnlyChoice solved ::sudoku at 4,5 for 2
::RuleOnlyChoice solved ::sudoku at 5,5 for 6
::RuleOnlyChoice solved ::sudoku at 8,5 for 4
::RuleOnlyChoice solved ::sudoku at 3,7 for 2
::RuleOnlyChoice solved ::sudoku at 7,7 for 4
::RuleOnlyChoice solved ::sudoku at 8,7 for 6
::RuleOnlyChoice solved ::sudoku at 0,1 for 2
Finished solving!

Ursala

<lang Ursala>#import std

  1. import nat

sudoku =

@FL mat0+ block3+ mat` *+ block3*+ block9+ -+

  ~&rSL+ (psort (nleq+)* <~&blrl,~&blrr>)+ ~&arg^& -+
     ~&al?\~&ar ~&aa^&~&afahPRPfafatPJPRY+ ~&farlthlriNCSPDPDrlCS2DlrTS2J,
     ^|J/~& ~&rt!=+ ^= ~&s+ ~&H(
        -+.|=&lrr;,|=&lrl;,|=≪+-,
        ~&rgg&& ~&irtPFXlrjrXPS; ~&lrK2tkZ2g&& ~&llrSL2rDrlPrrPljXSPTSL)+-,
  //~&p ^|DlrDSLlrlPXrrPDSL(~&,num*+ rep2 block3)*= num block27 ~&iiK0 iota9,
  * `0?=\~&iNC ! ~&t digits+-</lang>

test program: <lang Ursala>#show+

example =

sudoku

-[ 394002670 000300400 500690020 045000900 600000007 007000580 010067008 009008000 026400735]-</lang> output:

394 852 671
268 371 459
571 694 823

145 783 962
682 945 317
937 126 584

413 567 298
759 238 146
826 419 735

VBA

Translation of: Fortran

<lang VBA>Dim grid(9, 9) Dim gridSolved(9, 9)

Public Sub Solve(i, j)

 If i > 9 Then
   'exit with gridSolved = Grid
   For r = 1 To 9
     For c = 1 To 9
       gridSolved(r, c) = grid(r, c)
     Next c
   Next r
   Exit Sub
 End If
 For n = 1 To 9
   If isSafe(i, j, n) Then
     nTmp = grid(i, j)
     grid(i, j) = n
     If j = 9 Then
       Solve i + 1, 1
     Else
       Solve i, j + 1
     End If
     grid(i, j) = nTmp
   End If
 Next n

End Sub

Public Function isSafe(i, j, n) As Boolean Dim iMin As Integer Dim jMin As Integer

If grid(i, j) <> 0 Then

 isSafe = (grid(i, j) = n)
 Exit Function

End If

'grid(i,j) is an empty cell. Check if n is OK 'first check the row i For c = 1 To 9

 If grid(i, c) = n Then
   isSafe = False
   Exit Function
 End If

Next c

'now check the column j For r = 1 To 9

If grid(r, j) = n Then
  isSafe = False
  Exit Function
End If

Next r

'finally, check the 3x3 subsquare containing grid(i,j) iMin = 1 + 3 * Int((i - 1) / 3) jMin = 1 + 3 * Int((j - 1) / 3) For r = iMin To iMin + 2

 For c = jMin To jMin + 2
   If grid(r, c) = n Then
     isSafe = False
     Exit Function
   End If
 Next c

Next r

'all tests were OK isSafe = True End Function

Public Sub Sudoku()

 'main routine
 'to use, fill in the grid and
 'type "Sudoku" in the Immediate panel of the Visual Basic for Applications window
 Dim s(9) As String
 'initialise grid using 9 strings,one per row
 s(1) = "001005070"
 s(2) = "920600000"
 s(3) = "008000600"
 s(4) = "090020401"
 s(5) = "000000000"
 s(6) = "304080090"
 s(7) = "007000300"
 s(8) = "000007069"
 s(9) = "010800700"
 For i = 1 To 9
   For j = 1 To 9
     grid(i, j) = Int(Val(Mid$(s(i), j, 1)))
   Next j
 Next i
 'solve it!
 Solve 1, 1
 'print solution
 Debug.Print "Solution:"
 For i = 1 To 9
   For j = 1 To 9
     Debug.Print Format$(gridSolved(i, j)); " ";
   Next j
   Debug.Print
 Next i

End Sub</lang> Output:

Sudoku
Solution:
6 3 1 2 4 5 9 7 8 
9 2 5 6 7 8 1 4 3 
4 7 8 3 1 9 6 5 2 
7 9 6 5 2 3 4 8 1 
1 8 2 9 6 4 5 3 7 
3 5 4 7 8 1 2 9 6 
8 6 7 4 9 2 3 1 5 
2 4 3 1 5 7 8 6 9 
5 1 9 8 3 6 7 2 4 

XPL0

This is a translation of the C example, but with a solution that can be verified by several other examples.

<lang XPL0>code ChOut=8, CrLf=9, IntOut=11, Text=12;

proc Show(X); char X; int I, J; [for I:= 0 to 8 do

       [if rem(I/3) = 0 then CrLf(0);
       for J:= 0 to 8 do
               [if rem(J/3) = 0 then ChOut(0, ^ );
               ChOut(0, ^ );  IntOut(0, X(0));
               X:= X+1;
               ];
       CrLf(0);
       ];

];

func TryCell(X, Pos); char X; int Pos; int Row, Col, I, J, Used; [Row:= Pos/9; Col:= rem(0); Used:= 0;

if Pos = 81 then return true; if X(Pos) then return TryCell(X, Pos+1);

for I:= 0 to 8 do Used:= Used ! 1 << (X(I*9+Col)-1); for J:= 0 to 8 do Used:= Used ! 1 << (X(Row*9+J)-1);

Row:= Row/3*3; Col:= Col/3*3; for I:= Row to Row+2 do

       for J:= Col to Col+2 do
               Used:= Used ! 1 << (X(I*9+J)-1);

for I:= 1 to 9 do

       [X(Pos):= I;
       if (Used&1)=0 & TryCell(X, Pos+1) then return true;
       Used:= Used>>1;
       ];

X(Pos):= 0; return false; ];

proc Solve(S); char S; int I, J, C; char X(81); [J:= 0; for I:= 0 to 80 do

       [repeat C:= S(J);
               J:= J+1;
       until   C>=^1 & C<=^9 ! C=^.;
       X(I):= if C=^. then 0 else C-^0;
       ];

if TryCell(X, 0) then Show(X) else Text(0, "No solution"); ];

[Solve("394 ..2 67.

       ... 3.. 4..
       5.. 69. .2.
       .45 ... 9..
       6.. ... ..7
       ..7 ... 58.
       .1. .67 ..8
       ..9 ..8 ...
       .26 4.. 735 ");

]</lang>

Output:

  3 9 4  8 5 2  6 7 1
  2 6 8  3 7 1  4 5 9
  5 7 1  6 9 4  8 2 3

  1 4 5  7 8 3  9 6 2
  6 8 2  9 4 5  3 1 7
  9 3 7  1 2 6  5 8 4

  4 1 3  5 6 7  2 9 8
  7 5 9  2 3 8  1 4 6
  8 2 6  4 1 9  7 3 5