[Haskell-cafe] Acquiring a random set of a specific size (w/o dups) from a range of Ints

Jonas Almström Duregård jonas.duregard at chalmers.se
Tue Jun 14 11:17:41 CEST 2011


> Shuffle [1..20], then take 5?
> Yes, so simple, I'm embarrassed I didn't think of it.

That works well for small numbers, but I'm guessing it will evaluate the
entire list so it should not be used for large inputs. If you have a large
interval and use a relatively small part of it, the following function
should be significantly faster (it builds a random permutation lazily):

import System.Random
randomOrder :: (Ord a, Num a, Random a, RandomGen g) => (a,a) -> g -> [a]
randomOrder (low,high) g
 | low > high  = []
 | otherwise   = let
   (a,g') = randomR (low,high) g
   (gl,gr) = split g'
   in a : mergeRandom (a-1-low,randomOrder (low,a-1) gl)
                      (high-a-1, randomOrder (a+1,high) gr) g'
  where
    mergeRandom (_,[]) (_,xs) _       = xs
    mergeRandom (_,xs) (_,[]) _       = xs
    mergeRandom (lx,x:xs) (ly,y:ys) g = let
      (pick,g') = randomR (1,lx + ly) g
      in if pick <= lx
        then x : mergeRandom (lx-1,xs) (ly,y:ys) g'
        else y : mergeRandom (lx,x:xs) (ly-1,ys) g'



On 14 June 2011 04:31, michael rice <nowgate at yahoo.com> wrote:

> Thanks, all.
>
> It seemed like something like this should exist in a prob/stat package, and
> if so, didn't want to reinvent the wheel.
>
> Shuffle [1..20], then take 5?
>
> Yes, so simple, I'm embarrassed I didn't think of it.
>
> Michael
>
>
>
> --- On *Mon, 6/13/11, Felipe Almeida Lessa <felipe.lessa at gmail.com>*wrote:
>
>
> From: Felipe Almeida Lessa <felipe.lessa at gmail.com>
> Subject: Re: [Haskell-cafe] Acquiring a random set of a specific size (w/o
> dups) from a range of Ints
> To: "michael rice" <nowgate at yahoo.com>
> Cc: haskell-cafe at haskell.org
> Date: Monday, June 13, 2011, 9:38 PM
>
>
> On Mon, Jun 13, 2011 at 8:56 PM, michael rice <nowgate at yahoo.com> wrote:
> > Is there an (existing) way to select 5 Ints randomly (no duplicates) from
> a population, say 1-20 (inclusive)?
>
> Yes, already implemented in the monte-carlo package as sampleSubset [1],
>
>   sampleSubset :: MonadMC m => [a] -> Int -> m [a]
>
> Complete example code for your example:
>
>   evalMC (sampleSubset [1..20] 5) (mt19937 0)
>
> Cheers!
>
> [1]
> http://hackage.haskell.org/packages/archive/monte-carlo/0.4.1/doc/html/Control-Monad-MC-Class.html#v:sampleSubset
>
> --
> Felipe.
>
>
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://www.haskell.org/pipermail/haskell-cafe/attachments/20110614/5578a9b7/attachment.htm>


More information about the Haskell-Cafe mailing list