
On Sun, Feb 15, 2009 at 09:59:28PM -0000, Sittampalam, Ganesh wrote:
Stateful-mtl provides an ST monad transformer,
Is this safe? e.g. does it work correctly on [], Maybe etc?
If not this should be flagged very prominently in the documentation.
It is not safe: it has the same problem as the STMonadTrans package, discussed recently here: http://www.haskell.org/pipermail/glasgow-haskell-users/2009-February/016554.... The following code demonstrates that STT violates referential transparency:
import Control.Monad import Data.STRef import Control.Monad.Trans import Control.Monad.ST.Trans
data Tree a = Leaf a | Branch (Tree a) (Tree a) deriving Show
instance Monad Tree where return = Leaf Leaf a >>= k = k a Branch l r >>= k = Branch (l >>= k) (r >>= k)
foo :: STT s Tree Integer foo = do x <- liftST $ newSTRef 0 y <- lift (Branch (Leaf 1) (Leaf 2)) when (odd y) (liftST $ writeSTRef x y) liftST $ readSTRef x
main :: IO () main = do print $ runSTT foo let Branch _ (Leaf x) = runSTT foo print x
outputting: Branch (Leaf 1) (Leaf 1) 0 Demanding the value in the left Leaf affects the value seen in the right Leaf. Regards, Reid