[Haskell-beginners] Translating a while

Nicolas Couture-Grenier greniernic at gmail.com
Mon Mar 8 09:37:08 EST 2010


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 <daniel.is.fischer at web.de>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.
>
> >
> > 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?
>
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: http://www.haskell.org/pipermail/beginners/attachments/20100308/d34126b8/attachment.html


More information about the Beginners mailing list