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

Ryan Ingram ryani.spam at gmail.com
Tue May 19 04:23:01 EDT 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:

{-# LANGUAGE NoImplicitPrelude, TypeFamilies, MultiParamTypeClasses #-}
module SetMonad where
import qualified Data.Set as S
import qualified Prelude as P (Monad, (>>=), (>>), return, fail)
import Prelude hiding (Monad, (>>=), (>>), return, fail)

class ConstrainedPoint pa where
    type PointElem pa
    return :: PointElem pa -> pa

class ConstrainedBind ma mb where
    type BindElem ma
    (>>=) :: ma -> (BindElem ma -> mb) -> mb
    (>>) :: ma -> mb -> mb
    m >> n = m >>= const n

class ConstrainedFail pa where
    fail :: String -> pa

instance ConstrainedPoint (S.Set a) where
    type PointElem (S.Set a) = a
    return = S.singleton

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

test :: S.Set Int
test = do
    x <- S.fromList [1,2,3]
    y <- S.fromList [1,2,3]
    return (x+y)

-- ghci> test
-- fromList [2,3,4,5,6]

  -- ryan

[1] http://www.okmij.org/ftp/Haskell/types.html#restricted-datatypes

On Tue, May 19, 2009 at 12:46 AM, Henning Thielemann
<lemming at henning-thielemann.de> wrote:
>
> On Mon, 18 May 2009, Nicolas Pouillard wrote:
>
>> Excerpts from Jason Dusek's message of Sun May 17 15:45:25 +0200 2009:
>>>
>>>  From the documentation:
>>>
>>>  "  LI could be a strict monad and a strict applicative functor.
>>>    However it is not a lazy monad nor a lazy applicative
>>>    functor as required Haskell. Hopefully it is a lazy
>>>    (pointed) functor at least.
>>
>> The type I would need for bind is this one:
>>
>>  (>>=) :: NFData sa => LI sa -> (sa -> LI b) -> LI b
>>
>> And because of the NFData constraint this type bind is less general than
>> the
>> required one.
>
> Looks very similar to the operator I need for binding with respect to
> asynchronous exceptions:
>
> bind :: (Monoid a, Monad m) =>
>   ExceptionalT e m a -> (a -> ExceptionalT e m b) -> ExceptionalT e m b
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>


More information about the Haskell-Cafe mailing list