Send Beginners mailing list submissions to
        [email protected]

To subscribe or unsubscribe via the World Wide Web, visit
        http://www.haskell.org/mailman/listinfo/beginners
or, via email, send a message with subject or body 'help' to
        [email protected]

You can reach the person managing the list at
        [email protected]

When replying, please edit your Subject line so it is more specific
than "Re: Contents of Beginners digest..."


Today's Topics:

   1.  Exception Handling with Iteratees (Michael Craig)
   2. Re:  Exception Handling with Iteratees (Felipe Almeida Lessa)


----------------------------------------------------------------------

Message: 1
Date: Tue, 22 Nov 2011 01:35:46 -0500
From: Michael Craig <[email protected]>
Subject: [Haskell-beginners] Exception Handling with Iteratees
To: [email protected]
Message-ID:
        <caha9zaetyazaik44qozb1nbpudri0drhscjwmu3dc0uwglk...@mail.gmail.com>
Content-Type: text/plain; charset="iso-8859-1"

I have some exception types defined ...

    data POSTOnlyException = POSTOnlyException
        deriving ( Show, Typeable )
    instance Exception POSTOnlyException

    data BadPathException = BadPathException
        deriving ( Show, Typeable )
    instance Exception BadPathException

... and I want to use Data.Enumerator.catchError ...

    catchError :: Monad m => Iteratee a m b -> (SomeException -> Iteratee a
m b) -> Iteratee a m b

... so I define an error handler ...

    handleErrors :: SomeException -> Iteratee a m String
    handleErrors ex = case fromException ex of
        Just POSTOnlyException -> return "POSTs only!"
        Just BadPathException -> return "Bad path!"
        _ -> return "Unknown exception!"

... but of course this doesn't compile, because the types of the LHSs in
the case statement are different. I can get around it with some ugliness ...

    handleErrors :: SomeException -> Iteratee a m String
    handleErrors ex = case fromException ex of
        Just POSTOnlyException -> return "POSTs only!"
        _ -> case fromException ex of
            Just BadPathException -> return "Bad path!"
            _ -> return "Unknown exception!"

... but there must be a better way. Enlighten me?

Cheers,
Mike S Craig
-------------- next part --------------
An HTML attachment was scrubbed...
URL: 
<http://www.haskell.org/pipermail/beginners/attachments/20111122/532c4765/attachment-0001.htm>

------------------------------

Message: 2
Date: Tue, 22 Nov 2011 04:42:14 -0200
From: Felipe Almeida Lessa <[email protected]>
Subject: Re: [Haskell-beginners] Exception Handling with Iteratees
To: Michael Craig <[email protected]>
Cc: [email protected]
Message-ID:
        <CANd=ogejjdp9ejhurg15khlha53sdiy7kaxdgqu5ixscvan...@mail.gmail.com>
Content-Type: text/plain; charset=UTF-8

On Tue, Nov 22, 2011 at 4:35 AM, Michael Craig <[email protected]> wrote:
> ... but of course this doesn't compile, because the types of the LHSs in the
> case statement are different. I can get around it with some ugliness ...
> ? ? handleErrors :: SomeException -> Iteratee a m String
> ? ? handleErrors ex = case fromException ex of
> ? ? ? ? Just POSTOnlyException -> return "POSTs only!"
> ? ? ? ? _ -> case fromException ex of
> ? ? ? ? ? ? Just BadPathException -> return "Bad path!"
> ? ? ? ? ? ? _ -> return "Unknown exception!"
> ... but there must be a better way. Enlighten me?

If you enable the ViewPatterns extension

    {-# LANGUAGE ViewPatterns #-}

then you can write handleErrors as

    handleErrors :: SomeException -> Iteratee a m String
    handleErrors (fromException -> Just POSTOnlyException) = return
"POSTs only!"
    handleErrors (fromException -> Just BadPathException) = return "Bad path!"
    handleErrors _ = return "Unknown exception!"

Cheers,

-- 
Felipe.



------------------------------

_______________________________________________
Beginners mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/beginners


End of Beginners Digest, Vol 41, Issue 29
*****************************************

Reply via email to