[Haskell-cafe] class Ref...

David Menendez zednenem at psualum.com
Sun Jun 12 18:04:34 EDT 2005


Sven Panne writes:

| ajb at spamcop.net wrote:
| > Quoting Gracjan Polak <gracjan at acchsh.com>:
| > [...]
| >>Is there any reason why isn't it included?
| > 
| > 
| > Nobody could agree on the details.  For example, MVars are
| > perfectly respectable Refs on the IO monad.  So would it make sense
| > to add an instance for that?  If so, the functional dependency
| > should go, which introduces its own problems.
| 
| A few more design problems:
| 
|   * Due to the functional dependency, that class is not Haskell98, 
|     which is a *very* good reason IMHO not to standardize it, at least
|     in that way. Remember: There are not only GHC and Hugs out
|     there...
| 
|   * The 3 operations should not be packed together in a single class,
|     because there might be e.g. references which you can't create 
|     (e.g. OpenGL's state variables), references which are read-only >
|     and even references which are write-only.
| 
|   * What about strictness of e.g. the setter? There is no "right" 
|     version, this depends on the intended usage.
| 
|   * Are the references located in the monad (like in the suggested 
|     class) or are they within objects, which have to be given as 
|     additional arguments (e.g. like wxHaskell's widgets/Attr/Prop).
| 
|   * Atomic operations might be needed, too.

These are all good points, but while it's fair to say that a MonadRef
class is wrong for some situations, I don't think it's wrong for all
situations. It isn't Haskell98, but neither is the ST monad or
practically anything else in Control.Monad.*. Regarding strictness vs.
non-strictness, I would say leave it up to the specific monad.

I think the best way to look at MonadRef is as a generalization of
MonadState. 

Consider:

> {-# OPTIONS -fglasgow-exts #-}
> 
> import Control.Monad.Reader
> import Control.Monad.State
> import Control.Monad.ST
> import Data.STRef
> 
> class Monad m => MonadRef r m | m -> r where
>   newRef   :: a -> m (r a)
>   readRef  :: r a -> m a
>   writeRef :: r a -> a -> m ()
> 
> instance MonadRef (STRef r) (ST r) where
>   newRef   = newSTRef
>   readRef  = readSTRef
>   writeRef = writeSTRef
> 
> instance MonadRef r m => MonadRef r (ReaderT e m) where
>   newRef   = lift . newRef
>   readRef  = lift . readRef
>   writeRef = (lift.) . writeRef
> 
> 
> 
> newtype RefToState r s m a = RTS (ReaderT (r s) m a)
>   deriving (Functor, Monad)
> 
> instance MonadRef r m => MonadState s (RefToState r s m) where
>   get   = RTS (ask >>= readRef)
>   put s = RTS (ask >>= \r -> writeRef r s)
> 
> evalRefToState :: MonadRef r m => RefToState r s m a -> s -> m a
> evalRefToState (RTS m) s0 = newRef s0 >>= runReaderT m
> 
> runRefToState :: MonadRef r m => RefToState r s m a -> s -> m (a, s)
> runRefToState (RTS m) s0 = do
>   r <- newRef s0
>   x <- runReaderT m r
>   s <- readRef r
>   return (x,s)
-- 
David Menendez <zednenem at psualum.com> | "In this house, we obey the laws
<http://www.eyrie.org/~zednenem>      |        of thermodynamics!"


More information about the Haskell-Cafe mailing list