
Hello all, I tried to solve Problem 24 (https://projecteuler.net/problem=24) and came up with the following solution: import Data.List.Ordered import Data.Char elems = [0,1,2,3,4,5,6,7,8,9] :: [Int] x = do a <- elems b <- elems `without` [a] c <- elems `without` [a,b] d <- elems `without` [a,b,c] e <- elems `without` [a,b,c,d] f <- elems `without` [a,b,c,d,e] g <- elems `without` [a,b,c,d,e,f] h <- elems `without` [a,b,c,d,e,f,g] i <- elems `without` [a,b,c,d,e,f,g,h] j <- elems `without` [a,b,c,d,e,f,g,h,i] return [a,b,c,d,e,f,g,h,i,j] without a b = minus a ( sort b) solution = filter isDigit $ show $ (x !! 1000001) -- "2783915640" PE tells me that this is wrong, and I peeked the correct answer, which is 2783915460 (the 4 and 6 are swapped). So I tried to find out where the correct answer is in my list x and added y = filter (\(x,y) -> x == "2783915460") $ zip (map (filter isDigit . show) x) [1..] -- [("2783915460",1000000)] How can that be? "solution" tells me that the millionth element is "2783915640" but "y" tells me that "2783915460" is at the millionth position? I just cannot see it.

For what it is worth, I'm getting the same answer as you are.
head $ drop (1000000-1) $ sort $ Data.List.permutations [0..9] [2,7,8,3,9,1,5,4,6,0]
(sort $ Data.List.permutations [0..9]) !! (1000000-1) [2,7,8,3,9,1,5,4,6,0]
I guess either euler is wrong or we are both crazy.
On Wed, May 21, 2014 at 4:09 PM, martin
Hello all,
I tried to solve Problem 24 (https://projecteuler.net/problem=24) and came up with the following solution:
import Data.List.Ordered import Data.Char
elems = [0,1,2,3,4,5,6,7,8,9] :: [Int]
x = do a <- elems b <- elems `without` [a] c <- elems `without` [a,b] d <- elems `without` [a,b,c] e <- elems `without` [a,b,c,d] f <- elems `without` [a,b,c,d,e] g <- elems `without` [a,b,c,d,e,f] h <- elems `without` [a,b,c,d,e,f,g] i <- elems `without` [a,b,c,d,e,f,g,h] j <- elems `without` [a,b,c,d,e,f,g,h,i] return [a,b,c,d,e,f,g,h,i,j]
without a b = minus a ( sort b)
solution = filter isDigit $ show $ (x !! 1000001) -- "2783915640"
PE tells me that this is wrong, and I peeked the correct answer, which is 2783915460 (the 4 and 6 are swapped). So I tried to find out where the correct answer is in my list x and added
y = filter (\(x,y) -> x == "2783915460") $ zip (map (filter isDigit . show) x) [1..] -- [("2783915460",1000000)]
How can that be? "solution" tells me that the millionth element is "2783915640" but "y" tells me that "2783915460" is at the millionth position? I just cannot see it.
_______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners

Err actually I guess I got the euler answer, I guess I don't understand
your solution without the "minus" function definition.
On Wed, May 21, 2014 at 5:10 PM, David McBride
For what it is worth, I'm getting the same answer as you are.
head $ drop (1000000-1) $ sort $ Data.List.permutations [0..9] [2,7,8,3,9,1,5,4,6,0]
(sort $ Data.List.permutations [0..9]) !! (1000000-1) [2,7,8,3,9,1,5,4,6,0]
I guess either euler is wrong or we are both crazy.
On Wed, May 21, 2014 at 4:09 PM, martin
wrote: Hello all,
I tried to solve Problem 24 (https://projecteuler.net/problem=24) and came up with the following solution:
import Data.List.Ordered import Data.Char
elems = [0,1,2,3,4,5,6,7,8,9] :: [Int]
x = do a <- elems b <- elems `without` [a] c <- elems `without` [a,b] d <- elems `without` [a,b,c] e <- elems `without` [a,b,c,d] f <- elems `without` [a,b,c,d,e] g <- elems `without` [a,b,c,d,e,f] h <- elems `without` [a,b,c,d,e,f,g] i <- elems `without` [a,b,c,d,e,f,g,h] j <- elems `without` [a,b,c,d,e,f,g,h,i] return [a,b,c,d,e,f,g,h,i,j]
without a b = minus a ( sort b)
solution = filter isDigit $ show $ (x !! 1000001) -- "2783915640"
PE tells me that this is wrong, and I peeked the correct answer, which is 2783915460 (the 4 and 6 are swapped). So I tried to find out where the correct answer is in my list x and added
y = filter (\(x,y) -> x == "2783915460") $ zip (map (filter isDigit . show) x) [1..] -- [("2783915460",1000000)]
How can that be? "solution" tells me that the millionth element is "2783915640" but "y" tells me that "2783915460" is at the millionth position? I just cannot see it.
_______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners

Am 05/21/2014 11:14 PM, schrieb David McBride:
Err actually I guess I got the euler answer, I guess I don't understand your solution without the "minus" function definition.
"minus" is from Data.List.Ordered. It it like the standard set operation "minus" when both lists are ordered.
On Wed, May 21, 2014 at 5:10 PM, David McBride
mailto:toad3k@gmail.com> wrote: For what it is worth, I'm getting the same answer as you are.
> head $ drop (1000000-1) $ sort $ Data.List.permutations [0..9] [2,7,8,3,9,1,5,4,6,0]
>(sort $ Data.List.permutations [0..9]) !! (1000000-1) [2,7,8,3,9,1,5,4,6,0]
I guess either euler is wrong or we are both crazy.
On Wed, May 21, 2014 at 4:09 PM, martin
mailto:martin.drautzburg@web.de> wrote: Hello all,
I tried to solve Problem 24 (https://projecteuler.net/problem=24) and came up with the following solution:
import Data.List.Ordered import Data.Char
elems = [0,1,2,3,4,5,6,7,8,9] :: [Int]
x = do a <- elems b <- elems `without` [a] c <- elems `without` [a,b] d <- elems `without` [a,b,c] e <- elems `without` [a,b,c,d] f <- elems `without` [a,b,c,d,e] g <- elems `without` [a,b,c,d,e,f] h <- elems `without` [a,b,c,d,e,f,g] i <- elems `without` [a,b,c,d,e,f,g,h] j <- elems `without` [a,b,c,d,e,f,g,h,i] return [a,b,c,d,e,f,g,h,i,j]
without a b = minus a ( sort b)
solution = filter isDigit $ show $ (x !! 1000001) -- "2783915640"
PE tells me that this is wrong, and I peeked the correct answer, which is 2783915460 (the 4 and 6 are swapped). So I tried to find out where the correct answer is in my list x and added
y = filter (\(x,y) -> x == "2783915460") $ zip (map (filter isDigit . show) x) [1..] -- [("2783915460",1000000)]
How can that be? "solution" tells me that the millionth element is "2783915640" but "y" tells me that "2783915460" is at the millionth position? I just cannot see it.
_______________________________________________ Beginners mailing list Beginners@haskell.org mailto:Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners
_______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners

{- Hi Martin, I must say, I don't follow your solution. Are you
generating all the permutations according to lexicographic order and
then choosing the one millionth one? Is there any particular reason
why you're using a monad? For what it's worth here's how I solved the
problem. -}
nthPerm :: Ord a => Int -> [a] -> Maybe [a]
-- This wrapper function just tests for cases
-- where the arguments don't make sense.
nthPerm m cs
| m < 1
|| null cs
|| product [1 .. length cs] < m
|| nub cs /= cs
= Nothing
| otherwise
= Just (nthPerm' (m - 1) (sort cs))
nthPerm' :: Ord a => Int -> [a] -> [a]
-- This function calculates the solution for arguments that make sense.
-- Interpret the first argument as: the number of permutations, in
-- lexicographic order, that come BEFORE the one you want. So if you
-- wanted the 10-th permutation, the argument would be 9.
-- The second argument is the list of elements. It's assumed to be non
-- empty, contain no duplicates, and be sorted.
nthPerm' 0 cs = cs
nthPerm' m cs =
let -- Number of elements that are permuted:
n = length cs
-- Number of permutations for lists with one element less than n:
d = product [1 .. n - 1]
-- Express m, the number of permutations before the one we want
-- in this form: m = b * d + r, where 0 < r < d. This will tell
-- us which "branch" our permutation is in. See "diagram" below.
b = div m d
r = rem m d
-- Take out the element in the list that corresponds to the
-- correct "branch".
c = cs !! b
in -- The correct permutation = c : the correct sub-permutation
-- of the original list with element c removed.
c : nthPerm' r (delete c cs)
-- Diagram: The permutations of [0 .. 9] can be expressed as:
--
-- P [0 .. 9] = map (0 :) $ P (delete 0 [0 .. 9]) -- branch 0
-- ++ map (1 :) $ P (delete 1 [0 .. 9]) -- branch 1
-- ++ map (2 :) $ P (delete 2 [0 .. 9]) -- branch 2
-- .
-- .
-- .
-- ++ map (9 :) $ P (delete 9 [0 .. 9]) -- branch 9
On 5/22/14, martin
Am 05/21/2014 11:14 PM, schrieb David McBride:
Err actually I guess I got the euler answer, I guess I don't understand your solution without the "minus" function definition.
"minus" is from Data.List.Ordered. It it like the standard set operation "minus" when both lists are ordered.
On Wed, May 21, 2014 at 5:10 PM, David McBride
mailto:toad3k@gmail.com> wrote: For what it is worth, I'm getting the same answer as you are.
> head $ drop (1000000-1) $ sort $ Data.List.permutations [0..9] [2,7,8,3,9,1,5,4,6,0]
>(sort $ Data.List.permutations [0..9]) !! (1000000-1) [2,7,8,3,9,1,5,4,6,0]
I guess either euler is wrong or we are both crazy.
On Wed, May 21, 2014 at 4:09 PM, martin
mailto:martin.drautzburg@web.de> wrote: Hello all,
I tried to solve Problem 24 (https://projecteuler.net/problem=24) and came up with the following solution:
import Data.List.Ordered import Data.Char
elems = [0,1,2,3,4,5,6,7,8,9] :: [Int]
x = do a <- elems b <- elems `without` [a] c <- elems `without` [a,b] d <- elems `without` [a,b,c] e <- elems `without` [a,b,c,d] f <- elems `without` [a,b,c,d,e] g <- elems `without` [a,b,c,d,e,f] h <- elems `without` [a,b,c,d,e,f,g] i <- elems `without` [a,b,c,d,e,f,g,h] j <- elems `without` [a,b,c,d,e,f,g,h,i] return [a,b,c,d,e,f,g,h,i,j]
without a b = minus a ( sort b)
solution = filter isDigit $ show $ (x !! 1000001) -- "2783915640"
PE tells me that this is wrong, and I peeked the correct answer, which is 2783915460 (the 4 and 6 are swapped). So I tried to find out where the correct answer is in my list x and added
y = filter (\(x,y) -> x == "2783915460") $ zip (map (filter isDigit . show) x) [1..] -- [("2783915460",1000000)]
How can that be? "solution" tells me that the millionth element is "2783915640" but "y" tells me that "2783915460" is at the millionth position? I just cannot see it.
_______________________________________________ Beginners mailing list Beginners@haskell.org mailto:Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners
_______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners
_______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners

Hi All, Is there a way to use literate haskell with GHC using Markdown but *not* using the Bird style for the code? It seems either one uses Bird style or has to put latex style \begin{code} markup (which markdown doesn't hide) In other words, is there a way to mark up the code in Markdown in a way that GHC understands without having to preprocess the file? I just wanted to write a .lhs file in markdown like I write a .hs file today. Thanks, Dimitri

Because markdown knows about code in two ways, which differs by
implementation, I have to ask which you want to use.
Do you want to mark code by indenting it or by fencing it?
As far as I remember the documentation, fenced code blocks should be
possible where indented are not.
But how exactly I had to search again.
Am 05.06.2014 00:58 schrieb "Dimitri DeFigueiredo" : Hi All, Is there a way to use literate haskell with GHC using Markdown but *not*
using the Bird style for the code?
It seems either one uses Bird style or has to put latex style \begin{code}
markup (which markdown doesn't hide) In other words, is there a way to mark up the code in Markdown in a way
that GHC understands without having to preprocess the file? I just wanted
to write a .lhs file in markdown like I write a .hs file today. Thanks, Dimitri
_______________________________________________
Beginners mailing list
Beginners@haskell.org
http://www.haskell.org/mailman/listinfo/beginners

On Wed, Jun 04, 2014 at 04:58:27PM -0600, Dimitri DeFigueiredo wrote:
Hi All,
Is there a way to use literate haskell with GHC using Markdown but *not* using the Bird style for the code? It seems either one uses Bird style or has to put latex style \begin{code} markup (which markdown doesn't hide)
Those are the only two styles which GHC accepts.
In other words, is there a way to mark up the code in Markdown in a way that GHC understands without having to preprocess the file? I just wanted to write a .lhs file in markdown like I write a .hs file today.
If you are willing/able to use pandoc, it implements a special version of Markdown for .lhs files which understands Bird tracks. See http://johnmacfarlane.net/pandoc/README.html#pandocs-markdown -Brent

Thanks. I wanted to use the fenced version like so. ```haskell myFunction :: Int -> String -- some code goes here ``` I find that typing with the Bird style, I get lots of '>' left behind at the end of lines causing syntax problems before I compile. It also makes it harder for me to reformat the code. For example, 'unindent block' no longer works on my editor. Cheers, Dimitri Em 04/06/14 19:45, Brent Yorgey escreveu:
On Wed, Jun 04, 2014 at 04:58:27PM -0600, Dimitri DeFigueiredo wrote:
Hi All,
Is there a way to use literate haskell with GHC using Markdown but *not* using the Bird style for the code? It seems either one uses Bird style or has to put latex style \begin{code} markup (which markdown doesn't hide) Those are the only two styles which GHC accepts.
In other words, is there a way to mark up the code in Markdown in a way that GHC understands without having to preprocess the file? I just wanted to write a .lhs file in markdown like I write a .hs file today. If you are willing/able to use pandoc, it implements a special version of Markdown for .lhs files which understands Bird tracks. See
http://johnmacfarlane.net/pandoc/README.html#pandocs-markdown
-Brent _______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners

That makes sense. Perhaps you should use latex style,
then use a quick script to change the begin and end lines to
markdown fences. It would be a one-liner in bash,
or a very simple Haskell program, for example.
-Yitz
On Thu, Jun 5, 2014 at 9:53 AM, Dimitri DeFigueiredo
Thanks. I wanted to use the fenced version like so.
```haskell myFunction :: Int -> String -- some code goes here ```
I find that typing with the Bird style, I get lots of '>' left behind at the end of lines causing syntax problems before I compile. It also makes it harder for me to reformat the code. For example, 'unindent block' no longer works on my editor.
Cheers,
Dimitri
Em 04/06/14 19:45, Brent Yorgey escreveu:
On Wed, Jun 04, 2014 at 04:58:27PM -0600, Dimitri DeFigueiredo wrote:
Hi All,
Is there a way to use literate haskell with GHC using Markdown but *not* using the Bird style for the code? It seems either one uses Bird style or has to put latex style \begin{code} markup (which markdown doesn't hide)
Those are the only two styles which GHC accepts.
In other words, is there a way to mark up the code in Markdown in a way that GHC understands without having to preprocess the file? I just wanted to write a .lhs file in markdown like I write a .hs file today.
If you are willing/able to use pandoc, it implements a special version of Markdown for .lhs files which understands Bird tracks. See
http://johnmacfarlane.net/pandoc/README.html#pandocs-markdown
-Brent _______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners
_______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners

On Thu, Jun 05, 2014 at 12:53:05AM -0600, Dimitri DeFigueiredo wrote:
Thanks. I wanted to use the fenced version like so.
```haskell myFunction :: Int -> String -- some code goes here ```
OK. Unfortunately it is not possible to get GHC to recognize code in that format without some preprocessing.
I find that typing with the Bird style, I get lots of '>' left behind at the end of lines causing syntax problems before I compile. It also makes it harder for me to reformat the code. For example, 'unindent block' no longer works on my editor.
Sounds like the real issue is that you need better editor support. What editor are you using? I am just curious, I am not going to suggest that you change editors. =) -Brent
Em 04/06/14 19:45, Brent Yorgey escreveu:
On Wed, Jun 04, 2014 at 04:58:27PM -0600, Dimitri DeFigueiredo wrote:
Hi All,
Is there a way to use literate haskell with GHC using Markdown but *not* using the Bird style for the code? It seems either one uses Bird style or has to put latex style \begin{code} markup (which markdown doesn't hide) Those are the only two styles which GHC accepts.
In other words, is there a way to mark up the code in Markdown in a way that GHC understands without having to preprocess the file? I just wanted to write a .lhs file in markdown like I write a .hs file today. If you are willing/able to use pandoc, it implements a special version of Markdown for .lhs files which understands Bird tracks. See
http://johnmacfarlane.net/pandoc/README.html#pandocs-markdown
-Brent _______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners
_______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners

I'm using Sublime Text. I do like it a lot! I disagree that what I need is a better editor. What is the more popular to annotate code today: Github Markdown or Latex? The source file of a latex document is not amenable to be read as you are coding, but Markdown is. So, it helps make the code cleaner. ;-) Dimitri Em 05/06/14 10:30, Brent Yorgey escreveu:
Thanks. I wanted to use the fenced version like so.
```haskell myFunction :: Int -> String -- some code goes here ``` OK. Unfortunately it is not possible to get GHC to recognize code in
On Thu, Jun 05, 2014 at 12:53:05AM -0600, Dimitri DeFigueiredo wrote: that format without some preprocessing.
I find that typing with the Bird style, I get lots of '>' left behind at the end of lines causing syntax problems before I compile. It also makes it harder for me to reformat the code. For example, 'unindent block' no longer works on my editor. Sounds like the real issue is that you need better editor support. What editor are you using? I am just curious, I am not going to suggest that you change editors. =)
-Brent
Em 04/06/14 19:45, Brent Yorgey escreveu:
On Wed, Jun 04, 2014 at 04:58:27PM -0600, Dimitri DeFigueiredo wrote:
Hi All,
Is there a way to use literate haskell with GHC using Markdown but *not* using the Bird style for the code? It seems either one uses Bird style or has to put latex style \begin{code} markup (which markdown doesn't hide) Those are the only two styles which GHC accepts.
In other words, is there a way to mark up the code in Markdown in a way that GHC understands without having to preprocess the file? I just wanted to write a .lhs file in markdown like I write a .hs file today. If you are willing/able to use pandoc, it implements a special version of Markdown for .lhs files which understands Bird tracks. See
http://johnmacfarlane.net/pandoc/README.html#pandocs-markdown
-Brent _______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners
Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners
Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners

I didn't say you need a better editor! I said you need better *support* from your editor for writing literate Haskell code. I don't know much about Sublime Text but you might find this useful: https://bitbucket.org/wrossmck/literate-haskell-bird-style Anyway, I agree Markdown is better for annotating your code, unless you are writing a paper about it. -Brent On Thu, Jun 05, 2014 at 10:44:05AM -0600, Dimitri DeFigueiredo wrote:
I'm using Sublime Text. I do like it a lot! I disagree that what I need is a better editor. What is the more popular to annotate code today: Github Markdown or Latex? The source file of a latex document is not amenable to be read as you are coding, but Markdown is. So, it helps make the code cleaner. ;-)
Dimitri
Em 05/06/14 10:30, Brent Yorgey escreveu:
Thanks. I wanted to use the fenced version like so.
```haskell myFunction :: Int -> String -- some code goes here ``` OK. Unfortunately it is not possible to get GHC to recognize code in
On Thu, Jun 05, 2014 at 12:53:05AM -0600, Dimitri DeFigueiredo wrote: that format without some preprocessing.
I find that typing with the Bird style, I get lots of '>' left behind at the end of lines causing syntax problems before I compile. It also makes it harder for me to reformat the code. For example, 'unindent block' no longer works on my editor. Sounds like the real issue is that you need better editor support. What editor are you using? I am just curious, I am not going to suggest that you change editors. =)
-Brent
Em 04/06/14 19:45, Brent Yorgey escreveu:
On Wed, Jun 04, 2014 at 04:58:27PM -0600, Dimitri DeFigueiredo wrote:
Hi All,
Is there a way to use literate haskell with GHC using Markdown but *not* using the Bird style for the code? It seems either one uses Bird style or has to put latex style \begin{code} markup (which markdown doesn't hide) Those are the only two styles which GHC accepts.
In other words, is there a way to mark up the code in Markdown in a way that GHC understands without having to preprocess the file? I just wanted to write a .lhs file in markdown like I write a .hs file today. If you are willing/able to use pandoc, it implements a special version of Markdown for .lhs files which understands Bird tracks. See
http://johnmacfarlane.net/pandoc/README.html#pandocs-markdown
-Brent _______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners
Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners
Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners
_______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners

Thanks for the link. :-) Dimitri Em 05/06/14 11:15, Brent Yorgey escreveu:
I didn't say you need a better editor! I said you need better *support* from your editor for writing literate Haskell code. I don't know much about Sublime Text but you might find this useful:
https://bitbucket.org/wrossmck/literate-haskell-bird-style
Anyway, I agree Markdown is better for annotating your code, unless you are writing a paper about it.
-Brent
On Thu, Jun 05, 2014 at 10:44:05AM -0600, Dimitri DeFigueiredo wrote:
I'm using Sublime Text. I do like it a lot! I disagree that what I need is a better editor. What is the more popular to annotate code today: Github Markdown or Latex? The source file of a latex document is not amenable to be read as you are coding, but Markdown is. So, it helps make the code cleaner. ;-)
Dimitri
Em 05/06/14 10:30, Brent Yorgey escreveu:
Thanks. I wanted to use the fenced version like so.
```haskell myFunction :: Int -> String -- some code goes here ``` OK. Unfortunately it is not possible to get GHC to recognize code in
On Thu, Jun 05, 2014 at 12:53:05AM -0600, Dimitri DeFigueiredo wrote: that format without some preprocessing.
I find that typing with the Bird style, I get lots of '>' left behind at the end of lines causing syntax problems before I compile. It also makes it harder for me to reformat the code. For example, 'unindent block' no longer works on my editor. Sounds like the real issue is that you need better editor support. What editor are you using? I am just curious, I am not going to suggest that you change editors. =)
-Brent
Em 04/06/14 19:45, Brent Yorgey escreveu:
On Wed, Jun 04, 2014 at 04:58:27PM -0600, Dimitri DeFigueiredo wrote:
Hi All,
Is there a way to use literate haskell with GHC using Markdown but *not* using the Bird style for the code? It seems either one uses Bird style or has to put latex style \begin{code} markup (which markdown doesn't hide) Those are the only two styles which GHC accepts.
In other words, is there a way to mark up the code in Markdown in a way that GHC understands without having to preprocess the file? I just wanted to write a .lhs file in markdown like I write a .hs file today. If you are willing/able to use pandoc, it implements a special version of Markdown for .lhs files which understands Bird tracks. See
http://johnmacfarlane.net/pandoc/README.html#pandocs-markdown
-Brent _______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners
Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners
Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners
Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners
Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners

On Wednesday 21 May 2014, 22:09:24, martin wrote:
Hello all,
I tried to solve Problem 24 (https://projecteuler.net/problem=24) and came up with the following solution:
solution = filter isDigit $ show $ (x !! 1000001) -- "2783915640"
PE tells me that this is wrong,
Yes, you took the 1000002nd element. List indexing is 0-based, so the millionth element is at index (1000000 - 1), not (1000000 + 1).

Am 05/21/2014 11:18 PM, schrieb Daniel Fischer:
On Wednesday 21 May 2014, 22:09:24, martin wrote:
Hello all,
I tried to solve Problem 24 (https://projecteuler.net/problem=24) and came up with the following solution:
solution = filter isDigit $ show $ (x !! 1000001) -- "2783915640"
PE tells me that this is wrong,
Yes, you took the 1000002nd element. List indexing is 0-based, so the millionth element is at index (1000000 - 1), not (1000000 + 1).
Oops.
participants (8)
-
Brent Yorgey
-
Daniel Fischer
-
David McBride
-
Dimitri DeFigueiredo
-
Jacek Dudek
-
martin
-
Norbert Melzer
-
Yitzchak Gale