buzzard(131)% cat Bug6.hs
{-# OPTIONS -fglasgow-exts #-}

import Control.Monad.State

data S1 = S1 (M1 Int)
newtype M1 a = M1 { unM1 :: StateT S1 IO a } deriving (Monad)

data S2 = S2 (M2 Int)
newtype M2 a = M2 { unM2 :: S2 -> (a, S2) }
instance Monad M2 where
  return a = M2 $ \s -> (a, s)
  m >>= k  = M2 $ \s -> let (a, s') = unM2 m s in unM2 (k a) s'

main = return ()
buzzard(132)% ghc -c Bug6.hs

Bug6.hs:6:
    Can't make a derived instance of `Monad M1'
    (too hard for cunning newtype deriving)
    When deriving instances for type `M1'
buzzard(133)% ghc --version
The Glorious Glasgow Haskell Compilation System, version 5.04.2


Why is the newtype deriving too hard here?

_______________________________________________
Glasgow-haskell-bugs mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs

Reply via email to