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

From HaskellWiki
Jump to navigation Jump to search
(add minor variant of P95 solution)
(37 intermediate revisions by 8 users not shown)
Line 1: Line 1:
 
__NOTOC__
 
__NOTOC__
   
These are Haskell translations of [http://www.hta-bi.bfh.ch/~hew/informatik3/prolog/p-99/ Ninety-Nine Prolog Problems].
+
This is part of [[H-99:_Ninety-Nine_Haskell_Problems|Ninety-Nine Haskell Problems]], based on [https://prof.ti.bfh.ch/hew1/informatik3/prolog/p-99/ 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.
+
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 Haskell>,<solution in haskell> and <description of implementation> fields.
 
== Miscellaneous problems ==
 
   
 
== Problem 90 ==
 
== Problem 90 ==
Line 16: Line 14:
   
 
Example in Haskell:
 
Example in Haskell:
<pre>
 
> length queens
 
92
 
> take 1 queens
 
[[4,2,7,3,6,8,5,1]]
 
</pre>
 
   
Solution:
 
 
<haskell>
 
<haskell>
queens = queens' 8
+
λ> length (queens 8)
  +
92
where queens' 0 = [[]]
 
  +
λ> head (queens 8)
queens' n = [ try:qs | qs <- queens' (n-1), try <- [1..8], isSafe try qs]
 
  +
[1,5,8,6,3,7,2,4]
isSafe try qs = not (try `elem` qs || sameDiag try qs)
 
sameDiag try qs = any (\(colDist,q) -> abs(try - q) == colDist) $ zip [1..] qs
 
 
 
</haskell>
 
</haskell>
   
  +
[[99 questions/Solutions/90 | Solutions]]
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.
 
 
 
== Problem 91 ==
 
== Problem 91 ==
   
 
(**) Knight's tour
 
(**) 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?
+
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? A set of solutions is given on the [[The_Knights_Tour]] page.
   
 
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).
 
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).
Line 50: Line 38:
   
 
Example in Haskell:
 
Example in Haskell:
  +
<pre>
 
  +
<haskell>
Knights> head $ knightsTo 8 (1,1)
 
  +
λ> head $ knightsTo 8 (1,1)
 
[(2,7),(3,5),(5,6),(4,8),(3,6),(4,4),(6,5),(4,6),
 
[(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),
 
(5,4),(7,5),(6,3),(5,5),(4,3),(2,4),(1,6),(2,8),
Line 60: Line 49:
 
(2,1),(1,3),(2,5),(1,7),(3,8),(5,7),(7,8),(8,6),
 
(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)]
 
(6,7),(8,8),(7,6),(8,4),(7,2),(5,1),(3,2),(1,1)]
Knights> head $ closedKnights 8
+
λ> head $ closedKnights 8
 
[(1,1),(3,2),(1,3),(2,1),(3,3),(5,4),(6,6),(4,5),
 
[(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),
 
(2,6),(1,8),(3,7),(5,8),(4,6),(2,5),(4,4),(5,6),
Line 69: Line 58:
 
(6,2),(8,1),(7,3),(5,2),(7,1),(8,3),(7,5),(8,7),
 
(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)]
 
(6,8),(4,7),(2,8),(1,6),(2,4),(1,2),(3,1),(2,3)]
</pre>
 
 
Solution:
 
<haskell>
 
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)
 
</haskell>
 
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:
 
 
<haskell>
 
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)
 
 
</haskell>
 
</haskell>
   
  +
[[99 questions/Solutions/91 | Solutions]]
This is just the naive backtracking approach. I tried a speedup using Data.Map, but the code got too verbose to post.
 
   
 
== Problem 92 ==
 
== Problem 92 ==
Line 145: Line 66:
 
(***) Von Koch's conjecture
 
(***) 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.
+
Several years ago I met a mathematician who was intrigued by a problem whose solution he didn't know. His name was Von Koch, and I don't know whether the problem has been solved since.
   
http://www.hta-bi.bfh.ch/~hew/informatik3/prolog/p-99/p92a.gif
+
https://prof.ti.bfh.ch/hew1/informatik3/prolog/p-99/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.
 
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.
Line 155: Line 76:
 
Write a predicate that calculates a numbering scheme for a given tree. What is the solution for the larger tree pictured below?
 
Write a predicate that calculates a numbering scheme for a given tree. What is the solution for the larger tree pictured below?
   
http://www.hta-bi.bfh.ch/~hew/informatik3/prolog/p-99/p92b.gif
+
https://prof.ti.bfh.ch/hew1/informatik3/prolog/p-99/p92b.gif
 
Example:
 
<pre>
 
<example in lisp>
 
</pre>
 
   
 
Example in Haskell:
 
Example in Haskell:
<pre>
 
<example in Haskell>
 
</pre>
 
   
Solution:
 
 
<haskell>
 
<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)]
<solution in haskell>
 
  +
[6,7,8,9,3,4,10,11,5,12,2,13,14,1]
 
</haskell>
 
</haskell>
   
  +
[[99 questions/Solutions/92 | Solutions]]
<description of implementation>
 
  +
 
 
 
== Problem 93 ==
 
== Problem 93 ==
Line 183: Line 97:
   
 
Example in Haskell:
 
Example in Haskell:
  +
<pre>
 
  +
<haskell>
P93> putStr $ unlines $ puzzle [2,3,5,7,11]
 
  +
λ> mapM_ putStrLn $ 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)
Line 195: Line 110:
 
2-(3-5)+7 = 11
 
2-(3-5)+7 = 11
 
2-3+5+7 = 11
 
2-3+5+7 = 11
</pre>
+
</haskell>
  +
 
The other two solutions alluded to in the problem description are dropped by the Haskell solution as trivial variants:
 
The other two solutions alluded to in the problem description are dropped by the Haskell solution as trivial variants:
  +
 
<pre>
 
<pre>
 
2 = 3-(5+(7-11))
 
2 = 3-(5+(7-11))
Line 202: Line 119:
 
</pre>
 
</pre>
   
  +
[[99 questions/Solutions/93 | Solutions]]
Solution:
 
<haskell>
 
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 = "/"
 
</haskell>
 
Unlike the Prolog solution, I've eliminated solutions like
 
<tt>"1+(2+3) = 6"</tt> as a trivial variant of <tt>"1+2+3 = 6"</tt> (cf the function <tt>right_associative</tt>).
 
Apart from that, the Prolog solution is shorter because it uses built-in evaluation and printing of expressions.
 
   
 
== Problem 94 ==
 
== Problem 94 ==
   
  +
(***) Generate K-regular simple graphs with N nodes
<Problem description>
 
   
  +
In a K-regular graph all nodes have a degree of K; i.e. the number of edges incident in each node is K. How many (non-isomorphic!) 3-regular graphs with 6 nodes are there?
Example:
 
<pre>
 
<example in lisp>
 
</pre>
 
   
  +
[https://prof.ti.bfh.ch/hew1/informatik3/prolog/p-99/p94.txt Sample results]
Example in Haskell:
 
<pre>
 
<example in Haskell>
 
</pre>
 
 
Solution:
 
<haskell>
 
<solution in haskell>
 
</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:
 
Example in Haskell:
<pre>
 
> fullWords 175
 
one-seven-five
 
</pre>
 
 
Solution:
 
 
<haskell>
 
<haskell>
  +
λ> length $ regular 6 3
import Data.List
 
  +
2
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")]
 
 
</haskell>
 
</haskell>
   
  +
[[99 questions/Solutions/94 | Solutions]]
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:
 
<haskell>
 
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"]
 
</haskell>
 
 
== Problem 96 ==
 
 
(**) Syntax checker
 
 
In a certain programming language (Ada) identifiers are defined by the syntax diagram below.
 
 
http://www.hta-bi.bfh.ch/~hew/informatik3/prolog/p-99/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:
 
<pre>
 
% identifier(Str) :- Str is a legal identifier
 
</pre>
 
 
Example in Haskell:
 
<pre>
 
> identifier "this-is-a-long-identifier"
 
True
 
> identifier "this-ends-in-"
 
False
 
> identifier "two--hyphens"
 
False
 
</pre>
 
 
Solution:
 
<haskell>
 
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
 
</haskell>
 
 
Simple functional transcription of the diagram.
 
 
Another direct transcription of the diagram:
 
<haskell>
 
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
 
</haskell>
 
The functions <tt>hyphen</tt> and <tt>alphas</tt> correspond to states in the automaton at the start of the loop and before a compulsory alphanumeric, respectively.
 
== Problem 97 ==
 
 
(**) Sudoku
 
 
Sudoku puzzles go like this:
 
 
<pre>
 
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
 
</pre>
 
 
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 ==
 
 
<Problem description>
 
(***) 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:
 
<pre>
 
<example in Haskell>
 
</pre>
 
 
Solution:
 
<haskell>
 
<solution in haskell>
 
</haskell>
 
 
<description of implementation>
 
 
== 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.
 
 
http://www.hta-bi.bfh.ch/~hew/informatik3/prolog/p-99/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 [http://www.hta-bi.bfh.ch/~hew/informatik3/prolog/p-99/p99a.dat p99a.dat], other examples are [http://www.hta-bi.bfh.ch/~hew/informatik3/prolog/p-99/p99b.dat p99b.dat] and [http://www.hta-bi.bfh.ch/~hew/informatik3/prolog/p-99/p99d.dat p99d.dat]. There is also an example of a puzzle ([http://www.hta-bi.bfh.ch/~hew/informatik3/prolog/p-99/p99c.dat 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 [http://www.hta-bi.bfh.ch/~hew/informatik3/prolog/p-99/p99-readfile.pl 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:
 
<pre>
 
</pre>
 
 
Solution:
 
<haskell>
 
</haskell>
 
   
 
[[Category:Tutorials]]
 
[[Category:Tutorials]]

Revision as of 00:05, 18 November 2022


This is part of Ninety-Nine Haskell Problems, based on 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 Haskell>,<solution in haskell> and <description of implementation> fields.

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 8)
92
λ> head (queens 8)
[1,5,8,6,3,7,2,4]

Solutions


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? A set of solutions is given on the The_Knights_Tour page.

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:

λ> 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)]
λ> 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)]

Solutions

Problem 92

(***) Von Koch's conjecture

Several years ago I met a mathematician who was intrigued by a problem whose solution he didn't know. 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 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]

Solutions


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:

λ> mapM_ putStrLn $ 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

Solutions


Problem 94

(***) Generate K-regular simple graphs with N nodes

In a K-regular graph all nodes have a degree of K; i.e. the number of edges incident in each node is K. How many (non-isomorphic!) 3-regular graphs with 6 nodes are there?

Sample results

Example in Haskell:

λ> length $ regular 6 3
2

Solutions