[Haskell] Incoherent instances can make ST monad unsound

oleg at pobox.com oleg at pobox.com
Thu Jan 26 23:29:41 EST 2006


In the recent message about regions I wrote:
> Typeable constraint has reduced the problem of 'region nesting' to the
> regular problem of the 'linearity' of computations -- which is already
> solved in ST monad. We can add that pervasive 's' type parameter to
> our Q and IOM types. However, the simpler approach is just to use our
> 'mark' as that 's' parameter.

A small qualification should be added: although adding the 's'
parameter in addition to the unexported Z parameter we had before is
sound in all circumstances, the `simpler approach' may actually fail:
it is possible to declare an instance "Typeable a" -- and given enough
extensions, persuade GHC *and* Hugs to accept the code. The problem
with IO regions would be the least of our worries however: in these
circumstances, many things break, including the ST monad. One can
indeed break the essential guarantee of the ST monad -- for example,
create a top level STRef *and* fruitfully use in arbitrary ST
computations. The enclosed code does exactly that. Thus,
unsafePerformST becomes expressible in Haskell, given enough
features. The presence of top-level mutable cells breaks the
referential transparency. Hopefully the authors of Haskell' and
Haskell2 would attach all-upper-case warnings to these extensions.

The code below runs with GHC 6.4.1 (extensions are indicated
inline). It also runs with Hugs, as  hugs -98 +O /tmp/st.hs


{-# OPTIONS -fglasgow-exts #-}
{-# OPTIONS -fallow-undecidable-instances #-}
{-# OPTIONS -fallow-overlapping-instances #-}
{-# OPTIONS -fallow-incoherent-instances #-}

module STTest where

import Control.Monad.ST
import Data.Typeable
import Data.STRef
import Data.Dynamic

instance Typeable a where
    typeOf _ = mkTyConApp (mkTyCon "Anything goes") []


-- test1 = runST ( newSTRef 'a' )
leakedST = runST ( newSTRef 'a' >>= return . toDyn )

test3 :: Char
test3 = runST (readSTRef $ ((fromDyn leakedST undefined)::STRef s Char))

{- result:

*STTest> leakedST
<<STRef Anything goes Char>>
*STTest> test3
'a'
-}


More information about the Haskell mailing list