I wrote a function to generate two random numbers, which I then pass to a different function to use them there. The code for this is:
randomIntInRange :: (Int, Int, Int, Int) -> Board
randomIntInRange (min,max,min2,max2) = do r <- randomRIO (min, max)
r2 <- randomRIO (min2, max2)
randomCherryPosition (r, r2)
And the function this function calls in its 'do' block is:
randomCherryPosition :: (Int, Int) -> Board
randomCherryPosition (x, y) = initialBoard & element y . element x .~ C
Where initialBoard is a list of lists and C is a predefined data type. I am using lens to change values inside the list. Running this gives me the error:
Couldn't match type ‘IO’ with ‘[]’
Expected type: [Int]
Actual type: IO Int
for both r and r2 lines. I have absolutely no idea what is going on here, or what i'm doing wrong, so I would greatly appreciate any help.
randomRIO has type IO Int, not Int. As long as you use any IO functions, your surrounding function must also be in IO:
randomIntInRange :: (Int, Int, Int, Int) -> IO Board
randomIntInRange (min,max,min2,max2) = do r <- randomRIO (min, max)
r2 <- randomRIO (min2, max2)
pure $ randomCherryPosition (r, r2)
randomRIO is not a pure function. It returns a different value every time. Haskell bans such functions. There are numerous benefits that come from banning such functions, which I'm going to go into here. But you can still have such function if you wrap it in IO. The type IO Int means "it's a program that, when executed, will produce an Int". So when you call randomRIO (min, max), it returns you not an Int, but a program, which you can then execute to get an Int. You do the execution via the do notation with left arrow, but the result of that would also be a similar program.
Unfortunately there is no perfect solution to this problem. It has already been discussed on Stackoverflow, for example here.
The above solution provided by Fyodor involves IO. It works. The main drawback is that IO will propagate into your type system.
However, it is not strictly necessary to involve IO just because you want to use random numbers. An in-depth discussion of the pros and cons involved is available there.
There is no perfect solution, because something has to take care of updating the state of the random number generator every time you pick a random value. In imperative languages such as C/C++/Fortran, we use side effects for this. But Haskell functions have no side effects. So that something can be:
the Haskell IO subsystem (as in randomRIO)
yourself as the programmer - see code sample #1 below
a more specialized Haskell subsystem, for which you need to have: import Control.Monad.Random - see code sample #2 below
You can solve the problem without involving IO by creating your own random number generator, using library function mkStdGen, and then passing the updated states of this generator manually around your computations. In your problem, this gives something like this:
-- code sample #1
import System.Random
-- just for type check:
data Board = Board [(Int, Int)] deriving Show
initialBoard :: Board
initialBoard = Board [(0, 0)]
randomCherryPosition :: (Int, Int) -> Board
randomCherryPosition (x, y) = -- just for type check
let ls0 = (\(Board ls) -> ls) initialBoard
ls1 = (x, y) : ls0
in Board ls1
-- initial version with IO:
randomIntInRange :: (Int, Int, Int, Int) -> IO Board
randomIntInRange (min,max, min2,max2) = do r1 <- randomRIO (min, max)
r2 <- randomRIO (min2, max2)
return $ randomCherryPosition (r1, r2)
-- version with manual passing of state:
randomIntInRangeA :: RandomGen tg => (Int, Int, Int, Int) -> tg -> (Board, tg)
randomIntInRangeA (min1,max1, min2,max2) rng0 =
let (r1, rng1) = randomR (min1, max1) rng0
(r2, rng2) = randomR (min2, max2) rng1 -- pass the newer RNG
board = randomCherryPosition (r1, r2)
in (board, rng2)
main = do
-- get a random number generator:
let mySeed = 54321 -- actually better to pass seed from the command line.
let rng0 = mkStdGen mySeed
let (board1, rng) = randomIntInRangeA (0,10, 0,100) rng0
putStrLn $ show board1
This is cumbersome but can be made to work.
A more elegant alternative consists in using MonadRandom.
The idea is to define a monadic action representing the randomness-involving computation, and then to run this action using the aptly named runRand function.
This gives this code instead:
-- code sample #2
import System.Random
import Control.Monad.Random
-- just for type check:
data Board = Board [(Int, Int)] deriving Show
initialBoard :: Board
initialBoard = Board [(0, 0)]
-- just for type check:
randomCherryPosition :: (Int, Int) -> Board
randomCherryPosition (x, y) =
let ls0 = (\(Board ls) -> ls) initialBoard
ls1 = (x, y) : ls0
in Board ls1
-- monadic version of randomIntInRange:
randomIntInRangeB :: RandomGen tg => (Int, Int, Int, Int) -> Rand tg Board
randomIntInRangeB (min1,max1, min2,max2) =
do
r1 <- getRandomR (min1,max1)
r2 <- getRandomR (min2,max2)
return $ randomCherryPosition (r1, r2)
main = do
-- get a random number generator:
let mySeed = 54321 -- actually better to pass seed from the command line.
let rng0 = mkStdGen mySeed
-- create and run the monadic action:
let action = randomIntInRangeB (0,10, 0,100) -- of type: Rand tg Board
let (board1, rng) = runRand action rng0
putStrLn $ show board1
This is definitely less error prone than code sample #1, so you would typically prefer this solution as soon as your computations become complex enough. All the functions involved are ordinary pure Haskell functions, which the compiler can fully optimize using its usual techniques.
Related
I am trying to get a good grasp of the State-Monad (and Monads in general) but I am struggling with rewriting the below function using the state Monad and the do-notation, which resulted as an exercise for me propose here
import Control.Monad
import System.Random
import Data.Complex
import qualified System.Random as R
import Control.Monad.Trans.State.Lazy
giveRandomElement :: [a] -> State R.StdGen a
giveRandomElement lst = do
let n = length lst
rand <- state $ randomR (0, n-1)
return $ lst !! rand
random_response_monad :: a -> [a] -> State R.StdGen a
random_response_monad true_answer answers = do
tal <- state $ randomR (0, 1) :: StateT StdGen Data.Functor.Identity.Identity a
if (tal == 0) then true_answer
else giveRandomElement answers
As is immediately obvious there are some type problems for the tal-variable as it occurs in the if-clause and the first line of the do-expression. As is visible from the code I have tried to force the latter by a specific type in order to make it unambiguous and clearer for myself as well. I have done so by the compiler-suggestion I got when I first tried to force it to be of the Int-type. I Am however not able to use that value in an if-statement, and I am unsure of how to convert or unpack the value such that I get it as an Int.
So far I have tried to add the folloowing line after tal <- ... , resp <- get $ tal but I get this output.
error:
* Couldn't match expected type: t0
-> StateT StdGen Data.Functor.Identity.Identity a1
with actual type: StateT s0 m0 s0
* The first argument of ($) takes one value argument,
but its type `StateT s0 m0 s0' has none
In a stmt of a 'do' block: resp <- get $ tal
In the expression:
do tal <- state $ randomR (0, 1)
resp <- get $ tal
if (resp == 0) then
giveRandomElement answers
else
giveRandomElement answers
* Relevant bindings include tal :: t0
Furthermore I am baffled what would be the best way to 'print' the result returned by giveRandomElement as the type is based on the type declared for the State-monad which as I understand it doesn't use the deriving Show also. But this can perhaps be solved by unpacking the value as enquired about above.
EDIT
I used the above packages although they are probably not all used in the above code. I am unsure of which is used by the code by I suspect the qualified System.Random as R
The following code line:
tal <- state $ randomR (0, 1) :: StateT StdGen Data.Functor.Identity.Identity a
is quite long and might cause a horizontal slider to appear, at least on my platform.
So it is all too easy to overlook that at its very end, the a type variable is used, while it should be just Int.
Also, the two branches of the if construct use different types, making the construct ill-typed. The then branch gives a pure a value, while the else branch gives a monadic value. This is easily fixed by changing to:
if (tal == 0) then return true_answer
as the (slightly misnamed) return library function wraps its argument into the monad at hand.
The following code, which tries to keep code lines short enough, seems to work fine:
import Control.Monad.State
import qualified System.Random as R
import qualified Data.Functor.Identity as DFI
giveRandomElement :: [a] -> State R.StdGen a
giveRandomElement lst = do
let n = length lst
rand <- state $ R.randomR (0, n-1)
return $ lst !! rand
type ActionType = StateT R.StdGen DFI.Identity Int
random_response_monad :: a -> [a] -> State R.StdGen a
random_response_monad true_answer answers = do
tal <- (state $ R.randomR (0, 1) :: ActionType)
if (tal == 0) then return true_answer
else giveRandomElement answers
main :: IO ()
main = do
let g0 = R.mkStdGen 4243
action = random_response_monad 20 [0..9]
(k, g1) = runState action g0
putStrLn $ "k is set to: " ++ (show k)
Side note: the code can also be made to compile without the complex type annotation, like this:
tal <- state $ R.randomR (0::Int, 1)
Something like this seems to work:
random_response_monad :: a -> [a] -> State R.StdGen a
random_response_monad true_answer answers = do
tal <- state $ randomR (0 :: Int, 1)
if (tal == 0) then return true_answer
else giveRandomElement answers
Two changes:
Use a type annotation to tell the compiler what you mean by 0 and 1. Once you've told the compiler which type 0 is, it follows that 1 has the same type. (Keep in mind that in Haskell, numbers are polymorphic. Without more information, Haskell will see a literal such as 0 as potentially any Num instance.)
return in front of true_answer.
Here's a few samples from GHCi that seems to indicate that it works:
ghci> evalState (random_response_monad 42 [0..9]) <$> newStdGen
4
ghci> evalState (random_response_monad 42 [0..9]) <$> newStdGen
1
ghci> evalState (random_response_monad 42 [0..9]) <$> newStdGen
42
I am trying to solve arithmetic problems with SBV.
For example
solution :: SymbolicT IO ()
solution = do
[x, y] <- sFloats ["x", "y"]
constrain $ x + y .<= 2
Main> s1 = sat solution
Main> s2 = isSatisfiable solution
Main> s1
Satisfiable. Model:
x = -1.2030502e-17 :: Float
z = -2.2888208e-37 :: Float
Main> :t s1
s1 :: IO SatResult
Main> s2
True
Main> :t s2
s2 :: IO Bool
While I can do useful things, it is easier for me to work with the pure value (SatResult or Bool) and not with the IO monad.
According to the documentation
sat :: Provable a => a -> IO SatResult
constrain :: SolverContext m => SBool -> m ()
sFloats :: [String] -> Symbolic [SFloat]
type Symbolic = SymbolicT IO
Given the type of functions I use, I understand why I always get to the IO monad.
But looking in the generalized versions of the functions for example sFloats.
sFloats :: MonadSymbolic m => [String] -> m [SFloat]
Depending on type of the function, I can work with a different monad than IO. This gives me hope that we will reach a more useful monad, the Identity monad for example.
Unfortunately looking at the examples always solves the problems within the IO monad, so I couldn't find any examples that would work for me.Besides that I don't have much experience working with monads.
Finally My question is:
Is there any way to avoid the IO monad when solving such a problem with SBV?
Thanks in advance
SBV calls out to the SMT solver of your choice (most likely z3, but others are available too), and presents the results back to you. This means that it performs IO under the hood, and thus you cannot be outside the IO monad. You can create custom monads using MonadSymbolic, but that will not get you out of the IO monad: Since the call to the SMT solver does IO you'll always be in IO.
(And I'd strongly caution against uses of unsafePerformIO as suggested in one of the comments. This is really a bad idea; and you can find lots more information on this elsewhere why you shouldn't do so.)
Note that this is no different than any other IO based computation in Haskell: You perform the IO "in-the-wrapper," but once you get your results, you can do whatever you'd like to do with them in a "pure" environment.
Here's a simple example:
import Data.SBV
import Data.SBV.Control
example :: IO ()
example = runSMT $ do
[x, y] <- sFloats ["x", "y"]
constrain $ x + y .<= 2
query $ do cs <- checkSat
case cs of
Unsat -> io $ putStrLn "Unsatisfiable"
Sat -> do xv <- getValue x
yv <- getValue y
let result = use xv yv
io $ putStrLn $ "Result: " ++ show result
_ -> error $ "Solver said: " ++ show cs
-- Use the results from the solver, in a purely functional way
use :: Float -> Float -> Float
use x y = x + y
Now you can say:
*Main> example
Result: -Infinity
The function example has type IO (), because it does involve calling out to the solver and getting the results. However, once you extract those results (via calls to getValue), you can pass them to the function use which has a very simple purely functional type. So, you keep the "wrapper" in the monad, but actual processing, use-of-the values, etc., remain in the pure world.
Alternatively, you can also extract the values and continue from there:
import Data.SBV
import Data.SBV.Control
example :: IO (Maybe (Float, Float))
example = runSMT $ do
[x, y] <- sFloats ["x", "y"]
constrain $ x + y .<= 2
query $ do cs <- checkSat
case cs of
Unsat -> pure Nothing
Sat -> do xv <- getValue x
yv <- getValue y
pure $ Just (xv, yv)
_ -> error $ "Solver said: " ++ show cs
Now you can say:
*Main> Just (a, b) <- example
*Main> a
-Infinity
*Main> b
4.0302105e-21
Long story short: Don't avoid the IO monad. It's there for a very good reason. Get into it, get your results out, and then the rest of your program can remain purely functional, or whatever other monad you might find yourself in.
Note that none of this is really SBV specific. This is the usual Haskell paradigm of how to use functions with side-effects. (For instance, anytime you use readFile to read the contents of a file to process it further.) Do not try to "get rid of the IO." Instead, simply work with it.
Depending on type of the function, I can work with a different monad than IO.
Not meaningfully different, in the sense you'd hope. Every instance of this class is going to be some transformed version of IO. Sorry!
Time to make a plan that involves understanding and working with IO.
I'm writing a program that should be able to simulate many instances of trying the martingale betting system with roulette. I would like main to take an argument giving the number of tests to perform, perform the test that many times, and then print the number of wins divided by the total number of tests. My problem is that instead of ending up with a list of Bool that I could filter over to count successes, I have a list of IO Bool and I don't understand how I can filter over that.
Here's the source code:
-- file: Martingale.hs
-- a program to simulate the martingale doubling system
import System.Random (randomR, newStdGen, StdGen)
import System.Environment (getArgs)
red = [1,3,5,7,9,12,14,16,18,19,21,23,25,27,30,32,34,36]
martingale :: IO StdGen -> IO Bool
martingale ioGen = do
gen <- ioGen
return $ martingale' 1 0 gen
martingale' :: Real a => a -> a -> StdGen -> Bool
martingale' bet acc gen
| acc >= 5 = True
| acc <= -100 = False
| otherwise = do
let (randNumber, newGen) = randomR (0,37) gen :: (Int, StdGen)
if randNumber `elem` red
then martingale' 1 (acc + bet) newGen
else martingale' (bet * 2) (acc - bet) newGen
main :: IO ()
main = do
args <- getArgs
let iters = read $ head args
gens = replicate iters newStdGen
results = map martingale gens
--results = map (<-) results
print "THIS IS A STUB"
Like I have in my comments, I basically want to map (<-) over my list of IO Bool, but as I understand it, (<-) isn't actually a function but a keyword. Any help would be greatly appreciated.
map martingale gens will give you something of type [IO Bool]. You can then use sequence to unpack it:
sequence :: Monad m => [m a] -> m [a]
A more natural alternative is to use mapM directly:
mapM :: Monad m => (a -> m b) -> [a] -> m [b]
i.e. you can write
results <- mapM martingale gens
Note - even after doing it this way, your code feels a bit unnatural. I can see some advantages to the structure, in particular because martingale' is a pure function. However having something of type IO StdGen -> IO Bool seems a bit odd.
I can see a couple of ways to improve it:
make martingale' return an IO type itself and push the newStdGen call all the way down into it
make gens use replicateM rather than replicate
You may want to head over to http://codereview.stackexchange.com for more comprehensive feedback.
This question already has answers here:
Random number in Haskell [duplicate]
(5 answers)
Closed 8 years ago.
I am in the process of learning Haskell and to learn I want to generate a random Int type. I am confused because the following code works. Basically, I want an Int not an IO Int.
In ghci this works:
Prelude> import System.Random
Prelude System.Random> foo <- getStdRandom (randomR (1,1000000))
Prelude System.Random> fromIntegral foo :: Int
734077
Prelude System.Random> let bar = fromIntegral foo :: Int
Prelude System.Random> bar
734077
Prelude System.Random> :t bar
bar :: Int
So when I try to wrap this up with do it fails and I don't understand why.
randomInt = do
tmp <- getStdRandom (randomR (1,1000000))
fromIntegral tmp :: Int
The compiler produces the following:
Couldn't match expected type `IO b0' with actual type `Int'
In a stmt of a 'do' block: fromIntegral tmp :: Int
In the expression:
do { tmp <- getStdRandom (randomR (1, 1000000));
fromIntegral tmp :: Int }
In an equation for `randomInt':
randomInt
= do { tmp <- getStdRandom (randomR (1, 1000000));
fromIntegral tmp :: Int }
Failed, modules loaded: none.
I am new to Haskell, so if there is a better way to generate a random Int without do that would be preferred.
So my question is, why does my function not work and is there a better way to get a random Int.
The simple answer is that you can't generate random numbers without invoking some amount of IO. Whenever you get the standard generator, you have to interact with the host operating system and it makes a new seed. Because of this, there is non-determinism with any function that generates random numbers (the function returns different values for the same inputs). It would be like wanting to be able to get input from STDIN from the user without it being in the IO monad.
Instead, you have a few options. You can write all your code that depends on a randomly generated value as pure functions and only perform the IO to get the standard generator in main or some similar function, or you can use the MonadRandom package that gives you a pre-built monad for managing random values. Since most every pure function in System.Random takes a generator and returns a tuple containing the random value and a new generator, the Rand monad abstracts this pattern out so that you don't have to worry about it. You can end up writing code like
import Control.Monad.Random hiding (Random)
type Random a = Rand StdGen a
rollDie :: Int -> Random Int
rollDie n = getRandomR (1, n)
d6 :: Random Int
d6 = rollDie 6
d20 :: Random Int
d20 = rollDie 20
magicMissile :: Random (Maybe Int)
magicMissile = do
roll <- d20
if roll > 15
then do
damage1 <- d6
damage2 <- d6
return $ Just (damage1 + damage2)
else return Nothing
main :: IO ()
main = do
putStrLn "I'm going to cast Magic Missile!"
result <- evalRandIO magicMissile
case result of
Nothing -> putStrLn "Spell fizzled"
Just d -> putStrLn $ "You did " ++ show d ++ " damage!"
There's also an accompanying monad transformer, but I'd hold off on that until you have a good grasp on monads themselves. Compare this code to using System.Random:
rollDie :: Int -> StdGen -> (Int, StdGen)
rollDie n g = randomR (1, n) g
d6 :: StdGen -> (Int, StdGen)
d6 = rollDie 6
d20 :: StdGen -> (Int, StdGen)
d20 = rollDie 20
magicMissile :: StdGen -> (Maybe Int, StdGen)
magicMissile g =
let (roll, g1) = d20 g
(damage1, g2) = d6 g1
(damage2, g3) = d6 g2
in if roll > 15
then (Just $ damage1 + damage2, g3)
else Nothing
main :: IO ()
main = do
putStrLn "I'm going to case Magic Missile!"
g <- getStdGen
let (result, g1) = magicMissile g
case result of
Nothing -> putStrLn "Spell fizzled"
Just d -> putStrLn $ "You did " ++ show d ++ " damage!"
Here we have to manually have to manage the state of the generator and we don't get the handy do-notation that makes our order of execution more clear (laziness helps in the second case, but it makes it more confusing). Manually managing this state is boring, tedious, and error prone. The Rand monad makes everything much easier, more clear, and reduces the chance for bugs. This is usually the preferred way to do random number generation in Haskell.
It is worth mentioning that you can actually "unwrap" an IO a value to just an a value, but you should not use this unless you are 100% sure you know what you're doing. There is a function called unsafePerformIO, and as the name suggests it is not safe to use. It exists in Haskell mainly for when you are interfacing with the FFI, such as with a C DLL. Any foreign function is presumed to perform IO by default, but if you know with absolute certainty that the function you're calling has no side effects, then it's safe to use unsafePerformIO. Any other time is just a bad idea, it can lead to some really strange behaviors in your code that are virtually impossible to track down.
I think the above is slightly misleading. If you use the state monad then you can do something like this:
acceptOrRejects :: Int -> Int -> [Double]
acceptOrRejects seed nIters =
evalState (replicateM nIters (sample stdUniform))
(pureMT $ fromIntegral seed)
See here for an extended example of usage:Markov Chain Monte Carlo
I need to read some amount of bits from Get monad. Now my code looks like
readBits :: Int -> Int -> Get (Word32, Int)
readBits count state = ...
readValue :: Get (Word32, Word32)
readValue = do
-- read fst bit count
(bits1, s0) <- readBits 5 0
-- read bits1 bits as fst
(fst, s1) <- readBits bits1 s0
-- read snd bit count
(bits2, s2) <- readBits 5 s1
-- read bits2 bits as snd
(snd, s3) <- readBits bits2 s2
-- flush incomplete byte
when (s3 /= 0) $ skip 1
return (fst, snd)
I want to wrap this into some kind of state monad, to have code like
readBits :: Int -> BitReader Word32
readBits count = ...
runBitReader :: BitReader a -> Get a
readValue :: Get (Word32, Word32)
readValue = runBitReader $ do
bits1 <- readBits 5
fst <- readBits bits1
bits2 <- readBits 5
snd <- readBits bits2
return (fst, snd)
What functions should I implement? How should they be implemented?
I have looked into Get and BitGet source code, but not fully understand what's going on.
This is the most typical usecase for Monad Transformers.
You have defined most of the structure correctly. To answer your questions
What functions should I implement?
Well you first need to wrap Get monad into the StateT Transformer to get BitReader.
You need to implement proper definition for readBits using get to get the current state and put to save the state back.
You need to run your code wrapped in BitReader to get back the output in Get Monad. So you need to define runBitReader using runStateT.
To answer your next question.
How should they be implemented?
I have given the possible implementation. You still need to define some functions to make it work.
import Control.Monad.State
import qualified Control.Monad.State as ST
import Data.Binary
type BitReader = StateT Int Get
readBits' :: Int -> Int -> Get (Word32, Int)
readBits' = undefined
readBits :: Int -> BitReader Word32
readBits n = do
s0 <- ST.get
(a,s1) <- lift $ readBits' n s0
ST.put s1
return a
runBitReader :: BitReader a -> Get a
runBitReader w = do
(a,s) <- runStateT w 0
return a
readValue = do
fst <- readBits 5
snd <- readBits 10
return (fst, snd)
I don't know how looking into code of Get was going to help you. You were looking in the wrong house. You need to read about State Monads and Monad Transformers.
You can read more about monad transformers here.