
I'm learning Haskell and I'm trying to translate a pseudocode algorithm to generate the next permutation from a previous permutation. A permutation is a list of n numbers (let's call it a) in {1 .. n} appearing once in arbitrary order. The first step is to find the largest index j in the list for which a[j] < a[j+1]. The pseudocode is simple: j:= n-1 while a[j] > a[j+1] j:=j-1 I've coded a haskell function to do this, but it is much uglier than the pseudocode : j :: Integral a => [a] -> Int j [] = 0 j xs = if (head (tail (reverse xs)) < last xs) then (length xs)-2 else j (take (length xs - 1) xs) Does anyone has a more elegant solution for this first step?

Am Montag 08 März 2010 14:49:15 schrieb Nicolas Couture-Grenier:
I'm learning Haskell and I'm trying to translate a pseudocode algorithm to generate the next permutation from a previous permutation.
Don't try to translate it directly. In Haskell, generally a different approach than for imperative (pseudo-) code is better.
A permutation is a list of n numbers (let's call it a) in {1 .. n} appearing once in arbitrary order.
The first step is to find the largest index j in the list for which a[j] < a[j+1].
The pseudocode is simple:
j:= n-1
while a[j] > a[j+1] j:=j-1
I've coded a haskell function to do this, but it is much uglier than the pseudocode :
It's not appropriate for lists, therefore, it's ugly. You can work with arrays and have a fairly direct correspondence: import Data.Array fun :: Array Int Int -> Int fun a = go (hi-1) where (lo,hi) = bounds a go i | i < lo = i | a!i > a!(i+1) = go (i-1) | otherwise = i The local "go" is our while-loop, additionally, it checks that we don't fall off the front of the array. When working with lists, one would typically not produce the next permutation from the previous, but generate the list of all permutations (take a look at the code of "permutations" in Data.List).
j :: Integral a => [a] -> Int j [] = 0 j xs = if (head (tail (reverse xs)) < last xs) then (length xs)-2 else j (take (length xs - 1) xs)
Does anyone has a more elegant solution for this first step?

I hadn't noticed the permutation function. It's not listed in the synopis...
Nice.
Anyway, I found a better way around my little exercise.
import List
import Maybe
j :: Integral a => [a] -> Int
j xs = (fromMaybe 0 (findIndex (==False) (zipWith (<) (init xs) (tail xs))))
- 1
On Mon, Mar 8, 2010 at 9:29 AM, Daniel Fischer
Am Montag 08 März 2010 14:49:15 schrieb Nicolas Couture-Grenier:
I'm learning Haskell and I'm trying to translate a pseudocode algorithm to generate the next permutation from a previous permutation.
Don't try to translate it directly. In Haskell, generally a different approach than for imperative (pseudo-) code is better.
A permutation is a list of n numbers (let's call it a) in {1 .. n} appearing once in arbitrary order.
The first step is to find the largest index j in the list for which a[j] < a[j+1].
The pseudocode is simple:
j:= n-1
while a[j] > a[j+1] j:=j-1
I've coded a haskell function to do this, but it is much uglier than the pseudocode :
It's not appropriate for lists, therefore, it's ugly. You can work with arrays and have a fairly direct correspondence:
import Data.Array
fun :: Array Int Int -> Int fun a = go (hi-1) where (lo,hi) = bounds a go i | i < lo = i | a!i > a!(i+1) = go (i-1) | otherwise = i
The local "go" is our while-loop, additionally, it checks that we don't fall off the front of the array.
When working with lists, one would typically not produce the next permutation from the previous, but generate the list of all permutations (take a look at the code of "permutations" in Data.List).
j :: Integral a => [a] -> Int j [] = 0 j xs = if (head (tail (reverse xs)) < last xs) then (length xs)-2 else j (take (length xs - 1) xs)
Does anyone has a more elegant solution for this first step?

Daniel Fischer wrote:
When working with lists, one would typically not produce the next permutation from the previous, but generate the list of all permutations (take a look at the code of "permutations" in Data.List).
And even if you do need to use the classic "produce the next permutation from the previous" algorithm, with Haskell lists it would be more convenient to work from the beginning of the list rather than the end, if possible. That produces the permutations in "reverse dictionary" order instead of dictionary order though. In a "reverse dictionary", the words are ordered by looking at the last letter, then the previous letter, etc. Regards, Yitz

Daniel Fischer wrote:
Am Montag 08 März 2010 14:49:15 schrieb Nicolas Couture-Grenier:
I'm learning Haskell and I'm trying to translate a pseudocode algorithm to generate the next permutation from a previous permutation.
Don't try to translate it directly. In Haskell, generally a different approach than for imperative (pseudo-) code is better.
For instance, like this: -- next permutation in lexicographic order next :: Ord a => [a] -> Maybe [a] next [x] = Nothing next (x:xs) = case next xs of Nothing -> case span (> x) xs of ([],xs) -> Nothing (ys,zs) -> Just (last ys : reverse (init ys ++ x : zs)) Just xs' -> Just (x:xs') Since there is exactly one permutation that doesn't have a next one, the result has to be wrapped in a Maybe type. Of course, this is very handy and natural for the recursive formulation of the algorithm anyway. Since the above definition contains some thought™, here a helper function to test its correctness: permutationsFrom xs = xs : unfoldr (fmap (\x -> (x,x)) . next) xs correct n = let perms = permutationsFrom [1..n] in length perms == product [1..n] && sort perms == perms In other words, repeatedly applying next to the trivial permutation [1..n] should eventually yield a sorted list of all permutations. *Main> correct 8 True Regards, Heinrich Apfelmus -- http://apfelmus.nfshost.com

Nicolas Couture-Grenier
The first step is to find the largest index j in the list for which a[j] < a[j+1]. The pseudocode is simple...
The pseudo-code represents how you would write this algorithm in an imperative language. If you take the whole algorithm and express it naturally in Haskell, that would likely not be the first step at all. But in any case, I might write that version of the first step like this: j xs = maybeLast . filter snd . zip [0..] $ zipWith (<) xs (drop 1 xs) where maybeLast [] = Nothing maybeLast xs = Just (last xs) Notice my use of the Maybe type - there might not be any such index j at all. Regards, Yitz
j:= n-1
while a[j] > a[j+1] j:=j-1
I've coded a haskell function to do this, but it is much uglier than the pseudocode :
j :: Integral a => [a] -> Int j [] = 0 j xs = if (head (tail (reverse xs)) < last xs) then (length xs)-2 else j (take (length xs - 1) xs)
Does anyone has a more elegant solution for this first step?
_______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners
participants (4)
-
Daniel Fischer
-
Heinrich Apfelmus
-
Nicolas Couture-Grenier
-
Yitzchak Gale