[Haskell-cafe] Re: Haskell stacktrace

Krzysztof Kościuszkiewicz k.kosciuszkiewicz at gmail.com
Tue Sep 9 17:51:56 EDT 2008


On Tue, Sep 09, 2008 at 11:06:43PM +0200, Pieter Laeremans wrote:
> This :
> Prelude> let f = (\x -> return "something went wrong")  ::   IOError -> IO
> String
> Prelude> let t = return $ show $ "too short list" !! 100 :: IO String
> Prelude> catch t f
> "*** Exception: Prelude.(!!): index too large

How about:

> module Main where
>
> import Control.Exception
> import Prelude hiding (catch)
>
> f :: Exception -> IO String
> f = const $ return "sthg went wrong"
>
> g :: String
> g = show $ "too short list" !! 100
>
> h :: IO String
> h = do
>   print $ head [0 .. -1]
>   return "huh?"
>
> main = do
>   mapM_ print =<< sequence
>       [ h `catch` f
>       , evaluate g `catch` f
>       , (return $! g) `catch` f
>       , (return g) `catch` f
>       ]

Output:

kokr at copper:/tmp$ runhaskell test.lhs
"sthg went wrong"
"sthg went wrong"
"sthg went wrong"
"test.lhs: Prelude.(!!): index too large

Check documentation of catch and evaluate functions in Control.Exception.

Regards,
-- 
Krzysztof Kościuszkiewicz
Skype: dr.vee,  Gadu: 111851,  Jabber: kokr at jabster.pl
"Simplicity is the ultimate sophistication" -- Leonardo da Vinci


More information about the Haskell-Cafe mailing list