import System.Directory
import System.FilePath
import System.IO
-import System.IO.Error as IO
import Control.Monad
import Data.List ( isSuffixOf )
import Data.Maybe
-- modification times on all of the objects and libraries, then omit
-- linking (unless the -fforce-recomp flag was given).
let exe_file = exeFileName dflags
- e_exe_time <- IO.try $ getModificationTime exe_file
+ e_exe_time <- tryIO $ getModificationTime exe_file
case e_exe_time of
Left _ -> return True
Right t -> do
-- first check object files and extra_ld_inputs
extra_ld_inputs <- readIORef v_Ld_inputs
- e_extra_times <- mapM (IO.try . getModificationTime) extra_ld_inputs
+ e_extra_times <- mapM (tryIO . getModificationTime) extra_ld_inputs
let (errs,extra_times) = splitEithers e_extra_times
let obj_times = map linkableTime linkables ++ extra_times
if not (null errs) || any (t <) obj_times
pkg_libfiles <- mapM (uncurry findHSLib) pkg_hslibs
if any isNothing pkg_libfiles then return True else do
- e_lib_times <- mapM (IO.try . getModificationTime)
+ e_lib_times <- mapM (tryIO . getModificationTime)
(catMaybes pkg_libfiles)
let (lib_errs,lib_times) = splitEithers e_lib_times
if not (null lib_errs) || any (t <) lib_times
import Data.IORef
import System.FilePath
import System.IO
-import System.IO.Error ( try, isDoesNotExistError )
+import System.IO.Error ( isDoesNotExistError )
import Prelude hiding (init)
case maybe_buf of
Just (_,t) -> check_timestamp old_summary location src_fn t
Nothing -> do
- m <- System.IO.Error.try (getModificationTime src_fn)
+ m <- tryIO (getModificationTime src_fn)
case m of
Right t -> check_timestamp old_summary location src_fn t
Left e | isDoesNotExistError e -> find_it
createETagsFileCmd
) where
+import Exception
import GHC
import GhciMonad
import Outputable
import Data.List
import Control.Monad
import System.IO
-import System.IO.Error as IO
+import System.IO.Error
-----------------------------------------------------------------------------
-- create tags file for currently loaded modules.
-- ctags style with the Ex exresion being just the line number, Vim et al
collateAndWriteTags CTagsWithLineNumbers file tagInfos = do
let tags = unlines $ sortLe (<=) $ map showCTag tagInfos
- IO.try (writeFile file tags)
+ tryIO (writeFile file tags)
-- ctags style with the Ex exresion being a regex searching the line, Vim et al
collateAndWriteTags CTagsWithRegExes file tagInfos = do -- ctags style, Vim et al
tagInfoGroups <- makeTagGroupsWithSrcInfo tagInfos
let tags = unlines $ sortLe (<=) $ map showCTag $concat tagInfoGroups
- IO.try (writeFile file tags)
+ tryIO (writeFile file tags)
collateAndWriteTags ETags file tagInfos = do -- etags style, Emacs/XEmacs
tagInfoGroups <- makeTagGroupsWithSrcInfo $filter tagExported tagInfos
let tagGroups = map processGroup tagInfoGroups
- IO.try (writeFile file $ concat tagGroups)
+ tryIO (writeFile file $ concat tagGroups)
where
processGroup [] = ghcError (CmdLineError "empty tag file group??")
import System.Exit ( exitWith, ExitCode(..) )
import System.Directory
import System.IO
-import System.IO.Error as IO
+import System.IO.Error
import Data.Char
import Data.Array
import Control.Monad as Monad
withGhcAppData :: (FilePath -> IO a) -> IO a -> IO a
withGhcAppData right left = do
- either_dir <- IO.try (getAppUserDataDirectory "ghc")
+ either_dir <- tryIO (getAppUserDataDirectory "ghc")
case either_dir of
Right dir ->
do createDirectoryIfMissing False dir `catchIO` \_ -> return ()
(return Nothing)
home_dir = do
- either_dir <- liftIO $ IO.try (getEnv "HOME")
+ either_dir <- liftIO $ tryIO (getEnv "HOME")
case either_dir of
Right home -> return (Just (home </> ".ghci"))
_ -> return Nothing
dir_ok <- liftIO $ checkPerms (getDirectory file)
file_ok <- liftIO $ checkPerms file
when (dir_ok && file_ok) $ do
- either_hdl <- liftIO $ IO.try (openFile file ReadMode)
+ either_hdl <- liftIO $ tryIO (openFile file ReadMode)
case either_hdl of
Left _e -> return ()
-- NOTE: this assumes that runInputT won't affect the terminal;
fileLoop :: MonadIO m => Handle -> InputT m (Maybe String)
fileLoop hdl = do
- l <- liftIO $ IO.try $ hGetLine hdl
+ l <- liftIO $ tryIO $ hGetLine hdl
case l of
Left e | isEOFError e -> return Nothing
| InvalidArgument <- etype -> return Nothing
-- are really two stdin Handles. So we flush any bufferred data in
-- GHCi's stdin Handle here (only relevant if stdin is attached to
-- a file, otherwise the read buffer can't be flushed).
- _ <- liftIO $ IO.try $ hFlushAll stdin
+ _ <- liftIO $ tryIO $ hFlushAll stdin
result <- GhciMonad.runStmt stmt step
afterRunStmt (const True) result
changeDirectory :: String -> InputT GHCi ()
changeDirectory "" = do
-- :cd on its own changes to the user's home directory
- either_dir <- liftIO $ IO.try getHomeDirectory
+ either_dir <- liftIO $ tryIO getHomeDirectory
case either_dir of
Left _e -> return ()
Right dir -> changeDirectory dir
-- get the location of the user package database, and create it if necessary
-- getAppUserDataDirectory can fail (e.g. if $HOME isn't set)
- e_appdir <- try $ getAppUserDataDirectory "ghc"
+ e_appdir <- tryIO $ getAppUserDataDirectory "ghc"
mb_user_conf <-
if no_user_db then return Nothing else
modify || user_exists = [user_conf, global_conf]
| otherwise = [global_conf]
- e_pkg_path <- try (System.Environment.getEnv "GHC_PACKAGE_PATH")
+ e_pkg_path <- tryIO (System.Environment.getEnv "GHC_PACKAGE_PATH")
let env_stack =
case e_pkg_path of
Left _ -> sys_databases
| Just (user_conf,False) <- mb_user_conf, path == user_conf
= return PackageDB { location = path, packages = [] }
| otherwise
- = do e <- try $ getDirectoryContents path
+ = do e <- tryIO $ getDirectoryContents path
case e of
Left _ -> do
pkgs <- parseMultiPackageConf verbosity path
| otherwise -> do
let cache = path </> cachefilename
tdir <- getModificationTime path
- e_tcache <- try $ getModificationTime cache
+ e_tcache <- tryIO $ getModificationTime cache
case e_tcache of
Left ex -> do
when (verbosity > Normal) $
catchError io handler = io `Exception.catch` handler'
where handler' (Exception.ErrorCall err) = handler err
+tryIO :: IO a -> IO (Either Exception.IOException a)
+tryIO = Exception.try
writeBinaryFileAtomic :: Bin.Binary a => FilePath -> a -> IO ()
writeBinaryFileAtomic targetFile obj =