Skip to content
Snippets Groups Projects
Commit d26eaafa authored by Ian Lynagh's avatar Ian Lynagh
Browse files

Replace uses of the old catch function with the new one

parent 875b9103
No related branches found
No related tags found
No related merge requests found
......@@ -28,7 +28,7 @@ import Data.Char
-- been introduced in that module, accessed by tick-number position
-- in the list
import Trace.Hpc.Util (HpcPos, insideHpcPos, Hash, HpcHash(..))
import Trace.Hpc.Util (HpcPos, insideHpcPos, Hash, HpcHash(..), catchIO)
import Trace.Hpc.Tix
-- | 'Mix' is the information about a modules static properties, like
......@@ -98,7 +98,7 @@ readMix dirNames mod' = do
Left _ -> True
Right tix -> h == tixModuleHash tix
) -> return $ Just r
_ -> return $ Nothing) `catch` (\ _ -> return $ Nothing)
_ -> return $ Nothing) `catchIO` (\ _ -> return $ Nothing)
| dirName <- dirNames
]
case catMaybes res of
......
......@@ -9,7 +9,7 @@ module Trace.Hpc.Tix(Tix(..), TixModule(..),
readTix, writeTix, getTixFileName) where
import Data.List (isSuffixOf)
import Trace.Hpc.Util(Hash)
import Trace.Hpc.Util (Hash, catchIO)
-- 'Tix ' is the storage format for our dynamic imformation about what
-- boxes are ticked.
......@@ -34,11 +34,11 @@ tixModuleTixs (TixModule _ _ _ tixs) = tixs
-- read a Tix File.
readTix :: String
-> IO (Maybe Tix)
readTix tix_filename =
catch (do contents <- readFile $ tix_filename
return $ Just $ read contents)
(\ _ -> return $ Nothing)
-> IO (Maybe Tix)
readTix tix_filename =
catchIO (do contents <- readFile $ tix_filename
return $ Just $ read contents)
(\ _ -> return $ Nothing)
-- write a Tix File.
writeTix :: String
......
......@@ -11,8 +11,10 @@ module Trace.Hpc.Util
, insideHpcPos
, HpcHash(..)
, Hash
, catchIO
) where
import qualified Control.Exception as Exception
import Data.List(foldl')
import Data.Char (ord)
import Data.Bits (xor)
......@@ -103,3 +105,7 @@ instance HpcHash HpcPos where
hxor :: Hash -> Hash -> Hash
hxor (Hash x) (Hash y) = Hash $ x `xor` y
catchIO :: IO a -> (Exception.IOException -> IO a) -> IO a
catchIO = Exception.catch
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment