[Haskell-cafe] problem using ST monad
Paul L
ninegua at gmail.com
Sat Oct 25 21:18:20 EDT 2008
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
More information about the Haskell-Cafe
mailing list