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

From HaskellWiki
Jump to navigation Jump to search
(another solution to P93)
(note on P93 example)
Line 96: Line 96:
 
2-(3-5)+7 = 11
 
2-(3-5)+7 = 11
 
2-3+5+7 = 11
 
2-3+5+7 = 11
  +
</pre>
  +
The other two solutions alluded to in the problem description are dropped by solution 2 as trivial variants:
  +
<pre>
  +
2 = 3-(5+(7-11))
  +
2-3+(5+7) = 11
 
</pre>
 
</pre>
   

Revision as of 12:28, 13 December 2006


These are Haskell translations of Ninety Nine Lisp Problems, which are themselves 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

queens' 0     = [[]]
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

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 description>

Example:
<example in lisp>

Example in Haskell:
<example in Haskell>

Solution:

<solution in haskell>

<description of implementation>

Problem 92

<Problem description>

Example:
<example in lisp>

Example in Haskell:
<example in Haskell>

Solution:

<solution in haskell>

<description of implementation>

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!).

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 solution 2 as trivial variants:

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

Solution 1:

import Text.ParserCombinators.Parsec
import Text.ParserCombinators.Parsec.Expr

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 ("="==)


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)

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.

Solution 2:

module P93 where

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

type Equation = (Expr, Expr)
-- cache value in binary expression
data Expr = Const Integer | Binary Value 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 <- exprs ns1, e2 <- exprs ns2,
                value e1 == value e2]

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

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

-- the cached values of an expression
value :: Expr -> Value
value (Const n) = fromInteger n
value (Binary n _ _ _) = n

-- 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 = "/"

I've used rational division, because that's what the Prolog solution does. 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:
> numbers 175
one-seven-five

Solution:

import Data.List
import Data.Maybe

numbers :: Integer -> String
numbers 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.

Problem 96

Syntax checker

In a certain programming language (Ada) identifiers are defined by the 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.


Example in Prolog:
% identifier(Str) :- Str is a legal identifier 

Example in Haskell:
> syntax_check "Str"
True

Solution:

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

Simple functional transcription of the diagram.

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

<Problem description>

Example:
<example in lisp>

Example in Haskell:
<example in Haskell>

Solution:

<solution in 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.

Example in Haskell:

Solution:

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>

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