
Thank you for all the hints. Here's how I ended up solving it:
module Main where
import Data.List import Data.Maybe
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"
type Grid a = [[a]]
readGrid :: (Read a) => String -> Grid a readGrid = (map ((map read) . words)) . lines
grid :: Grid Integer grid = readGrid gridText
takeExactly - extract the first "n" elements of a list; there must be at least "n" elements, n > 0
takeExactly :: (Monad m) => Int -> [a] -> m [a] takeExactly n xs | n > 0 = let ys = take n xs in if length ys == n then return ys else fail "takeExactly: list is too short" | otherwise = fail "takeExactly: empty list"
extractGroups :: Int -> [[a]] -> [[a]] extractGroups n = catMaybes . map (takeExactly n)
gridExtractGroups :: Int -> Grid [a] -> Grid [a] gridExtractGroups n = filter (not . null) . map (extractGroups n)
gridTails - generate a list of grids with sequential starting places Parameters a and b determine the offset bewteen successive grids, as follows: (note that a, b may not be negative) Grid x_{0,1.., 0,1..} -> [ Grid x_{ 0, 1 .., 0, 1 ..} , Grid x_{ a, a+1 .., b, b+1 ..} , Grid x_{2*a, 2*a+1 .., 2*b, 2*b+1 ..} etc. ]
gridTails :: (Int, Int) -> Grid a -> [Grid a] gridTails (a,b) xs = if not $ null $ concat xs then xs : gridTails (a,b) ((drop a) $ map (drop b) xs) else []
transpose3d - converts x_{i,j,k} to x_{j,k,i} using sequence is x_{i,j,k} -> x_{j,i,k} -> x_{j,k,i}
transpose3d :: [Grid a] -> Grid [a] transpose3d = map transpose . transpose
reorient - transform a direction vector so that both components are non-negative
reorient :: (Int, Int) -> (Grid a -> Grid a, (Int, Int), Grid b -> Grid b) reorient (a,b) | a>=0 && b>=0 = (id , ( a, b), id) | a< 0 && b>=0 = (reverse , (-a, b), reverse) | a>=0 && b< 0 = (map reverse , ( a,-b), map reverse) | a< 0 && b< 0 = (reverse . map reverse, (-a,-b), reverse . map reverse)
makeEls - convert a grid to grid of Equidistant Letter Sequences
makeEls :: (Int, Int) -> Grid a -> Grid [a] makeEls vec = let (reflect2, rvec, reflect1) = reorient vec in reflect2 . transpose3d . gridTails rvec . reflect1
getGroups :: Int -> (Int, Int) -> Grid a -> [[a]] getGroups n (a,b) = concat . gridExtractGroups n . makeEls (a,b)
findMaxProduct :: (Ord a, Num a) => Int -> (Int, Int) -> Grid a -> a findMaxProduct n (a,b) = maximum . map product . getGroups n (a,b)
main :: IO() main = do print $ findMaxProduct 4 (1,0) grid print $ findMaxProduct 4 (0,1) grid print $ findMaxProduct 4 (1,1) grid print $ findMaxProduct 4 (1,-1) grid
-- Ron

Spotted this thread as I was working on a Haskell solution for this one myself - here's the solution I came up with: module Main where import List raw_matrix = "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 " ++ "81 49 31 73 55 79 14 29 93 71 40 67 53 88 30 03 49 13 36 65 " ++ "52 70 95 23 04 60 11 42 69 24 68 56 01 32 56 71 37 02 36 91 " ++ "22 31 16 71 51 67 63 89 41 92 36 54 22 40 40 28 66 33 13 80 " ++ "24 47 32 60 99 03 45 02 44 75 33 53 78 36 84 20 35 17 12 50 " ++ "32 98 81 28 64 23 67 10 26 38 40 67 59 54 70 66 18 38 64 70 " ++ "67 26 20 68 02 62 12 20 95 63 94 39 63 08 40 91 66 49 94 21 " ++ "24 55 58 05 66 73 99 26 97 17 78 78 96 83 14 88 34 89 63 72 " ++ "21 36 23 09 75 00 76 44 20 45 35 14 00 61 33 97 34 31 33 95 " ++ "78 17 53 28 22 75 31 67 15 94 03 80 04 62 16 14 09 53 56 92 " ++ "16 39 05 42 96 35 31 47 55 58 88 24 00 17 54 24 36 29 85 57 " ++ "86 56 00 48 35 71 89 07 05 44 44 37 44 60 21 58 51 54 17 58 " ++ "19 80 81 68 05 94 47 69 28 73 92 13 86 52 17 77 04 89 55 40 " ++ "04 52 08 83 97 35 99 16 07 97 57 32 16 26 26 79 33 27 98 66 " ++ "88 36 68 87 57 62 20 72 03 46 33 67 46 55 12 32 63 93 53 69 " ++ "04 42 16 73 38 25 39 11 24 94 72 18 08 46 29 32 40 62 76 36 " ++ "20 69 36 41 72 30 23 88 34 62 99 69 82 67 59 85 74 04 36 16 " ++ "20 73 35 29 78 31 90 01 74 31 49 71 48 86 81 16 23 57 05 54 " ++ "01 70 54 71 83 51 54 69 16 92 33 48 61 43 52 01 89 19 67 48 " matrix :: [Int] matrix = map read (words raw_matrix) rows = map (\i -> take 20 (drop (i * 20) matrix)) [0..19] cols = transpose rows diag m = (map (\i -> map (\p -> m !! p !! (i+p)) [0..(19-i)]) [0..19]) ++ (map (\i -> map (\p -> m !! (i+p) !! p) [0..(19-i)]) [0..19]) all_matrix_combinations = rows ++ cols ++ (diag rows) ++ (diag $ reverse rows) -- This function finds the maximum sequence of 4 in a given list find_max_product_of_4 l = find_max_4' 0 l where find_max_4' m [] = m find_max_4' m l = find_max_4' (max m (product $ take 4 l)) (tail l) all_maximums = map find_max_product_of_4 all_combinations max_product = maximum all_maximums main = putStrLn $ show max_product

On 8/15/07, Mathias Biilmann Christensen
Spotted this thread as I was working on a Haskell solution for this one myself - here's the solution I came up with: [ ... ] raw_matrix = "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 " ++ "81 49 31 73 55 79 14 29 93 71 40 67 53 88 30 03 49 13 36 65 " ++ [ ... ]
A little style issue here on the side, if I may. You don't need to use (++) to join multiline string literals. text = "If you want to have multiline string literals \ \in your source code, you can break them up with \ \backslashes. Any whitespace characters between \ \two backslashes will be ignored." (The Haskell 98 Report calls them backslants.) Pekka

On 2007-08-15, Pekka Karjalainen
On 8/15/07, Mathias Biilmann Christensen
wrote: Spotted this thread as I was working on a Haskell solution for this one myself - here's the solution I came up with: [ ... ] raw_matrix = "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 " ++ "81 49 31 73 55 79 14 29 93 71 40 67 53 88 30 03 49 13 36 65 " ++ [ ... ]
A little style issue here on the side, if I may. You don't need to use (++) to join multiline string literals.
text = "If you want to have multiline string literals \ \in your source code, you can break them up with \ \backslashes. Any whitespace characters between \ \two backslashes will be ignored."
I find the first far more readable. The compiler should be able to assemble it all at compile time, right? -- Aaron Denney -><-

Aaron Denney wrote:
On 2007-08-15, Pekka Karjalainen
wrote: A little style issue here on the side, if I may. You don't need to use (++) to join multiline string literals.
text = "If you want to have multiline string literals \ \in your source code, you can break them up with \ \backslashes. Any whitespace characters between \ \two backslashes will be ignored."
I find the first far more readable. The compiler should be able to assemble it all at compile time, right?
'Course not. The (++) function like all Haskell functions is only a /promise/ to do its job. What does "assembling at compile time" mean here: s = "I will not write infinite loops " ++ s -- View this message in context: http://www.nabble.com/Hints-for-Euler-Problem-11-tf4114963.html#a12188224 Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.

But if the strings are all constant it's perfectly feasible to concatenate
them at compile time.
On 8/16/07, Kim-Ee Yeoh
Aaron Denney wrote:
On 2007-08-15, Pekka Karjalainen
wrote: A little style issue here on the side, if I may. You don't need to use (++) to join multiline string literals.
text = "If you want to have multiline string literals \ \in your source code, you can break them up with \ \backslashes. Any whitespace characters between \ \two backslashes will be ignored."
I find the first far more readable. The compiler should be able to assemble it all at compile time, right?
'Course not. The (++) function like all Haskell functions is only a /promise/ to do its job. What does "assembling at compile time" mean here:
s = "I will not write infinite loops " ++ s
-- View this message in context: http://www.nabble.com/Hints-for-Euler-Problem-11-tf4114963.html#a12188224 Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Lennart Augustsson wrote:
On 8/16/07, Kim-Ee Yeoh
wrote: 'Course not. The (++) function like all Haskell functions is only a /promise/ to do its job. What does "assembling at compile time" mean here:
s = "I will not write infinite loops " ++ s
But if the strings are all constant it's perfectly feasible to concatenate them at compile time.
It's feasible and I might add that it isn't worth it. Not for just concatenation. How much static evaluation do you want to see in Haskell? -- View this message in context: http://www.nabble.com/Hints-for-Euler-Problem-11-tf4114963.html#a12195537 Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.

It's very hard to tell if it's worth it or not. Concatenating constant
strings will turn the string into WHNF, which might enable some other
transformation. By having lots of little transformations that on their own
look worthless you can make big improvements.
I'd like to see as much static evaluation as is practically possible.
And as a previous poster showed, ghc does concatenate strings.
On 8/17/07, Kim-Ee Yeoh
Lennart Augustsson wrote:
On 8/16/07, Kim-Ee Yeoh
wrote: 'Course not. The (++) function like all Haskell functions is only a /promise/ to do its job. What does "assembling at compile time" mean here:
s = "I will not write infinite loops " ++ s
But if the strings are all constant it's perfectly feasible to
concatenate
them at compile time.
It's feasible and I might add that it isn't worth it. Not for just concatenation. How much static evaluation do you want to see in Haskell?
-- View this message in context: http://www.nabble.com/Hints-for-Euler-Problem-11-tf4114963.html#a12195537 Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Lennart Augustsson wrote:
On 8/17/07, Kim-Ee Yeoh
wrote: How much static evaluation do you want to see in Haskell?
I'd like to see as much static evaluation as is practically possible.
Yes but not in (the language formally defined as) Haskell. Not even in {your favorite Haskell compiler/interpreter} without -O. With -O by all means let her rip. Incidentally, GHC's type checker is Turing complete. You already have as much static evaluation as is practically possible. You already knew that. Lennart Augustsson wrote:
And as a previous poster showed, ghc does concatenate strings.
And Haskell (as in the current language definition) does not. I was talking about Haskell. Having said that, I'll concede there may be room for more than one language here. I want syntax transparently reflecting straightforward if slowpoke operational semantics. You want fast, tight programs. I want fast, tight programs too, but not by giving up the former. -- View this message in context: http://www.nabble.com/Hints-for-Euler-Problem-11-tf4114963.html#a12197224 Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.

On 8/17/07, Kim-Ee Yeoh
Lennart Augustsson wrote:
And as a previous poster showed, ghc does concatenate strings.
And Haskell (as in the current language definition) does not. I was talking about Haskell.
Haskell says nothing about compile time or run time in the language definition. Nor does it say exactly when things are evaluated. Even the tag line for Haskell says "non-strict" rather than lazy. So Haskell semantics allows many evaluation strategies, and evaluating terminating constant expression at compile time is certainly one of them. You don't have to, but it's permissible. -- Lennart

On 8/17/07, Kim-Ee Yeoh
Incidentally, GHC's type checker is Turing complete. You already have as much static evaluation as is practically possible. You already knew that.
I don't see how the first statement implies the second. Cheers, Tim -- Tim Chevalier * catamorphism.org * Often in error, never in doubt "It's never too early to start drilling holes in your car." -- Tom Magliozzi

I agree. Computation on the type level does not imply computation on the
value level.
On 8/18/07, Tim Chevalier
On 8/17/07, Kim-Ee Yeoh
wrote: Incidentally, GHC's type checker is Turing complete. You already have as much static evaluation as is practically possible. You already knew that.
I don't see how the first statement implies the second.
Cheers, Tim
-- Tim Chevalier * catamorphism.org * Often in error, never in doubt "It's never too early to start drilling holes in your car." -- Tom Magliozzi _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

On 2007-08-16, Kim-Ee Yeoh
Aaron Denney wrote:
On 2007-08-15, Pekka Karjalainen
wrote: A little style issue here on the side, if I may. You don't need to use (++) to join multiline string literals.
text = "If you want to have multiline string literals \ \in your source code, you can break them up with \ \backslashes. Any whitespace characters between \ \two backslashes will be ignored."
I find the first far more readable. The compiler should be able to assemble it all at compile time, right?
'Course not. The (++) function like all Haskell functions is only a /promise/ to do its job. What does "assembling at compile time" mean here:
s = "I will not write infinite loops " ++ s
It's a circular list of characters. Quite feasible to do at compile time. -- Aaron Denney -><-

On Thu, 2007-08-16 at 12:50 -0700, Kim-Ee Yeoh wrote:
Aaron Denney wrote:
On 2007-08-15, Pekka Karjalainen
wrote: A little style issue here on the side, if I may. You don't need to use (++) to join multiline string literals.
text = "If you want to have multiline string literals \ \in your source code, you can break them up with \ \backslashes. Any whitespace characters between \ \two backslashes will be ignored."
I find the first far more readable. The compiler should be able to assemble it all at compile time, right?
'Course not. The (++) function like all Haskell functions is only a /promise/ to do its job. What does "assembling at compile time" mean here:
s = "I will not write infinite loops " ++ s
Let's check, shall we? I've never used core before, but there's a first time for everything: % cat C.hs module Test where x = "Foo" ++ "Bar" y = "Zot" ++ y % ghc -ddump-simpl C.hs ==================== Tidy Core ==================== Test.x :: [GHC.Base.Char] [GlobalId] [] Test.x = GHC.Base.++ @ GHC.Base.Char (GHC.Base.unpackCString# "Foo") (GHC.Base.unpackCString# "Bar") Rec { Test.y :: [GHC.Base.Char] [GlobalId] [] Test.y = GHC.Base.++ @ GHC.Base.Char (GHC.Base.unpackCString# "Zot") Test.y end Rec } If I interpret it correctly, the compiler does approximately nothing - reasonably enough, since we didn't ask for optimization. With -O: % ghc -ddump-simpl C.hs -O ==================== Tidy Core ==================== Rec { Test.y :: [GHC.Base.Char] [GlobalId] [Str: DmdType] Test.y = GHC.Base.unpackAppendCString# "Zot" Test.y end Rec } Test.x :: [GHC.Base.Char] [GlobalId] [Str: DmdType] Test.x = GHC.Base.unpackCString# "FooBar" y gets turned into an unpackAppendCString#, which I can only presume is a sensible way to represent a cyclic list, while x gets concatenated compile-time. -k

The compiler dumps are illuminating, thank you. I'm afraid I don't always compile under -O. In fact I never debug with -O. I see now what I'm missing. (Pain, grief, despair.) Ketil Malde wrote:
On Thu, 2007-08-16 at 12:50 -0700, Kim-Ee Yeoh wrote:
Aaron Denney wrote:
The compiler should be able to assemble it all at compile time, right?
'Course not. The (++) function like all Haskell functions is only a /promise/ to do its job. What does "assembling at compile time" mean here:
s = "I will not write infinite loops " ++ s
% cat C.hs
module Test where
x = "Foo" ++ "Bar" y = "Zot" ++ y
% ghc -ddump-simpl C.hs
==================== Tidy Core ==================== Test.x :: [GHC.Base.Char] [GlobalId] [] Test.x = GHC.Base.++ @ GHC.Base.Char (GHC.Base.unpackCString# "Foo") (GHC.Base.unpackCString# "Bar")
Rec { Test.y :: [GHC.Base.Char] [GlobalId] [] Test.y = GHC.Base.++ @ GHC.Base.Char (GHC.Base.unpackCString# "Zot") Test.y end Rec }
If I interpret it correctly, the compiler does approximately nothing - reasonably enough, since we didn't ask for optimization. With -O:
% ghc -ddump-simpl C.hs -O
==================== Tidy Core ==================== Rec { Test.y :: [GHC.Base.Char] [GlobalId] [Str: DmdType] Test.y = GHC.Base.unpackAppendCString# "Zot" Test.y end Rec }
Test.x :: [GHC.Base.Char] [GlobalId] [Str: DmdType] Test.x = GHC.Base.unpackCString# "FooBar"
y gets turned into an unpackAppendCString#, which I can only presume is a sensible way to represent a cyclic list, while x gets concatenated compile-time.
-- View this message in context: http://www.nabble.com/Hints-for-Euler-Problem-11-tf4114963.html#a12196104 Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.

Kim-Ee Yeoh
Aaron Denney wrote:
I find the first far more readable. The compiler should be able to assemble it all at compile time, right?
'Course not. The (++) function like all Haskell functions is only a /promise/ to do its job.
I find this comment rather strange. One of the beauties of a pure language (especially a lazy one) is that there is no requirement for evaluation to take place at at any particular time as long as it's done before it's needed. So the compile-time/run-time dichotomy is only relevant when a value depends on data only available at run-time. Given that "foo "++"bar" can be evaluated at compile time and there are advantages and no disadvantages, it should be evaluated at compile time. In general, I don't think we should clutter the language with syntax for things for which there has to be a more general mechanism; including string breaks in the language was a mistake. Compare "thing1\n\ \thing2\n\ \thing3\n"++ otherThing++ "penultimate thing\n\ \last thing\n" with "thing1\n"++ "thing2\n"++ "thing3\n"++ otherThing++ "penultimate thing\n"++ "last thing\n" What /is/ the advantage of the former? -- Jón Fairbairn Jon.Fairbairn@cl.cam.ac.uk

I wrote:
the compile-time/run-time dichotomy is only relevant when a value depends on data only available at run-time.
Something I've wanted to experiment with for a long time and never got round to is writing CAFs back to the load module at the end of a run (if they're small enough or took a long time to evaluate). Has anyone tried this? (It would have a jolly entertaining effect on benchmark pages!). The logical extension of this would be that compiling a programme did the typechecking and then just wrote the binary equivalent of 'evaluate $ code-generate "...lambda expressions from programme text..."' into the load-module. If you never run the programme, this would be quicker. If you only run the programme once, it would take about the same time, and running it several times would be quicker -- very much so if it didn't depend on any run-time data. -- Jón Fairbairn Jon.Fairbairn@cl.cam.ac.uk

If RAM was treated as an extension of non-volatile storage instead of the other way round, we'd already be there. Put another way, would "suspending" program to disk achieve the same results? Jon Fairbairn wrote:
Something I've wanted to experiment with for a long time and never got round to is writing CAFs back to the load module at the end of a run (if they're small enough or took a long time to evaluate). Has anyone tried this? (It would have a jolly entertaining effect on benchmark pages!).
The logical extension of this would be that compiling a programme did the typechecking and then just wrote the binary equivalent of 'evaluate $ code-generate "...lambda expressions from programme text..."' into the load-module. If you never run the programme, this would be quicker. If you only run the programme once, it would take about the same time, and running it several times would be quicker -- very much so if it didn't depend on any run-time data.
-- View this message in context: http://www.nabble.com/Hints-for-Euler-Problem-11-tf4114963.html#a12197690 Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.

Kim-Ee Yeoh
Jon Fairbairn wrote:
Something I've wanted to experiment with for a long time and never got round to is writing CAFs back to the load module at the end of a run (if they're small enough or took a long time to evaluate).
If RAM was treated as an extension of non-volatile storage instead of the other way round, we'd already be there.
Not exactly
Put another way, would "suspending" program to disk achieve the same results?
No, because the state in RAM includes not only CAFs but data that depends on the history of the present run. If you only write CAFs back, running the modified module gives the same effect as running the unmodified version. Resuming a suspended programme has the effect of continuing from where you left off. -- Jón Fairbairn Jon.Fairbairn@cl.cam.ac.uk
participants (9)
-
Aaron Denney
-
Jon Fairbairn
-
Ketil Malde
-
Kim-Ee Yeoh
-
Lennart Augustsson
-
Mathias Biilmann Christensen
-
Pekka Karjalainen
-
ronguida@mindspring.com
-
Tim Chevalier