I'm not sure what you're asking by "define type Random [Int]"? Your type Random a will allow a to be any type, e.g. [Int] is perfectly fine.

If what you're asking is how do you get from Random Int to Random [Int], the usual answer would be to use

replicateM :: Monad m => Int -> m a -> m [a]

which is formulated from

replicate :: Int -> a -> [a]

and

sequence :: Monad m => [m a] -> m [a]

of course, you're implementing Monad all over again without using the Monad typeclass, so you can't use the library functions pertaining to monads. In your case, I'd build it up the same way the library does it -- create a list of actions, and then use a function to bind all the actions together, e.g.

rolls :: Int -> [Random Int]
rolls n = replicate n rollDie

and then create something that binds them together, usually a foldr, so you could use it like this:

sequenceRandom :: [Random a] -> Random [a]
sequenceRandom = ...

rollNDice :: Int -> Random [Int]
rollNDice = sequenceRandom . rolls

-Ross


On Apr 26, 2009, at 8:45 PM, michael rice wrote:

How do I define type Random [Int] for rollNDice in Exercise 1, given the code below?

Michael

============

Exercises

1. Implement rollNDice :: Int -> Random [Int] from the previous subsection with >>= and return.

NOTE: Since >>= and return are already present in the Prelude, you may want to use import Prelude hiding ((>>=),return) to avoid compilation errors.

=================

{-# LANGUAGE NoImplicitPrelude #-}

import Prelude hiding ((>>), (>>=), return)

type Seed = Int
type Random a = Seed -> (a, Seed)

randomNext :: Seed -> Seed
randomNext rand = if newRand > 0 then newRand else newRand + 2147483647
    where newRand = 16807 * lo - 2836 * hi
          (hi,lo) = rand `divMod` 127773

rollDie :: Random Int
rollDie seed = ((seed `mod` 6) + 1, randomNext seed)

(>>) :: Random a -> Random b -> Random b
(>>) m n = \seed0 ->
  let (result1, seed1) = m seed0
      (result2, seed2) = n seed1
  in (result2, seed2)

(>>=) :: Random a -> (a -> Random b) -> Random b
(>>=) m g = \seed0 ->
  let (result1, seed1) = m seed0
      (result2, seed2) = (g result1) seed1
  in (result2, seed2)

return :: a -> Random a
return x = \seed0 -> (x, seed0)

sumTwoDice :: Random Int
sumTwoDice = rollDie >>= (\die1 -> rollDie >>= (\die2 -> return (die1 + die2)))

rollNDice :: Int -> Random [Int]


--- On Thu, 4/23/09, michael rice <nowg...@yahoo.com> wrote:

From: michael rice <nowg...@yahoo.com>
Subject: Re: [Haskell-cafe] Random number example
To: "Ross Mellgren" <rmm-hask...@z.odi.ac>
Cc: haskell-cafe@haskell.org
Date: Thursday, April 23, 2009, 5:49 PM

Hi Ross,

Thanks for going the extra mile. A lot of what you did I haven't seen before, so it's going to take me some time to go through it. But I'll be back.

Michael

--- On Thu, 4/23/09, Ross Mellgren <rmm-hask...@z.odi.ac> wrote:

From: Ross Mellgren <rmm-hask...@z.odi.ac>
Subject: Re: [Haskell-cafe] Random number example
To: "michael rice" <nowg...@yahoo.com>
Cc: haskell-cafe@haskell.org
Date: Thursday, April 23, 2009, 11:51 AM

So there are a couple problems. First is you are trying to rebind prelude functions, when instead you should be creating an instance of Monad. This requires a bit of shuffling because without language extensions you can't instance Monad Random for your type of Random, as it is a type synonym. So, changing the type synonym to a newtype and instancing monad, you get:

module Rand9b where

import Control.Applicative (Applicative(..), (<$>), (<*>))
import Control.Monad (ap, liftM)

type Seed = Int
newtype Random a = Rand { unRand :: (Seed -> (a, Seed)) }

randomNext :: Seed -> Seed
randomNext rand = if newRand > 0 then newRand else newRand + 2147483647
    where newRand = 16807 * lo - 2836 * hi
          (hi,lo) = rand `divMod` 127773

rollDie :: Random Int
rollDie = Rand $ \ seed -> ((seed `mod` 6) + 1, randomNext seed)

instance Monad Random where
    (>>=) = randomBind
    return = randomReturn

instance Functor Random where
    fmap = liftM

instance Applicative Random where
    pure = return
    (<*>) = ap

randomBind :: Random a -> (a -> Random b) -> Random b
m `randomBind` g = Rand $ \seed0 ->
  let (result1, seed1) = unRand m $ seed0
      (result2, seed2) = unRand (g result1) $ seed1
  in (result2, seed2)

randomReturn :: a -> Random a
randomReturn x = Rand $ \ seed0 -> (x, seed0)

sumTwoDice :: Random Int
sumTwoDice = (+) <$> rollDie <*> rollDie


I also threw in instances of Functor and Applicative, so that I could simplify sumTwoDice using applicative form (much nicer, no? Applicative is totally rockin')

Now you need one more thing, a way to convert a series of Random actions into a pure function:


runRandom :: Seed -> Random a -> a
runRandom s f = fst . unRand f $ s

which now makes what you want to do in GHCi easy and well wrapped:

Prelude> :reload
[1 of 1] Compiling Rand9b           ( rand9b.hs, interpreted )
Ok, modules loaded: Rand9b.
*Rand9b> runRandom 0 sumTwoDice
3


Hope this helps,
-Ross


On Apr 23, 2009, at 11:28 AM, michael rice wrote:

I pretty much followed the sequence of steps that led to this final code (see below), but will be looking it over for a while to make sure it sinks in. In the meantime, I get this when I try to use it (sumTwoDice) at the command line:

[mich...@localhost ~]$ ghci rand9
GHCi, version 6.10.1: http://www.haskell.org/ghc/  :? for help
Loading package ghc-prim ... linking ... done.
Loading package integer ... linking ... done.
Loading package base ... linking ... done.
[1 of 1] Compiling Main             ( rand9.hs, interpreted )
Ok, modules loaded: Main.
*Main> sumTwoDice

<interactive>:1:0:
    No instance for (Show (Seed -> (Int, Seed)))
      arising from a use of `print' at <interactive>:1:0-9
    Possible fix:
      add an instance declaration for (Show (Seed -> (Int, Seed)))
    In a stmt of a 'do' expression: print it
*Main>


Can I employ a 'do' expression from the command line?

Also, can I now use functions (>>) (>>=) and 'return' defined in the Prelude and still have this code work?

Michael

==================

{-# LANGUAGE NoImplicitPrelude #-}

import Prelude hiding ((>>), (>>=), return)

type Seed = Int
type Random a = Seed -> (a, Seed)

randomNext :: Seed -> Seed
randomNext rand = if newRand > 0 then newRand else newRand + 2147483647
    where newRand = 16807 * lo - 2836 * hi
          (hi,lo) = rand `divMod` 127773

rollDie :: Random Int
rollDie seed = ((seed `mod` 6) + 1, randomNext seed)

(>>) :: Random a -> Random b -> Random b
(>>) m n = \seed0 ->
  let (result1, seed1) = m seed0
      (result2, seed2) = n seed1
  in (result2, seed2)

(>>=) :: Random a -> (a -> Random b) -> Random b
(>>=) m g = \seed0 ->
  let (result1, seed1) = m seed0
      (result2, seed2) = (g result1) seed1
  in (result2, seed2)

return :: a -> Random a
return x = \seed0 -> (x, seed0)

sumTwoDice :: Random Int
sumTwoDice = rollDie >>= (\die1 -> rollDie >>= (\die2 -> return (die1 + die2)))


_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe



-----Inline Attachment Follows-----

_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe

Reply via email to