Problem with lexically scoped type variables.

Mirko Rahn rahn at ira.uka.de
Mon Oct 2 10:06:07 EDT 2006


Dear all, in

http://www.haskell.org/pipermail/glasgow-haskell-users/2006-January/009565.html

Simon Peyton-Jones asks for programs that are broken by the proposed 
change. Here is a nearly real world one:

{-# OPTIONS_GHC -fglasgow-exts #-}

import Control.Monad
import Control.Monad.ST
import Data.Array.MArray
import Data.Array.ST
import Data.STRef
import Data.Set hiding (map,filter)

-- a store that allows to mark keys
class Mark m store key | store -> key m where
     new   :: (key,key) -> m store
     mark  :: store -> key -> m ()
     markQ :: store -> key -> m Bool
     seen  :: store -> m [ key ]

-- implementation 1
instance Ord key => Mark (ST s) (STRef s (Set key)) key where
     new   _   = newSTRef empty
     mark  s k = modifySTRef s (insert k)
     markQ s k = liftM (member k) (readSTRef s)
     seen  s   = liftM elems (readSTRef s)

-- implementation 2
instance Ix key => Mark (ST s) (STUArray s key Bool) key where
     new   bnd = newArray bnd False
     mark  s k = writeArray s k True
     markQ     = readArray
     seen  s   = liftM (map fst . filter snd) (getAssocs s)

-- traversing the hull suc^*(start) with loop detection
trav suc start i = new i >>= \ c -> mapM_ (compo c) start >> return c
     where compo c x = markQ c x >>= flip unless (visit c x)
	  visit c x = mark c x >> mapM_ (compo c) (suc x)

-- sample graph
f 1 = 1 : []
f n = n : f (if even n then div n 2 else 3*n+1)

t1 = runST (trav f [1..10] (1,52) >>= \ (s::STRef s (Set Int)) -> seen s)
t2 = runST (trav f [1..10] (1,52) >>= \ (s::STUArray s Int Bool) -> seen s)

In ghc-6.4.2 this works as expected, but ghc-6.5.20061001 says

B.hs:40:44:
     A pattern type signature cannot bind scoped type variables `s'
       unless the pattern has a rigid type context
     In the pattern: s :: STRef s (Set Int)
     In a lambda abstraction: \ (s :: STRef s (Set Int)) -> seen s
     In the second argument of `(>>=)', namely
         `\ (s :: STRef s (Set Int)) -> seen s'

Unfortunately I cannot find an easy workaround but use similiar patterns 
somewhere deeply nested in my programs...

Is there a simple workaround? Could we relax the rules for lexically 
scoped type variables a bit?

Regards, Mirko Rahn

-- 
-- Mirko Rahn -- Tel +49-721 608 7504 --
--- http://liinwww.ira.uka.de/~rahn/ ---


More information about the Glasgow-haskell-users mailing list