[Haskell-cafe] ANN: monad-interleave 0.1

Patrick Perry patperry at stanford.edu
Thu Jan 15 14:49:59 EST 2009


My two favorite functions in Haskell are "unsafeInterleaveIO" and  
"unsafeInterleaveST".  I'm surprised there isn't a type class for  
them.  I just fixed this by adding the "monad-interleave" package to  
hackage:

http://hackage.haskell.org/cgi-bin/hackage-scripts/package/monad-interleave

The package adds a "Control.Monad.Interleave" module.  Here is the  
entirety of the module:

\begin{code}
-- | Monads that have an operation like 'unsafeInterleaveIO'.
class Monad m => MonadInterleave m where
     -- | Get the baton from the monad without doing any computation.
     unsafeInterleave :: m a -> m a

instance MonadInterleave IO where
     unsafeInterleave = unsafeInterleaveIO
     {-# INLINE unsafeInterleave #-}

instance MonadInterleave (ST s) where
     unsafeInterleave = unsafeInterleaveST
     {-# INLINE unsafeInterleave #-}

instance MonadInterleave (Lazy.ST s) where
     unsafeInterleave = Lazy.unsafeInterleaveST
     {-# INLINE unsafeInterleave #-}
\end{code}

Use it if you need it.


Patrick




More information about the Haskell-Cafe mailing list