Random pattern generation with list comprehensions

I am looking for a way to generate random patterns for hardware validation. The goal is to separate patten generation from execution in hardware, and from pure code used to compute expected behavior from a model, detection of bad behavior, in the form of predicates, etc. The purpose of random patterns is to explore the behavior space in less time, as well as improve time to discovery by preventing long runs that focus in narrow areas for long periods. Patterns are to be infinite lists with the ability to specify run length for any run, which becomes a quality dial of sorts. I initially started with finite sequences expressed as list comprehensions, that generate tuples of ints, floats, structured data, and lists of attributes (bit combinations of hardware registers). I believe the list comprehension evaluates each generator (a | a <- ...) in a strict order, such that an infinite list will cause infinite evaluation of a single generator, such that other generators are not evaluated. Even if each generator is constrained (take n), results will not not be completely random. What I need is for each generator to supply one value each, and combine them into a tuple. I could probable express this in a monadic loop construct, as long as each generator is random and holds state, like the article I saw using the State Monad to generate random numbers. Or perhaps a State monad that holds multiple generators. Is there a better way to express the solution or a helpful module others use for this? Mike Sent from my iPad

Hello! It sounds like you're looking for the ParallelListComp language extension[1] Another option might be to leverage the Arbitrary typeclass in QuickCheck[2]. It has instances for tuples, so if each component of the tuple has an Arbitrary instance, you can generate the whole tuple with one invocation of "arbitrary". The CoArbitrary typeclass is also rather handy and clever, as it allows you to create random functions, as long as the arguments are instances of CoArbitrary and the result is an instance of Arbitrary. Your concept of specifying run length is very similar to QuickCheck's "size parameter". I hope that's helpful! -Michael [1] https://downloads.haskell.org/~ghc/7.8.3/docs/html/users_guide/syntax-extns.... [2] http://hackage.haskell.org/package/QuickCheck

So, with ParallelListComp, because it is basically a zip, the evaluation will take one item from each generator, where generator is the v <- generator to the right of the “|”.
The implication being that if each generator produces random data, it will not evaluate each generator one by one in a systematic order, like multi digit counting. Basically it forces evaluation of each generator for each round, which would be like multi digit number generation where each digit changes with its own algorithm.
If that is what it does, then this probably would work. I could create each generator within a State Monad, and use ParallelListComp to combine them, provided I can put a monadic operation in the comprehension.
This page https://www.haskell.org/haskellwiki/List_comprehension
seems to indicate it can't be directly done in a comprehension, which is limited to lists, and provides a do syntax alternative. I think that implies I can’t use ParallelListComp, and I would have to follow the examples on that page and zip things myself to force evaluation of each generator one by one.
The alternative might be to make a State Monad where the State is a tuple with each item holding the state for each generator. Given that the number of items is fixed by hardware, I would not have to manage arbitrary tuple sizes. Each evaluation round of State would produce a tuple, and I would have to use a looping construct to generate values.
QuickCheck is interesting, but I would prefer to draw on a simple language construct rather than take on a whole framework, unless there is no basic simple approach.
Mike
On Dec 12, 2014, at 8:16 PM, Michael Sloan
Hello!
It sounds like you're looking for the ParallelListComp language extension[1]
Another option might be to leverage the Arbitrary typeclass in QuickCheck[2]. It has instances for tuples, so if each component of the tuple has an Arbitrary instance, you can generate the whole tuple with one invocation of "arbitrary". The CoArbitrary typeclass is also rather handy and clever, as it allows you to create random functions, as long as the arguments are instances of CoArbitrary and the result is an instance of Arbitrary. Your concept of specifying run length is very similar to QuickCheck's "size parameter".
I hope that's helpful!
-Michael
[1] https://downloads.haskell.org/~ghc/7.8.3/docs/html/users_guide/syntax-extns.... [2] http://hackage.haskell.org/package/QuickCheck

There's also Monad Comprehensions. A topical recent article: https://ocharles.org.uk/blog/guest-posts/2014-12-07-list-comprehensions.html Michael Jones writes:
So, with ParallelListComp, because it is basically a zip, the evaluation will take one item from each generator, where generator is the v <- generator to the right of the “|”.
The implication being that if each generator produces random data, it will not evaluate each generator one by one in a systematic order, like multi digit counting. Basically it forces evaluation of each generator for each round, which would be like multi digit number generation where each digit changes with its own algorithm.
If that is what it does, then this probably would work. I could create each generator within a State Monad, and use ParallelListComp to combine them, provided I can put a monadic operation in the comprehension.
This page https://www.haskell.org/haskellwiki/List_comprehension
seems to indicate it can't be directly done in a comprehension, which is limited to lists, and provides a do syntax alternative. I think that implies I can’t use ParallelListComp, and I would have to follow the examples on that page and zip things myself to force evaluation of each generator one by one.
The alternative might be to make a State Monad where the State is a tuple with each item holding the state for each generator. Given that the number of items is fixed by hardware, I would not have to manage arbitrary tuple sizes. Each evaluation round of State would produce a tuple, and I would have to use a looping construct to generate values.
QuickCheck is interesting, but I would prefer to draw on a simple language construct rather than take on a whole framework, unless there is no basic simple approach.
Mike
On Dec 12, 2014, at 8:16 PM, Michael Sloan
wrote: Hello!
It sounds like you're looking for the ParallelListComp language extension[1]
Another option might be to leverage the Arbitrary typeclass in QuickCheck[2]. It has instances for tuples, so if each component of the tuple has an Arbitrary instance, you can generate the whole tuple with one invocation of "arbitrary". The CoArbitrary typeclass is also rather handy and clever, as it allows you to create random functions, as long as the arguments are instances of CoArbitrary and the result is an instance of Arbitrary. Your concept of specifying run length is very similar to QuickCheck's "size parameter".
I hope that's helpful!
-Michael
[1] https://downloads.haskell.org/~ghc/7.8.3/docs/html/users_guide/syntax-extns.... [2] http://hackage.haskell.org/package/QuickCheck
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
-- Kyle Marek-Spartz

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

Here is some prototype code, and some comments and questions.
getInts and getDoubles use the State Monad approach to generate data. getInts requires putting the generator in the list comprehension. getDouble wraps it in a function.
getLetters just directly generates ints and converts to enums.
This is in an IO monad because the final code will be in the IO monad.
Questions:
- Can anyone see any value in the StateMonad in terms of ways to exploit it?
- Is there a way to get the number of constructors in Letter rather than code the number directly as (0,2)?
- What is the impact of defining the helper functions in let vs. where?
Mike
type GeneratorState = State StdGen
getRandom :: Random a => GeneratorState a
getRandom = do
generator <- get
let (value, newGenerator) = random generator
put newGenerator
return value
data Letter = A | B | C
deriving (Eq, Enum, Show)
runRandomTest = do
let ds = [(i, d, l) | i <- getInts (mkStdGen 0)
| d <- getDoubles
| l <- getLetters ]
print $ take 5 ds
where
getInts :: StdGen -> [Int]
getInts state =
let (val, state') = runState getRandom state in
val:(getInts state')
getDoubles :: [Double]
getDoubles = getDoubles' (mkStdGen 0)
getDoubles' state =
let (val, state') = runState getRandom state in
val:(getDoubles' state')
getLetters :: [Letter]
getLetters = map toEnum $ randomRs (0,2) (mkStdGen 0)
On Dec 15, 2014, at 8:14 AM, Erik Rantapaa
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
participants (5)
-
Erik Rantapaa
-
Kyle Marek-Spartz
-
Michael Jones
-
Michael Sloan
-
Mike Jones