Difference between revisions of "99 questions/90 to 94"

From HaskellWiki
Jump to navigation Jump to search
m
(P98.2: fuse row generation with matching to speed it up a little, and add a guessing phase (stolen from solution 1) after deduction for completeness.)
Line 533: Line 533:
 
One nice idea would be to use CaleGibbard's Sudoku Backtracking Monad or alternatively add a few simplistic "heuristics" which should reduce the complexity early on.
 
One nice idea would be to use CaleGibbard's Sudoku Backtracking Monad or alternatively add a few simplistic "heuristics" which should reduce the complexity early on.
   
Solution 2 (faster, but doesn't work if guessing is required):
+
Solution 2 (faster):
 
<haskell>
 
<haskell>
 
module Nonogram where
 
module Nonogram where
   
  +
import Control.Monad
 
import Data.List
 
import Data.List
  +
import Data.Maybe
   
 
data Square = Filled | Blank | Unknown
 
data Square = Filled | Blank | Unknown
 
deriving (Eq, Show)
 
deriving (Eq, Show)
  +
type Row = [Square]
  +
type Grid = [Row]
   
  +
-- Print the first solution (if any) to the nonogram
unify :: Square -> Square -> Square
 
  +
nonogram :: [[Int]] -> [[Int]] -> String
unify Filled Filled = Filled
 
  +
nonogram rs cs = case solve rs cs of
unify Blank Blank = Blank
 
  +
[] -> "Inconsistent\n"
unify _ _ = Unknown
 
  +
(grid:_) -> showGrid rs cs grid
   
  +
-- All solutions to the nonogram
match :: Square -> Square -> Bool
 
  +
solve :: [[Int]] -> [[Int]] -> [Grid]
match Filled Filled = True
 
  +
solve rs cs = [grid' |
match Blank Blank = True
 
  +
-- deduce as many squares as we can
match Unknown _ = True
 
  +
grid <- maybeToList (deduction rs cs),
match _ _ = False
 
  +
-- guess the rest, governed by rs
 
  +
grid' <- zipWithM (rowsMatching nc) rs grid,
name :: Square -> Char
 
  +
-- check each guess against cs
name Filled = 'X'
 
  +
map contract (transpose grid') == cs]
name Blank = '_'
 
  +
where nc = length cs
name Unknown = '?'
 
  +
contract = map length . filter (\(x:_) -> x==Filled) . group
 
-- rows n ks = all possible ways of placing blocks of length ks
 
-- in a row of length n.
 
rows :: Int -> [Int] -> [[Square]]
 
rows n [] = [replicate n Blank]
 
rows n (k:ks) | n < k = []
 
rows n (k:ks) =
 
[Blank:row | row <- rows (n-1) (k:ks)] ++
 
if null ks
 
then [replicate k Filled ++ replicate (n-k) Blank]
 
else [replicate k Filled ++ Blank : row | row <- rows (n-k-1) ks]
 
 
-- Does r2 match all the known squares of r1?
 
matchRow :: [Square] -> [Square] -> Bool
 
matchRow r1 r2 = and (zipWith match r1 r2)
 
 
-- common n ks partial = commonality between all possible ways of
 
-- placing blocks of length ks in a row of length n that match partial.
 
common :: Int -> [Int] -> [Square] -> Maybe [Square]
 
common n ks partial = case filter (matchRow partial) (rows n ks) of
 
[] -> Nothing
 
rs -> Just (foldr1 (zipWith unify) rs)
 
   
  +
-- A nonogram with all the values we can deduce
solve :: [[Int]] -> [[Int]] -> Maybe [[Square]]
 
  +
deduction :: [[Int]] -> [[Int]] -> Maybe Grid
solve rs cs = converge step init
 
  +
deduction rs cs = converge step init
 
where nr = length rs
 
where nr = length rs
 
nc = length cs
 
nc = length cs
Line 595: Line 580:
 
if s' == s then return s else converge f s'
 
if s' == s then return s else converge f s'
   
  +
-- common n ks partial = commonality between all possible ways of
showGrid :: [[Int]] -> [[Int]] -> [[Square]] -> String
 
  +
-- placing blocks of length ks in a row of length n that match partial.
  +
common :: Int -> [Int] -> Row -> Maybe Row
  +
common n ks partial = case rowsMatching n ks partial of
  +
[] -> Nothing
  +
rs -> Just (foldr1 (zipWith unify) rs)
  +
  +
-- rowsMatching n ks partial = all possible ways of placing blocks of
  +
-- length ks in a row of length n that match partial.
  +
rowsMatching :: Int -> [Int] -> [Square] -> [[Square]]
  +
rowsMatching n [] partial = [replicate n Blank | all (/= Filled) partial]
  +
rowsMatching n ks [] = []
  +
rowsMatching n ks (Unknown:partial) =
  +
rowsMatching n ks (Filled:partial) ++
  +
rowsMatching n ks (Blank:partial)
  +
rowsMatching n ks (Blank:partial) =
  +
[Blank : row | row <- rowsMatching (n-1) ks partial]
  +
rowsMatching n [k] (Filled:partial) =
  +
[replicate k Filled ++ replicate (n-k) Blank |
  +
n >= k && all (/= Blank) front && all (/= Filled) back]
  +
where (front, back) = splitAt (k-1) partial
  +
rowsMatching n (k:ks) (Filled:partial) =
  +
[replicate k Filled ++ Blank : row |
  +
n > k+1 && all (/= Blank) front && blank /= Filled,
  +
row <- rowsMatching (n-k-1) ks partial']
  +
where (front, blank:partial') = splitAt (k-1) partial
  +
  +
unify :: Square -> Square -> Square
  +
unify Filled Filled = Filled
  +
unify Blank Blank = Blank
  +
unify _ _ = Unknown
  +
  +
showGrid :: [[Int]] -> [[Int]] -> Grid -> String
 
showGrid rs cs ss = unlines (zipWith showRow rs ss ++ showCols cs)
 
showGrid rs cs ss = unlines (zipWith showRow rs ss ++ showCols cs)
 
where showRow rs ss = concat [['|', name s] | s <- ss] ++ "| " ++
 
where showRow rs ss = concat [['|', name s] | s <- ss] ++ "| " ++
Line 609: Line 626:
 
advance (x:xs) = xs
 
advance (x:xs) = xs
   
  +
name :: Square -> Char
nonogram :: [[Int]] -> [[Int]] -> String
 
  +
name Filled = 'X'
nonogram rs cs = case solve rs cs of
 
  +
name Blank = '_'
Nothing -> "Inconsistent\n"
 
  +
name Unknown = '?'
Just grid -> showGrid rs cs grid
 
 
</haskell>
 
</haskell>
 
We build up knowledge of which squares must be filled and which must be blank, until we can't make any more deductions.
 
We build up knowledge of which squares must be filled and which must be blank, until we can't make any more deductions.
  +
Some puzzles cannot be completely solved in this way, so then we guess values (using a method stolen from solution 1) for any remaining squares.
 
The method of trying all placements of blocks in a row (<tt>rows</tt>) to determine commonality (<tt>common</tt>) could be more sophisticated, but seems fast enough.
 
 
It seems that there are puzzles that have a unique solution but which cannot be completely solved in this way, so we'll have to add backtracking.
 
   
 
== Problem 99 ==
 
== Problem 99 ==

Revision as of 18:24, 15 December 2006


These are Haskell translations of Ninety-Nine Prolog Problems.

If you want to work on one of these, put your name in the block so we know someone's working on it. Then, change n in your block to the appropriate problem number, and fill in the <Problem description>,<example in lisp>,<example in Haskell>,<solution in haskell> and <description of implementation> fields.

Miscellaneous problems

Problem 90

(**) Eight queens problem

This is a classical problem in computer science. The objective is to place eight queens on a chessboard so that no two queens are attacking each other; i.e., no two queens are in the same row, the same column, or on the same diagonal.

Hint: Represent the positions of the queens as a list of numbers 1..N. Example: [4,2,7,3,6,8,5,1] means that the queen in the first column is in row 4, the queen in the second column is in row 2, etc. Use the generate-and-test paradigm.

Example in Haskell:

> length queens
92
> take 1 queens
[[4,2,7,3,6,8,5,1]]

Solution:

queens = queens' 8
    where queens' 0       = [[]]
          queens' n       = [ try:qs | qs <- queens' (n-1), try <- [1..8], isSafe try qs]
          isSafe   try qs = not (try `elem` qs || sameDiag try qs)
          sameDiag try qs = any (\(colDist,q) -> abs(try - q) == colDist) $ zip [1..] qs

By definition/data representation no two queens can occupy the same column. "try `elem` alreadySet" checks for a queen in the same row, "abs(try - q) == col" checks for a queen in the same diagonal.

This is a modification of a function I wrote when I was just learning haskell, so there's certainly much to improve here! For one thing there is speedup potential in caching "blocked" rows, columns and diagonals.

Otherwise a smarter representation in memory might simplify the whole thing drastically as well.

Problem 91

(**) Knight's tour

Another famous problem is this one: How can a knight jump on an NxN chessboard in such a way that it visits every square exactly once?

Hints: Represent the squares by pairs of their coordinates of the form X/Y, where both X and Y are integers between 1 and N. (Note that '/' is just a convenient functor, not division!) Define the relation jump(N,X/Y,U/V) to express the fact that a knight can jump from X/Y to U/V on a NxN chessboard. And finally, represent the solution of our problem as a list of N*N knight positions (the knight's tour).

There are two variants of this problem:

  1. find a tour ending at a particular square
  2. find a circular tour, ending a knight's jump from the start (clearly it doesn't matter where you start, so choose (1,1))

Example in Haskell:

Knights> head $ knightsTo 8 (1,1)
[(2,7),(3,5),(5,6),(4,8),(3,6),(4,4),(6,5),(4,6),
(5,4),(7,5),(6,3),(5,5),(4,3),(2,4),(1,6),(2,8),
(4,7),(6,8),(8,7),(6,6),(4,5),(6,4),(5,2),(7,1),
(8,3),(6,2),(8,1),(7,3),(8,5),(7,7),(5,8),(3,7),
(1,8),(2,6),(3,4),(1,5),(2,3),(3,1),(1,2),(3,3),
(1,4),(2,2),(4,1),(5,3),(7,4),(8,2),(6,1),(4,2),
(2,1),(1,3),(2,5),(1,7),(3,8),(5,7),(7,8),(8,6),
(6,7),(8,8),(7,6),(8,4),(7,2),(5,1),(3,2),(1,1)]
Knights> head $ closedKnights 8  
[(1,1),(3,2),(1,3),(2,1),(3,3),(5,4),(6,6),(4,5),
(2,6),(1,8),(3,7),(5,8),(4,6),(2,5),(4,4),(5,6),
(6,4),(8,5),(7,7),(6,5),(5,3),(6,1),(4,2),(6,3),
(8,2),(7,4),(5,5),(3,4),(1,5),(2,7),(4,8),(3,6),
(1,7),(3,8),(5,7),(7,8),(8,6),(6,7),(8,8),(7,6),
(8,4),(7,2),(5,1),(4,3),(3,5),(1,4),(2,2),(4,1),
(6,2),(8,1),(7,3),(5,2),(7,1),(8,3),(7,5),(8,7),
(6,8),(4,7),(2,8),(1,6),(2,4),(1,2),(3,1),(2,3)]

Solution:

module Knights where

import Data.List

type Square = (Int, Int)

-- Possible knight moves from a given square on an nxn board
knightMoves :: Int -> Square -> [Square]
knightMoves n (x, y) = filter (onBoard n)
        [(x+2, y+1), (x+2, y-1), (x+1, y+2), (x+1, y-2),
         (x-1, y+2), (x-1, y-2), (x-2, y+1), (x-2, y-1)]

-- Is the square within an nxn board?
onBoard :: Int -> Square -> Bool
onBoard n (x, y) = 1 <= x && x <= n && 1 <= y && y <= n

-- Knight's tours on an nxn board ending at the given square
knightsTo :: Int -> Square -> [[Square]]
knightsTo n finish = [pos:path | (pos, path) <- tour (n*n)]
  where tour 1 = [(finish, [])]
        tour k = [(pos', pos:path) |
                (pos, path) <- tour (k-1),
                pos' <- sortImage (entrances path)
                        (filter (`notElem` path) (knightMoves n pos))]
        entrances path pos =
                length (filter (`notElem` path) (knightMoves n pos))

-- Closed knight's tours on an nxn board
closedKnights :: Int -> [[Square]]
closedKnights n = [pos:path | (pos, path) <- tour (n*n), pos == start]
  where tour 1 = [(finish, [])]
        tour k = [(pos', pos:path) |
                (pos, path) <- tour (k-1),
                pos' <- sortImage (entrances path)
                        (filter (`notElem` path) (knightMoves n pos))]
        entrances path pos
          | pos == start = 100  -- don't visit start until there are no others
          | otherwise = length (filter (`notElem` path) (knightMoves n pos))
        start = (1,1)
        finish = (2,3)

-- Sort by comparing the image of list elements under a function f.
-- These images are saved to avoid recomputation.
sortImage :: Ord b => (a -> b) -> [a] -> [a]
sortImage f xs = map snd (sortBy cmpFst [(f x, x) | x <- xs])
  where cmpFst x y = compare (fst x) (fst y)

This has a similar structure to the 8 Queens problem, except that we apply a heuristic invented by Warnsdorff: when considering next possible moves, we prefer squares with fewer open entrances. This speeds things up enormously, and finds the first solution to boards smaller than 76x76 without backtracking.


Solution 2:

knights :: Int -> [[(Int,Int)]]
knights n = loop (n*n) [[(1,1)]]
    where loop 1 = map reverse . id
          loop i = loop (i-1) . concatMap nextMoves

          nextMoves already@(x:xs) = [next:already | next <- possible]
              where possible = filter (\x -> on_board x && not (x `elem` already)) $ jumps x

          jumps (x,y)    = [(x+a, y+b) | (a,b) <- [(1,2), (2,1), (2,-1), (1,-2), (-1,-2), (-2,-1), (-2,1), (-1,2)]]
          on_board (x,y) = (x >= 1) && (x <= n) && (y >= 1) && (y <= n)

This is just the naive backtracking approach. I tried a speedup using Data.Map, but the code got too verbose to post.

Problem 92

(***) Von Koch's conjecture

Several years ago I met a mathematician who was intrigued by a problem for which he didn't know a solution. His name was Von Koch, and I don't know whether the problem has been solved since.

p92a.gif

Anyway the puzzle goes like this: Given a tree with N nodes (and hence N-1 edges). Find a way to enumerate the nodes from 1 to N and, accordingly, the edges from 1 to N-1 in such a way, that for each edge K the difference of its node numbers equals to K. The conjecture is that this is always possible.

For small trees the problem is easy to solve by hand. However, for larger trees, and 14 is already very large, it is extremely difficult to find a solution. And remember, we don't know for sure whether there is always a solution!

Write a predicate that calculates a numbering scheme for a given tree. What is the solution for the larger tree pictured below?

p92b.gif

Example:

<example in lisp>

Example in Haskell:

> head $ vonKoch [(1,6),(2,6),(3,6),(4,6),(5,6),(5,7),(5,8),(8,9),(5,10),(10,11),(11,12),(11,13),(13,14)]
[6,7,8,9,3,4,10,11,5,12,2,13,14,1]

Solution:

vonKoch edges = do
    let n = length edges + 1
    nodes <- permutations [1..n]
    let nodeArray = listArray (1,n) nodes
    let dists = sort $ map (\(x,y) -> abs (nodeArray ! x - nodeArray ! y)) edges
    guard $ and $ zipWith (/=) dists (tail dists)
    return nodes

This is a simple brute-force solver. This function will permute all assignments of the different node numbers and will then verify that all of the edge differences are different. This code uses the List Monad.

Problem 93

(***) An arithmetic puzzle

Given a list of integer numbers, find a correct way of inserting arithmetic signs (operators) such that the result is a correct equation. Example: With the list of numbers [2,3,5,7,11] we can form the equations 2-3+5+7 = 11 or 2 = (3*5+7)/11 (and ten others!).

Division should be interpreted as operating on rationals, and division by zero should be avoided.

Example in Haskell:

P93> putStr $ unlines $ puzzle [2,3,5,7,11]
2 = 3-(5+7-11)
2 = 3-5-(7-11)
2 = 3-(5+7)+11
2 = 3-5-7+11
2 = (3*5+7)/11
2*(3-5) = 7-11
2-(3-(5+7)) = 11
2-(3-5-7) = 11
2-(3-5)+7 = 11
2-3+5+7 = 11

The other two solutions alluded to in the problem description are dropped by the Haskell solution as trivial variants:

2 = 3-(5+(7-11))
2-3+(5+7) = 11

Solution:

module P93 where

import Control.Monad
import Data.List
import Data.Maybe

type Equation = (Expr, Expr)
data Expr = Const Integer | Binary Expr Op Expr
        deriving (Eq, Show)
data Op = Plus | Minus | Multiply | Divide
        deriving (Bounded, Eq, Enum, Show)
type Value = Rational

-- top-level function: all correct equations generated from the list of
-- numbers, as pretty strings.
puzzle :: [Integer] -> [String]
puzzle ns = map (flip showsEquation "") (equations ns)

-- generate all correct equations from the list of numbers
equations :: [Integer] -> [Equation]
equations [] = error "empty list of numbers"
equations [n] = error "only one number"
equations ns = [(e1, e2) |
                (ns1, ns2) <- splits ns,
                (e1, v1) <- exprs ns1,
                (e2, v2) <- exprs ns2,
                v1 == v2]

-- generate all expressions from the numbers, except those containing
-- a division by zero, or redundant right-associativity.
exprs :: [Integer] -> [(Expr, Value)]
exprs [n] = [(Const n, fromInteger n)]
exprs ns = [(Binary e1 op e2, v) | (ns1, ns2) <- splits ns,
                (e1, v1) <- exprs ns1,
                (e2, v2) <- exprs ns2,
                op <- [minBound..maxBound],
                not (right_associative op e2),
                v <- maybeToList (apply op v1 v2)]

-- splittings of a list into two non-empty lists
splits :: [a] -> [([a],[a])]
splits xs = tail (init (zip (inits xs) (tails xs)))

-- applying an operator to arguments may fail (division by zero)
apply :: Op -> Value -> Value -> Maybe Value
apply Plus x y = Just (x + y)
apply Minus x y = Just (x - y)
apply Multiply x y = Just (x * y)
apply Divide x 0 = Nothing
apply Divide x y = Just (x / y)

-- e1 op (e2 op' e3) == (e1 op e2) op' e3
right_associative :: Op -> Expr -> Bool
right_associative Plus (Binary _ Plus _) = True
right_associative Plus (Binary _ Minus _) = True
right_associative Multiply (Binary _ Multiply _) = True
right_associative Multiply (Binary _ Divide _) = True
right_associative _ _ = False

-- Printing of equations and expressions

showsEquation :: Equation -> ShowS
showsEquation (l, r) = showsExprPrec 0 l . showString " = " . showsExprPrec 0 r

-- all operations are left associative
showsExprPrec :: Int -> Expr -> ShowS
showsExprPrec _ (Const n) = shows n
showsExprPrec p (Binary e1 op e2) = showParen (p > op_prec) $
        showsExprPrec op_prec e1 . showString (opName op) .
                showsExprPrec (op_prec+1) e2
  where op_prec = precedence op

precedence :: Op -> Int
precedence Plus = 6
precedence Minus = 6
precedence Multiply = 7
precedence Divide = 7

opName :: Op -> String
opName Plus = "+"
opName Minus = "-"
opName Multiply = "*"
opName Divide = "/"

Unlike the Prolog solution, I've eliminated solutions like "1+(2+3) = 6" as a trivial variant of "1+2+3 = 6" (cf the function right_associative). Apart from that, the Prolog solution is shorter because it uses built-in evaluation and printing of expressions.

Problem 94

<Problem description>

Example:

<example in lisp>

Example in Haskell:

<example in Haskell>

Solution:

<solution in haskell>

<description of implementation>

Problem 95

(**) English number words

On financial documents, like cheques, numbers must sometimes be written in full words. Example: 175 must be written as one-seven-five. Write a predicate full-words/1 to print (non-negative) integer numbers in full words.

Example in Haskell:

> fullWords 175
one-seven-five

Solution:

import Data.List
import Data.Maybe

fullWords :: Integer -> String
fullWords n = concat . intersperse "-" . map (fromJust . (`lookup` table)) $ show n
    where table = [('0',"zero"), ('1',"one"), ('2',"two"),   ('3',"three"), ('4',"four"), 
                   ('5',"five"), ('6',"six"), ('7',"seven"), ('8',"eight"), ('9',"nine")]

This solution does a simple table lookup after converting the positive integer into a string. Thus dividing into digits is much simplified.

A minor variant of the above solution:

import Data.Char
import Data.List

fullWords :: Integer -> String
fullWords n = concat $ intersperse "-" [digits!!digitToInt d | d <- show n]
  where digits = ["zero", "one", "two", "three", "four",
                  "five", "six", "seven", "eight", "nine"]

Problem 96

(**) Syntax checker

In a certain programming language (Ada) identifiers are defined by the syntax diagram below.

p96.gif

Transform the syntax diagram into a system of syntax diagrams which do not contain loops; i.e. which are purely recursive. Using these modified diagrams, write a predicate identifier/1 that can check whether or not a given string is a legal identifier.

Example in Prolog:

% identifier(Str) :- Str is a legal identifier 

Example in Haskell:

> identifier "this-is-a-long-identifier"
True
> identifier "this-ends-in-"            
False
> identifier "two--hyphens" 
False

Solution:

import Data.Char
syntax_check :: String -> Bool
syntax_check []     = False
syntax_check (x:xs) = isLetter x && loop xs
    where loop [] = True
          loop (y:ys) | y == '-'     = (not . null) ys && isAlphaNum (head ys) && loop (tail ys) 
                      | isAlphaNum y = loop ys
                      | otherwise    = False

Simple functional transcription of the diagram.

Another direct transcription of the diagram:

identifier :: String -> Bool
identifier (c:cs) = isLetter c && hyphen cs
  where hyphen [] = True
        hyphen ('-':cs) = alphas cs
        hyphen cs = alphas cs
        alphas [] = False
        alphas (c:cs) = isAlphaNum c && hyphen cs

The functions hyphen and alphas correspond to states in the automaton at the start of the loop and before a compulsory alphanumeric, respectively.

Parsec is a parser library that is commonly used in Haskell code. This is a solution using Parsec to parse the identifier.

isRight (Right _) = True
isRight (Left  _) = False

identifier x = isRight $ parse parser "" x where
   parser = letter >> loop
   loop = optional $ do
             optional (char '-')
             letter <|> digit
             loop

Problem 97

(**) Sudoku

Sudoku puzzles go like this:

       Problem statement                 Solution

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

Every spot in the puzzle belongs to a (horizontal) row and a (vertical) column, as well as to one single 3x3 square (which we call "square" for short). At the beginning, some of the spots carry a single-digit number between 1 and 9. The problem is to fill the missing spots with digits in such a way that every number between 1 and 9 appears exactly once in each row, in each column, and in each square.

Solutions: see Sudoku

Problem 98

(***) Nonograms

Around 1994, a certain kind of puzzle was very popular in England. The "Sunday Telegraph" newspaper wrote: "Nonograms are puzzles from Japan and are currently published each week only in The Sunday Telegraph. Simply use your logic and skill to complete the grid and reveal a picture or diagram." As a Prolog programmer, you are in a better situation: you can have your computer do the work! Just write a little program ;-).

The puzzle goes like this: Essentially, each row and column of a rectangular bitmap is annotated with the respective lengths of its distinct strings of occupied cells. The person who solves the puzzle must complete the bitmap given only these lengths.

             Problem statement:          Solution:
             |_|_|_|_|_|_|_|_| 3         |_|X|X|X|_|_|_|_| 3           
             |_|_|_|_|_|_|_|_| 2 1       |X|X|_|X|_|_|_|_| 2 1         
             |_|_|_|_|_|_|_|_| 3 2       |_|X|X|X|_|_|X|X| 3 2         
             |_|_|_|_|_|_|_|_| 2 2       |_|_|X|X|_|_|X|X| 2 2         
             |_|_|_|_|_|_|_|_| 6         |_|_|X|X|X|X|X|X| 6           
             |_|_|_|_|_|_|_|_| 1 5       |X|_|X|X|X|X|X|_| 1 5         
             |_|_|_|_|_|_|_|_| 6         |X|X|X|X|X|X|_|_| 6           
             |_|_|_|_|_|_|_|_| 1         |_|_|_|_|X|_|_|_| 1           
             |_|_|_|_|_|_|_|_| 2         |_|_|_|X|X|_|_|_| 2           
              1 3 1 7 5 3 4 3             1 3 1 7 5 3 4 3              
              2 1 5 1                     2 1 5 1                      
      

For the example above, the problem can be stated as the two lists [[3],[2,1],[3,2],[2,2],[6],[1,5],[6],[1],[2]] and [[1,2],[3,1],[1,5],[7,1],[5],[3],[4],[3]] which give the "solid" lengths of the rows and columns, top-to-bottom and left-to-right, respectively. Published puzzles are larger than this example, e.g. 25 x 20, and apparently always have unique solutions.

Example in Haskell:

Nonogram> putStr $ nonogram [[3],[2,1],[3,2],[2,2],[6],[1,5],[6],[1],[2]] [[1,2],[3,1],[1,5],[7,1],[5],[3],[4],[3]]
|_|X|X|X|_|_|_|_| 3
|X|X|_|X|_|_|_|_| 2 1
|_|X|X|X|_|_|X|X| 3 2
|_|_|X|X|_|_|X|X| 2 2
|_|_|X|X|X|X|X|X| 6
|X|_|X|X|X|X|X|_| 1 5
|X|X|X|X|X|X|_|_| 6
|_|_|_|_|X|_|_|_| 1
|_|_|_|X|X|_|_|_| 2
 1 3 1 7 5 3 4 3
 2 1 5 1        

Solution 1 (SLOOW):

data Square = Blank | Cross deriving (Eq)
instance Show Square where
    show Blank = " "
    show Cross = "X"

-- stolen from solution 2.
-- create all possibilities of arranging the given blocks in a line of "n" elements
rows n []             = [replicate n Blank]
rows n (k:ks) | n < k = []
rows n (k:ks)         = 
    [Blank : row | row <- rows (n-1) (k:ks)] ++
    if null ks then [replicate k Cross ++ replicate (n-k) Blank]
               else [replicate k Cross ++ Blank : row | row <- rows (n-k-1) ks]

-- contract a given line into the block format
-- i.e. contract [Cross,Blank,Cross] == [1,1]
contract = map length . filter (\(x:_) -> x==Cross) . group

-- create all solutions by combining all possible rows in all possible ways
-- then pick a solution and check whether its block signature fits
solver horz vert = filter fitsVert possSolution
    where possSolution = sequence $ map (rows (length vert)) horz
          fitsVert rs  = map contract (transpose rs) == vert

-- output the (first) solution
nonogram horz vert = printSolution $ head $ solver horz vert
    where printSolution = putStr . unlines . map (concatMap show) . transpose

This is a solution done for simplicity rather than performance. It's SLOOOOW.

It builds all combinations of blocks in a row (stolen from solution 2 :) and then builds all combinations of rows. The resulting columns are then contracted into the short block block form and the signature compared to the target.

One nice idea would be to use CaleGibbard's Sudoku Backtracking Monad or alternatively add a few simplistic "heuristics" which should reduce the complexity early on.

Solution 2 (faster):

module Nonogram where

import Control.Monad
import Data.List
import Data.Maybe

data Square = Filled | Blank | Unknown
        deriving (Eq, Show)
type Row = [Square]
type Grid = [Row]

-- Print the first solution (if any) to the nonogram
nonogram :: [[Int]] -> [[Int]] -> String
nonogram rs cs = case solve rs cs of
        [] -> "Inconsistent\n"
        (grid:_) -> showGrid rs cs grid

-- All solutions to the nonogram
solve :: [[Int]] -> [[Int]] -> [Grid]
solve rs cs = [grid' |
                        -- deduce as many squares as we can
                grid <- maybeToList (deduction rs cs),
                        -- guess the rest, governed by rs
                grid' <- zipWithM (rowsMatching nc) rs grid,
                        -- check each guess against cs
                map contract (transpose grid') == cs]
  where nc = length cs
        contract = map length . filter (\(x:_) -> x==Filled) . group

-- A nonogram with all the values we can deduce
deduction :: [[Int]] -> [[Int]] -> Maybe Grid
deduction rs cs = converge step init
  where nr = length rs
        nc = length cs
        init = replicate nr (replicate nc Unknown)
        step = (improve nc rs . transpose) <.> (improve nr cs . transpose)
        improve n = zipWithM (common n)
        (g <.> f) x = f x >>= g

-- repeatedly apply f until a fixed point is reached
converge :: (Monad m, Eq a) => (a -> m a) -> a -> m a
converge f s = do
        s' <- f s
        if s' == s then return s else converge f s'

-- common n ks partial = commonality between all possible ways of
-- placing blocks of length ks in a row of length n that match partial.
common :: Int -> [Int] -> Row -> Maybe Row
common n ks partial = case rowsMatching n ks partial of
        [] -> Nothing
        rs -> Just (foldr1 (zipWith unify) rs)

-- rowsMatching n ks partial = all possible ways of placing blocks of
-- length ks in a row of length n that match partial.
rowsMatching :: Int -> [Int] -> [Square] -> [[Square]]
rowsMatching n [] partial = [replicate n Blank | all (/= Filled) partial]
rowsMatching n ks [] = []
rowsMatching n ks (Unknown:partial) =
        rowsMatching n ks (Filled:partial) ++
        rowsMatching n ks (Blank:partial)
rowsMatching n ks (Blank:partial) =
        [Blank : row | row <- rowsMatching (n-1) ks partial]
rowsMatching n [k] (Filled:partial) =
        [replicate k Filled ++ replicate (n-k) Blank |
                n >= k && all (/= Blank) front && all (/= Filled) back]
  where (front, back) = splitAt (k-1) partial
rowsMatching n (k:ks) (Filled:partial) =
        [replicate k Filled ++ Blank : row |
                n > k+1 && all (/= Blank) front && blank /= Filled,
                row <- rowsMatching (n-k-1) ks partial']
  where (front, blank:partial') = splitAt (k-1) partial

unify :: Square -> Square -> Square
unify Filled Filled = Filled
unify Blank Blank = Blank
unify _ _ = Unknown

showGrid :: [[Int]] -> [[Int]] -> Grid -> String
showGrid rs cs ss = unlines (zipWith showRow rs ss ++ showCols cs)
  where showRow rs ss = concat [['|', name s] | s <- ss] ++ "| " ++
                unwords (map show rs)
        showCols cs
          | all null cs = []
          | otherwise = concatMap showCol cs : showCols (map advance cs)
        showCol (k:_)
          | k < 10 = ' ':show k
          | otherwise = show k
        showCol [] = "  "
        advance [] = []
        advance (x:xs) = xs

name :: Square -> Char
name Filled = 'X'
name Blank = '_'
name Unknown = '?'

We build up knowledge of which squares must be filled and which must be blank, until we can't make any more deductions. Some puzzles cannot be completely solved in this way, so then we guess values (using a method stolen from solution 1) for any remaining squares.

Problem 99

(***) Crossword puzzle

Given an empty (or almost empty) framework of a crossword puzzle and a set of words. The problem is to place the words into the framework.

p99.gif

The particular crossword puzzle is specified in a text file which first lists the words (one word per line) in an arbitrary order. Then, after an empty line, the crossword framework is defined. In this framework specification, an empty character location is represented by a dot (.). In order to make the solution easier, character locations can also contain predefined character values. The puzzle above is defined in the file p99a.dat, other examples are p99b.dat and p99d.dat. There is also an example of a puzzle (p99c.dat) which does not have a solution.

Words are strings (character lists) of at least two characters. A horizontal or vertical sequence of character places in the crossword puzzle framework is called a site. Our problem is to find a compatible way of placing words onto sites.

Hints: (1) The problem is not easy. You will need some time to thoroughly understand it. So, don't give up too early! And remember that the objective is a clean solution, not just a quick-and-dirty hack!

(2) Reading the data file is a tricky problem for which a solution is provided in the file p99-readfile.pl. See the predicate read_lines/2.

(3) For efficiency reasons it is important, at least for larger puzzles, to sort the words and the sites in a particular order. For this part of the problem, the solution of P28 may be very helpful.

Example in Haskell:

ALPHA
ARES
POPPY

  .
  .
.....
  . .
  . .
    .

> solve $ readCrossword "ALPHA\nARES\nPOPPY\n\n  .  \n  .  \n.....\n  . .\n  . .\n    .\n"

[[((3,1),'A'),((3,2),'L'),((3,3),'P'),((3,4),'H'),((3,5),'A'),((1,3),'P'),((2,3)
,'O'),((3,3),'P'),((4,3),'P'),((5,3),'Y'),((3,5),'A'),((4,5),'R'),((5,5),'E'),((
6,5),'S')]]

Solution:

-- import Control.Monad
-- import Data.List

type Coord     = (Int,Int)
type Word      = String
data Site      = Site {siteCoords :: [Coord], siteLen :: Int} deriving (Show,Eq)
data Crossword = Crossword {cwWords :: [Word], cwSites :: [Site]}  deriving (Show,Eq)

comparing f = \a b -> f a `compare` f b
equaling  f = \a b -> f a == f b

-- convert the text lines from the file to the "Site" datatype, 
--   which contain the adjacent coordinates of the site and its length
toSites :: [String] -> [Site]
toSites lines = find (index_it lines) ++ find (transpose . index_it $ lines)
    where find       = map makePos . concat . map extractor
          extractor  = filter ((>1) . length) . map (filter (\(_,x) -> x=='.')) . groupBy (equaling snd)
          index_it   = map (\(row,e) -> zip [(col,row) | col <- [1..]] e) . zip [1..]
          makePos xs = Site {siteCoords = map fst xs, siteLen = length xs}

-- test whether there exist no two different letters at the same coordinate
noCollision :: [(String, Site)] -> Bool
noCollision xs = all allEqual groupedByCoord
    where groupedByCoord = map (map snd) . groupBy (equaling fst) . sortBy (comparing fst) . concatMap together $ xs
          allEqual []     = True
          allEqual (x:xs) = all (x==) xs

-- merge a word and a site by assigning each letter to its respective coordinate
together :: (Word, Site) -> [(Coord, Char)]
together (w,s) = zip (siteCoords s) w

-- returns all solutions for the crossword as lists of occupied coordinates and their respective letters
solve :: Crossword -> [[(Coord, Char)]]
solve cw = map (concatMap together) solution
    where solution = solve' (cwWords cw) (cwSites cw)

solve' :: [Word] -> [Site] -> [[(Word, Site)]]
solve' _     []     = [[]]
solve' words (s:ss) = if null possWords
                        then error ("too few words of length " ++ show (siteLen s))
                        else do try <- possWords
                                let restWords = Data.List.delete try words
                                more <- solve' restWords ss
                                let attempt = (try,s):more
                                Control.Monad.guard $ noCollision attempt
                                return attempt
    where possWords = filter (\w -> siteLen s == length w) words                       

-- read the content of a file into the "Crossword" datatype
readCrossword :: String -> Crossword
readCrossword = (\(ws,ss) -> Crossword ws (toSites (drop 1 ss))) . break (""==) . lines


This is a simplistic solution with no consideration for speed. Especially sites and words aren't ordered as propesed in (3) of the problem. Words of the correct length are naively tried for all blanks (without heuristics) and the possible solutions are then backtracked.

To test for collisions, all (Word, Site) pairs are merged to result in a list of (Coord, Char) elements which represent all letters placed so far. If all (two) characters of the same coordinate are identical, there exist no collisions between words.