Difference between revisions of "99 questions/95 to 99"
(moved nonogram solvers to separate page) |
RossPaterson (talk | contribs) m (new URL) |
||
Line 1: | Line 1: | ||
__NOTOC__ | __NOTOC__ | ||
− | This is part of [[H-99:_Ninety-Nine_Haskell_Problems|Ninety-Nine Haskell Problems]], based on [ | + | 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 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. | ||
Line 38: | Line 38: | ||
In a certain programming language (Ada) identifiers are defined by the syntax diagram below. | In a certain programming language (Ada) identifiers are defined by the syntax diagram below. | ||
− | + | https://prof.ti.bfh.ch/hew1/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. | 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. | ||
Line 170: | Line 170: | ||
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. | 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. | ||
− | + | https://prof.ti.bfh.ch/hew1/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. | 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. | ||
Line 256: | Line 256: | ||
readCrossword = (\(ws,ss) -> Crossword ws (toSites (drop 1 ss))) . break (""==) . lines | readCrossword = (\(ws,ss) -> Crossword ws (toSites (drop 1 ss))) . break (""==) . lines | ||
</haskell> | </haskell> | ||
− | |||
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. | 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. |
Revision as of 23:41, 29 January 2007
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.
Miscellaneous problems
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.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"]
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 below.
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.
Here is a solution that parses the identifier using Parsec, a parser library that is commonly used in Haskell code:
identifier x = either (const False) (const True) $ parse parser "" x where
parser = letter >> many (optional (char '-') >> alphaNum)
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
Solutions: see Nonogram
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 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.