<table cellspacing="0" cellpadding="0" border="0" ><tr><td valign="top" style="font: inherit;">How do I define type Random [Int] for rollNDice in Exercise 1, given the code below?<br><br>Michael<br><br>============<br><br>Exercises<br><br>&nbsp;&nbsp; 1. Implement rollNDice :: Int -&gt; Random [Int] from the previous subsection with &gt;&gt;= and return.<br><br>NOTE: Since &gt;&gt;= and return are already present in the Prelude, you may want to use import Prelude hiding ((&gt;&gt;=),return) to avoid compilation errors.<br><br>=================<br><br>{-# LANGUAGE NoImplicitPrelude #-}<br><br>import Prelude hiding ((&gt;&gt;), (&gt;&gt;=), return)<br><br>type Seed = Int<br>type Random a = Seed -&gt; (a, Seed)<br><br>randomNext :: Seed -&gt; Seed<br>randomNext rand = if newRand &gt; 0 then newRand else newRand + 2147483647<br>&nbsp;&nbsp;&nbsp; where newRand = 16807 * lo - 2836 * hi<br>&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp; (hi,lo) = rand
 `divMod` 127773<br><br>rollDie :: Random Int<br>rollDie seed = ((seed `mod` 6) + 1, randomNext seed)<br><br>(&gt;&gt;) :: Random a -&gt; Random b -&gt; Random b<br>(&gt;&gt;) m n = \seed0 -&gt;<br>&nbsp; let (result1, seed1) = m seed0<br>&nbsp;&nbsp;&nbsp;&nbsp;&nbsp; (result2, seed2) = n seed1<br>&nbsp; in (result2, seed2)<br><br>(&gt;&gt;=) :: Random a -&gt; (a -&gt; Random b) -&gt; Random b<br>(&gt;&gt;=) m g = \seed0 -&gt; <br>&nbsp; let (result1, seed1) = m seed0<br>&nbsp;&nbsp;&nbsp;&nbsp;&nbsp; (result2, seed2) = (g result1) seed1<br>&nbsp; in (result2, seed2)<br><br>return :: a -&gt; Random a<br>return x = \seed0 -&gt; (x, seed0)<br><br>sumTwoDice :: Random Int<br>sumTwoDice = rollDie &gt;&gt;= (\die1 -&gt; rollDie &gt;&gt;= (\die2 -&gt; return (die1 + die2)))<br><br>rollNDice :: Int -&gt; Random [Int]<br><br><br>--- On <b>Thu, 4/23/09, michael rice <i>&lt;nowgate@yahoo.com&gt;</i></b> wrote:<br><blockquote style="border-left: 2px solid rgb(16,
 16, 255); margin-left: 5px; padding-left: 5px;"><br>From: michael rice &lt;nowgate@yahoo.com&gt;<br>Subject: Re: [Haskell-cafe] Random number example<br>To: "Ross Mellgren" &lt;rmm-haskell@z.odi.ac&gt;<br>Cc: haskell-cafe@haskell.org<br>Date: Thursday, April 23, 2009, 5:49 PM<br><br><div id="yiv1912088525"><table border="0" cellpadding="0" cellspacing="0"><tbody><tr><td style="font-family: inherit; font-style: inherit; font-variant: inherit; font-weight: inherit; font-size: inherit; line-height: inherit; font-size-adjust: inherit; font-stretch: inherit; -x-system-font: none;" valign="top">Hi Ross,<br><br>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.<br><br>Michael<br><br>--- On <b>Thu, 4/23/09, Ross Mellgren <i>&lt;rmm-haskell@z.odi.ac&gt;</i></b> wrote:<br><blockquote style="border-left: 2px solid rgb(16, 16, 255); margin-left: 5px; padding-left:
 5px;"><br>From: Ross Mellgren &lt;rmm-haskell@z.odi.ac&gt;<br>Subject: Re: [Haskell-cafe] Random number example<br>To: "michael rice" &lt;nowgate@yahoo.com&gt;<br>Cc: haskell-cafe@haskell.org<br>Date: Thursday, April 23, 2009, 11:51 AM<br><br><div id="yiv2081336851">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:<div><br><div><div><div>module Rand9b where</div><div><br></div><div>import Control.Applicative (Applicative(..), (&lt;$&gt;), (&lt;*&gt;))</div><div>import Control.Monad (ap, liftM)</div><div><br></div><div>type Seed = Int</div><div>newtype Random a = Rand { unRand :: (Seed -&gt; (a, Seed)) }</div><div><br></div><div>randomNext :: Seed -&gt; Seed</div><div>randomNext rand = if newRand &gt; 0 then newRand else newRand + 2147483647</div><div>&nbsp;&nbsp; &nbsp;where newRand = 16807 * lo - 2836 * hi</div><div>&nbsp;&nbsp; &nbsp; &nbsp; &nbsp; &nbsp;(hi,lo) = rand `divMod` 127773</div><div><br></div><div>rollDie :: Random Int</div><div>rollDie = Rand $ \ seed -&gt; ((seed `mod` 6) + 1, randomNext seed)</div><div><br></div><div>instance Monad Random where</div><div>&nbsp;&nbsp; &nbsp;(&gt;&gt;=) =
 randomBind</div><div>&nbsp;&nbsp; &nbsp;return = randomReturn</div><div><br></div><div>instance Functor Random where</div><div>&nbsp;&nbsp; &nbsp;fmap = liftM</div><div><br></div><div>instance Applicative Random where</div><div>&nbsp;&nbsp; &nbsp;pure = return</div><div>&nbsp;&nbsp; &nbsp;(&lt;*&gt;) = ap</div><div><br></div><div>randomBind :: Random a -&gt; (a -&gt; Random b) -&gt; Random b</div><div>m `randomBind` g = Rand $ \seed0 -&gt;&nbsp;</div><div>&nbsp;&nbsp;let (result1, seed1) = unRand m $ seed0</div><div>&nbsp;&nbsp; &nbsp; &nbsp;(result2, seed2) = unRand (g result1) $ seed1</div><div>&nbsp;&nbsp;in (result2, seed2)</div><div><br></div><div>randomReturn :: a -&gt; Random a</div><div>randomReturn x = Rand $ \ seed0 -&gt; (x, seed0)</div><div><br></div><div>sumTwoDice :: Random Int</div><div>sumTwoDice = (+) &lt;$&gt; rollDie &lt;*&gt; rollDie</div><div><br></div></div><div><br></div><div>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')</div><div><br></div><div>Now you need one more thing, a way to convert a series of Random actions into a pure function:</div><div><br></div><div><br></div><div>runRandom :: Seed -&gt; Random a -&gt; a</div><div>runRandom s f = fst . unRand f $ s&nbsp;</div><div><br></div><div>which now makes what you want to do in GHCi easy and well wrapped:</div><div><br></div><div><div>Prelude&gt; :reload</div><div>[1 of 1] Compiling Rand9b &nbsp; &nbsp; &nbsp; &nbsp; &nbsp; ( rand9b.hs, interpreted )</div><div>Ok, modules loaded: Rand9b.</div><div>*Rand9b&gt; runRandom 0 sumTwoDice</div><div>3</div><div><br></div></div><div><br></div><div>Hope this helps,</div><div>-Ross</div><div><br></div><div><br><div><div>On Apr 23, 2009, at 11:28 AM, michael rice wrote:</div><br class="Apple-interchange-newline"><blockquote type="cite"><table style="" border="0"
 cellpadding="0" cellspacing="0"><tbody><tr><td style="font-family: inherit; font-style: inherit; font-variant: inherit; font-weight: inherit; font-size: inherit; line-height: inherit; font-size-adjust: inherit; font-stretch: inherit;" valign="top">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:<br><br>[michael@localhost ~]$ ghci rand9<br>GHCi, version 6.10.1: <a rel="nofollow" target="_blank" href="http://www.haskell.org/ghc/">http://www.haskell.org/ghc/</a>&nbsp; :? for help<br>Loading package ghc-prim ... linking ... done.<br>Loading package integer ... linking ... done.<br>Loading package base ... linking ... done.<br>[1 of 1] Compiling Main&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp; ( rand9.hs, interpreted )<br>Ok,
 modules loaded: Main.<br>*Main&gt; sumTwoDice<br><br>&lt;interactive&gt;:1:0:<br>&nbsp;&nbsp;&nbsp; No instance for (Show (Seed -&gt; (Int, Seed)))<br>&nbsp;&nbsp;&nbsp;&nbsp;&nbsp; arising from a use of `print' at &lt;interactive&gt;:1:0-9<br>&nbsp;&nbsp;&nbsp; Possible fix:<br>&nbsp;&nbsp;&nbsp;&nbsp;&nbsp; add an instance declaration for (Show (Seed -&gt; (Int, Seed)))<br>&nbsp;&nbsp;&nbsp; In a stmt of a 'do' expression: print it<br>*Main&gt; <br><br><br>Can I employ a 'do' expression from the command line?<br><br>Also, can I now use functions (&gt;&gt;) (&gt;&gt;=) and 'return' defined in the Prelude and still have this code work?<br><br>Michael<br><br>==================<br><br>{-# LANGUAGE NoImplicitPrelude #-}<br><br>import Prelude hiding ((&gt;&gt;), (&gt;&gt;=), return)<br><br>type Seed = Int<br>type Random a = Seed -&gt; (a, Seed)<br><br>randomNext :: Seed -&gt; Seed<br>randomNext rand = if newRand &gt; 0 then newRand else newRand +
 2147483647<br>&nbsp;&nbsp;&nbsp; where newRand = 16807 * lo - 2836 * hi<br>&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp; (hi,lo) = rand `divMod` 127773<br><br>rollDie :: Random Int<br>rollDie seed = ((seed `mod` 6) + 1, randomNext seed)<br><br>(&gt;&gt;) :: Random a -&gt; Random b -&gt; Random b<br>(&gt;&gt;) m n = \seed0 -&gt;<br>&nbsp; let (result1, seed1) = m seed0<br>&nbsp;&nbsp;&nbsp;&nbsp;&nbsp; (result2, seed2) = n seed1<br>&nbsp; in (result2, seed2)<br><br>(&gt;&gt;=) :: Random a -&gt; (a -&gt; Random b) -&gt; Random b<br>(&gt;&gt;=) m g = \seed0 -&gt; <br>&nbsp; let (result1, seed1) = m seed0<br>&nbsp;&nbsp;&nbsp;&nbsp;&nbsp; (result2, seed2) = (g result1) seed1<br>&nbsp; in (result2, seed2)<br><br>return :: a -&gt; Random a<br>return x = \seed0 -&gt; (x, seed0)<br><br>sumTwoDice :: Random Int<br>sumTwoDice = rollDie &gt;&gt;= (\die1 -&gt; rollDie &gt;&gt;= (\die2 -&gt; return (die1 + die2)))<br><br></td></tr></tbody></table><br>      
 _______________________________________________<br>Haskell-Cafe mailing list<br><a rel="nofollow">Haskell-Cafe@haskell.org</a><br>http://www.haskell.org/mailman/listinfo/haskell-cafe<br></blockquote></div><br></div></div></div></div></blockquote></td></tr></tbody></table><br>



      </div><br>-----Inline Attachment Follows-----<br><br><div class="plainMail">_______________________________________________<br>Haskell-Cafe mailing list<br><a ymailto="mailto:Haskell-Cafe@haskell.org" href="/mc/compose?to=Haskell-Cafe@haskell.org">Haskell-Cafe@haskell.org</a><br><a href="http://www.haskell.org/mailman/listinfo/haskell-cafe" target="_blank">http://www.haskell.org/mailman/listinfo/haskell-cafe</a><br></div></blockquote></td></tr></table><br>