[Haskell-cafe] Re: Simple Sudoku solver using Control.Monad.Logic

Johannes Waldmann waldmann at imn.htwk-leipzig.de
Sun Aug 22 18:26:45 EDT 2010


Ah, whenever I see "div/mod 3" in a Sudoku solver,
I feel that's not using the right model. 
It's not a square, it's a hypercube, folks!

type Index = ( Int,Int,Int,Int )

neighbours :: Index -> [ Index ]
neighbours (a,b,c,d) = do
    i <- [ 0 .. 2 ] ; j <- [ 0 .. 2 ]
    [ (i,j,c,d), (a,b,i,j), (a,i,c,j) ]


Here is a solver that branches on the position
with the least number of possible values.
It is backtracking (in the List monad,
could probably be rewritten in Control.Monad.Logic)

type Matrix = Array Index (Either [Int] Int)

solutions :: Matrix -> [ Matrix ]
solutions m =
    case sort $ do
            ( i, Left xs ) <- assocs m
            return ( length xs, i, xs )
    of
        [] -> return m
        (_,i,xs) : _ -> do
            x <- xs
            solutions $ set (i,x) m

set :: (Index, Int) -> Matrix -> Matrix
set (i, x) m = accum ( \ e _ -> case e of
              Left ys -> Left $ filter ( /= x ) ys
              Right y -> Right y
            )
            ( m // [ (i, Right x ) ] )
            ( zip ( neighbours i ) $ repeat () )





More information about the Haskell-Cafe mailing list