I'm trying to convert from 0.2 to 0.3, but in way over my head.

{-# LANGUAGE GeneralizedNewtypeDeriving #-}
newtype Annex a = Annex { runAnnex :: StateT AnnexState IO a }
        deriving (
                Monad,
                MonadIO,
                -- MonadControlIO
                MonadBaseControl IO
        )

I added that after seeing this when I changed some code to use
the new liftBaseOp instead of liftIOOp. (They're equivilant, right?)

    No instance for (MonadBaseControl IO Annex)
         arising from a use of `liftBaseOp'

But with ghc 7.0.4, the derivation fails:

Annex.hs:45:17:
    Can't make a derived instance of `MonadBaseControl IO Annex'
      (even with cunning newtype deriving):
      the class has associated types
    In the newtype declaration for `Annex'

The only way I can find to make my code compile is to lose the newtype.
But of course that makes for some ugly type messages.

-- 
see shy jo

Attachment: signature.asc
Description: Digital signature

_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe

Reply via email to