[Haskell] Catching error / making library functions monadic
(in failure)
Mitchell, Neil
neil.mitchell.2 at credit-suisse.com
Wed Oct 8 10:42:16 EDT 2008
Hi Philip,
You might want to take a look at the Safe library, which does pretty close to what you request.
http://www-users.cs.york.ac.uk/~ndm/safe/
(or cabal install safe)
I would happily accept a patch adding *Fail variants that failed in some appropriate Monad if that is what you want.
Thanks
Neil
> -----Original Message-----
> From: haskell-bounces at haskell.org
> [mailto:haskell-bounces at haskell.org] On Behalf Of Philip K.F.
> Hölzenspies
> Sent: 08 October 2008 3:38 pm
> To: haskell at haskell.org
> Subject: [Haskell] Catching error / making library functions
> monadic (in failure)
>
> Dear Hask'lers,
>
> I'm working on a graph generator that involves a lot of
> random selection out of a list of vertices. Basically, there
> are functions that look a little like
> this:
>
> select vs = randomRM (0,length vs - 1) >>= return . (vs !!)
>
> where randomRM is a lot like Random.randomRIO, except that it
> is not in the IO monad, but rather in any monad, i.e.
>
> class Monad m => RandomM m where
> randomM :: m a
> randomRM :: (a,a) -> m a
>
> instance RandomM IO where
> randomM = randomIO
> randomRM = randomRIO
>
> The problem is, obviously, that when the list of vertices
> (vs) is empty, "select vs" will result in an error. The
> Prelude defines (!!) as:
>
> xs !! n | n < 0 = error "Prelude.!!: negative index"
> [] !! _ = error "Prelude.!!: index too large"
> (x:_) !! 0 = x
> (_:xs) !! n = xs !! (n-1)
>
> The function 'error' is implemented (at least in GHC) using
> Control.Exception.throw. Unfortunately, 'catch' does not seem
> to work. From
> ghci:
>
> Prelude> catch (return $ [] !! 0) (const $ putStrLn "foo" >>
> return 42)
> *** Exception: Prelude.(!!): index too large
>
> Is there any way to catch errors in functions in libraries
> (like the Prelude)?
> This is made even more necessary by the fact that the default
> implementation for 'fail' in a monad is 'error'. I would
> already be happy if I could make all applications of error
> change into applications of fail, as defined in my monad.
> Preferably, though, I would not even need a failure mechanism
> in my own monad, but rather have an ErrorMonad (or something
> similar) and just have
>
> class Monad m => ErrorMonad error m | m -> error where
> onError :: m a -> (error -> a) -> a
>
> For now, I simply reimplement the functions I need that give errors.
>
> Regards,
> Philip
> _______________________________________________
> Haskell mailing list
> Haskell at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell
>
>
==============================================================================
Please access the attached hyperlink for an important electronic communications disclaimer:
http://www.credit-suisse.com/legal/en/disclaimer_email_ib.html
==============================================================================
More information about the Haskell
mailing list