Hints for Euler Problem 11

Hi, again. I started looking at the Euler problems [1]. I had no trouble with problems 1 through 10, but I'm stuck on problem 11. I am aware that the solutions are available ([2]), but I would rather not look just yet. In Problem 11, a 20x20 grid of numbers is given, and the problem is to find the largest product of four numbers along a straight line in the grid. The line can be horizontal, vertical, or diagonal. I figured out how to handle the horizontal and vertical products, but I'm stuck on how to approach the problem of extracting the diagonals. Here is what I have so far; it does the horizontal and vertical cases:
module Main where
import Data.List
gridText = "08 02 22 97 38 15 00 40 00 75 04 05 07 78 52 12 50 77 91 08\n\ \49 49 99 40 17 81 18 57 60 87 17 40 98 43 69 48 04 56 62 00\n\ \81 49 31 73 55 79 14 29 93 71 40 67 53 88 30 03 49 13 36 65\n\ \52 70 95 23 04 60 11 42 69 24 68 56 01 32 56 71 37 02 36 91\n\ \22 31 16 71 51 67 63 89 41 92 36 54 22 40 40 28 66 33 13 80\n\ \24 47 32 60 99 03 45 02 44 75 33 53 78 36 84 20 35 17 12 50\n\ \32 98 81 28 64 23 67 10 26 38 40 67 59 54 70 66 18 38 64 70\n\ \67 26 20 68 02 62 12 20 95 63 94 39 63 08 40 91 66 49 94 21\n\ \24 55 58 05 66 73 99 26 97 17 78 78 96 83 14 88 34 89 63 72\n\ \21 36 23 09 75 00 76 44 20 45 35 14 00 61 33 97 34 31 33 95\n\ \78 17 53 28 22 75 31 67 15 94 03 80 04 62 16 14 09 53 56 92\n\ \16 39 05 42 96 35 31 47 55 58 88 24 00 17 54 24 36 29 85 57\n\ \86 56 00 48 35 71 89 07 05 44 44 37 44 60 21 58 51 54 17 58\n\ \19 80 81 68 05 94 47 69 28 73 92 13 86 52 17 77 04 89 55 40\n\ \04 52 08 83 97 35 99 16 07 97 57 32 16 26 26 79 33 27 98 66\n\ \88 36 68 87 57 62 20 72 03 46 33 67 46 55 12 32 63 93 53 69\n\ \04 42 16 73 38 25 39 11 24 94 72 18 08 46 29 32 40 62 76 36\n\ \20 69 36 41 72 30 23 88 34 62 99 69 82 67 59 85 74 04 36 16\n\ \20 73 35 29 78 31 90 01 74 31 49 71 48 86 81 16 23 57 05 54\n\ \01 70 54 71 83 51 54 69 16 92 33 48 61 43 52 01 89 19 67 48"
readGrid :: (Read a) => String -> [[a]] readGrid = (map ((map read) . words)) . lines
grid :: [[Integer]] grid = readGrid gridText
makeGroups :: Int -> [a] -> [[a]] makeGroups 0 _ = [] makeGroups n xs = let ys = take n xs in if n == length ys then ys : (makeGroups n $ tail xs) else []
maxHorizontal :: (Ord a, Num a) => Int -> [[a]] -> a maxHorizontal length = maximum . map product . concat . map (makeGroups length)
maxVertical :: (Ord a, Num a) => Int -> [[a]] -> a maxVertical length = maxHorizontal length . transpose
main :: IO() main = do print $ maxHorizontal 4 grid print $ maxVertical 4 grid
To handle the diagonals, my plan is to try to extract each diagonal as a list of elements and put all the diagonals into a list; then I can use maxHorizontal. I came up with this function to try to extract the main diagonal.
getDiag :: [[a]] -> [a] getDiag = map (head . head) . iterate (tail . map tail)
The problem is, this function doesn't work unless I have an infinite grid. Could anyone provide me with some hints to lead me in the right direction? Thank you -- Ron References: [1] http://projecteuler.net/index.php?section=view [2] http://www.haskell.org/haskellwiki/Euler_problems

Here's my hint, FWIW. Pick a data structure that makes your life easier, i.e. where horz, vert, and diag lines are handled the same way. Instead of a 2D structure, use a 1D structure. Then, data Dir = Horz | Vert | LL | LR stride Horz = 1 stride Vert = rowLength stride LL = rowLength - 1 stride LR = rowLength + 1 nextItem dir = drop (stride dir) Now all your directions are treated the same way, and you save a lot of case analysis. Dan Ronald Guida wrote:
Hi, again.
I started looking at the Euler problems [1]. I had no trouble with problems 1 through 10, but I'm stuck on problem 11. I am aware that the solutions are available ([2]), but I would rather not look just yet.
In Problem 11, a 20x20 grid of numbers is given, and the problem is to find the largest product of four numbers along a straight line in the grid. The line can be horizontal, vertical, or diagonal.
I figured out how to handle the horizontal and vertical products, but I'm stuck on how to approach the problem of extracting the diagonals.
Here is what I have so far; it does the horizontal and vertical cases:
module Main where
import Data.List
gridText = "08 02 22 97 38 15 00 40 00 75 04 05 07 78 52 12 50 77 91 08\n\ \49 49 99 40 17 81 18 57 60 87 17 40 98 43 69 48 04 56 62 00\n\ \81 49 31 73 55 79 14 29 93 71 40 67 53 88 30 03 49 13 36 65\n\ \52 70 95 23 04 60 11 42 69 24 68 56 01 32 56 71 37 02 36 91\n\ \22 31 16 71 51 67 63 89 41 92 36 54 22 40 40 28 66 33 13 80\n\ \24 47 32 60 99 03 45 02 44 75 33 53 78 36 84 20 35 17 12 50\n\ \32 98 81 28 64 23 67 10 26 38 40 67 59 54 70 66 18 38 64 70\n\ \67 26 20 68 02 62 12 20 95 63 94 39 63 08 40 91 66 49 94 21\n\ \24 55 58 05 66 73 99 26 97 17 78 78 96 83 14 88 34 89 63 72\n\ \21 36 23 09 75 00 76 44 20 45 35 14 00 61 33 97 34 31 33 95\n\ \78 17 53 28 22 75 31 67 15 94 03 80 04 62 16 14 09 53 56 92\n\ \16 39 05 42 96 35 31 47 55 58 88 24 00 17 54 24 36 29 85 57\n\ \86 56 00 48 35 71 89 07 05 44 44 37 44 60 21 58 51 54 17 58\n\ \19 80 81 68 05 94 47 69 28 73 92 13 86 52 17 77 04 89 55 40\n\ \04 52 08 83 97 35 99 16 07 97 57 32 16 26 26 79 33 27 98 66\n\ \88 36 68 87 57 62 20 72 03 46 33 67 46 55 12 32 63 93 53 69\n\ \04 42 16 73 38 25 39 11 24 94 72 18 08 46 29 32 40 62 76 36\n\ \20 69 36 41 72 30 23 88 34 62 99 69 82 67 59 85 74 04 36 16\n\ \20 73 35 29 78 31 90 01 74 31 49 71 48 86 81 16 23 57 05 54\n\ \01 70 54 71 83 51 54 69 16 92 33 48 61 43 52 01 89 19 67 48"
readGrid :: (Read a) => String -> [[a]] readGrid = (map ((map read) . words)) . lines
grid :: [[Integer]] grid = readGrid gridText
makeGroups :: Int -> [a] -> [[a]] makeGroups 0 _ = [] makeGroups n xs = let ys = take n xs in if n == length ys then ys : (makeGroups n $ tail xs) else []
maxHorizontal :: (Ord a, Num a) => Int -> [[a]] -> a maxHorizontal length = maximum . map product . concat . map (makeGroups length)
maxVertical :: (Ord a, Num a) => Int -> [[a]] -> a maxVertical length = maxHorizontal length . transpose
main :: IO() main = do print $ maxHorizontal 4 grid print $ maxVertical 4 grid
To handle the diagonals, my plan is to try to extract each diagonal as a list of elements and put all the diagonals into a list; then I can use maxHorizontal.
I came up with this function to try to extract the main diagonal.
getDiag :: [[a]] -> [a] getDiag = map (head . head) . iterate (tail . map tail)
The problem is, this function doesn't work unless I have an infinite grid.
Could anyone provide me with some hints to lead me in the right direction?
Thank you -- Ron
References:
[1] http://projecteuler.net/index.php?section=view
[2] http://www.haskell.org/haskellwiki/Euler_problems
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

I came up with this function to try to extract the main diagonal.
getDiag :: [[a]] -> [a] getDiag = map (head . head) . iterate (tail . map tail)
The problem is, this function doesn't work unless I have an infinite grid.
Could anyone provide me with some hints to lead me in the right direction?
I think Dan's hint is pretty good, but a hint for this *specific* part of the problem, rather than the whole thing. 'head' and 'tail' blow up on empty lists. So any kind of solution involving iterate and similar with them tends to eventually blow up on finite lists. (take 1) and (drop 1) are rather similar functions, but they simply give [] on [] instead of blowing up. Then, on a finite list, you just keep getting []s after a while, which you can trim with takeWhile (not . null). Another approach is to replace iterate with an unfoldr; an unfoldr is rather like a 'general iterate' which 'knows when to stop' : it stops when your unfolding function gives Nothing. Jules

On Thu, Jul 19, 2007 at 11:39:26PM -0400, Ronald Guida wrote:
In Problem 11, a 20x20 grid of numbers is given, and the problem is to find the largest product of four numbers along a straight line in the grid. The line can be horizontal, vertical, or diagonal.
I found it easier to work with Arrays in this example:
grid :: [[Integer]] grid = readGrid gridText
gridArr :: [[Integer]] -> Array (Int, Int) Integer gridArr = array ((0, 0), (19, 19))
Then you can define a handy function for extracting whatever combination of indices you need:
extractBy :: (Ix i, Ord a) => ((i, e) -> a) -> Array i e -> [[e]] extractBy f = map (map snd) . groupBy (equals f) . sortBy (comparing f) . assocs
And from there on you can work your way out of this problem by replacing ??? with functions that map ((i, j), v) to some value common for same row, col, or diagonal:
rows = extractBy ??? cols = extractBy ??? diags = extractBy ??? adiags = extractBy ???
makeGroups :: Int -> [a] -> [[a]] makeGroups 0 _ = [] makeGroups n xs = let ys = take n xs in if n == length ys then ys : (makeGroups n $ tail xs) else []
The above can be shortened to:
makeGroupsOf n = map (take n) . tails
From here on you should be able to compute products of whatever is required. Good luck and have fun!
Regards, -- Krzysztof Kościuszkiewicz Skype: dr.vee, Gadu: 111851, Jabber: kokr@jabberpl.org Phone IRL: +353851383329, Phone PL: +48783303040 "Simplicity is the ultimate sophistication" -- Leonardo da Vinci

Ronald Guida
I started looking at the Euler problems [1]. I had no trouble with problems 1 through 10, but I'm stuck on problem 11. I am aware that the solutions are available ([2]), but I would rather not look just yet.
I am the author of that solution http://www.haskell.org/haskellwiki/Euler_problems/11_to_20 My solution has a word count of 191 words, which might amuse you considering that there are 400 entries to the table. Hint: "zipWith4" is your friend; see Data.List. Feed it four lists of different lengths, and it stops gracefully when any list runs out. So one can use skew (w,x,y,z) = (w, drop 1 x, drop 2 y, drop 3 z) to stagger four lists before multiplying corresponding elements. I was using the Euler problems to learn Haskell, as you're doing, so I don't know if my solution is the most readable one. I built up a vocabulary of short functions to compose. I remember finding it odd at the time that I had to use tuples to handle multiple return values. C annoyed me for being mostly peanut shells and few peanuts: one seems to spend all of one's time tossing arguments back and forth onto the stack for nested function calls, when it seemed that the real work could be done in place with less effort. Sure, optimizing compilers do exactly that, with registers, but then why was I explicitly worrying about passing around all of these arguments, in order to code in C? Haskell is much more concise, but the tupling and untupling in my code seems a distraction, even looking back at it now.

Ronald Guida wrote:
Hi, again.
I started looking at the Euler problems [1]. I had no trouble with problems 1 through 10, but I'm stuck on problem 11. I am aware that the solutions are available ([2]), but I would rather not look just yet. [...]
FWIW I used a 2D array and a function to retrieve the values in every direction from a given row,col, for each direction valid for that array index. Getting the 4 vals in each direction is done by iterating 2 functions on the (row,col) index to move in the right direction I.e., vals (row,col) = north : south : ... : [] where north = if toohigh then [] else stream (subtract 1) (id) south = if toolow then [] else stream (+1) (id) ....... -- View this message in context: http://www.nabble.com/Hints-for-Euler-Problem-11-tf4114963.html#a11710468 Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.

Jim Burton wrote:
Ronald Guida wrote:
Hi, again.
I started looking at the Euler problems [1]. I had no trouble with problems 1 through 10, but I'm stuck on problem 11. I am aware that the solutions are available ([2]), but I would rather not look just yet. [...]
FWIW I used a 2D array and a function to retrieve the values in every direction from a given row,col, for each direction valid for that array index. Getting the 4 vals in each direction is done by iterating 2 functions on the (row,col) index to move in the right direction I.e.,
vals (row,col) = north : south : ... : [] where north = if toohigh then [] else stream (subtract 1) (id) south = if toolow then [] else stream (+1) (id) .......
where `stream' is badly named -- rather than a stream it's the 4 vals in that direction. -- View this message in context: http://www.nabble.com/Hints-for-Euler-Problem-11-tf4114963.html#a11710683 Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.

Hi. My plan is just add some *unusable* data to make diagonal grid normally. Here this is. p011_input = input ++ (transpose input) ++ diagInput ++ diagInputT where diagInput = p011_toDiag input diagInputT = p011_toDiag . (map reverse) $ input input = [ [08,02,22,97,38,15,00,40,00,75,04,05,07,78,52,12,50,77,91,08], [49,49,99,40,17,81,18,57,60,87,17,40,98,43,69,48,04,56,62,00], ... , [01,70,54,71,83,51,54,69,16,92,33,48,61,43,52,01,89,19,67,48] ] p011_toDiag = (map remove) . transpose . (map append) . addIndex where addIndex = zip [0..] append (n,y) = replicate n (-1) ++ y ++ replicate (19-n) (-1) remove = filter (-1/=) p011_toGroups x = case x of (a:b:c:d:xs) -> [a,b,c,d] : p011_toGroups (b:c:d:xs) _ -> [] p011_solve = putStrLn . show $ (foldl1 max) . (map product) . concat . (map p011_toGroups) $ p011_input ------------------ L.Guo 2007-08-17 ------------------------------------------------------------- From: Ronald Guida At: 2007-07-20 11:39:50 Subject: [Haskell-cafe] Hints for Euler Problem 11 To handle the diagonals, my plan is to try to extract each diagonal as a list of elements and put all the diagonals into a list; then I can use maxHorizontal. I came up with this function to try to extract the main diagonal.
getDiag :: [[a]] -> [a] getDiag = map (head . head) . iterate (tail . map tail)
The problem is, this function doesn't work unless I have an infinite grid.
participants (7)
-
Dan Weston
-
Dave Bayer
-
Jim Burton
-
Jules Bean
-
Krzysztof Kościuszkiewicz
-
L.Guo
-
Ronald Guida