
For the translation of the above OCaml code, there is not much to do, in fact it is mostly functional, and so easily translated in Haskell code, note that I add a code to handle input of the form "4.....8.5.3..........7......2.....6.....8.4......1.......6.3.7.5..2.....1.4......", to resolve it and print a solution : <haskell> import Data.Ix import Data.List import Data.Char import qualified Data.Map as M invalid :: (Int, Int) -> (Int, Int) -> Bool invalid (i, j) (i', j') = i==i' || j==j' || (i `div` 3 == i' `div` 3 && j `div` 3 == j' `div` 3) select p n p' ns = if invalid p p' then filter (/= n) ns else ns cmp (_, l1) (_, l2) = (length l1) `compare` (length l2) add p n sols = sortBy cmp $ map (\(p', ns) -> (p', select p n p' ns)) sols search f sol [] = f sol search f sol ((p, ns):sols) = concatMap (\n -> search f (M.insert p n sol) (add p n sols)) ns </haskell> My additions : <haskell> base :: [((Int, Int),[Int])] base = [((i,j), [1..9]) | i <- [0..8], j <- [0..8]] createBoard input = foldr constraint (M.empty, purge base input) input where constraint (p, [n]) (sol,sols) = (M.insert p n sol,add p n sols) purge b i = filter (maybe True (const False) . flip lookup i . fst) b inputBoard :: String -> [((Int, Int), [Int])] inputBoard = filter (not . null . snd) . zip (range ((0,0),(8,8))) . map (\c -> if isDigit c then [read [c]] else []) showSol = unlines . concat . intersperse ([replicate 15 '-']) . split 3 . map (unwords . intersperse "|" . split 3) . split 9 . map (chr . (+ ord '0')) . M.elems where split n = takeWhile (not . null) . unfoldr (Just . splitAt n) solve = head . uncurry (search ((:[]).showSol)) . createBoard . inputBoard main = interact $ solve </haskell> -- Jedaï