
Yes, monomorphism. "do" binding requires your fold'' to be of some monomorphic type, but runST requires some polymorphism.
If you want, you can use special type like that:
data FoldSTVoid = FoldSTVoid {runFold :: forall a. (Int -> ST a ()) -> ST a ()}
fold :: Monad m => (Int -> m ()) -> m ()
fold f = mapM_ f [0..20]
selectFold :: String -> IO FoldSTVoid -- ((Int -> m ()) -> m ())
selectFold method = do
-- in real program I'd like to choose between
-- different fold methods, based on some IO context
return $ FoldSTVoid fold
useFold :: FoldSTVoid -> ST a ()
useFold fold' = runFold fold' f
where f _ = return () -- some trivial iterator
main = do
fold'' <- selectFold "some-method-id"
print $ runST $ useFold fold''
On Nov 28, 2012, at 9:52 PM, Dmitry Kulagin
Hi Cafe,
I try to implement some sort of monadic fold, where traversing is polymorphic over monad type. The problem is that the code below does not compile. It works with any monad except for ST. I suspect that monomorphism is at work here, but it is unclear for me how to change the code to make it work with ST.
fold :: Monad m => (Int -> m ()) -> m () fold f = mapM_ f [0..20]
selectFold :: Monad m => String -> IO ((Int -> m ()) -> m ()) selectFold method = do -- in real program I'd like to choose between -- different fold methods, based on some IO context return fold
useFold :: Monad m => ((Int -> m ()) -> m ()) -> m () useFold fold' = fold' f where f _ = return () -- some trivial iterator
main = do fold'' <- selectFold "some-method-id" print $ runST $ useFold fold''
Thank you! Dmitry _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe