Re: [Haskell-cafe] Re: [Haskell] [ANN] Safe Lazy IO in Haskell

2009-05-18 Thread Ryan Ingram
On Mon, May 18, 2009 at 3:05 PM, Taral wrote: > Will this do? > > (>>=) :: (NFData sa, NFData b) => LI sa -> (sa -> LI b) -> LI b No, the problem is that >>= on monads has no constraints, it must have the type > LI a -> (a -> LI b) -> LI b This is a common problem with trying to use do-notation;

Re: [Haskell-cafe] Re: [Haskell] [ANN] Safe Lazy IO in Haskell

2009-05-18 Thread Miguel Mitrofanov
On 19 May 2009, at 09:06, Ryan Ingram wrote: This is a common problem with trying to use do-notation; there are some cases where you can't make the object an instance of Monad. The same problem holds for Data.Set; you'd can write setBind :: Ord b => Set a -> (a -> Set b) -> Set b setBind m f

Re: [Haskell-cafe] Re: [Haskell] [ANN] Safe Lazy IO in Haskell

2009-05-18 Thread Jason Dusek
2009/05/18 Miguel Mitrofanov : > On 19 May 2009, at 09:06, Ryan Ingram wrote: > >> This is a common problem with trying to use do-notation; there are >> some cases where you can't make the object an instance of Monad.  The >> same problem holds for Data.Set; you'd can write >> >> setBind :: Ord b =

Re: [Haskell-cafe] Re: [Haskell] [ANN] Safe Lazy IO in Haskell

2009-05-18 Thread Taral
On Mon, May 18, 2009 at 10:06 PM, Ryan Ingram wrote: > On Mon, May 18, 2009 at 3:05 PM, Taral wrote: >> Will this do? >> >> (>>=) :: (NFData sa, NFData b) => LI sa -> (sa -> LI b) -> LI b > > No, the problem is that >>= on monads has no constraints, it must have the > type >> LI a -> (a -> LI b)

Re: [Haskell-cafe] Re: [Haskell] [ANN] Safe Lazy IO in Haskell

2009-05-19 Thread Ryan Ingram
To be fair, you can do this with some extensions; I first saw this in a paper on Oleg's site [1]. Here's some sample code: {-# LANGUAGE NoImplicitPrelude, TypeFamilies, MultiParamTypeClasses #-} module SetMonad where import qualified Data.Set as S import qualified Prelude as P (Monad, (>>=), (>>)

Re: [Haskell-cafe] Re: [Haskell] [ANN] Safe Lazy IO in Haskell

2009-05-19 Thread Miguel Mitrofanov
I've posted it once or twice. newtype C m r a = C ((a -> m r) -> m r) It's a monad, regardless of whether m is one or not. If you have something like "return" and "bind", but not exactly the same, you can make "casting" functions m a -> C m r a and backwards. Jason Dusek wrote on 19.05.2009

Re: [Haskell-cafe] Re: [Haskell] [ANN] Safe Lazy IO in Haskell

2009-05-19 Thread Nicolas Pouillard
Excerpts from Ryan Ingram's message of Tue May 19 10:23:01 +0200 2009: > To be fair, you can do this with some extensions; I first saw this in > a paper on Oleg's site [1]. Here's some sample code: This seems like the same trick as the rmonad package: http://hackage.haskell.org/cgi-bin/hackage-sc

Re: [Haskell-cafe] Re: [Haskell] [ANN] Safe Lazy IO in Haskell

2009-05-19 Thread Ryan Ingram
Minor addition, optimize >> (I couldn't help myself!) -- ryan > instance Ord b => ConstrainedBind (S.Set a) (S.Set b) where >type BindElem (S.Set a) = a >m >>= f = S.unions $ map f $ S.toList m >m >> n = if S.null m then S.empty else n __

RE: [Haskell-cafe] Re: [Haskell] [ANN] Safe Lazy IO in Haskell

2009-05-19 Thread Sittampalam, Ganesh
Nicolas Pouillard wrote: > Excerpts from Ryan Ingram's message of Tue May 19 10:23:01 +0200 2009: >> To be fair, you can do this with some extensions; I first saw this in >> a paper on Oleg's site [1]. Here's some sample code: > > This seems like the same trick as the rmonad package: > http://hac

Re: [Haskell-cafe] Re: [Haskell] [ANN] Safe Lazy IO in Haskell

2009-05-19 Thread Ryan Ingram
On Tue, May 19, 2009 at 12:54 AM, Miguel Mitrofanov wrote: > I've posted it once or twice. > > newtype C m r a = C ((a -> m r) -> m r) > > It's a monad, regardless of whether m is one or not. If you have something > like "return" and "bind", but not exactly the same, you can make "casting" > funct