[Haskell-beginners] Errors involving rigid skolem types

Matthew Moppett matthewmoppett at gmail.com
Mon Aug 27 15:21:55 CEST 2012


The following code is intended as a first step towards creating a
cyclical enumerable type, such that:
     (e.g.) [Cyc Friday .. Cyc Tuesday] would yield [Friday, Saturday,
Sunday, Monday, Tuesday]

module Cycle where

newtype Cyc a = Cyc a deriving (Eq, Ord, Bounded, Show, Read)

fromCyc :: Cyc a -> a
fromCyc (Cyc a) = a

instance (Enum a, Bounded a) => Enum (Cyc a) where
    fromEnum = fromEnum . fromCyc
    toEnum n = Cyc x
        where (x, max) = (x', maxBound) :: (a, a)
              x' = toEnum $ n `mod` ((fromEnum max) - 1)

This yields a kind of error message that I've often bashed my head against
in other code I've written, without ever really understanding what the
problem is exactly:

Couldn't match type `a0' with `a1'
      because type variable `a1' would escape its scope
    This (rigid, skolem) type variable is bound by
      an expression type signature: (a1, a1)
    The following variables have types that mention a0
      x' :: a0 (bound at Cycle.hs:12:15)
    In the expression: (x', maxBound) :: (a, a)
    In a pattern binding: (x, max) = (x', maxBound) :: (a, a)
    In an equation for `toEnum':
        toEnum n
          = Cyc x
          where
              (x, max) = (x', maxBound) :: (a, a)
              x' = toEnum $ n `mod` ((fromEnum max) - 1)

The problem comes up when I'm trying to give hints to the compiler about
the type that a particular expression should have.

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?
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://www.haskell.org/pipermail/beginners/attachments/20120827/c0e47bc9/attachment.htm>


More information about the Beginners mailing list