A couple of clarifications regarding my previous post:<div><br></div><div>It should be ((fromEnum max) + 1) rather than ((fromEnum max) - 1); and</div><div><br></div><div>Perhaps question (2) should be: are there any lessons to be learnt about how to avoid this problem in future?</div>
<div><br><div class="gmail_quote">On Mon, Aug 27, 2012 at 11:21 PM, Matthew Moppett <span dir="ltr">&lt;<a href="mailto:matthewmoppett@gmail.com" target="_blank">matthewmoppett@gmail.com</a>&gt;</span> wrote:<br><blockquote class="gmail_quote" style="margin:0 0 0 .8ex;border-left:1px #ccc solid;padding-left:1ex">
The following code is intended as a first step towards creating a cyclical enumerable type, such that:<div>     (e.g.) [Cyc Friday .. Cyc Tuesday] would yield [Friday, Saturday, Sunday, Monday, Tuesday]</div><div><br></div>

<div><div>module Cycle where</div><div><br></div><div>newtype Cyc a = Cyc a deriving (Eq, Ord, Bounded, Show, Read)</div><div><br></div><div>fromCyc :: Cyc a -&gt; a</div><div>fromCyc (Cyc a) = a</div><div><br></div><div>

instance (Enum a, Bounded a) =&gt; Enum (Cyc a) where</div><div>    fromEnum = fromEnum . fromCyc</div><div>    toEnum n = Cyc x</div><div>        where (x, max) = (x&#39;, maxBound) :: (a, a)</div><div>              x&#39; = toEnum $ n `mod` ((fromEnum max) - 1)</div>

</div><div><br></div><div>This yields a kind of error message that I&#39;ve often bashed my head against in other code I&#39;ve written, without ever really understanding what the problem is exactly:</div><div><br></div>
<div>
<div>Couldn&#39;t match type `a0&#39; with `a1&#39;</div><div>      because type variable `a1&#39; would escape its scope</div><div>    This (rigid, skolem) type variable is bound by</div><div>      an expression type signature: (a1, a1)</div>

<div>    The following variables have types that mention a0</div><div>      x&#39; :: a0 (bound at Cycle.hs:12:15)</div><div>    In the expression: (x&#39;, maxBound) :: (a, a)</div><div>    In a pattern binding: (x, max) = (x&#39;, maxBound) :: (a, a)</div>

<div>    In an equation for `toEnum&#39;:</div><div>        toEnum n</div><div>          = Cyc x</div><div>          where</div><div>              (x, max) = (x&#39;, maxBound) :: (a, a)</div><div>              x&#39; = toEnum $ n `mod` ((fromEnum max) - 1)</div>

</div><div><br></div><div>The problem comes up when I&#39;m trying to give hints to the compiler about the type that a particular expression should have. </div><div><br></div><div>My questions are: (1) what exactly is going on here, and (2) is there any general technique for specifying types in situations like this that gets around this problem?</div>

</blockquote></div><br></div>