
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))

Thanks! It works this way.
I often forget the dangers of point-free notation...
2011/3/9 Jake McArthur
Try `return x = MyST (return x)`. It's (.) that throws it off.
- Jake
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

On Wed, 9 Mar 2011, Yves Parès wrote:
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
Would it make sense to make the 's' type explicit? newtype MyST s a = MyST (ST s a)

Well, I want to hide the fact that I'm using ST, so if I can hide the
existential type 's' it is better.
BTW, does someone know why the ST default implementation (the one exposed by
Control.Monad.ST) is strict, whereas those of State et Writer are lazy?
2011/3/9 Henning Thielemann
On Wed, 9 Mar 2011, Yves Parès wrote:
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
Would it make sense to make the 's' type explicit?
newtype MyST s a = MyST (ST s a)

On Wed, Mar 9, 2011 at 6:21 PM, Yves Parès
Well, I want to hide the fact that I'm using ST, so if I can hide the existential type 's' it is better.
In practice if you want to actually _use_ ST you'll find you'll need to let the world escape into your type. Otherwise you won't be able to create and pass around any STRefs or arrays and use them later. The universal quantification inside of MyST's definition will keep you from holding on to them. BTW, does someone know why the ST default implementation (the one exposed by
Control.Monad.ST) is strict, whereas those of State et Writer are lazy?
Mostly because of the principle of least surprise. It makes it act more like IO. -Edward

In practice if you want to actually _use_ ST you'll find you'll need to let the world escape into your type. Otherwise you won't be able to create and pass around any STRefs or arrays and use them later. The universal quantification inside of MyST's definition will keep you from holding on to them.
Okay, what you are saying is that two MyST action declared separately will
not be compatible, right?
I have another problem. One of my goal is to be able to alter an STRef when
it is accessed. To do so, I use the following type:
STRef s (ST s a).
So the actual variable 'a' contained by my STRef is wrapped inside an ST
action which goal is to modify the STRef and then return the value of type
'a'.
My problem is that the STRef is not modfied, it always returns the same
value.
Example of this with IORefs, it is simpler to test:
selfAlteringRef :: Int -> IO (IORef (IO Int))
selfAlteringRef init = mfix $ \ref ->
newIORef $ do
writeIORef ref (return 0)
return init
2011/3/10 Edward Kmett
On Wed, Mar 9, 2011 at 6:21 PM, Yves Parès
wrote: Well, I want to hide the fact that I'm using ST, so if I can hide the existential type 's' it is better.
In practice if you want to actually _use_ ST you'll find you'll need to let the world escape into your type. Otherwise you won't be able to create and pass around any STRefs or arrays and use them later. The universal quantification inside of MyST's definition will keep you from holding on to them.
BTW, does someone know why the ST default implementation (the one exposed
by Control.Monad.ST) is strict, whereas those of State et Writer are lazy?
Mostly because of the principle of least surprise. It makes it act more like IO.
-Edward
participants (4)
-
Edward Kmett
-
Henning Thielemann
-
Jake McArthur
-
Yves Parès