warning - Euler problem spoiler enclosed

Hi, In the following solution to problem 24, why is nub ignored? I.e. if you do lexOrder of "0012," you get twice as many permutations as with "012," even though I have used nub. puzzled, Bar -- file Euler.hs module Euler where import Data.List {- problem 24 A permutation is an ordered arrangement of objects. For example, 3124 is one possible permutation of the digits 1, 2, 3 and 4. If all of the permutations are listed numerically or alphabetically, we call it lexicographic order. The lexicographic permutations of 0, 1 and 2 are: 012 021 102 120 201 210 What is the millionth lexicographic permutation of the digits 0, 1, 2, 3, 4, 5, 6, 7, 8 and 9? -} lexI :: Char -> String -> Int lexI c s = maybe 1 (id) $ elemIndex c s lexOrder :: [Char] -> [[Char]] lexOrder s | length s == 1 = [s] | length s == 2 = z : [reverse z] | otherwise = concat $ map (\n -> h n) [0..((length s) - 1)] where z = sort $ nub s -- why is the nub ignored here? h :: Int -> [String] h n = map (z!!n :) $ lexOrder $ filter (\c -> lexI c z /= n) z p24 = (lexOrder "1234567890")!!999999 main :: IO() main = do putStrLn $ show $ p24

On Wed, 2011-05-04 at 07:13 -0600, Barbara Shirtcliff wrote:
In the following solution to problem 24, why is nub ignored? I.e. if you do lexOrder of "0012," you get twice as many permutations as with "012," even though I have used nub.
lexOrder :: [Char] -> [[Char]] lexOrder s | length s == 1 = [s] | length s == 2 = z : [reverse z] | otherwise = concat $ map (\n -> h n) [0..((length s) - 1)] where z = sort $ nub s -- why is the nub ignored here? h :: Int -> [String] h n = map (z!!n :) $ lexOrder $ filter (\c -> lexI c z /= n) z
You are using (length s) in the otherwise case. If you want the results to be identical with duplicates, perhaps you meant to say (length z)? -- Chris

On 4 May 2011 13:13, Barbara Shirtcliff
Hi,
In the following solution to problem 24, why is nub ignored? I.e. if you do lexOrder of "0012," you get twice as many permutations as with "012," even though I have used nub.
[snip]
lexOrder :: [Char] -> [[Char]] lexOrder s | length s == 1 = [s] | length s == 2 = z : [reverse z] | otherwise = concat $ map (\n -> h n) [0..((length s) - 1)] where z = sort $ nub s -- why is the nub ignored here? h :: Int -> [String] h n = map (z!!n :) $ lexOrder $ filter (\c -> lexI c z /= n) z
As a guess, I think it's from the usage of length on the right-hand size. Also, note that "lexOrder s@[_] = [s]" is nicer than "lexOrder s | length s == 1 = [s]". -- Ivan Lazar Miljenovic Ivan.Miljenovic@gmail.com IvanMiljenovic.wordpress.com

Ah, thanks! On May 4, 2011, at 7:21 AM, Ivan Lazar Miljenovic wrote:
On 4 May 2011 13:13, Barbara Shirtcliff
wrote: Hi,
In the following solution to problem 24, why is nub ignored? I.e. if you do lexOrder of "0012," you get twice as many permutations as with "012," even though I have used nub.
[snip]
lexOrder :: [Char] -> [[Char]] lexOrder s | length s == 1 = [s] | length s == 2 = z : [reverse z] | otherwise = concat $ map (\n -> h n) [0..((length s) - 1)] where z = sort $ nub s -- why is the nub ignored here? h :: Int -> [String] h n = map (z!!n :) $ lexOrder $ filter (\c -> lexI c z /= n) z
As a guess, I think it's from the usage of length on the right-hand size.
Also, note that "lexOrder s@[_] = [s]" is nicer than "lexOrder s | length s == 1 = [s]".
-- Ivan Lazar Miljenovic Ivan.Miljenovic@gmail.com IvanMiljenovic.wordpress.com

On May 4, 2011, at 7:21 AM, Ivan Lazar Miljenovic wrote:
On 4 May 2011 13:13, Barbara Shirtcliff
wrote: Hi,
In the following solution to problem 24, why is nub ignored? I.e. if you do lexOrder of "0012," you get twice as many permutations as with "012," even though I have used nub.
[snip]
lexOrder :: [Char] -> [[Char]] lexOrder s | length s == 1 = [s] | length s == 2 = z : [reverse z] | otherwise = concat $ map (\n -> h n) [0..((length s) - 1)] where z = sort $ nub s -- why is the nub ignored here? h :: Int -> [String] h n = map (z!!n :) $ lexOrder $ filter (\c -> lexI c z /= n) z
As a guess, I think it's from the usage of length on the right-hand size.
Also, note that "lexOrder s@[_] = [s]" is nicer than "lexOrder s | length s == 1 = [s]".
I agree that that initial version was a little clumsy, but your suggestion doesn't really seem to work: lexOrder :: [Char] -> [[Char]] lexOrder s@[_] = s lexOrder s = concat $ map (\n -> h n) [0..((length z) - 1)] where z = sort $ nub s h :: Int -> [String] h n = map (z!!n :) $ lexOrder $ filter (\c -> lexI c z /= n) z Euler.hs:8:18: Couldn't match expected type `[Char]' with actual type `Char' Expected type: [[Char]] Actual type: [Char] In the expression: s In an equation for `lexOrder': lexOrder s@[_] = s

Barbara Shirtcliff
Also, note that "lexOrder s@[_] = [s]" is nicer than "lexOrder s | length s == 1 = [s]".
I agree that that initial version was a little clumsy, but your suggestion doesn't really seem to work:
lexOrder :: [Char] -> [[Char]] lexOrder s@[_] = s lexOrder s = concat $ map (\n -> h n) [0..((length z) - 1)] where z = sort $ nub s h :: Int -> [String] h n = map (z!!n :) $ lexOrder $ filter (\c -> lexI c z /= n) z
Euler.hs:8:18: Couldn't match expected type `[Char]' with actual type `Char' Expected type: [[Char]] Actual type: [Char] In the expression: s In an equation for `lexOrder': lexOrder s@[_] = s
It actually works, you have forgotten square brackets: "lexOrder s@[_] = [s] --not s!".

On May 4, 2011, at 9:18 AM, Artyom Kazak wrote:
Barbara Shirtcliff
писал(а) в своём письме Wed, 04 May 2011 16:41:07 +0300: Also, note that "lexOrder s@[_] = [s]" is nicer than "lexOrder s | length s == 1 = [s]".
I agree that that initial version was a little clumsy, but your suggestion doesn't really seem to work:
lexOrder :: [Char] -> [[Char]] lexOrder s@[_] = s lexOrder s = concat $ map (\n -> h n) [0..((length z) - 1)] where z = sort $ nub s h :: Int -> [String] h n = map (z!!n :) $ lexOrder $ filter (\c -> lexI c z /= n) z
Euler.hs:8:18: Couldn't match expected type `[Char]' with actual type `Char' Expected type: [[Char]] Actual type: [Char] In the expression: s In an equation for `lexOrder': lexOrder s@[_] = s
It actually works, you have forgotten square brackets: "lexOrder s@[_] = [s] --not s!".
Прабда! Спасибо---- Б

The problem is lexOrder s@[_] = s where you just give back what you receive, i.e. [Char]. But you claim to give back [[Char]]. Try [s] on the right-hand side. On 05/04/2011 02:41 PM, Barbara Shirtcliff wrote:
On May 4, 2011, at 7:21 AM, Ivan Lazar Miljenovic wrote:
On 4 May 2011 13:13, Barbara Shirtcliff
wrote: Hi,
In the following solution to problem 24, why is nub ignored? I.e. if you do lexOrder of "0012," you get twice as many permutations as with "012," even though I have used nub.
[snip]
lexOrder :: [Char] -> [[Char]] lexOrder s | length s == 1 = [s] | length s == 2 = z : [reverse z] | otherwise = concat $ map (\n -> h n) [0..((length s) - 1)] where z = sort $ nub s -- why is the nub ignored here? h :: Int -> [String] h n = map (z!!n :) $ lexOrder $ filter (\c -> lexI c z /= n) z As a guess, I think it's from the usage of length on the right-hand size.
Also, note that "lexOrder s@[_] = [s]" is nicer than "lexOrder s | length s == 1 = [s]". I agree that that initial version was a little clumsy, but your suggestion doesn't really seem to work:
lexOrder :: [Char] -> [[Char]] lexOrder s@[_] = s lexOrder s = concat $ map (\n -> h n) [0..((length z) - 1)] where z = sort $ nub s h :: Int -> [String] h n = map (z!!n :) $ lexOrder $ filter (\c -> lexI c z /= n) z
Euler.hs:8:18: Couldn't match expected type `[Char]' with actual type `Char' Expected type: [[Char]] Actual type: [Char] In the expression: s In an equation for `lexOrder': lexOrder s@[_] = s
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

On Wednesday 04 May 2011 15:13:07, Barbara Shirtcliff wrote:
Hi,
In the following solution to problem 24, why is nub ignored?
It isn't: *LexOrder> lexOrder "00" ["0","0"] *LexOrder> lexOrder "001" ["01","10","*** Exception: Prelude.(!!): index too large
lexI :: Char -> String -> Int lexI c s = maybe 1 (id) $ elemIndex c s
lexOrder :: [Char] -> [[Char]] lexOrder s
| length s == 1 = [s] | length s == 2 = z : [reverse z] | otherwise = concat $ map (\n -> h n) [0..((length s) - 1)]
where z = sort $ nub s -- why is the nub ignored here? h :: Int -> [String] h n = map (z!!n :) $ lexOrder $ filter (\c -> lexI c z /= n) z
Your problem is (well, the one I see immediately) that you check for the length of s, where you should check for the length of z.
participants (6)
-
Artyom Kazak
-
Barbara Shirtcliff
-
Chris Smith
-
Daniel Fischer
-
Ivan Lazar Miljenovic
-
Tobias Schoofs