#303: Rebindable syntax doesn't work as advertised
----------------------------------------+-----------------------------------
    Reporter:  nobody                   |        Owner:  nobody  
        Type:  bug                      |       Status:  reopened
    Priority:  normal                   |    Milestone:          
   Component:  Compiler (Type checker)  |      Version:  6.8.3   
    Severity:  normal                   |   Resolution:          
    Keywords:                           |     Testcase:          
Architecture:  Unknown                  |           Os:  Unknown 
----------------------------------------+-----------------------------------
Changes (by ryani):

  * status:  closed => reopened
  * os:  => Unknown
  * testcase:  =>
  * version:  6.4 => 6.8.3
  * architecture:  => Unknown
  * resolution:  Fixed =>

Comment:

 This seems to be broken in 6.8.3, at least for "weird" monad types.  Test
 case follows:
 {{{
 {-# LANGUAGE NoImplicitPrelude #-}
 module T where
 import qualified Prelude as P

 class IxMonad m where
     return :: a -> m i i a
     (>>=) :: m i j a -> (a -> m j k b) -> m i k b
     (>>)  :: m i j a -> m j k b -> m i k b
     m >> n = m >>= \_ -> n

     fail :: P.String -> m i j a
     fail s = P.error s

 data T a b c = T
 instance IxMonad T where
     return _ = T
     m >>= f  = T
     fail _   = T

 testM :: T (a,b) b a
 testM = T

 test1 = testM >>= \x -> return x

 test2  = do
    x <- testM
    return x
 }}}

 test1 compiles fine, but test2 (which should be identical up-to-sugaring)
 fails.

 {{{
 $ ghc -c -XNoImplicitPrelude T.hs
 T.hs:27:3:
     Occurs check: cannot construct the infinite type: b = (a, b)
       Expected type: T (a, b) b t
       Inferred type: T (a, b) (a, b) a
     In the expression: return x
     In the expression:
         do x <- testM
            return x
 }}}

-- 
Ticket URL: <http://hackage.haskell.org/trac/ghc/ticket/303#comment:7>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
_______________________________________________
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs

Reply via email to