Re: ANNOUNCE: attribute 0.1

[switching to libraries] On Thu, Nov 13, 2003 at 04:29:49PM -0500, Derek Elkins wrote:
Sorry that I'm too lazy to download the the tar.bz2 and see for myself, but...
On Thu, 13 Nov 2003 16:06:24 -0500 "Abraham Egnor"
wrote: that applies those functions to a monadic reference. Instances for MRef are provided for both IORef and STRef.
Assuming MRef is like the below, did you include Lazy.ST too?
On a more general note, sticking something like MonadRef somewhere in the heirarchical libs seems like it would be useful. Or perhaps Iavor's monad library?
instance MonadRef IO IORef where newRef = newIORef readRef = readIORef writeRef = writeIORef
instance MonadRef (Lazy.ST s) (STRef s) where newRef = Lazy.strictToLazyST . newSTRef readRef = Lazy.strictToLazyST . readSTRef writeRef = (Lazy.strictToLazyST .) . writeSTRef
instance MonadRef (Strict.ST s) (STRef s) where newRef = newSTRef readRef = readSTRef writeRef = writeSTRef
For an alternative design, see http://haskell.org/pipermail/libraries/2003-September/001411.html

G'day all.
Quoting Ross Paterson
For an alternative design, see
http://haskell.org/pipermail/libraries/2003-September/001411.html
The problem with this design is that there may, in general, be more than one "interesting" kind of Ref on a given state monad. For example, I often use my own IORef-like class which supports the Ord interface. Others might want IORef-like objects which support Hashable, or Show. Cheers, Andrew Bromage

On Thu, 13 Nov 2003 23:58:29 +0000
Ross Paterson
[switching to libraries]
Yes, I did think of adding a comment to that effect.
On Thu, Nov 13, 2003 at 04:29:49PM -0500, Derek Elkins wrote:
The class declaration I missed in my cut & paste: class MonadRef m r | m -> r where newRef :: a -> m (r a) readRef :: r a -> m a writeRef :: r a -> a -> m ()
instance MonadRef IO IORef where newRef = newIORef readRef = readIORef writeRef = writeIORef
instance MonadRef (Lazy.ST s) (STRef s) where newRef = Lazy.strictToLazyST . newSTRef readRef = Lazy.strictToLazyST . readSTRef writeRef = (Lazy.strictToLazyST .) . writeSTRef
instance MonadRef (Strict.ST s) (STRef s) where newRef = newSTRef readRef = readSTRef writeRef = writeSTRef
For an alternative design, see
(MonadST)
http://haskell.org/pipermail/libraries/2003-September/001411.html
Here's the earlier RefMonad emails: http://haskell.org/pipermail/haskell/2002-February/008842.html Well, you have a point. MonadRef is broken, at least as I have it. Unless both Lazy and Strict ST's didn't exist at the time, I don't know how Simon Peyton Jones came up with his fundeps, but those are the problem. An r -> m fundep breaks right off the bat with STRef and Lazy/Strict.ST. With an m -> r fundep, as I have it, it's also broken right off the bat via IO and MVar/IORef*. So basically, with the MonadRef interface, the only (potentially) reasonable interface is with no fundeps, though this has it's nuisances too. Andrew Bromage brought up one problem with the MonadST interface, namely that it requires you to use STRefs. (Which obviously means it doesn't work with MVars as well.) Another problem with the MonadST interface(or at least I don't see what to do about it) is the following: I'm using MonadRef to abstract away from the implementation of a backtrackable reference type. Though it isn't now, it would be perfectly reasonable to make it too an instance of MonadRef like so, instance MonadRef m r => MonadRef (LP m) r where newRef = newLPRef -- etc. newLPRef/readLPRef just lift the underlying functions, but writeLPRef handles the restoring when backtracking. Now if we write some function f :: MonadRef m r => r a -> m () (e.g. \r -> writeRef r 10) it will behave correctly even when used in the LP monad. I don't see how to do this with the MonadST interface. In a nutshell, MonadST seems to solve a different problem than MonadRef. Altogether, I don't (yet) see any crippling problem with MonadRef with no fundeps, but this has turned out to be a lot trickier than I expected. As several people have their MonadRef/MRef/RefMonad/MonadST classes floating around, I certainly had no illusion that I was the first to suggest it, it looks like a good thing to add to the libraries. Though MonadRef with no fundeps seems less than ideal. * Andrew Bromage just pointed this one out. I'd thought up milder cases, but this one is devastating.
participants (3)
-
ajb@spamcop.net
-
Derek Elkins
-
Ross Paterson