[Haskell-cafe] Random pattern generation with list comprehensions

Erik Rantapaa erantapaa at gmail.com
Mon Dec 15 15:14:58 UTC 2014



On Sunday, December 14, 2014 5:22:14 PM UTC-6, Michael Jones wrote:
>
> The alternative might be to make a State Monad where the State is a tuple 
> with each item holding the state for each generator. 
>

There is a common technique of using `split` and `randoms` (or `randomsR`) 
to create a pure list of random values which you might find helpful. Here 
is an example:

{-# LANGUAGE ParallelListComp #-}

import System.Random

main = do
  g <- newStdGen
  let (g1,g2) = split g
      letters = randomRs ('a','z') g1
      numbers = randomRs (15,35) g2 :: [Int]
      pairs = [ (a,n) | (a,n) <- zip letters numbers ]
      pairs2 = [ (a,n) | a <- letters | n <- numbers ]
  print $ take 10 pairs
  print $ take 10 pairs2  -- produces the same list of pairs  

-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://www.haskell.org/pipermail/haskell-cafe/attachments/20141215/09b30dc4/attachment.html>


More information about the Haskell-Cafe mailing list