New style exceptions...

Hi there, Exception handling in RWH is called old-style and deprecated. I didn't find a tutorial telling how to do the new style. Here I created two examples both dealing with an exception when creating a directory. I would like to know if the way I did is ok or not. Improvements resp. corrections are most welcome First way: <--------------snip------------------------------------> {-# LANGUAGE ScopedTypeVariables #-} module Main where import System.Exit import System.Directory import Control.Exception import Prelude hiding ( catch, readFile ) main :: IO () main = do handle (\(e :: SomeException) -> print $ show e) $ do createDirectoryIfMissing True "/tmr/a/b/c/d" _ <- exitWith $ ExitFailure 1 return () print "Directory created successfully" <--------------snap------------------------------------> Second way: <--------------snip------------------------------------> module Main where import System.Exit import System.Directory import Control.Exception import Prelude hiding ( catch, readFile ) main :: IO () main = do catch (createDirectoryIfMissing True "/tmr/a/b/c/d") exhandler print "Directory created successfully" where exhandler :: SomeException -> IO () exhandler e = do print e _ <- exitWith $ ExitFailure 1 return () <--------------snap------------------------------------> -- Tnanks, Manfred

On Wed, 10 Aug 2011 07:01:42 +0200
Manfred Lotz
Hi there, Exception handling in RWH is called old-style and deprecated. I didn't find a tutorial telling how to do the new style.
Here I created two examples both dealing with an exception when creating a directory.
I would like to know if the way I did is ok or not. Improvements resp. corrections are most welcome
First way:
<--------------snip------------------------------------> {-# LANGUAGE ScopedTypeVariables #-} module Main where
import System.Exit import System.Directory import Control.Exception
import Prelude hiding ( catch, readFile )
main :: IO () main = do handle (\(e :: SomeException) -> print $ show e) $ do createDirectoryIfMissing True "/tmr/a/b/c/d" _ <- exitWith $ ExitFailure 1 return () print "Directory created successfully" <--------------snap------------------------------------>
This was stupid. Should be like this: main :: IO () main = do handle (\(e :: SomeException) -> do print $ show e _ <- exitWith $ ExitFailure 1 return () ) $ do createDirectoryIfMissing True "/tmr/a/b/c/d" print "Directory created successfully" -- Manfred
participants (1)
-
Manfred Lotz