
I note that all of your "broken" issues revolve around calls that
can't be written in terms of lift; that is, you need access to the STT
constructor in order to create these problems.
It's obvious that anything that accesses the STT constructor will
potentially not be typesafe; the question I have is that whether you
can construct something that isn't typesafe just via the use of runSTT
& lift.
If you wanted to implement callCC directly (as opposed to lift .
callCC) you would need to be extremely careful, as you noticed.
-- ryan
On Fri, Feb 27, 2009 at 2:27 PM, David Menendez
On Fri, Feb 27, 2009 at 1:28 PM, Ryan Ingram
wrote: Then it comes down to, within a session, is there some way for an STTRef to "mingle" and break the type-safety rule. I can think of two potential ways this might happen. First, if the underlying monad is something like List or Logic, there may be a way for STTRefs to move between otherwise unrelated branches of the computation. Second, if the underlying monad is something like Cont, there may be a way for an STTRef to get transmitted "back in time" via a continuation to a point where it hadn't been allocated yet.
I think promoting MonadPlus would be safe. The code for mplus will end up looking something like:
mplus (STT a) (STT b) = STT (StateT (\heap -> runStateT a heap `mplus` runStateT b heap))
so each branch is getting its own copy of the heap.
The fancier logic stuff, like msplit, doesn't promote well through StateT, and isn't type-safe in STT
For example:
class (MonadPlus m) => ChoiceMonad m where msplit :: m a -> m (Maybe (a, m a))
instance ChoiceMonad [] where msplit [] = [Nothing] msplit (x:xs) = [Just (x,xs)]
There are at least two ways to promote msplit through StateT. The method I used in my library is,
instance (ChoiceMonad m) => ChoiceMonad (StateT s m) where msplit m = StateT $ \s -> msplit (runStateT m s) >>= return . maybe (Nothing, s) (\ ((a,s'),r) -> (Just (a, StateT (\_ -> r)), s'))
If you promoted that instance through STT, it would no longer be safe.
test = do Just (_, rest) <- msplit $ mplus (return ()) (return ()) ref1 <- newSTTRef 'a' rest ref2 <- newSTTRef (65 :: Int) readSTTRef ref1
The call to "rest" effectively undoes the first call to newSTTRef, so that ref1 and ref2 end up referring to the same cell in the heap.
I'm confident callCC and shift will cause similar problems.
-- Dave Menendez
http://www.eyrie.org/~zednenem/