list-shuffle-1.0.0: List shuffling and sampling
Safe HaskellSafe-Inferred
LanguageHaskell2010

List.Shuffle

Description

List shuffling and sampling with optimal asymptotic time and space complexity using the imperative Fisher–Yates algorithm.

Synopsis

Shuffling

shuffle :: RandomGen g => [a] -> g -> ([a], g) Source #

\(\mathcal{O}(n)\). Shuffle a list.

shuffle_ :: RandomGen g => [a] -> g -> [a] Source #

\(\mathcal{O}(n)\). Like shuffle, but discards the final generator.

shuffleIO :: MonadIO m => [a] -> m [a] Source #

\(\mathcal{O}(n)\). Like shuffle, but uses the global random number generator.

Sampling

sample :: RandomGen g => Int -> [a] -> g -> ([a], g) Source #

\(\mathcal{O}(n)\). Sample elements of a list, without replacement.

sample_ c xs is equivalent to take c . shuffle_ xs, but with a constant factor that is proportional to c, not the length of xs.

sample_ :: RandomGen g => Int -> [a] -> g -> [a] Source #

\(\mathcal{O}(n)\). Like sample, but discards the final generator.

sampleIO :: MonadIO m => Int -> [a] -> m [a] Source #

\(\mathcal{O}(n)\). Like sample, but uses the global random number generator.

Adapting to other monads

Reader monad

You are working in a reader monad, with access to a pseudo-random number generator somewhere in the environment, in a mutable cell like an IORef or TVar:

import System.Random qualified as Random
import System.Random.Stateful qualified as Random

data MyMonad a

instance MonadIO MyMonad
instance MonadReader MyEnv MyMonad

data MyEnv = MyEnv
  { ...
  , prng :: Random.AtomicGenM Random.StdGen
  , ...
  }

In this case, you can adapt shuffle to work in your monad as follows:

import List.Shuffle qualified as List
import System.Random qualified as Random

shuffleList :: [a] -> MyMonad [a]
shuffleList list = do
  MyEnv {prng} <- ask
  Random.applyAtomicGen (List.shuffle list) prng

State monad

You are working in a state monad with access to a pseudo-random number generator somewhere in the state type. You also have a lens onto this field, which is commonly either provided by generic-lens/optics or written manually:

import System.Random qualified as Random

data MyState = MyState
  { ...
  , prng :: Random.StdGen
  , ...
  }

prngLens :: Lens' MyState Random.StdGen

In this case, you can adapt shuffle to work in your monad as follows:

import Control.Lens qualified as Lens
import Control.Monad.Trans.State.Strict qualified as State
import List.Shuffle qualified as List

shuffleList :: Monad m => [a] -> StateT MyState m [a]
shuffleList =
  Lens.zoom prngLens . State.state . List.shuffle