
Heinrich Apfelmus wrote:
Jon Fairbairn wrote:
Heinrich Apfelmus writes:
The answer is a resounding "yes" and the main idea is that shuffling a list is *essentially the same* as sorting a list; the minor difference being that the former chooses a permutation at random while the latter chooses a very particular permutation, namely the one that sorts the input.
For the full exposition, see
http://apfelmus.nfshost.com/random-permutations.html I haven't been following the thread, but my initial reaction would have been something like use System.Random.randoms to get a list rs and then do (roughly)
randomPerm = map snd . sortBy (compare `on` fst) . zip rs
How bad is that? I mean, how unfair does it get?
It's fair, but may duplicate elements, i.e. it doesn't necessarily create a permutation. For example, rs could be something like
rs = [5,3,3,3,2,4]
How about using random doubles? randomPerm xs = fmap (map snd . sort . flip zip xs) rs where rs = fmap (randoms . mkStdGen) randomIO :: IO [Double]


Paul Johnson
I should have read that first time round! -- Jón Fairbairn Jon.Fairbairn@cl.cam.ac.uk http://www.chaos.org.uk/~jf/Stuff-I-dont-want.html (updated 2009-01-31)

Hi all, This is my first post in this forum, I'm pretty new to Haskell (although I have some previous experience in functional programming with OCaml). I'm trying to write the typical function that determines if a list is a palindrome. The typical answer would be something like: isPalindrome xs = xs == (reverse xs) But I find this pretty inefficient (duplication of the list and double of needed comparisons). So I tried my own version using just indexes: isPalindrome xs = isPalindrome' 0 (length xs) where isPalindrome' i j = if i == j -- line 43 then True else if (xs !! i) == (xs !! (j-1)) then isPalindrome' (i+1) (j-1) else False But, when trying to load this in ghci it throws the following error: xxx.hs:43:12: parse error (possibly incorrect indentation) Failed, modules loaded: none. (Line 43 is marked in the code) I seems that the definition of isPalindrome' must be in one line. So, this works as expected: isPalindrome xs = isPalindrome' 0 (length xs) where isPalindrome' i j = if i == j then True else if (xs !! i) == (xs !! (j-1)) then isPalindrome' (i+1) (j-1) else False Is there any way to make the local definition of isPalindrome' more readable? Any help in understanding this would be appreciated Thanks in advance, M;

Here's one solution:isPalindrome xs =
isPalindrome' 0 (length xs)
where isPalindrome' i j = if i == j then True else check i j
check i j = if (xs !! i) == (xs !! (j-1)) then recurse i j
else False
recurse i j = isPalindrome' (i+1) (j-1)
On Mon, Feb 16, 2009 at 10:32 AM, Miguel Pignatelli wrote: Hi all,
This is my first post in this forum, I'm pretty new to Haskell (although I
have some previous experience in functional programming with OCaml). I'm trying to write the typical function that determines if a list is a
palindrome.
The typical answer would be something like: isPalindrome xs = xs == (reverse xs) But I find this pretty inefficient (duplication of the list and double of
needed comparisons).
So I tried my own version using just indexes: isPalindrome xs =
isPalindrome' 0 (length xs)
where isPalindrome' i j =
if i == j -- line 43
then True
else
if (xs !! i) == (xs !! (j-1))
then isPalindrome' (i+1) (j-1)
else False But, when trying to load this in ghci it throws the following error: xxx.hs:43:12: parse error (possibly incorrect indentation)
Failed, modules loaded: none.
(Line 43 is marked in the code) I seems that the definition of isPalindrome' must be in one line. So,
this works as expected: isPalindrome xs =
isPalindrome' 0 (length xs)
where isPalindrome' i j = if i == j then True else if (xs !! i) ==
(xs !! (j-1)) then isPalindrome' (i+1) (j-1) else False Is there any way to make the local definition of isPalindrome' more
readable? Any help in understanding this would be appreciated Thanks in advance, M; _______________________________________________
Beginners mailing list
Beginners@haskell.org
http://www.haskell.org/mailman/listinfo/beginners

Am Montag, 16. Februar 2009 16:32 schrieb Miguel Pignatelli:
Hi all,
This is my first post in this forum, I'm pretty new to Haskell (although I have some previous experience in functional programming with OCaml).
I'm trying to write the typical function that determines if a list is a palindrome. The typical answer would be something like:
isPalindrome xs = xs == (reverse xs)
But I find this pretty inefficient (duplication of the list and double of needed comparisons). So I tried my own version using just indexes:
isPalindrome xs = isPalindrome' 0 (length xs) where isPalindrome' i j = if i == j -- line 43 then True else if (xs !! i) == (xs !! (j-1)) then isPalindrome' (i+1) (j-1) else False
But, when trying to load this in ghci it throws the following error:
xxx.hs:43:12: parse error (possibly incorrect indentation) Failed, modules loaded: none. (Line 43 is marked in the code)
I seems that the definition of isPalindrome' must be in one line. So, this works as expected:
isPalindrome xs = isPalindrome' 0 (length xs) where isPalindrome' i j = if i == j then True else if (xs !! i) == (xs !! (j-1)) then isPalindrome' (i+1) (j-1) else False
Is there any way to make the local definition of isPalindrome' more readable?
Yes, it would be horrible to look at Haskell code if there weren't. The problem is that originally, the code for isPalindrome' was indented less than the function name. Specifically, the first relevant token (i.e. not whitespace or comments) after the keywords do, let, where, case ... of opens up a new scope, which lasts until something is indented less or equally far. To not suffer from e-mailing programmes behaviour regarding leading spaces on a line, I replace those with '°', then a more readable formatting of your code would be isPalindrome xs = isPalindrome' 0 (length xs) °°°where °°°°°°isPalindrome' i j °°°°°°°°°| j <= i = True °°°°°°°°°| xs !! i /= xs !! (j-1) = False °°°°°°°°°| otherwise = isPalindrome (i+1) (j-1) I have replaced your nested ifs by guards (increases readability, IMO) and corrected the stopping condition so that it also works on words of odd length. However, note that Haskell lists aren't arrays, but singly linked lists, so to find xs !! k, all the first (k+1) cells of the list must be visited, making your algorithm less efficient than the naive one, since you must visit O((length xs)^2) cells.
Any help in understanding this would be appreciated
Thanks in advance,
M;
Cheers, Daniel

Nice! Thanks a lot for the explanation. (and to the others that have replied!) M; El 16/02/2009, a las 17:05, Daniel Fischer escribió:
Am Montag, 16. Februar 2009 16:32 schrieb Miguel Pignatelli:
Hi all,
This is my first post in this forum, I'm pretty new to Haskell (although I have some previous experience in functional programming with OCaml).
I'm trying to write the typical function that determines if a list is a palindrome. The typical answer would be something like:
isPalindrome xs = xs == (reverse xs)
But I find this pretty inefficient (duplication of the list and double of needed comparisons). So I tried my own version using just indexes:
isPalindrome xs = isPalindrome' 0 (length xs) where isPalindrome' i j = if i == j -- line 43 then True else if (xs !! i) == (xs !! (j-1)) then isPalindrome' (i+1) (j-1) else False
But, when trying to load this in ghci it throws the following error:
xxx.hs:43:12: parse error (possibly incorrect indentation) Failed, modules loaded: none. (Line 43 is marked in the code)
I seems that the definition of isPalindrome' must be in one line. So, this works as expected:
isPalindrome xs = isPalindrome' 0 (length xs) where isPalindrome' i j = if i == j then True else if (xs !! i) == (xs !! (j-1)) then isPalindrome' (i+1) (j-1) else False
Is there any way to make the local definition of isPalindrome' more readable?
Yes, it would be horrible to look at Haskell code if there weren't. The problem is that originally, the code for isPalindrome' was indented less than the function name. Specifically, the first relevant token (i.e. not whitespace or comments) after the keywords do, let, where, case ... of opens up a new scope, which lasts until something is indented less or equally far. To not suffer from e-mailing programmes behaviour regarding leading spaces on a line, I replace those with '°', then a more readable formatting of your code would be
isPalindrome xs = isPalindrome' 0 (length xs) °°°where °°°°°°isPalindrome' i j °°°°°°°°°| j <= i = True °°°°°°°°°| xs !! i /= xs !! (j-1) = False °°°°°°°°°| otherwise = isPalindrome (i+1) (j-1)
I have replaced your nested ifs by guards (increases readability, IMO) and corrected the stopping condition so that it also works on words of odd length.
However, note that Haskell lists aren't arrays, but singly linked lists, so to find xs !! k, all the first (k+1) cells of the list must be visited, making your algorithm less efficient than the naive one, since you must visit O((length xs)^2) cells.
Any help in understanding this would be appreciated
Thanks in advance,
M;
Cheers, Daniel

Dear all:
Do we really have better method than this version (if list is used as the
data structure):
isPalindrome xs = xs == (reverse xs)?
Since we need to get the last xs, we already has to visit all the elements,
so nothing can be saved.
To avoid the double comparisons, maybe we will use:
let l = length xs / 2 in
take l x == take l $ reverse xs
But the length function added one more extra iteration.
We could write our own reverse function to obtain the length in the same
time with reversing. But the gain is not large enough to justify the
optimization in my opinion.
Best Regards,
Cheng Wei
On Tue, Feb 17, 2009 at 7:24 AM, Miguel Pignatelli
Nice! Thanks a lot for the explanation. (and to the others that have replied!)
M;
El 16/02/2009, a las 17:05, Daniel Fischer escribió:
Am Montag, 16. Februar 2009 16:32 schrieb Miguel Pignatelli:
Hi all,
This is my first post in this forum, I'm pretty new to Haskell (although I have some previous experience in functional programming with OCaml).
I'm trying to write the typical function that determines if a list is a palindrome. The typical answer would be something like:
isPalindrome xs = xs == (reverse xs)
But I find this pretty inefficient (duplication of the list and double of needed comparisons). So I tried my own version using just indexes:
isPalindrome xs = isPalindrome' 0 (length xs) where isPalindrome' i j = if i == j -- line 43 then True else if (xs !! i) == (xs !! (j-1)) then isPalindrome' (i+1) (j-1) else False
But, when trying to load this in ghci it throws the following error:
xxx.hs:43:12: parse error (possibly incorrect indentation) Failed, modules loaded: none. (Line 43 is marked in the code)
I seems that the definition of isPalindrome' must be in one line. So, this works as expected:
isPalindrome xs = isPalindrome' 0 (length xs) where isPalindrome' i j = if i == j then True else if (xs !! i) == (xs !! (j-1)) then isPalindrome' (i+1) (j-1) else False
Is there any way to make the local definition of isPalindrome' more readable?
Yes, it would be horrible to look at Haskell code if there weren't. The problem is that originally, the code for isPalindrome' was indented less than the function name. Specifically, the first relevant token (i.e. not whitespace or comments) after the keywords do, let, where, case ... of opens up a new scope, which lasts until something is indented less or equally far. To not suffer from e-mailing programmes behaviour regarding leading spaces on a line, I replace those with '°', then a more readable formatting of your code would be
isPalindrome xs = isPalindrome' 0 (length xs) °°°where °°°°°°isPalindrome' i j °°°°°°°°°| j <= i = True °°°°°°°°°| xs !! i /= xs !! (j-1) = False °°°°°°°°°| otherwise = isPalindrome (i+1) (j-1)
I have replaced your nested ifs by guards (increases readability, IMO) and corrected the stopping condition so that it also works on words of odd length.
However, note that Haskell lists aren't arrays, but singly linked lists, so to find xs !! k, all the first (k+1) cells of the list must be visited, making your algorithm less efficient than the naive one, since you must visit O((length xs)^2) cells.
Any help in understanding this would be appreciated
Thanks in advance,
M;
Cheers, Daniel
_______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners

Daniel Fischer wrote:
isPalindrome xs = isPalindrome' 0 (length xs) °°°where °°°°°°isPalindrome' i j °°°°°°°°°| j <= i = True °°°°°°°°°| xs !! i /= xs !! (j-1) = False °°°°°°°°°| otherwise = isPalindrome (i+1) (j-1)
I only want to point out, that it is possible to put "where" ("do" or "let") at the end of the previous line, but a separate line for "where" is a good idea, too.
I have replaced your nested ifs by guards (increases readability, IMO) and corrected the stopping condition so that it also works on words of odd length.
Instead of course I prefer boolean expressions in some cases: isPalindrome xs = isPalindrome' 0 (length xs) where isPalindrome' i j = j <= i || xs !! i == xs !! (j-1) && isPalindrome' (i+1) (j-1)
However, note that Haskell lists aren't arrays, but singly linked lists, so to find xs !! k, all the first (k+1) cells of the list must be visited, making your algorithm less efficient than the naive one, since you must visit O((length xs)^2) cells.
Right, and only computing the length takes n steps, which is hard to avoid when one wants to avoid double equality tests. isPalindrome xs = and $ zipWith (==) xs $ reverse $ drop (div (length xs + 1) 2) xs Cheers Christian

Alberto Ruiz wrote:
How about using random doubles?
randomPerm xs = fmap (map snd . sort . flip zip xs) rs where rs = fmap (randoms . mkStdGen) randomIO :: IO [Double]
Interesting idea. The chance of duplicates should be negligible now, but that's because we're using a large amount of random bits, far more than n! would require. Regards, apfelmus -- http://apfelmus.nfshost.com

Heinrich Apfelmus wrote:
Alberto Ruiz wrote:
How about using random doubles?
randomPerm xs = fmap (map snd . sort . flip zip xs) rs where rs = fmap (randoms . mkStdGen) randomIO :: IO [Double]
Interesting idea. The chance of duplicates should be negligible now, but that's because we're using a large amount of random bits, far more than n! would require.
Another possibility is using infinite lists of random bits as keys. Then we only extract from the random number generator the number of bits required to avoid duplicates. -Alberto
participants (9)
-
Alberto Ruiz
-
Andrew Wagner
-
ChengWei
-
Christian Maeder
-
Daniel Fischer
-
Heinrich Apfelmus
-
Jon Fairbairn
-
Miguel Pignatelli
-
Paul Johnson