[Haskell-beginners] Re: How to create a monad instance

Marco De Oliveira deolivem at gmail.com
Sat Dec 12 05:18:51 EST 2009


2009/12/12 Maciej Piechotka <uzytkownik2 at gmail.com>:
> On Sat, 2009-12-12 at 01:17 +0100, Marco De Oliveira wrote:
>> Hi,
>>
>> Is it possible to create an instance of Monad for IOException?
>> Each time a try I stay blocked by IO monad.
>>
>> with the definition:
>>
>> data IOException a = IOExceptionCons (IO (Exception a))
>>
>> data Exception a = SuccessCons (Maybe Warning) a
>>                           | ErrorCons Error
>>
>> data Warning = WarningCons1
>>                     | WarningCons2
>>
>> data Error = ErrorCons1
>>                 | ErrorCons2
>>
>> Regards
>
> Yes - to begin with:
>
> newtype IOException a = IOException {runIOException :: IO (Exception a)}
>
> data Exception a = Success (Maybe Warning) a
>                 | Exception Error
>
> data Warning = Warning1
>             | Warning2
> data Error = Error1
>           | Error2
>
> instance Monad Exception where
>    return = Success Nothing
>    (Success w v) >>= f = f v
> --    (Success w v) >>= f = case f v of
> --                            Success _ v' -> Success w v'
> --                            Exception e  -> Exception e
>    (Exception e) >>= _ = Exception e
> instance Monad IOException where
>    return = IOException . return . return
>    m >>= f = IOException $ runIOException m >>= runIOException . f
>
> However:
> 1. What should be the combination of warnings I'd rather threat them as
> some 'proper' monoid (for ex. List instead of Maybe)
> 2. It is much easier to use mtl:
> type IOException = ErrorT (Either Error) (WriterT [Warning] IO)
>
> Regards
>
>
> _______________________________________________
> Beginners mailing list
> Beginners at haskell.org
> http://www.haskell.org/mailman/listinfo/beginners
>

Thanks for your help.

I have try your code ghci and I think there is a mistake in the
definition of (>>=) operator.

test1 m f = IOException $ runIOException m >>= runIOException . f
:t test1
test1 :: IOException a
         -> (Exception a -> IOException a)
         -> IOException a

I think the defintion is:
test :: IOException a -> ( a -> IOException a) -> IOException a

1. why I am not using monoid? I try to bind C code and the function
return only one warning. But if I change i little the structure of
IOException, it may have sense to use a List.
newtype IOException a = IOException {runIOException :: ([Warning] ->
IO (Exception a))}

2. Sorry but I have a lot of difficulties to understand the concept of
Monad Transformers


More information about the Beginners mailing list