The type inferer seems to struggle to find the type of minBound and maxBound, and GHC asks to use a type annotation.<div><div><br></div><div>To only way I see how to add a type annotation here is to use a GHC extension:</div>
<div><br></div><div><div><span class="Apple-style-span" style="font-family: &#39;courier new&#39;, monospace;"><span class="Apple-style-span" style="font-size: large;">{-# LANGUAGE ScopedTypeVariables #-}</span></span></div>
<div><span class="Apple-style-span" style="font-family: &#39;courier new&#39;, monospace;"><span class="Apple-style-span" style="font-size: large;"><br></span></span></div></div><div><div><span class="Apple-style-span" style="font-family: &#39;courier new&#39;, monospace;"><span class="Apple-style-span" style="font-size: large;">randomEnum :: forall a g. (Enum a, Bounded a, RandomGen g) =&gt; Rand g a</span></span></div>
<div><span class="Apple-style-span" style="font-family: &#39;courier new&#39;, monospace;"><span class="Apple-style-span" style="font-size: large;">randomEnum = do</span></span></div><div><span class="Apple-style-span" style="font-family: &#39;courier new&#39;, monospace;"><span class="Apple-style-span" style="font-size: large;">    randVal &lt;- getRandomR (fromEnum (minBound::a), fromEnum (maxBound::a))</span></span></div>
<div><span class="Apple-style-span" style="font-family: &#39;courier new&#39;, monospace;"><span class="Apple-style-span" style="font-size: large;">    return $ toEnum randVal</span></span></div><div><br></div><div><br></div>
<div>It is annoying when the type inferer encounters ambiguities - you also get this all the time when using OpenGL e.g. GL.colour - but I don&#39;t know how to solve this without adding type annotations</div><div><br></div>
<div><br></div><div class="gmail_quote">On Thu, Apr 2, 2009 at 8:03 PM, Michael Snoyman <span dir="ltr">&lt;<a href="mailto:michael@snoyman.com">michael@snoyman.com</a>&gt;</span> wrote:<br><blockquote class="gmail_quote" style="margin:0 0 0 .8ex;border-left:1px #ccc solid;padding-left:1ex;">
<div dir="ltr">I&#39;ve butted into this problem multiple times, so I thought it&#39;s finally time to get a good solution. I don&#39;t even have the terminology to describe the issue, so I&#39;ll just post the code I&#39;m annoyed with and hope someone understands what I mean.<br>

<br><div style="margin-left:40px">import Control.Monad.Random<br>import System.Random<br><br>data Marital = Single | Married | Divorced<br>    deriving (Enum, Bounded, Show)<br><br>randomEnum :: (Enum a, Bounded a, RandomGen g) =&gt; Rand g a<br>

randomEnum = do<br>    let minb = minBound<br>        maxb = maxBound<br>    randVal &lt;- getRandomR (fromEnum minb, fromEnum maxb)<br>    return $ head [toEnum randVal, minb, maxb] -- if I do the obvious thing (return $ toEnum randVal) I get funny errors<br>

<br>main = do<br>    stdGen &lt;- newStdGen<br>    let marital = evalRand randomEnum stdGen :: Marital<br>    putStrLn $ &quot;Random marital status: &quot; ++ show marital<br><br></div>Any help is appreciated. Thanks!<br>

Michael<br></div>
<br>_______________________________________________<br>
Haskell-Cafe mailing list<br>
<a href="mailto: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>
<br></blockquote></div><br></div></div>