[Haskell-cafe] Type family oddity

Manuel M T Chakravarty chak at cse.unsw.edu.au
Sun Oct 5 06:19:15 EDT 2008


Florian Weimer:
> 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.

It's a bug that the code is accepted *without* the signature, as the  
signature is ambiguous:

   http://hackage.haskell.org/trac/ghc/ticket/1897

This is not because the code fails to be type-safe, but because (a)  
you can't use the function erase_range anyway and (b) that it is  
accepted without a signature, but not with the signature leads to  
confusion, as you experienced.

BTW, the method 'erase' in your code has the same problem.

Manuel

>
>
> 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?
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe



More information about the Haskell-Cafe mailing list