[Haskell-cafe] Re: Hints for Euler Problem 11

2007-08-17 Thread Jon Fairbairn
Kim-Ee Yeoh [EMAIL PROTECTED] writes:

 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 [EMAIL PROTECTED]


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: Hints for Euler Problem 11

2007-08-16 Thread Aaron Denney
On 2007-08-16, Kim-Ee Yeoh [EMAIL PROTECTED] wrote:


 Aaron Denney wrote:
 
 On 2007-08-15, Pekka Karjalainen [EMAIL PROTECTED] 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
--

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Hints for Euler Problem 11

2007-08-15 Thread 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:

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
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Hints for Euler Problem 11

2007-08-15 Thread Pekka Karjalainen
On 8/15/07, Mathias Biilmann Christensen [EMAIL PROTECTED] 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.

(The Haskell 98 Report calls them backslants.)

Pekka
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: Hints for Euler Problem 11

2007-08-15 Thread Aaron Denney
On 2007-08-15, Pekka Karjalainen [EMAIL PROTECTED] wrote:
 On 8/15/07, Mathias Biilmann Christensen [EMAIL PROTECTED] 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
--

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: Hints for Euler Problem 11

2007-07-20 Thread Dave Bayer
Ronald Guida ronguida at mindspring.com writes:

 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.

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: Hints for Euler Problem 11

2007-07-20 Thread ronguida
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

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe