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

From HaskellWiki
Jump to navigation Jump to search
m (verbose solution 96)
m
 
(56 intermediate revisions by 9 users not shown)
Line 1: Line 1:
 
__NOTOC__
 
__NOTOC__
   
  +
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].
These are Haskell translations of [http://www.ic.unicamp.br/~meidanis/courses/mc336/2006s2/funcional/L-99_Ninety-Nine_Lisp_Problems.html Ninety Nine Lisp 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.
+
<small>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 <tt><Problem description>,<example in Haskell>,<solution in haskell></tt> and <tt><description of implementation></tt> fields.</small>
   
== Miscellaneous problems ==
 
   
 
== Problem 90 ==
 
== Problem 90 ==
  +
<div style="border-bottom:1px solid #eee">(**) Eight queens problem. <span style="float:right"><small>[[99 questions/Solutions/90|Solutions]]</small></span>
 
  +
</div>
Eight queens problem
 
  +
&nbsp;<br>
   
 
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.
 
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.
Line 15: Line 15:
 
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.
 
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.
   
<pre>
 
 
Example in Haskell:
 
Example in Haskell:
> 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
 
  +
λ> head (queens 8)
queens' 0 = [[]]
 
  +
[1,5,8,6,3,7,2,4]
queens' (n+1) = [ try:alreadySet | alreadySet <- queens' n, try <- [1..8], isSafe try alreadySet]
 
where isSafe try alreadySet = not (sameRow try alreadySet || sameDiagonal try alreadySet)
 
sameRow try alreadySet = try `elem` alreadySet
 
sameDiagonal try alreadySet = any (\(col,q) -> abs(try - q) == col) $ zip [1..] alreadySet
 
 
</haskell>
 
</haskell>
   
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 ==
  +
<div style="border-bottom:1px solid #eee">(**) Knight's tour. <span style="float:right"><small>[[99 questions/Solutions/91|Solutions]]</small></span>
  +
</div>
  +
&nbsp;<br>
   
  +
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.
<Problem description>
 
   
  +
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).
<pre>
 
Example:
 
<example in lisp>
 
   
  +
There are two variants of this problem:
Example in Haskell:
 
  +
# find a tour ending at a particular square
<example in Haskell>
 
  +
# find a circular tour, ending a knight's jump from the start (clearly it doesn't matter where you start, so choose (1,1))
</pre>
 
 
Solution:
 
<haskell>
 
<solution in haskell>
 
</haskell>
 
 
<description of implementation>
 
 
== Problem 92 ==
 
 
<Problem description>
 
 
<pre>
 
Example:
 
<example in lisp>
 
   
 
Example in Haskell:
 
Example in Haskell:
<example in Haskell>
 
</pre>
 
   
Solution:
 
 
<haskell>
 
<haskell>
  +
λ> head $ knightsTo 8 (1,1)
<solution in haskell>
 
  +
[(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)]
 
</haskell>
 
</haskell>
   
<description of implementation>
 
 
== Problem 93 ==
 
   
  +
== Problem 92 ==
An arithmetic puzzle
 
  +
<div style="border-bottom:1px solid #eee">(***) Von Koch's conjecture. <span style="float:right"><small>[[99 questions/Solutions/92|Solutions]]</small></span>
  +
</div>
  +
&nbsp;<br>
   
  +
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.
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!).
 
   
  +
https://prof.ti.bfh.ch/hew1/informatik3/prolog/p-99/p92a.gif
<pre>
 
Example in Haskell:
 
> 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"]
 
</pre>
 
   
  +
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.
Solution:
 
<haskell>
 
import Text.ParserCombinators.Parsec
 
import Text.ParserCombinators.Parsec.Expr
 
   
  +
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!
puzzle :: [Integer] -> [String]
 
puzzle xs = filter ((\(a,b) -> calcExp a == calcExp b) . split) equations
 
where equations = map concat . filter isValid . sequence . intersperse ops . map ((:[]) . show) $ xs
 
split = (\(a,b) -> (a, drop 1 b)) . break ('='==)
 
ops = ["+", "-", "/", "*", "="]
 
isValid = (1==) . length . filter ("="==)
 
   
  +
Write a predicate that calculates a numbering scheme for a given tree. What is the solution for the larger tree pictured below?
   
  +
https://prof.ti.bfh.ch/hew1/informatik3/prolog/p-99/p92b.gif
expr :: Parser Integer
 
expr = buildExpressionParser optable factor
 
 
optable = [[op "*" (*) AssocLeft, op "/" div AssocLeft]
 
,[op "+" (+) AssocLeft, op "-" (-) AssocLeft]
 
]
 
where op s f assoc = Infix (do{ string s; return f}) assoc
 
 
factor = do{ char '('
 
; x <- expr
 
; char ')'
 
; return x
 
}
 
<|> number
 
 
number :: Parser Integer
 
number = do{ ds <- many1 digit
 
; return (read ds)
 
}
 
 
calcExp e = either (error . show) id (parse expr "source" e)
 
</haskell>
 
 
I chose using parsec to evaluate the arithmetic expressions. Parentheses are not yet supported. Integer division is used (i.e. 7/11 == 0).
 
 
Using Template Haskell or hs-plugins would likely yield a more concise solution.
 
 
== Problem 94 ==
 
 
<Problem description>
 
 
<pre>
 
Example:
 
<example in lisp>
 
   
 
Example in Haskell:
 
Example in Haskell:
<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>
   
<description of implementation>
 
 
 
== Problem 95 ==
+
== Problem 93 ==
  +
<div style="border-bottom:1px solid #eee">(***) An arithmetic puzzle. <span style="float:right"><small>[[99 questions/Solutions/93|Solutions]]</small></span>
  +
</div>
  +
&nbsp;<br>
   
  +
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!).
English number words
 
   
  +
Division should be interpreted as operating on rationals, and division by zero should be avoided.
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.
 
   
<pre>
 
 
Example in Haskell:
 
Example in Haskell:
> numbers 175
 
one-seven-five
 
</pre>
 
   
Solution:
 
 
<haskell>
 
<haskell>
  +
λ> mapM_ putStrLn $ puzzle [2,3,5,7,11]
import Data.List
 
  +
2 = 3-(5+7-11)
import Data.Maybe
 
  +
2 = 3-5-(7-11)
 
  +
2 = 3-(5+7)+11
numbers :: Integer -> String
 
  +
2 = 3-5-7+11
numbers n = concat . intersperse "-" . map (fromJust . (`lookup` table)) $ show n
 
  +
2 = (3*5+7)/11
where table = [('0',"zero"), ('1',"one"), ('2',"two"), ('3',"three"), ('4',"four"),
 
  +
2*(3-5) = 7-11
('5',"five"), ('6',"six"), ('7',"seven"), ('8',"eight"), ('9',"nine")]
 
  +
2-(3-(5+7)) = 11
  +
2-(3-5-7) = 11
  +
2-(3-5)+7 = 11
  +
2-3+5+7 = 11
 
</haskell>
 
</haskell>
   
  +
The other two solutions alluded to in the problem description are dropped by the Haskell solution as trivial variants:
This solution does a simple table lookup after converting the positive integer into a string. Thus dividing into digits is much simplified.
 
 
== Problem 96 ==
 
 
Syntax checker
 
 
In a certain programming language (Ada) identifiers are defined by the [http://www.hta-bi.bfh.ch/~hew/informatik3/prolog/p-99/p96.gif syntax diagram]. 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.
 
 
   
 
<pre>
 
<pre>
  +
2 = 3-(5+(7-11))
Example in Prolog:
 
  +
2-3+(5+7) = 11
% identifier(Str) :- Str is a legal identifier
 
 
Example in Haskell:
 
> syntax_check "Str"
 
True
 
 
</pre>
 
</pre>
   
Solution:
 
<haskell>
 
syntax_check [] = False
 
syntax_check (x:xs) = letter x && loop xs
 
where loop [] = True
 
loop (x':xs') | x' == '-' = (not . null) xs' && (letter (head xs') || digit (head xs')) && loop (tail xs')
 
| letter x' = loop xs'
 
| digit x' = loop xs'
 
| otherwise = False
 
letter x = x `elem` (['a'..'z'] ++ ['A'..'Z'])
 
digit x = x `elem` ['0'..'9']
 
</haskell>
 
   
  +
== Problem 94 ==
Simple functional transcription of the diagram.
 
  +
<div style="border-bottom:1px solid #eee">(***) Generate K-regular simple graphs with N nodes. <span style="float:right"><small>[[99 questions/Solutions/94|Solutions]]</small></span>
 
  +
</div>
== Problem 97 ==
 
  +
&nbsp;<br>
   
  +
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?
Sudoku
 
   
  +
[https://prof.ti.bfh.ch/hew1/informatik3/prolog/p-99/p94.txt Sample results]
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.
 
 
see [[Sudoku]]
 
 
== Problem 98 ==
 
 
<Problem description>
 
 
<pre>
 
Example:
 
<example in lisp>
 
   
 
Example in Haskell:
 
Example in Haskell:
<example in Haskell>
 
</pre>
 
 
Solution:
 
 
<haskell>
 
<haskell>
  +
λ> length $ regular 6 3
<solution in haskell>
 
  +
2
 
</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.
 
 
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 opposite 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.lisp. Use 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.
 
 
<pre>
 
Example in Haskell:
 
</pre>
 
 
Solution:
 
<haskell>
 
type Word = String
 
data LayoutPos = LayoutPos {row, col, len :: Int, horizontal :: Bool} deriving Show
 
data Desc = Desc [Word] [LayoutPos] deriving Show
 
 
word = do w <- many1 letter
 
newline
 
return w
 
<?> "word"
 
 
emptyLine = char '\n' <?> "emptyLine"
 
 
layoutLine = do line <- many1 (oneOf [' ', '.'])
 
newline
 
return line
 
<?> "layoutLine"
 
 
description = do words <- manyTill word emptyLine
 
layout <- manyTill layoutLine eof
 
return $ Desc words (toLayout layout)
 
<?> "description"
 
 
--toLayout :: [String] -> Layout
 
toLayout lines = find True lines ++ map (\lp@LayoutPos{row=x, col=y} -> lp{row=y, col=x}) (find False (transpose lines))
 
where find horz lines = filter ((>1) . len) . map (makePos horz) . concat . savePosition . map group $ lines
 
makePos horz ((x,y), str) = LayoutPos {col = x, row = y, len = length str, horizontal = horz}
 
savePosition = map (\(n,e) -> zip [(n,x) | x <- [1..]] e) . zip [1..]
 
 
-- parseText description <string containing file content>
 
 
</haskell>
 
 
I did start the work, but only finished the parsing bit so far. Feel free to modify this radically. It parses the file format into a list of datatype "LayoutPos" which contains the position of a space with length>1 as well as its orientation (horizontal/vertical) and length. At the moment (due to my stupidity and the late hour) the final newline before the EOF is necessary, but that should be easily fixed with even a little brains.
 
 
Easier/shorter than parsec would probably be 'splitAt "\n" . lines'
 
 
The hard(?) part is still left to be done :) I guess the next part would be to interface the LayoutPos datatype with some kind of "collision detection" and backtrack for solutions. Sensible heuristics would be fitting definitive words first and finding collisions as early as possible.
 
 
See the prolog version of the problems for [working links | http://www.hta-bi.bfh.ch/~hew/informatik3/prolog/p-99/]
 
   
 
[[Category:Tutorials]]
 
[[Category:Tutorials]]

Latest revision as of 06:27, 11 June 2023


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. Solutions

 

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]


Problem 91

(**) Knight's tour. Solutions

 

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


Problem 92

(***) Von Koch's conjecture. Solutions

 

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]


Problem 93

(***) An arithmetic puzzle. Solutions

 

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


Problem 94

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

 

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