[Haskell-cafe] ANNOUNCE: pqueue-mtl, stateful-mtl
Louis Wasserman
wasserman.louis at gmail.com
Sun Feb 15 18:02:00 EST 2009
I follow. The primary issue, I'm sort of wildly inferring, is that use of
STT -- despite being pretty much a State monad on the inside -- allows
access to things like mutable references?
More serious question: The issue of nondeterministic branching and the State
monad is something that's occurred to me previously. Do I understand
correctly that this would require use of an arrow transformer, rather than a
monad? For a generic State monad, that would be something like
newtype StateArrow a x y = SA (a (s, x) (s,y))
and then StateArrow (Kleisli []) x y translates into approximately (s, x) ->
[(s, y)], as desired?
Louis Wasserman
wasserman.louis at gmail.com
On Sun, Feb 15, 2009 at 4:06 PM, Reid Barton <rwbarton at math.harvard.edu>wrote:
> 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.html
>
> 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
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: http://www.haskell.org/pipermail/haskell-cafe/attachments/20090215/300ba161/attachment.htm
More information about the Haskell-Cafe
mailing list