#1369: Type error when compiling ST-monad-like code
---------------------------------+------------------------------------------
    Reporter:  [EMAIL PROTECTED]  |        Owner:         
        Type:  bug               |       Status:  new    
    Priority:  normal            |    Milestone:         
   Component:  Compiler          |      Version:  6.6.1  
    Severity:  normal            |   Resolution:         
    Keywords:                    |   Difficulty:  Unknown
          Os:  Unknown           |     Testcase:         
Architecture:  Unknown           |  
---------------------------------+------------------------------------------
Old description:

> Compiling the module below works fine in GHC 6.4.2.
>
> In GHC 6.6 and 6.6.1, it gives a type error.
>
> /Koen
>
> >>>
> {-# OPTIONS -fglasgow-exts #-}
> module Bug where
>
> import Control.Monad.ST
> import Data.STRef
>
> ---------------------------------------------------------------------------
>
> newtype M s a =
>   MkM (STRef s Int -> ST s a)
>
> runM :: (forall s . M s a) -> a
> runM mm =
>   runST (
>     do ref <- newSTRef 0
>        m ref
>   )
>  where
>   MkM m = mm
>
> ---------------------------------------------------------------------------
>
> -- the instance declaration and function definition of "inc" are just
> here
> -- for giving context; removing them still makes runM not type check in
> GHC 6.6
>
> instance Monad (M s) where
>   return x =
>     MkM (\_ -> return x)
>
>   MkM m >>= k =
>     MkM (\ref ->
>       do x <- m ref
>          let MkM m' = k x
>          m' ref
>     )
>
> inc :: M s Int
> inc = MkM (\ref ->
>   do n <- readSTRef ref
>      writeSTRef ref (n+1)
>      return n
>   )
>
> ---------------------------------------------------------------------------

New description:

 Compiling the module below works fine in GHC 6.4.2.  In GHC 6.6 and 6.6.1,
 it gives a type error.

 /Koen

 {{{
 {-# OPTIONS -fglasgow-exts #-}
 module Bug where

 import Control.Monad.ST
 import Data.STRef

 newtype M s a =
   MkM (STRef s Int -> ST s a)

 runM :: (forall s . M s a) -> a
 runM mm =
   runST (
     do ref <- newSTRef 0
        m ref
   )
  where
   MkM m = mm

 -- the instance declaration and function definition
 -- of "inc" are just here for giving context;
 -- removing them still makes runM not type check in GHC 6.6

 instance Monad (M s) where
   return x =
     MkM (\_ -> return x)

   MkM m >>= k =
     MkM (\ref ->
       do x <- m ref
          let MkM m' = k x
          m' ref
     )

 inc :: M s Int
 inc = MkM (\ref ->
   do n <- readSTRef ref
      writeSTRef ref (n+1)
      return n
   )
 }}}

-- 
Ticket URL: <http://hackage.haskell.org/trac/ghc/ticket/1369>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
_______________________________________________
Glasgow-haskell-bugs mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs

Reply via email to