hpath-0.7.1: Support for well-typed paths

Copyright© 2016 Julian Ospald
LicenseGPL-2
MaintainerJulian Ospald <hasufell@posteo.de>
Stabilityexperimental
Portabilityportable
Safe HaskellSafe
LanguageHaskell2010

HPath.IO.Errors

Contents

Description

Provides error handling.

Synopsis

Types

data HPathIOException Source #

Instances

Eq HPathIOException Source # 
Data HPathIOException Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HPathIOException -> c HPathIOException #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c HPathIOException #

toConstr :: HPathIOException -> Constr #

dataTypeOf :: HPathIOException -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c HPathIOException) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c HPathIOException) #

gmapT :: (forall b. Data b => b -> b) -> HPathIOException -> HPathIOException #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HPathIOException -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HPathIOException -> r #

gmapQ :: (forall d. Data d => d -> u) -> HPathIOException -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> HPathIOException -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HPathIOException -> m HPathIOException #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HPathIOException -> m HPathIOException #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HPathIOException -> m HPathIOException #

Show HPathIOException Source # 
Exception HPathIOException Source # 

Exception identifiers

Path based functions

throwSameFile :: Path Abs -> Path Abs -> IO () Source #

Uses isSameFile and throws SameFile if it returns True.

sameFile :: Path Abs -> Path Abs -> IO Bool Source #

Check if the files are the same by examining device and file id. This follows symbolic links.

throwDestinationInSource Source #

Arguments

:: Path Abs

source dir

-> Path Abs

full destination, dirname dest must exist

-> IO () 

Checks whether the destination directory is contained within the source directory by comparing the device+file ID of the source directory with all device+file IDs of the parent directories of the destination.

doesFileExist :: Path Abs -> IO Bool Source #

Checks if the given file exists and is not a directory. Does not follow symlinks.

doesDirectoryExist :: Path Abs -> IO Bool Source #

Checks if the given file exists and is a directory. Does not follow symlinks.

isWritable :: Path Abs -> IO Bool Source #

Checks whether a file or folder is writable.

canOpenDirectory :: Path Abs -> IO Bool Source #

Checks whether the directory at the given path exists and can be opened. This invokes openDirStream which follows symlinks.

throwCantOpenDirectory :: Path Abs -> IO () Source #

Throws a Can'tOpenDirectory HPathIOException if the directory at the given path cannot be opened.

Error handling functions

catchErrno Source #

Arguments

:: [Errno]

errno to catch

-> IO a

action to try, which can raise an IOException

-> IO a

action to carry out in case of an IOException and if errno matches

-> IO a 

Carries out an action, then checks if there is an IOException and a specific errno. If so, then it carries out another action, otherwise it rethrows the error.

rethrowErrnoAs Source #

Arguments

:: Exception e 
=> [Errno]

errno to catch

-> e

rethrow as if errno matches

-> IO a

action to try

-> IO a 

Execute the given action and retrow IO exceptions as a new Exception that have the given errno. If errno does not match the exception is rethrown as is.

handleIOError :: (IOError -> IO a) -> IO a -> IO a Source #

Like catchIOError, with arguments swapped.

bracketeer Source #

Arguments

:: IO a

computation to run first

-> (a -> IO b)

computation to run last, when no exception was raised

-> (a -> IO b)

computation to run last, when an exception was raised

-> (a -> IO c)

computation to run in-between

-> IO c 

Like bracket, but allows to have different clean-up actions depending on whether the in-between computation has raised an exception or not.

reactOnError Source #

Arguments

:: IO a 
-> [(IOErrorType, IO a)]

reaction on IO errors

-> [(HPathIOException, IO a)]

reaction on HPathIOException

-> IO a