
You can roll your own pure STT monad, at the cost of performance:
-- Do not export any of these constructors, just the types STT and STTRef.
data W = forall a. W !a
data Heap s = Heap !Int !(IntMap W)
newtype STT s m a = STT (StateT (Heap s) m a) deriving (Monad,
MonadTrans, MonadIO, insert other stuff here, but not MonadState)
newtype STTRef s a = Ref Int
liftState :: (MonadState s m) => (s -> (a,s)) -> m a
liftState f = do
(a, s') <- liftM f get
put s'
return a
newSTTRef :: forall s m a. a -> STT s m a
newSTTRef a = STT $ liftState go where
go (Heap sz m) = (Ref sz, Heap (sz+1) (insert sz (W a) m)
readSTTRef :: forall s m a. STTRef s a -> STT s m a
readSTTRef (Ref n) = STT $ liftM go get where
go (Heap _ m) = case lookup n m of
Just (~(W a)) -> unsafeCoerce a
_ -> error "impossible: map lookup failed."
writeSTTRef :: forall s m a. STTRef s a -> a -> STT s m ()
writeSTTRef (Ref n) a = STT $ modify go where
go (Heap sz m) = Heap sz (insert n (W a) m)
-- forall s. here makes unsafeCoerce in readSTTRef safe. Otherwise
references could escape and break unsafeCoerce.
runSTT :: (forall s. STT s m a) -> m a
runSTT (STT m) = evalStateT m (Heap 0 empty)
instance (MonadState s m) => MonadState s (STT st m) where
get = lift get
put = lift . put
modify = lift . modify
Unfortunately, you lose garbage collection on referenced data since
it's all stored in an IntMap. Is there a way to solve this problem,
perhaps using some form of weak reference? Ideally you'd like to be
able to find that all references to a particular Ref have been GC'd so
that you can reuse that Ref index. Otherwise eventually the IntMap
will fill up if you keep allocating references and throwing them away.
-- ryan
2009/2/15 Louis Wasserman
Well, it makes me sad, I guess. pqueue-mtl provides an array-backed heap monad transformer that is supposed to keep its own ST thread, if only for the sake of retaining a purely functional interface without any externally visible forall'd types, which is perfectly fine in most cases, but I'd have to think about whether or not it'd remain referentially transparent if the ST thread were only visible to a very tightly encapsulated set of commands (i.e. priority queue operations).
Louis Wasserman wasserman.louis@gmail.com
On Sun, Feb 15, 2009 at 5:33 PM, Henning Thielemann
wrote: On Sun, 15 Feb 2009, Louis Wasserman wrote:
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?
I assume that ST must always be the most inner monad, like IO. Is this a problem in an application?
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe