suggestion: A common type class for mutable variables
Dominique Devriese
dominique.devriese at cs.kuleuven.be
Sun Jun 9 20:17:11 CEST 2013
Perhaps it's worth pointing out that one can avoid the functional
dependencies (not the MPTCs) with a common API based on an explicit
state dictionary: see code below. I would also personally find such an
API more elegant, but I'm not sure others would agree with this.
There is also an advantage that StateD is also usable with the state
monad and monad transformer (see function stateD below). I'm not sure
whether this idea has been tried out in practice yet.
Regards,
Dominique
module Ref where
import Data.IORef
import Data.STRef
import Control.Monad.ST
import Control.Applicative
import Control.Monad.State
data StateD s m = StateD { putM :: s -> m (), getM :: m s }
class MutRef m where
newRef :: s -> m (StateD s m)
ioRefStateD :: IORef a -> StateD a IO
ioRefStateD r = StateD (writeIORef r) (readIORef r)
instance MutRef IO where
newRef v = ioRefStateD <$> newIORef v
stRefStateD :: STRef s a -> StateD a (ST s)
stRefStateD r = StateD (writeSTRef r) (readSTRef r)
instance MutRef (ST s) where
newRef v = stRefStateD <$> newSTRef v
stateD :: MonadState s m => StateD s m
stateD = StateD put get
2013/5/30 Petr Pudlák <petr.mvd at gmail.com>:
> Dear Haskellers,
>
> I noticed that there is no common typeclass that would unify STRefs and
> IORefs. We already have MArray for ST(U)Arrays and IO(U)Arrays, so why not
> for references as well? This would allow writing generic code that can use
> both ST- and IO-based variables.
>
> I've found that there is a package that provides such a type class:
> http://hackage.haskell.org/package/reference
> I'd suggest to add similar functionality to base, perhaps with some
> different wording - I'd rather use Data.MRef (as "mutable reference").
>
> If there is some interest in it, I'd prepare a concrete code for
> consideration.
>
> Best regards,
> Petr Pudlak
>
>
> _______________________________________________
> Libraries mailing list
> Libraries at haskell.org
> http://www.haskell.org/mailman/listinfo/libraries
More information about the Libraries
mailing list