[Haskell] unsafeInterleaveST

Bulat Ziganshin bulatz at HotPOP.com
Mon Feb 6 10:31:17 EST 2006


Hello haskell,

is it possible to implement unsafeInterleaveST?

why i want it: i have the following definitions:

class (MonadHelper m) => Stream m h where
    vGetContents :: h -> m String

    -- default definition
    vGetContents h = mUnsafeInterleaveIO $ do
                         eof <- vIsEOF h
                         if eof
                           then return []
                           else do x <- vGetChar h
                                   x `seq` return ()
                                   xs <- vGetContents h
                                   return (x:xs)

class (Monad m) => MonadHelper m where
    mUnsafeInterleaveIO :: m a -> m a

instance MonadHelper IO where
    mUnsafeInterleaveIO = unsafeInterleaveIO

instance MonadHelper (ST s) where
    mUnsafeInterleaveIO = id


that allows to make much more efficient lazy implementation of
vGetContents for streams that work in IO monad. on the other side,
ST-based streams will need to build full list before returning from
vGetContents. if the unsafeInterleaveST is possible, then this type of
computations will become much more efficient

moreover, this can be way to mix up several ST computations and to
implicitly define parallelism in algorithm so that compiler can better
optimize program

-- 
Best regards,
 Bulat                          mailto:bulatz at HotPOP.com





More information about the Haskell mailing list