[Haskell-cafe] Random Numbers for the beginner ?

Stefan Holdermans sholderm at students.cs.uu.nl
Tue Jul 6 15:20:47 EDT 2004


Crypt Master,

  CM> I have tried I swear, even googled for 45 minutes, but I
  CM> cant seem to get random numbers working.
  CM> 
  CM> In the documentation is has:
  CM> 
  CM> rollDice :: IO Int
  CM> rollDice = getStdRandom (randomR (1,6))
  CM> 
  CM> But if I type "getStdRandom (randomR (1,6))" into hugs
  CM> in the context of module which imports Random, I get get
  CM> errors.
  CM> 
  CM> ERROR - Unresolved overloading
  CM> *** Type       : (Random a, Num a) => IO a
  CM> *** Expression : getStdRandom (randomR (1,6))

Use

  (getStdRandom (randomR (1,6))) :: IO Int 

instead.

\begin{code}
module Main where
import Random


main :: IO ()
main =  do n <- (getStdRandom (randomR (1,6))) :: IO Int
         ; print n
\end{code}

Explanation. The compiler/interpreter knows your expressing is producing a
value of type IO a. It also knows a is an instance of Num. But it just does
not have enough information to resolve the exact type a. So, you have to
help the compiler/interpreter a little and provide the information it needs
through explicit type signatures or annotations.

HTH,

Stefan




More information about the Haskell-Cafe mailing list