Choosing a function randomly...

Hi, This is kind-of related to my earlier question on looking up functions by name. Suppose I have a module with a number of functions with the same signature: scale :: Int -> Int -> Int scale s x = s * x add :: Int -> Int -> Int add a x = a + x ... I'd like to choose and run one of these functions randomly at run time. I can see I could use some kind of case expression: op :: Int -> Int -> Int op p x = case random(1,2) of 1 -> scale p x 2 -> add p x Or some kind of pattern guards: op p x | random(1,2) == 1 = scale p x | otherwise = add p x Although that method won't work as is for more than two choices. Are these methods the most idiomatic way of randomly choosing a function? How hard would it be to use the machinery of the QuickCheck library for this, given it must be doing something similar in test suites? Thanks, Stu

Stuart Hungerford
This is kind-of related to my earlier question on looking up functions by name. Suppose I have a module with a number of functions with the same signature:
[...]
I'd like to choose and run one of these functions randomly at run time. [...]
Again the lookup approach seems most reasonable. The cleanest way is to define a simple name type for your functions: data FuncIx = FuncA | FuncB deriving (Ord) instance Random FuncIx where ... funcA :: A -> B funcB :: A -> B funcs :: Map FuncIx (A -> B) funcs = M.fromList (zip [FuncA, FuncB] [funcA, funcB]) If you want to go for maximum speed instead: import qualified Data.Vector as V type FuncIx = Int ... funcs :: V.Vector (A -> B) funcs = V.fromList [funcA, funcB] randFunc :: (RandomGen g) => g -> (A -> B, g) randFunc = first (funcs V.!) . randomR (0, 1) Greets, Ertugrul -- nightmare = unsafePerformIO (getWrongWife >>= sex) http://ertes.de/

Why not just construct a list of the functions, and randomly select an
element from the list?
Tom
On May 20, 2012 5:14 AM, "Ertugrul Söylemez"
Stuart Hungerford
wrote: This is kind-of related to my earlier question on looking up functions by name. Suppose I have a module with a number of functions with the same signature:
[...]
I'd like to choose and run one of these functions randomly at run time. [...]
Again the lookup approach seems most reasonable. The cleanest way is to define a simple name type for your functions:
data FuncIx = FuncA | FuncB deriving (Ord)
instance Random FuncIx where ...
funcA :: A -> B funcB :: A -> B
funcs :: Map FuncIx (A -> B) funcs = M.fromList (zip [FuncA, FuncB] [funcA, funcB])
If you want to go for maximum speed instead:
import qualified Data.Vector as V
type FuncIx = Int
...
funcs :: V.Vector (A -> B) funcs = V.fromList [funcA, funcB]
randFunc :: (RandomGen g) => g -> (A -> B, g) randFunc = first (funcs V.!) . randomR (0, 1)
Greets, Ertugrul
-- nightmare = unsafePerformIO (getWrongWife >>= sex) http://ertes.de/
_______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners

I think the MonadRandom package has a elegant solution for your problem: fromList :: MonadRandomhttp://hackage.haskell.org/packages/archive/MonadRandom/0.1.6/doc/html/Contr...m => [(a, Rationalhttp://hackage.haskell.org/packages/archive/base/4.4.1.0/doc/html/Prelude.ht...)] -> m a Example: fromList [(add, 1), (scale, 1), (rareFunction, 0.1)] On Sun, May 20, 2012 at 8:42 AM, Stuart Hungerford < stuart.hungerford@gmail.com> wrote:
Hi,
This is kind-of related to my earlier question on looking up functions by name. Suppose I have a module with a number of functions with the same signature:
scale :: Int -> Int -> Int
scale s x = s * x
add :: Int -> Int -> Int
add a x = a + x
...
I'd like to choose and run one of these functions randomly at run time. I can see I could use some kind of case expression:
op :: Int -> Int -> Int
op p x = case random(1,2) of 1 -> scale p x 2 -> add p x
Or some kind of pattern guards:
op p x | random(1,2) == 1 = scale p x | otherwise = add p x
Although that method won't work as is for more than two choices. Are these methods the most idiomatic way of randomly choosing a function? How hard would it be to use the machinery of the QuickCheck library for this, given it must be doing something similar in test suites?
Thanks,
Stu
_______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners
participants (4)
-
edgar klerks
-
Ertugrul Söylemez
-
Stuart Hungerford
-
Tom Murphy