{-# LANGUAGE Trustworthy #-}
{-# LANGUAGE NoImplicitPrelude #-}

-----------------------------------------------------------------------------
-- |
-- Module      :  System.IO.Error
-- Copyright   :  (c) The University of Glasgow 2001
-- License     :  BSD-style (see the file libraries/base/LICENSE)
--
-- Maintainer  :  libraries@haskell.org
-- Stability   :  provisional
-- Portability :  portable
--
-- Standard IO Errors.
--
-----------------------------------------------------------------------------

module System.IO.Error (

    -- * I\/O errors
    IOError,

    userError,

    mkIOError,

    annotateIOError,

    -- ** Classifying I\/O errors
    isAlreadyExistsError,
    isDoesNotExistError,
    isAlreadyInUseError,
    isFullError,
    isEOFError,
    isIllegalOperation,
    isPermissionError,
    isUserError,
    isResourceVanishedError,

    -- ** Attributes of I\/O errors
    ioeGetErrorType,
    ioeGetLocation,
    ioeGetErrorString,
    ioeGetHandle,
    ioeGetFileName,

    ioeSetErrorType,
    ioeSetErrorString,
    ioeSetLocation,
    ioeSetHandle,
    ioeSetFileName,

    -- * Types of I\/O error
    IOErrorType,                -- abstract

    alreadyExistsErrorType,
    doesNotExistErrorType,
    alreadyInUseErrorType,
    fullErrorType,
    eofErrorType,
    illegalOperationErrorType,
    permissionErrorType,
    userErrorType,
    resourceVanishedErrorType,

    -- ** 'IOErrorType' predicates
    isAlreadyExistsErrorType,
    isDoesNotExistErrorType,
    isAlreadyInUseErrorType,
    isFullErrorType,
    isEOFErrorType,
    isIllegalOperationErrorType,
    isPermissionErrorType,
    isUserErrorType,
    isResourceVanishedErrorType,

    -- * Throwing and catching I\/O errors

    ioError,

    catchIOError,
    tryIOError,

    modifyIOError,
  ) where

import Control.Exception.Base

import Data.Either
import Data.Maybe

import GHC.Base
import GHC.IO
import GHC.IO.Exception
import GHC.IO.Handle.Types
import Text.Show

-- | The construct 'tryIOError' @comp@ exposes IO errors which occur within a
-- computation, and which are not fully handled.
--
-- Non-I\/O exceptions are not caught by this variant; to catch all
-- exceptions, use 'Control.Exception.try' from "Control.Exception".
--
-- @since 4.4.0.0
tryIOError     :: IO a -> IO (Either IOError a)
tryIOError :: forall a. IO a -> IO (Either IOError a)
tryIOError IO a
f   =  IO (Either IOError a)
-> (IOError -> IO (Either IOError a)) -> IO (Either IOError a)
forall e a. Exception e => IO a -> (e -> IO a) -> IO a
catch (do a
r <- IO a
f
                            Either IOError a -> IO (Either IOError a)
forall (m :: * -> *) a. Monad m => a -> m a
return (a -> Either IOError a
forall a b. b -> Either a b
Right a
r))
                        (Either IOError a -> IO (Either IOError a)
forall (m :: * -> *) a. Monad m => a -> m a
return (Either IOError a -> IO (Either IOError a))
-> (IOError -> Either IOError a)
-> IOError
-> IO (Either IOError a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. IOError -> Either IOError a
forall a b. a -> Either a b
Left)

-- -----------------------------------------------------------------------------
-- Constructing an IOError

-- | Construct an 'IOError' of the given type where the second argument
-- describes the error location and the third and fourth argument
-- contain the file handle and file path of the file involved in the
-- error if applicable.
mkIOError :: IOErrorType -> String -> Maybe Handle -> Maybe FilePath -> IOError
mkIOError :: IOErrorType -> String -> Maybe Handle -> Maybe String -> IOError
mkIOError IOErrorType
t String
location Maybe Handle
maybe_hdl Maybe String
maybe_filename =
               IOError :: Maybe Handle
-> IOErrorType
-> String
-> String
-> Maybe CInt
-> Maybe String
-> IOError
IOError{ ioe_type :: IOErrorType
ioe_type = IOErrorType
t,
                        ioe_location :: String
ioe_location = String
location,
                        ioe_description :: String
ioe_description = String
"",
                        ioe_errno :: Maybe CInt
ioe_errno = Maybe CInt
forall a. Maybe a
Nothing,
                        ioe_handle :: Maybe Handle
ioe_handle = Maybe Handle
maybe_hdl,
                        ioe_filename :: Maybe String
ioe_filename = Maybe String
maybe_filename
                        }

-- -----------------------------------------------------------------------------
-- IOErrorType

-- | An error indicating that an 'IO' operation failed because
-- one of its arguments already exists.
isAlreadyExistsError :: IOError -> Bool
isAlreadyExistsError :: IOError -> Bool
isAlreadyExistsError = IOErrorType -> Bool
isAlreadyExistsErrorType    (IOErrorType -> Bool)
-> (IOError -> IOErrorType) -> IOError -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. IOError -> IOErrorType
ioeGetErrorType

-- | An error indicating that an 'IO' operation failed because
-- one of its arguments does not exist.
isDoesNotExistError :: IOError -> Bool
isDoesNotExistError :: IOError -> Bool
isDoesNotExistError  = IOErrorType -> Bool
isDoesNotExistErrorType     (IOErrorType -> Bool)
-> (IOError -> IOErrorType) -> IOError -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. IOError -> IOErrorType
ioeGetErrorType

-- | An error indicating that an 'IO' operation failed because
-- one of its arguments is a single-use resource, which is already
-- being used (for example, opening the same file twice for writing
-- might give this error).
isAlreadyInUseError :: IOError -> Bool
isAlreadyInUseError :: IOError -> Bool
isAlreadyInUseError  = IOErrorType -> Bool
isAlreadyInUseErrorType     (IOErrorType -> Bool)
-> (IOError -> IOErrorType) -> IOError -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. IOError -> IOErrorType
ioeGetErrorType

-- | An error indicating that an 'IO' operation failed because
-- the device is full.
isFullError         :: IOError -> Bool
isFullError :: IOError -> Bool
isFullError          = IOErrorType -> Bool
isFullErrorType             (IOErrorType -> Bool)
-> (IOError -> IOErrorType) -> IOError -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. IOError -> IOErrorType
ioeGetErrorType

-- | An error indicating that an 'IO' operation failed because
-- the end of file has been reached.
isEOFError          :: IOError -> Bool
isEOFError :: IOError -> Bool
isEOFError           = IOErrorType -> Bool
isEOFErrorType              (IOErrorType -> Bool)
-> (IOError -> IOErrorType) -> IOError -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. IOError -> IOErrorType
ioeGetErrorType

-- | An error indicating that an 'IO' operation failed because
-- the operation was not possible.
-- Any computation which returns an 'IO' result may fail with
-- 'isIllegalOperation'.  In some cases, an implementation will not be
-- able to distinguish between the possible error causes.  In this case
-- it should fail with 'isIllegalOperation'.
isIllegalOperation  :: IOError -> Bool
isIllegalOperation :: IOError -> Bool
isIllegalOperation   = IOErrorType -> Bool
isIllegalOperationErrorType (IOErrorType -> Bool)
-> (IOError -> IOErrorType) -> IOError -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. IOError -> IOErrorType
ioeGetErrorType

-- | An error indicating that an 'IO' operation failed because
-- the user does not have sufficient operating system privilege
-- to perform that operation.
isPermissionError   :: IOError -> Bool
isPermissionError :: IOError -> Bool
isPermissionError    = IOErrorType -> Bool
isPermissionErrorType       (IOErrorType -> Bool)
-> (IOError -> IOErrorType) -> IOError -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. IOError -> IOErrorType
ioeGetErrorType

-- | A programmer-defined error value constructed using 'userError'.
isUserError         :: IOError -> Bool
isUserError :: IOError -> Bool
isUserError          = IOErrorType -> Bool
isUserErrorType             (IOErrorType -> Bool)
-> (IOError -> IOErrorType) -> IOError -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. IOError -> IOErrorType
ioeGetErrorType

-- | An error indicating that the operation failed because the
-- resource vanished. See 'resourceVanishedErrorType'.
--
-- @since 4.14.0.0
isResourceVanishedError :: IOError -> Bool
isResourceVanishedError :: IOError -> Bool
isResourceVanishedError = IOErrorType -> Bool
isResourceVanishedErrorType (IOErrorType -> Bool)
-> (IOError -> IOErrorType) -> IOError -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. IOError -> IOErrorType
ioeGetErrorType

-- -----------------------------------------------------------------------------
-- IOErrorTypes

-- | I\/O error where the operation failed because one of its arguments
-- already exists.
alreadyExistsErrorType   :: IOErrorType
alreadyExistsErrorType :: IOErrorType
alreadyExistsErrorType    = IOErrorType
AlreadyExists

-- | I\/O error where the operation failed because one of its arguments
-- does not exist.
doesNotExistErrorType    :: IOErrorType
doesNotExistErrorType :: IOErrorType
doesNotExistErrorType     = IOErrorType
NoSuchThing

-- | I\/O error where the operation failed because one of its arguments
-- is a single-use resource, which is already being used.
alreadyInUseErrorType    :: IOErrorType
alreadyInUseErrorType :: IOErrorType
alreadyInUseErrorType     = IOErrorType
ResourceBusy

-- | I\/O error where the operation failed because the device is full.
fullErrorType            :: IOErrorType
fullErrorType :: IOErrorType
fullErrorType             = IOErrorType
ResourceExhausted

-- | I\/O error where the operation failed because the end of file has
-- been reached.
eofErrorType             :: IOErrorType
eofErrorType :: IOErrorType
eofErrorType              = IOErrorType
EOF

-- | I\/O error where the operation is not possible.
illegalOperationErrorType :: IOErrorType
illegalOperationErrorType :: IOErrorType
illegalOperationErrorType = IOErrorType
IllegalOperation

-- | I\/O error where the operation failed because the user does not
-- have sufficient operating system privilege to perform that operation.
permissionErrorType      :: IOErrorType
permissionErrorType :: IOErrorType
permissionErrorType       = IOErrorType
PermissionDenied

-- | I\/O error that is programmer-defined.
userErrorType            :: IOErrorType
userErrorType :: IOErrorType
userErrorType             = IOErrorType
UserError

-- | I\/O error where the operation failed because the resource vanished.
-- This happens when, for example, attempting to write to a closed
-- socket or attempting to write to a named pipe that was deleted.
--
-- @since 4.14.0.0
resourceVanishedErrorType :: IOErrorType
resourceVanishedErrorType :: IOErrorType
resourceVanishedErrorType = IOErrorType
ResourceVanished

-- -----------------------------------------------------------------------------
-- IOErrorType predicates

-- | I\/O error where the operation failed because one of its arguments
-- already exists.
isAlreadyExistsErrorType :: IOErrorType -> Bool
isAlreadyExistsErrorType :: IOErrorType -> Bool
isAlreadyExistsErrorType IOErrorType
AlreadyExists = Bool
True
isAlreadyExistsErrorType IOErrorType
_ = Bool
False

-- | I\/O error where the operation failed because one of its arguments
-- does not exist.
isDoesNotExistErrorType :: IOErrorType -> Bool
isDoesNotExistErrorType :: IOErrorType -> Bool
isDoesNotExistErrorType IOErrorType
NoSuchThing = Bool
True
isDoesNotExistErrorType IOErrorType
_ = Bool
False

-- | I\/O error where the operation failed because one of its arguments
-- is a single-use resource, which is already being used.
isAlreadyInUseErrorType :: IOErrorType -> Bool
isAlreadyInUseErrorType :: IOErrorType -> Bool
isAlreadyInUseErrorType IOErrorType
ResourceBusy = Bool
True
isAlreadyInUseErrorType IOErrorType
_ = Bool
False

-- | I\/O error where the operation failed because the device is full.
isFullErrorType :: IOErrorType -> Bool
isFullErrorType :: IOErrorType -> Bool
isFullErrorType IOErrorType
ResourceExhausted = Bool
True
isFullErrorType IOErrorType
_ = Bool
False

-- | I\/O error where the operation failed because the end of file has
-- been reached.
isEOFErrorType :: IOErrorType -> Bool
isEOFErrorType :: IOErrorType -> Bool
isEOFErrorType IOErrorType
EOF = Bool
True
isEOFErrorType IOErrorType
_ = Bool
False

-- | I\/O error where the operation is not possible.
isIllegalOperationErrorType :: IOErrorType -> Bool
isIllegalOperationErrorType :: IOErrorType -> Bool
isIllegalOperationErrorType IOErrorType
IllegalOperation = Bool
True
isIllegalOperationErrorType IOErrorType
_ = Bool
False

-- | I\/O error where the operation failed because the user does not
-- have sufficient operating system privilege to perform that operation.
isPermissionErrorType :: IOErrorType -> Bool
isPermissionErrorType :: IOErrorType -> Bool
isPermissionErrorType IOErrorType
PermissionDenied = Bool
True
isPermissionErrorType IOErrorType
_ = Bool
False

-- | I\/O error that is programmer-defined.
isUserErrorType :: IOErrorType -> Bool
isUserErrorType :: IOErrorType -> Bool
isUserErrorType IOErrorType
UserError = Bool
True
isUserErrorType IOErrorType
_ = Bool
False

-- | I\/O error where the operation failed because the resource vanished.
-- See 'resourceVanishedErrorType'.
--
-- @since 4.14.0.0
isResourceVanishedErrorType :: IOErrorType -> Bool
isResourceVanishedErrorType :: IOErrorType -> Bool
isResourceVanishedErrorType IOErrorType
ResourceVanished = Bool
True
isResourceVanishedErrorType IOErrorType
_ = Bool
False

-- -----------------------------------------------------------------------------
-- Miscellaneous

ioeGetErrorType       :: IOError -> IOErrorType
ioeGetErrorString     :: IOError -> String
ioeGetLocation        :: IOError -> String
ioeGetHandle          :: IOError -> Maybe Handle
ioeGetFileName        :: IOError -> Maybe FilePath

ioeGetErrorType :: IOError -> IOErrorType
ioeGetErrorType IOError
ioe = IOError -> IOErrorType
ioe_type IOError
ioe

ioeGetErrorString :: IOError -> String
ioeGetErrorString IOError
ioe
   | IOErrorType -> Bool
isUserErrorType (IOError -> IOErrorType
ioe_type IOError
ioe) = IOError -> String
ioe_description IOError
ioe
   | Bool
otherwise                      = IOErrorType -> String
forall a. Show a => a -> String
show (IOError -> IOErrorType
ioe_type IOError
ioe)

ioeGetLocation :: IOError -> String
ioeGetLocation IOError
ioe = IOError -> String
ioe_location IOError
ioe

ioeGetHandle :: IOError -> Maybe Handle
ioeGetHandle IOError
ioe = IOError -> Maybe Handle
ioe_handle IOError
ioe

ioeGetFileName :: IOError -> Maybe String
ioeGetFileName IOError
ioe = IOError -> Maybe String
ioe_filename IOError
ioe

ioeSetErrorType   :: IOError -> IOErrorType -> IOError
ioeSetErrorString :: IOError -> String      -> IOError
ioeSetLocation    :: IOError -> String      -> IOError
ioeSetHandle      :: IOError -> Handle      -> IOError
ioeSetFileName    :: IOError -> FilePath    -> IOError

ioeSetErrorType :: IOError -> IOErrorType -> IOError
ioeSetErrorType   IOError
ioe IOErrorType
errtype  = IOError
ioe{ ioe_type :: IOErrorType
ioe_type = IOErrorType
errtype }
ioeSetErrorString :: IOError -> String -> IOError
ioeSetErrorString IOError
ioe String
str      = IOError
ioe{ ioe_description :: String
ioe_description = String
str }
ioeSetLocation :: IOError -> String -> IOError
ioeSetLocation    IOError
ioe String
str      = IOError
ioe{ ioe_location :: String
ioe_location = String
str }
ioeSetHandle :: IOError -> Handle -> IOError
ioeSetHandle      IOError
ioe Handle
hdl      = IOError
ioe{ ioe_handle :: Maybe Handle
ioe_handle = Handle -> Maybe Handle
forall a. a -> Maybe a
Just Handle
hdl }
ioeSetFileName :: IOError -> String -> IOError
ioeSetFileName    IOError
ioe String
filename = IOError
ioe{ ioe_filename :: Maybe String
ioe_filename = String -> Maybe String
forall a. a -> Maybe a
Just String
filename }

-- | Catch any 'IOError' that occurs in the computation and throw a
-- modified version.
modifyIOError :: (IOError -> IOError) -> IO a -> IO a
modifyIOError :: forall a. (IOError -> IOError) -> IO a -> IO a
modifyIOError IOError -> IOError
f IO a
io = IO a -> (IOError -> IO a) -> IO a
forall e a. Exception e => IO a -> (e -> IO a) -> IO a
catch IO a
io (\IOError
e -> IOError -> IO a
forall a. IOError -> IO a
ioError (IOError -> IOError
f IOError
e))

-- -----------------------------------------------------------------------------
-- annotating an IOError

-- | Adds a location description and maybe a file path and file handle
-- to an 'IOError'.  If any of the file handle or file path is not given
-- the corresponding value in the 'IOError' remains unaltered.
annotateIOError :: IOError
              -> String
              -> Maybe Handle
              -> Maybe FilePath
              -> IOError
annotateIOError :: IOError -> String -> Maybe Handle -> Maybe String -> IOError
annotateIOError IOError
ioe String
loc Maybe Handle
hdl Maybe String
path =
  IOError
ioe{ ioe_handle :: Maybe Handle
ioe_handle = Maybe Handle
hdl Maybe Handle -> Maybe Handle -> Maybe Handle
forall (m :: * -> *) a. MonadPlus m => m a -> m a -> m a
`mplus` IOError -> Maybe Handle
ioe_handle IOError
ioe,
       ioe_location :: String
ioe_location = String
loc, ioe_filename :: Maybe String
ioe_filename = Maybe String
path Maybe String -> Maybe String -> Maybe String
forall (m :: * -> *) a. MonadPlus m => m a -> m a -> m a
`mplus` IOError -> Maybe String
ioe_filename IOError
ioe }

-- | The 'catchIOError' function establishes a handler that receives any
-- 'IOError' raised in the action protected by 'catchIOError'.
-- An 'IOError' is caught by
-- the most recent handler established by one of the exception handling
-- functions.  These handlers are
-- not selective: all 'IOError's are caught.  Exception propagation
-- must be explicitly provided in a handler by re-raising any unwanted
-- exceptions.  For example, in
--
-- > f = catchIOError g (\e -> if IO.isEOFError e then return [] else ioError e)
--
-- the function @f@ returns @[]@ when an end-of-file exception
-- (cf. 'System.IO.Error.isEOFError') occurs in @g@; otherwise, the
-- exception is propagated to the next outer handler.
--
-- When an exception propagates outside the main program, the Haskell
-- system prints the associated 'IOError' value and exits the program.
--
-- Non-I\/O exceptions are not caught by this variant; to catch all
-- exceptions, use 'Control.Exception.catch' from "Control.Exception".
--
-- @since 4.4.0.0
catchIOError :: IO a -> (IOError -> IO a) -> IO a
catchIOError :: forall a. IO a -> (IOError -> IO a) -> IO a
catchIOError = IO a -> (IOError -> IO a) -> IO a
forall e a. Exception e => IO a -> (e -> IO a) -> IO a
catch