problem using ST monad

I'm have some trouble using the ST monad, and I think I'm confused about its use of existential type.
{-# OPTIONS -XRankNTypes #-} import Control.Monad.ST import Data.Array.ST
I want to implement a map function that unfold all ST monads in a list:
mapST :: (a -> (forall s . ST s b)) -> [a] -> [b] mapST f (x:xs) = runST (f x) : mapST f xs mapST f [] = []
This is fine. However, it wouldn't typecheck if I had declared its type differently: mapST :: (a -> ST s b) -> [a] -> [b] I first thought the reason could be that runST has to take something of type (forall s . ST s b), but apparently this is not the case:
g :: (STArray s Int Int -> ST s a) -> ST s a g f = newArray (0,0) 0 >>= f
with this definition, runST (t (flip readArray 0)) happily returns me 0, despite the fact that the "s" in the type of "g" is not existentially quantified. Then when I try this one: mapST g [flip readArray 0] It fails to typecheck. Why? Is it possible, if at all, to implement a generic mapST? -- Regards, Paul Liu Yale Haskell Group http://www.haskell.org/yale

Am Sonntag, 26. Oktober 2008 02:18 schrieb Paul L:
I'm have some trouble using the ST monad, and I think I'm confused about its use of existential type.
{-# OPTIONS -XRankNTypes #-} import Control.Monad.ST import Data.Array.ST
I want to implement a map function that unfold
all ST monads in a list:
mapST :: (a -> (forall s . ST s b)) -> [a] -> [b] mapST f (x:xs) = runST (f x) : mapST f xs mapST f [] = []
This is fine. However, it wouldn't typecheck if I had declared its type differently:
mapST :: (a -> ST s b) -> [a] -> [b]
I first thought the reason could be that runST has to take something of type (forall s . ST s b), but apparently
this is not the case:
g :: (STArray s Int Int -> ST s a) -> ST s a g f = newArray (0,0) 0 >>= f
with this definition,
runST (t (flip readArray 0))
happily returns me 0, despite the fact that the "s" in the type of "g" is not existentially quantified.
Sure, (g (flip readArray 0)) :: ST s Int, or, explicitly, forall s. ST s Int, there's nothing to restrict the s, so it's legitimate to pass it to runST.
Then when I try this one:
mapST g [flip readArray 0]
It fails to typecheck. Why?
The type of g is forall s. (STArray s Int Int -> ST s a) -> ST s a, but mapST needs a function of type a -> forall s. ST s b, not forall s. a -> ST s b. Since for g, s appears in a, these types are different, s escapes.
Is it possible, if at all, to implement a generic mapST?
What would be a generic mapST, which type should it have?

Tnaks for the clarification, please see my further questions below
On 10/25/08, Daniel Fischer
Sure, (g (flip readArray 0)) :: ST s Int, or, explicitly, forall s. ST s Int, there's nothing to restrict the s, so it's legitimate to pass it to runST.
..[snipped]..
What would be a generic mapST, which type should it have?
I tried this type for mapST, it doesn't work: mapST :: (a -> ST s b) -> [a] -> [b] mapST f (x:xs) = runST (f x) : mapST f xs mapST f [] = [] By your reasoning, (f x) should have type forall s . ST s b, and should match what runST expects, but apparently GHC complains about it. Why? -- Regards, Paul Liu Yale Haskell Group http://www.haskell.org/yale

On Sat, Oct 25, 2008 at 11:55 PM, Paul L
Tnaks for the clarification, please see my further questions below
On 10/25/08, Daniel Fischer
wrote: Sure, (g (flip readArray 0)) :: ST s Int, or, explicitly, forall s. ST s Int, there's nothing to restrict the s, so it's legitimate to pass it to runST.
..[snipped]..
What would be a generic mapST, which type should it have?
I tried this type for mapST, it doesn't work:
mapST :: (a -> ST s b) -> [a] -> [b] mapST f (x:xs) = runST (f x) : mapST f xs mapST f [] = []
By your reasoning, (f x) should have type forall s . ST s b, and should match what runST expects, but apparently GHC complains about it. Why?
From the perspective of code inside the definition of mapST, f is not
The problem is that the type variable s is determined by the caller of
mapST. If you write the type with explicit foralls, you get:
mapST :: forall a b s. (a -> ST s b) -> [a] -> [b]
polymorphic, because a, b, and s have already been determined.
The type you need is,
mapST :: forall a b. (forall s. a -> ST s b) -> [a] -> [b]
Now runST is able to pass an arbitrary type for s to f.
(GHC can silently convert between "forall s. a -> ST s b" and "a ->
forall s. ST s b".)
It may be helpful to rewrite the types with a more explicit notation.
For example,
runST :: (a :: *) -> ((s :: *) -> ST s a) -> a
mapST_wrong :: (a :: *) -> (b :: *) -> (s :: *) -> (f :: a -> ST s b)
-> [a] -> [b]
mapST_right :: (a :: *) -> (b :: *) -> (f :: (s :: *) -> a -> ST s b)
-> [a] -> [b]
--
Dave Menendez

Thanks very much for the explanation, I now have a better understanding.
On 10/26/08, David Menendez
It may be helpful to rewrite the types with a more explicit notation. For example,
runST :: (a :: *) -> ((s :: *) -> ST s a) -> a
mapST_wrong :: (a :: *) -> (b :: *) -> (s :: *) -> (f :: a -> ST s b) -> [a] -> [b] mapST_right :: (a :: *) -> (b :: *) -> (f :: (s :: *) -> a -> ST s b) -> [a] -> [b]
Is this the kind syntax? Very cool indeed!
On 10/26/08, Henning Thielemann
I think mapM with subsequent runST should work.
Ha, glad that you mentioned it, the purpose I was trying at mapST is to eventually use `par` to enable parallel evalation of a set of ST monads instead of, let's say, using thread with IO monads. -- Regards, Paul Liu Yale Haskell Group http://www.haskell.org/yale

On Sun, Oct 26, 2008 at 8:17 AM, Paul L
Thanks very much for the explanation, I now have a better understanding.
I'm glad I could help.
On 10/26/08, David Menendez
wrote: ..[snipped].. It may be helpful to rewrite the types with a more explicit notation. For example,
runST :: (a :: *) -> ((s :: *) -> ST s a) -> a
mapST_wrong :: (a :: *) -> (b :: *) -> (s :: *) -> (f :: a -> ST s b) -> [a] -> [b] mapST_right :: (a :: *) -> (b :: *) -> (f :: (s :: *) -> a -> ST s b) -> [a] -> [b]
Is this the kind syntax? Very cool indeed!
If you're referring to the kind signatures feature in GHC, then no,
although the use of * is related.
It's actually a way of writing dependent products, which generalize
foralls and the function arrow. This particular syntax is used by
Agda, but I've also seen it in some proposals to add limited dependent
types to Haskell. I've found it very helpful in understanding how
universal and existential quantification behave, because it treats the
type and value parameters uniformly.
--
Dave Menendez

On Sat, 25 Oct 2008, Paul L wrote:
I'm have some trouble using the ST monad, and I think I'm confused about its use of existential type.
{-# OPTIONS -XRankNTypes #-} import Control.Monad.ST import Data.Array.ST
I want to implement a map function that unfold all ST monads in a list:
mapST :: (a -> (forall s . ST s b)) -> [a] -> [b] mapST f (x:xs) = runST (f x) : mapST f xs mapST f [] = []
I think mapM with subsequent runST should work.
participants (4)
-
Daniel Fischer
-
David Menendez
-
Henning Thielemann
-
Paul L