
I've hammered through the bulk of my issues as I try to build a matrix that consists of random numbers, but the final hurdle is mixing pure and impure functions. Does "impurity" from something like a random number generator or file I/O have to move it's way all the way through my code? Here is the specific example. I have a function that makes a row in a matrix, it looks like this: makerow :: Int -> (Float, Float) -> IO (U.Vector Float) The IO (U.Vector Float) is the result of the random number generation that is an impure call, making this an impure result. I want to compose this into a list makerows :: Int -> Int -> (Float, Float) -> [U.Vector Float] makerows 0 _ _ = [] makerows r n range = makerow n range : makerows r' n range where r' = r - 1 But, of course, I can't mix the IO (U.Vector Float) with a U.Vector Float The compilation result in: Couldn't match expected type `U.Vector Float' with actual type `IO (U.Vector Float)' In the return type of a call of `makerow' So, at some point, I have to lift I believe … is there a simple lifting solution? It initially seemed that Monads were the solution … but liftIO resulted in the same thing … just with Monad (U.Vector Float) … There is just some "simple" Haskellism I'm missing here, but after an ginormous amount of reading and googling, it is still eluding me :( Any thoughts (besides the one page I found that helpfully … basically … said "Go back to Java" ;-) Paul Monday Parallel Scientific, LLC. paul.monday@parsci.com

On Fri, Dec 9, 2011 at 2:00 PM, Paul Monday
I've hammered through the bulk of my issues as I try to build a matrix that consists of random numbers, but the final hurdle is mixing pure and impure functions. Does "impurity" from something like a random number generator or file I/O have to move it's way all the way through my code?
Here is the specific example. I have a function that makes a row in a matrix, it looks like this: makerow :: Int -> (Float, Float) -> IO (U.Vector Float)
The IO (U.Vector Float) is the result of the random number generation that is an impure call, making this an impure result.
I want to compose this into a list makerows :: Int -> Int -> (Float, Float) -> [U.Vector Float] makerows 0 _ _ = [] makerows r n range = makerow n range : makerows r' n range where r' = r - 1
The lifting operator you're looking for is the 'return' function. A direct fix for your code given above would be: makerows 0 _ _ = return [] makerows r n range = do x <- makerow n range xs <- makerows r' n range return (x:xs) If you understand why that works, you now understand Haskell IO. Congratulations! Even better, though, is: makerows r n range = replicateM r (makerow n range) See: http://hackage.haskell.org/packages/archive/base/latest/doc/html/Control-Mon... Antoine

Does "impurity" from something like a random number generator or file I/O have to move it's way all the way through my code?
No, only through the parts that actually have to do file I/O or generate random numbers or whatever. However, cleanly separating the IO code from the non-IO/"pure" code takes some experience. It does seem to be a common experience of people learning Haskell that IO ends up "infecting" everything, even stuff that shouldn't have to do any IO, but with good design this is not necessary. In your particular case, your matrix generation function does depend on random number generation so it makes sense that its type must involve IO. However, if you go on to write other functions which do deterministic operations on matrices, their types should *not* involve IO, even if you pass randomly generated matrices to them as arguments. -Brent

I wish I'd known this when I was first beginning, but it is possible
to do randomness outside of IO, surprisingly easily. I like to use
the monadRandom library, which provides some monads and monad
transformers for this task. I too became frustrated when I wrote a
roguelike but could not figure out how to inject randomness into it
when I wanted. A program you would write might be like this:
data Obstacle = Mon (Int, Int) Monster | Door (Int, Int) | Trap (Int,
Int) deriving (Show, Enum)
data Monster = Orc | Wolf | Dragon deriving (Show, Enum)
main = do
print =<< evalRandIO randomObstacle
randomObstacle :: RandomGen g => Rand g Obstacle
randomObstacle = do
x <- getRandomR (0,2::Int)
case x of
0 -> Mon <$> randomLocation <*> randomMonster
1 -> Door <$> randomLocation
2 -> Trap <$> randomLocation
randomLocation :: RandomGen g => Rand g (Int,Int)
randomLocation = do
x <- getRandomR (0,10)
y <- getRandomR (0,10)
return (x,y)
randomMonster :: RandomGen g => Rand g Monster
randomMonster = do
x <- getRandomR (0,2::Int)
return $ case x of
0 -> Orc
1 -> Dragon
2 -> Wolf
This way, even though my randomBlah functions do not have IO in them,
nor do they pass around a stdGen around, but they can be combined
willy nilly as needed, and only computed when you want them to. I
also could have made Random instances for Obstacle and Monster so that
I did not have to do the cases in the code, making things easier to
understand.
On Fri, Dec 9, 2011 at 3:27 PM, Brent Yorgey
Does "impurity" from something like a random number generator or file I/O have to move it's way all the way through my code?
No, only through the parts that actually have to do file I/O or generate random numbers or whatever. However, cleanly separating the IO code from the non-IO/"pure" code takes some experience. It does seem to be a common experience of people learning Haskell that IO ends up "infecting" everything, even stuff that shouldn't have to do any IO, but with good design this is not necessary.
In your particular case, your matrix generation function does depend on random number generation so it makes sense that its type must involve IO. However, if you go on to write other functions which do deterministic operations on matrices, their types should *not* involve IO, even if you pass randomly generated matrices to them as arguments.
-Brent
_______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners

On Fri, Dec 09, 2011 at 05:05:15PM -0500, David McBride wrote:
randomMonster :: RandomGen g => Rand g Monster randomMonster = do x <- getRandomR (0,2::Int) return $ case x of 0 -> Orc 1 -> Dragon 2 -> Wolf
This looks like a bug to me. Everyone knows orcs are much more likely than dragons. ;) -Brent

On 12/09/2011 05:27 PM, Brent Yorgey wrote:
On Fri, Dec 09, 2011 at 05:05:15PM -0500, David McBride wrote:
randomMonster :: RandomGen g => Rand g Monster randomMonster = do x<- getRandomR (0,2::Int) return $ case x of 0 -> Orc 1 -> Dragon 2 -> Wolf
This looks like a bug to me. Everyone knows orcs are much more likely than dragons. ;)
I once wrote a function something like randomDistributed :: (Num a, RandomGen g) => [(a, b)] -> g -> (b, g) so that e.g. randomDistributed [(10, Orc), (1, Dragon), (3.7, Wolf)] would get you ten orcs for every dragon on average, the overall chance of an orc being (10 / (10 + 1 + 3.7)). ~Isaac

On Fri, 09 Dec 2011 23:05:15 +0100, David McBride
data Monster = Orc | Wolf | Dragon deriving (Show, Enum)
randomMonster :: RandomGen g => Rand g Monster randomMonster = do x <- getRandomR (0,2::Int) return $ case x of 0 -> Orc 1 -> Dragon 2 -> Wolf
You have already created an Enum instance of Monster, so why not use it: randomMonster :: RandomGen g => Rand g Monster randomMonster = do x <- getRandomR (0,2::Int) return $ toEnum x Or: randomMonster :: RandomGen g => Rand g Monster randomMonster = toEnum <$> getRandomR (0,2::Int) where <$> is imported from module Data.Functor or Control.Applicative. Regards, Henk-Jan van Tuyl -- http://Van.Tuyl.eu/ http://members.chello.nl/hjgtuyl/tourdemonad.html --

Thank you SO much for the discussion. I've learned quite a bit over the course of it. As one would expect, lifting wasn't my only issue … I had some rather annoying Unbox / Boxed / [] problems with the recursion. I stepped way back finally this morning to think about the problem and the discussion points. I was able to make use of laziness with the randomRs function. randomRs is nice since there are no side-effects, I get an "infinite" list of random numbers that can easily be broken into rows and matrices lazily. So, here is how I generated two square matrices with rows and columns = n (some other artifacts are included here as well, like the Matrix type I'm using) data Matrix a = Matrix (V.Vector (U.Vector a)) deriving (Show, Eq) makematrix :: [Float] -> Int -> Int -> [U.Vector Float] makematrix xs n 0 = [] makematrix xs n r = (U.fromList $ ys) : makematrix zs n (r - 1) where (ys, zs) = splitAt n xs main :: IO () main = do args <- getArgs let n = read (args !! 0) :: Int let minrange = read (args !! 1) :: Float let maxrange = read (args !! 2) :: Float let s = read (args !! 3) :: Int let g = mkStdGen s let range = (minrange, maxrange) let all = randomRs range g let ma = Matrix $ (V.fromList (makematrix all n n)) let mb = Matrix $ (V.fromList (makematrix (drop (n*n) all) n n)) ... As with all Haskell I'm learning, I'm 100% sure there are quite a few better ways to write this ;-) Still, again, I can't thank you enough for the thoughtful discussion on IO and randomness. I have avoided running back to Java with my tail between my legs for another day. Paul Monday Parallel Scientific, LLC. paul.monday@parsci.com On Dec 9, 2011, at 3:05 PM, David McBride wrote:
I wish I'd known this when I was first beginning, but it is possible to do randomness outside of IO, surprisingly easily. I like to use the monadRandom library, which provides some monads and monad transformers for this task. I too became frustrated when I wrote a roguelike but could not figure out how to inject randomness into it when I wanted. A program you would write might be like this:
data Obstacle = Mon (Int, Int) Monster | Door (Int, Int) | Trap (Int, Int) deriving (Show, Enum) data Monster = Orc | Wolf | Dragon deriving (Show, Enum)
main = do print =<< evalRandIO randomObstacle
randomObstacle :: RandomGen g => Rand g Obstacle randomObstacle = do x <- getRandomR (0,2::Int) case x of 0 -> Mon <$> randomLocation <*> randomMonster 1 -> Door <$> randomLocation 2 -> Trap <$> randomLocation
randomLocation :: RandomGen g => Rand g (Int,Int) randomLocation = do x <- getRandomR (0,10) y <- getRandomR (0,10) return (x,y)
randomMonster :: RandomGen g => Rand g Monster randomMonster = do x <- getRandomR (0,2::Int) return $ case x of 0 -> Orc 1 -> Dragon 2 -> Wolf
This way, even though my randomBlah functions do not have IO in them, nor do they pass around a stdGen around, but they can be combined willy nilly as needed, and only computed when you want them to. I also could have made Random instances for Obstacle and Monster so that I did not have to do the cases in the code, making things easier to understand.
On Fri, Dec 9, 2011 at 3:27 PM, Brent Yorgey
wrote: Does "impurity" from something like a random number generator or file I/O have to move it's way all the way through my code?
No, only through the parts that actually have to do file I/O or generate random numbers or whatever. However, cleanly separating the IO code from the non-IO/"pure" code takes some experience. It does seem to be a common experience of people learning Haskell that IO ends up "infecting" everything, even stuff that shouldn't have to do any IO, but with good design this is not necessary.
In your particular case, your matrix generation function does depend on random number generation so it makes sense that its type must involve IO. However, if you go on to write other functions which do deterministic operations on matrices, their types should *not* involve IO, even if you pass randomly generated matrices to them as arguments.
-Brent
_______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners
_______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners
participants (6)
-
Antoine Latter
-
Brent Yorgey
-
David McBride
-
Henk-Jan van Tuyl
-
Isaac Dupree
-
Paul Monday