
{- 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