[Haskell-cafe] Type family oddity

Florian Weimer fw at deneb.enyo.de
Sat Oct 4 06:52:57 EDT 2008


I can't figure out why the following code doesn't compile with the
October 2n GHC 6.10 beta (-XTypeFamilies -XFlexibleContexts) when the
type declaration is not commented out.

module T where

type family RangeTrait c

class InputRange r where
    remaining :: r -> Bool
    advance :: r -> r

class (InputRange (RangeTrait s)) => Sequence s where
    erase :: RangeTrait s -> IO (RangeTrait s)

-- erase_range :: (Sequence s) => RangeTrait s -> IO (RangeTrait s)
erase_range r =
      if remaining r
        then do
          r' <- erase r
          erase_range r'
        else return r

GHCi says the type is precisely as specified in the comment.  However,
when I activate the type declaration, GHC complains:

T.hs:16:22:
    Couldn't match expected type `RangeTrait s'
           against inferred type `RangeTrait s2'
    In the first argument of `erase', namely `r'
    In a stmt of a 'do' expression: r' <- erase r
    In the expression:
        do r' <- erase r
           erase_range r'

T.hs:17:22:
    Couldn't match expected type `RangeTrait s1'
           against inferred type `RangeTrait s2'
    In the first argument of `erase_range', namely `r''
    In the expression: erase_range r'
    In the expression:
        do r' <- erase r
           erase_range r'

Any suggestions?  Is this a bug in GHC?


More information about the Haskell-Cafe mailing list