1

I'm trying to make a simple random number generator in Haskell using IORef now to store mutable variables. The idea is that I can initialise the seed, and then generate numbers based on the seed, and store the new seed for the next random int.

The full error I'm getting is:

random2.hs:9:17:
    Couldn't match type `IO Int' with `Int'
    Expected type: IO (IORef Integer)
                   -> (IORef Integer -> IO Int) -> Int
      Actual type: IO (IORef Integer)
                   -> (IORef Integer -> IO Int) -> IO Int
    In a stmt of a 'do' block: seed <- newIORef 7
    In the expression:
      do { seed <- newIORef 7;
           randomGen (readIORef seed) }
    In an equation for `getRandom':
        getRandom
          = do { seed <- newIORef 7;
                 randomGen (readIORef seed) }

random2.hs:10:17:
    Couldn't match type `(,) Int' with `IO'
    Expected type: IO Int
      Actual type: (Int, Int)
    In the return type of a call of `randomGen'
    In a stmt of a 'do' block: randomGen (readIORef seed)
    In the expression:
      do { seed <- newIORef 7;
           randomGen (readIORef seed) }

random2.hs:10:28:
    Couldn't match expected type `Int' with actual type `IO Integer'
    In the return type of a call of `readIORef'
    In the first argument of `randomGen', namely `(readIORef seed)'
    In a stmt of a 'do' block: randomGen (readIORef seed)
Failed, modules loaded: none.

I don't understand how it can not be matching the type - I'm explicit that the randomGen takes/returns an Int. Here's my code:

module Main where
    import Data.IORef

    randomGen :: Int -> (Int, Int)
    randomGen x = (x,x+1)

    getRandom :: Int
    getRandom = do
        seed <- newIORef 7
        randomGen (readIORef seed)

Any idea what's going on here?

Thanks,

Updated code:

module Main where
    import Data.IORef
    import Control.Monad

    randomGen :: Int -> (Int, Int)
    randomGen x = (x,x+1)

    getRandom :: IO Int
    getRandom = do
        seed <- newIORef 7
        liftM (fst (randomGen (readIORef seed)))
Robin Green
  • 32,079
  • 16
  • 104
  • 187
Sam Heather
  • 1,493
  • 3
  • 19
  • 42
  • 1
    `randomGen` is pure but `readIORef` returns `IO a`. You're going to have use `liftM` in front of `randomGen` in the do clause. Also `getRandom :: IO Int`. Once it's IO you can't get rid of it. – dumb0 May 12 '14 at 19:55
  • @dumb0 so I added the import Control.Monad, changed the def of `getRandom :: Int` to `getRandom :: IO Int` and changed the last line from `randomGen (readIORef seed)` to `liftM (randomGen (readIORef seed))` - is this what you were describing? Because this throws another error. – Sam Heather May 12 '14 at 20:00
  • 1
    My comment has an error its : `getRandom :: IO (Int,Int)` – dumb0 May 12 '14 at 20:01
  • @dumb0 still an error - `Couldn't match expected type `IO (Int, Int)' with actual type `m0 a10 -> m0 r0' ` – Sam Heather May 12 '14 at 20:04
  • @dumb0 code updated to show what I currently have - changed getRandom to only return the random int with fst – Sam Heather May 12 '14 at 20:05
  • 1
    On what lines number is the new error? – dumb0 May 12 '14 at 20:05
  • @dumb0 3 errors, all on line 11 – Sam Heather May 12 '14 at 20:07

2 Answers2

3

The types IO Int and Int are entirely different in Haskell. This applies to any other type of that form, like Maybe Int or Either String Int. This is part of Haskell's type system design that makes it so powerful. You can think of anything in this form as a sort of container, it's parametrized over that type. Therefore you can do something like

getRandom :: IO Int
getRandom = do
    seed <- newIORef 7           -- IO (IORef Int)
    g <- readIORef seed          -- IO Int
    let (x, newG) = randomGen g  -- (Int, Int)
    writeIORef seed newG         -- IO ()
    return x                     -- IO Int

However, this will always return the same value since the seed is discarded after every call. I'm curious as to why you want to take this approach to generating random numbers at all, since there is such a nice API in the MonadRandom package. See this answer I wrote a while back for an example of how to use the Rand monad, and this answer for a bit more of an in depth explanation of how it works.

Community
  • 1
  • 1
bheklilr
  • 53,530
  • 6
  • 107
  • 163
  • I'm taking this approach because I thought I understood monads, and was told to test this by trying to write an application contained a function that I could call to get a random number based on a seed that I had initially provided (i.e. to prevent the user having to keep updating their seed). My example is obviously trivial (the random number is the seed, and the seed is just incremented). – Sam Heather May 12 '14 at 20:22
  • so is there no way I can stop the seed IORef been discarded every call, so it persists between function calls? – Sam Heather May 12 '14 at 20:29
  • I read here that there is a Global namespace, is it possible I can store the variable in here in my application? http://hackage.haskell.org/package/global-variables-1.0.1.1/docs/Data-Global.html – Sam Heather May 12 '14 at 20:30
  • @SamHeather It is, but global mutable variables in Haskell are only used as a last resort. The natural way of getting hold of something you need is always returning it from a function. If you want an exercise involving monads, I suggest you try using `State` to wrap `getRandom` and have a more convenient way of updating the seed between computations. – duplode May 12 '14 at 20:42
  • @duplode ok - let's say I did want to try storing these variables globally, how would I go about doing this? Defining them outside of a function doesn't seem to work. – Sam Heather May 12 '14 at 20:54
  • 2
    @SamHeather With the package you linked to you would use `declareIORef` at the top level, which would make the `IORef` magically available to any `IO` function in your program (I say "magically" because that package wraps around a notorious ugly hack, so that it is harder to shoot yourself in the foot with it). I insist, however, that if you want to test your understanding of monads using globals would be missing the point. Monads /= IO. – duplode May 12 '14 at 21:07
1

Try:

module Main where
import Data.IORef
import Control.Monad
import Data.Tuple(fst,snd)

randomGen :: Int -> (Int, Int)
randomGen x = (x,x+1)

getRandom :: IO Int -> IO (Int,Int)
getRandom x = do
    y <- x
    seed <- newIORef y
    liftM randomGen $ readIORef seed

At which point, use liftM fst on the output of getRandom to get the random number and liftM snd to get the seed for the next call... Oh and btw System.Random has randoms to generate an infinite list of random numbers (or anything else of Random instance). No point in reinventing the wheel.

dumb0
  • 337
  • 1
  • 8
  • awesome, this works for the above. But because it's now using liftM, I can't save the second value in the tuple right? I want to save this back to IORef so the next call to getRandom returns a different random number, but this is not possible with the current structure? Was going to do with updateIORef – Sam Heather May 12 '14 at 20:10
  • @SamHeather You can't avoid returning the seed and passing it to the next call. The `IORef` in `getRandom` is local to the function, so you have to return the seed any way, and so using the `IORef` makes your generator impure and gains you nothing. A better approach if you want to make the seed passing implicit is using the `State` monad. – duplode May 12 '14 at 20:16
  • @dumb0 I'm not trying to re-invent the wheel, only learn. I'm trying to come up with some really simple example of a stateful program in Haskell (this), but even this implementation doesn't seem stateful since everytime it runs it returns 7, never changing (incrementing) as I desired - my misunderstanding I think. Any way you can think of getting it to do this, or an idea of a different simple stateful problem I could look at? – Sam Heather May 12 '14 at 20:25
  • OK, my bad. From my limited experience of Haskell, there is no state. Once getRandom returns, it's done. If you call `getRandom` with the same value (e.g.`return 4`) then you'll get the same output. What I've done is create an output which give the random number and the seed for the next time you call `getRandom` (e.g. (1,4) where 1 is the random number and 4 the number you use when you call `getRandom` again). This simulates state in a sense. Hope that helps... – dumb0 May 12 '14 at 20:33