
Hello, I am trying to make a monad that uses ST internally. But even when reducing this to the simplest case I'm still cramped by the 's' phantom type : {-# LANGUAGE Rank2Types #-} newtype MyST a = MyST (forall s. ST s a) -- ^ I cannot use " deriving (Monad) " through GeneralizedNewtypeDeriving runMyST (MyST m) = runST m -- ^ works thanks to declaration of 's' at rank 2 in the definition of MyST -- It refuses to compile if MyST is declared as such: -- data MyST s a = MyST (ST s a) instance Monad MyST where return = MyST . return -- and this does not compile (MyST m) >>= f = MyST $ do x <- m case f x of (MyST m) -> m If you try it, GHC will complain: Simple.hs:13:20: Couldn't match expected type `forall s. ST s a' with actual type `ST s a' Expected type: a -> forall s1. ST s1 a Actual type: a -> ST s a In the second argument of `(.)', namely `(return :: a -> (forall s. ST s a))' In the expression: MyST . (return :: a -> (forall s. ST s a))