Movatterモバイル変換
[0]ホーム
{-# LANGUAGE Trustworthy #-}{-# LANGUAGE DeriveGeneric, NoImplicitPrelude, MagicHash, ExistentialQuantification, ImplicitParams #-}{-# OPTIONS_GHC -funbox-strict-fields #-}{-# OPTIONS_HADDOCK not-home #-}------------------------------------------------------------------------------- |-- Module : GHC.IO.Exception-- Copyright : (c) The University of Glasgow, 2009-- License : see libraries/base/LICENSE---- Maintainer : libraries@haskell.org-- Stability : internal-- Portability : non-portable---- IO-related Exception types and functions-------------------------------------------------------------------------------moduleGHC.IO.Exception(BlockedIndefinitelyOnMVar(..),blockedIndefinitelyOnMVar,BlockedIndefinitelyOnSTM(..),blockedIndefinitelyOnSTM,Deadlock(..),AllocationLimitExceeded(..),allocationLimitExceeded,AssertionFailed(..),CompactionFailed(..),cannotCompactFunction,cannotCompactPinned,cannotCompactMutable,SomeAsyncException(..),asyncExceptionToException,asyncExceptionFromException,AsyncException(..),stackOverflow,heapOverflow,ArrayException(..),ExitCode(..),FixIOException(..),ioException,ioError,IOError,IOException(..),IOErrorType(..),userError,assertError,unsupportedOperation,untangle,)whereimportGHC.BaseimportGHC.GenericsimportGHC.ListimportGHC.IOimportGHC.ShowimportGHC.ReadimportGHC.ExceptionimportGHC.IO.Handle.TypesimportGHC.OldList(intercalate)import{-# SOURCE#-}GHC.Stack.CCSimportForeign.C.TypesimportData.Typeable(cast)-- -------------------------------------------------------------------------- Exception datatypes and operations-- |The thread is blocked on an @MVar@, but there are no other references-- to the @MVar@ so it can't ever continue.dataBlockedIndefinitelyOnMVar=BlockedIndefinitelyOnMVar-- | @since 4.1.0.0instanceExceptionBlockedIndefinitelyOnMVar-- | @since 4.1.0.0instanceShowBlockedIndefinitelyOnMVarwhereshowsPrec :: Int -> BlockedIndefinitelyOnMVar -> ShowSshowsPrecInt_BlockedIndefinitelyOnMVarBlockedIndefinitelyOnMVar=String -> ShowSshowStringString"thread blocked indefinitely in an MVar operation"blockedIndefinitelyOnMVar::SomeException-- for the RTSblockedIndefinitelyOnMVar :: SomeExceptionblockedIndefinitelyOnMVar=BlockedIndefinitelyOnMVar -> SomeExceptionforall e. Exception e => e -> SomeExceptiontoExceptionBlockedIndefinitelyOnMVarBlockedIndefinitelyOnMVar------- |The thread is waiting to retry an STM transaction, but there are no-- other references to any @TVar@s involved, so it can't ever continue.dataBlockedIndefinitelyOnSTM=BlockedIndefinitelyOnSTM-- | @since 4.1.0.0instanceExceptionBlockedIndefinitelyOnSTM-- | @since 4.1.0.0instanceShowBlockedIndefinitelyOnSTMwhereshowsPrec :: Int -> BlockedIndefinitelyOnSTM -> ShowSshowsPrecInt_BlockedIndefinitelyOnSTMBlockedIndefinitelyOnSTM=String -> ShowSshowStringString"thread blocked indefinitely in an STM transaction"blockedIndefinitelyOnSTM::SomeException-- for the RTSblockedIndefinitelyOnSTM :: SomeExceptionblockedIndefinitelyOnSTM=BlockedIndefinitelyOnSTM -> SomeExceptionforall e. Exception e => e -> SomeExceptiontoExceptionBlockedIndefinitelyOnSTMBlockedIndefinitelyOnSTM------- |There are no runnable threads, so the program is deadlocked.-- The @Deadlock@ exception is raised in the main thread only.dataDeadlock=Deadlock-- | @since 4.1.0.0instanceExceptionDeadlock-- | @since 4.1.0.0instanceShowDeadlockwhereshowsPrec :: Int -> Deadlock -> ShowSshowsPrecInt_DeadlockDeadlock=String -> ShowSshowStringString"<<deadlock>>"------- |This thread has exceeded its allocation limit. See-- 'System.Mem.setAllocationCounter' and-- 'System.Mem.enableAllocationLimit'.---- @since 4.8.0.0dataAllocationLimitExceeded=AllocationLimitExceeded-- | @since 4.8.0.0instanceExceptionAllocationLimitExceededwheretoException :: AllocationLimitExceeded -> SomeExceptiontoException=AllocationLimitExceeded -> SomeExceptionforall e. Exception e => e -> SomeExceptionasyncExceptionToExceptionfromException :: SomeException -> Maybe AllocationLimitExceededfromException=SomeException -> Maybe AllocationLimitExceededforall e. Exception e => SomeException -> Maybe easyncExceptionFromException-- | @since 4.7.1.0instanceShowAllocationLimitExceededwhereshowsPrec :: Int -> AllocationLimitExceeded -> ShowSshowsPrecInt_AllocationLimitExceededAllocationLimitExceeded=String -> ShowSshowStringString"allocation limit exceeded"allocationLimitExceeded::SomeException-- for the RTSallocationLimitExceeded :: SomeExceptionallocationLimitExceeded=AllocationLimitExceeded -> SomeExceptionforall e. Exception e => e -> SomeExceptiontoExceptionAllocationLimitExceededAllocationLimitExceeded------- | Compaction found an object that cannot be compacted. Functions-- cannot be compacted, nor can mutable objects or pinned objects.-- See 'GHC.Compact.compact'.---- @since 4.10.0.0newtypeCompactionFailed=CompactionFailedString-- | @since 4.10.0.0instanceExceptionCompactionFailedwhere-- | @since 4.10.0.0instanceShowCompactionFailedwhereshowsPrec :: Int -> CompactionFailed -> ShowSshowsPrecInt_(CompactionFailedStringwhy)=String -> ShowSshowString(String"compaction failed: "String -> ShowSforall a. [a] -> [a] -> [a]++Stringwhy)cannotCompactFunction::SomeException-- for the RTScannotCompactFunction :: SomeExceptioncannotCompactFunction=CompactionFailed -> SomeExceptionforall e. Exception e => e -> SomeExceptiontoException(String -> CompactionFailedCompactionFailedString"cannot compact functions")cannotCompactPinned::SomeException-- for the RTScannotCompactPinned :: SomeExceptioncannotCompactPinned=CompactionFailed -> SomeExceptionforall e. Exception e => e -> SomeExceptiontoException(String -> CompactionFailedCompactionFailedString"cannot compact pinned objects")cannotCompactMutable::SomeException-- for the RTScannotCompactMutable :: SomeExceptioncannotCompactMutable=CompactionFailed -> SomeExceptionforall e. Exception e => e -> SomeExceptiontoException(String -> CompactionFailedCompactionFailedString"cannot compact mutable objects")------- |'assert' was applied to 'False'.newtypeAssertionFailed=AssertionFailedString-- | @since 4.1.0.0instanceExceptionAssertionFailed-- | @since 4.1.0.0instanceShowAssertionFailedwhereshowsPrec :: Int -> AssertionFailed -> ShowSshowsPrecInt_(AssertionFailedStringerr)=String -> ShowSshowStringStringerr------- |Superclass for asynchronous exceptions.---- @since 4.7.0.0dataSomeAsyncException=foralle.Exceptione=>SomeAsyncExceptione-- | @since 4.7.0.0instanceShowSomeAsyncExceptionwhereshowsPrec :: Int -> SomeAsyncException -> ShowSshowsPrecIntp(SomeAsyncExceptionee)=Int -> e -> ShowSforall a. Show a => Int -> a -> ShowSshowsPrecIntpee-- | @since 4.7.0.0instanceExceptionSomeAsyncException-- |@since 4.7.0.0asyncExceptionToException::Exceptione=>e->SomeExceptionasyncExceptionToException :: forall e. Exception e => e -> SomeExceptionasyncExceptionToException=SomeAsyncException -> SomeExceptionforall e. Exception e => e -> SomeExceptiontoException(SomeAsyncException -> SomeException)-> (e -> SomeAsyncException) -> e -> SomeExceptionforall b c a. (b -> c) -> (a -> b) -> a -> c.e -> SomeAsyncExceptionforall e. Exception e => e -> SomeAsyncExceptionSomeAsyncException-- |@since 4.7.0.0asyncExceptionFromException::Exceptione=>SomeException->MaybeeasyncExceptionFromException :: forall e. Exception e => SomeException -> Maybe easyncExceptionFromExceptionSomeExceptionx=doSomeAsyncExceptionea<-SomeException -> Maybe SomeAsyncExceptionforall e. Exception e => SomeException -> Maybe efromExceptionSomeExceptionxe -> Maybe eforall a b. (Typeable a, Typeable b) => a -> Maybe bcastea-- |Asynchronous exceptions.dataAsyncException=StackOverflow-- ^The current thread\'s stack exceeded its limit.-- Since an exception has been raised, the thread\'s stack-- will certainly be below its limit again, but the-- programmer should take remedial action-- immediately.|HeapOverflow-- ^The program\'s heap is reaching its limit, and-- the program should take action to reduce the amount of-- live data it has. Notes:---- * It is undefined which thread receives this exception.-- GHC currently throws this to the same thread that-- receives 'UserInterrupt', but this may change in the-- future.---- * The GHC RTS currently can only recover from heap overflow-- if it detects that an explicit memory limit (set via RTS flags).-- has been exceeded. Currently, failure to allocate memory from-- the operating system results in immediate termination of the-- program.|ThreadKilled-- ^This exception is raised by another thread-- calling 'Control.Concurrent.killThread', or by the system-- if it needs to terminate the thread for some-- reason.|UserInterrupt-- ^This exception is raised by default in the main thread of-- the program when the user requests to terminate the program-- via the usual mechanism(s) (e.g. Control-C in the console).deriving(AsyncException -> AsyncException -> Bool(AsyncException -> AsyncException -> Bool)-> (AsyncException -> AsyncException -> Bool) -> Eq AsyncExceptionforall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a$c== :: AsyncException -> AsyncException -> Bool== :: AsyncException -> AsyncException -> Bool$c/= :: AsyncException -> AsyncException -> Bool/= :: AsyncException -> AsyncException -> BoolEq-- ^ @since 4.2.0.0,Eq AsyncExceptionEq AsyncException =>(AsyncException -> AsyncException -> Ordering)-> (AsyncException -> AsyncException -> Bool)-> (AsyncException -> AsyncException -> Bool)-> (AsyncException -> AsyncException -> Bool)-> (AsyncException -> AsyncException -> Bool)-> (AsyncException -> AsyncException -> AsyncException)-> (AsyncException -> AsyncException -> AsyncException)-> Ord AsyncExceptionAsyncException -> AsyncException -> BoolAsyncException -> AsyncException -> OrderingAsyncException -> AsyncException -> AsyncExceptionforall a.Eq a =>(a -> a -> Ordering)-> (a -> a -> Bool)-> (a -> a -> Bool)-> (a -> a -> Bool)-> (a -> a -> Bool)-> (a -> a -> a)-> (a -> a -> a)-> Ord a$ccompare :: AsyncException -> AsyncException -> Orderingcompare :: AsyncException -> AsyncException -> Ordering$c< :: AsyncException -> AsyncException -> Bool< :: AsyncException -> AsyncException -> Bool$c<= :: AsyncException -> AsyncException -> Bool<= :: AsyncException -> AsyncException -> Bool$c> :: AsyncException -> AsyncException -> Bool> :: AsyncException -> AsyncException -> Bool$c>= :: AsyncException -> AsyncException -> Bool>= :: AsyncException -> AsyncException -> Bool$cmax :: AsyncException -> AsyncException -> AsyncExceptionmax :: AsyncException -> AsyncException -> AsyncException$cmin :: AsyncException -> AsyncException -> AsyncExceptionmin :: AsyncException -> AsyncException -> AsyncExceptionOrd-- ^ @since 4.2.0.0)-- | @since 4.7.0.0instanceExceptionAsyncExceptionwheretoException :: AsyncException -> SomeExceptiontoException=AsyncException -> SomeExceptionforall e. Exception e => e -> SomeExceptionasyncExceptionToExceptionfromException :: SomeException -> Maybe AsyncExceptionfromException=SomeException -> Maybe AsyncExceptionforall e. Exception e => SomeException -> Maybe easyncExceptionFromException-- | Exceptions generated by array operationsdataArrayException=IndexOutOfBoundsString-- ^An attempt was made to index an array outside-- its declared bounds.|UndefinedElementString-- ^An attempt was made to evaluate an element of an-- array that had not been initialized.deriving(ArrayException -> ArrayException -> Bool(ArrayException -> ArrayException -> Bool)-> (ArrayException -> ArrayException -> Bool) -> Eq ArrayExceptionforall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a$c== :: ArrayException -> ArrayException -> Bool== :: ArrayException -> ArrayException -> Bool$c/= :: ArrayException -> ArrayException -> Bool/= :: ArrayException -> ArrayException -> BoolEq-- ^ @since 4.2.0.0,Eq ArrayExceptionEq ArrayException =>(ArrayException -> ArrayException -> Ordering)-> (ArrayException -> ArrayException -> Bool)-> (ArrayException -> ArrayException -> Bool)-> (ArrayException -> ArrayException -> Bool)-> (ArrayException -> ArrayException -> Bool)-> (ArrayException -> ArrayException -> ArrayException)-> (ArrayException -> ArrayException -> ArrayException)-> Ord ArrayExceptionArrayException -> ArrayException -> BoolArrayException -> ArrayException -> OrderingArrayException -> ArrayException -> ArrayExceptionforall a.Eq a =>(a -> a -> Ordering)-> (a -> a -> Bool)-> (a -> a -> Bool)-> (a -> a -> Bool)-> (a -> a -> Bool)-> (a -> a -> a)-> (a -> a -> a)-> Ord a$ccompare :: ArrayException -> ArrayException -> Orderingcompare :: ArrayException -> ArrayException -> Ordering$c< :: ArrayException -> ArrayException -> Bool< :: ArrayException -> ArrayException -> Bool$c<= :: ArrayException -> ArrayException -> Bool<= :: ArrayException -> ArrayException -> Bool$c> :: ArrayException -> ArrayException -> Bool> :: ArrayException -> ArrayException -> Bool$c>= :: ArrayException -> ArrayException -> Bool>= :: ArrayException -> ArrayException -> Bool$cmax :: ArrayException -> ArrayException -> ArrayExceptionmax :: ArrayException -> ArrayException -> ArrayException$cmin :: ArrayException -> ArrayException -> ArrayExceptionmin :: ArrayException -> ArrayException -> ArrayExceptionOrd-- ^ @since 4.2.0.0)-- | @since 4.1.0.0instanceExceptionArrayException-- for the RTSstackOverflow,heapOverflow::SomeExceptionstackOverflow :: SomeExceptionstackOverflow=AsyncException -> SomeExceptionforall e. Exception e => e -> SomeExceptiontoExceptionAsyncExceptionStackOverflowheapOverflow :: SomeExceptionheapOverflow=AsyncException -> SomeExceptionforall e. Exception e => e -> SomeExceptiontoExceptionAsyncExceptionHeapOverflow-- | @since 4.1.0.0instanceShowAsyncExceptionwhereshowsPrec :: Int -> AsyncException -> ShowSshowsPrecInt_AsyncExceptionStackOverflow=String -> ShowSshowStringString"stack overflow"showsPrecInt_AsyncExceptionHeapOverflow=String -> ShowSshowStringString"heap overflow"showsPrecInt_AsyncExceptionThreadKilled=String -> ShowSshowStringString"thread killed"showsPrecInt_AsyncExceptionUserInterrupt=String -> ShowSshowStringString"user interrupt"-- | @since 4.1.0.0instanceShowArrayExceptionwhereshowsPrec :: Int -> ArrayException -> ShowSshowsPrecInt_(IndexOutOfBoundsStrings)=String -> ShowSshowStringString"array index out of range"ShowS -> ShowS -> ShowSforall b c a. (b -> c) -> (a -> b) -> a -> c.(ifBool -> Boolnot(String -> Boolforall a. [a] -> BoolnullStrings)thenString -> ShowSshowStringString": "ShowS -> ShowS -> ShowSforall b c a. (b -> c) -> (a -> b) -> a -> c.String -> ShowSshowStringStringselseShowSforall a. a -> aid)showsPrecInt_(UndefinedElementStrings)=String -> ShowSshowStringString"undefined array element"ShowS -> ShowS -> ShowSforall b c a. (b -> c) -> (a -> b) -> a -> c.(ifBool -> Boolnot(String -> Boolforall a. [a] -> BoolnullStrings)thenString -> ShowSshowStringString": "ShowS -> ShowS -> ShowSforall b c a. (b -> c) -> (a -> b) -> a -> c.String -> ShowSshowStringStringselseShowSforall a. a -> aid)-- | The exception thrown when an infinite cycle is detected in-- 'System.IO.fixIO'.---- @since 4.11.0.0dataFixIOException=FixIOException-- | @since 4.11.0.0instanceExceptionFixIOException-- | @since 4.11.0.0instanceShowFixIOExceptionwhereshowsPrec :: Int -> FixIOException -> ShowSshowsPrecInt_FixIOExceptionFixIOException=String -> ShowSshowStringString"cyclic evaluation in fixIO"-- ------------------------------------------------------------------------------- The ExitCode type-- We need it here because it is used in ExitException in the-- Exception datatype (above).-- | Defines the exit codes that a program can return.dataExitCode=ExitSuccess-- ^ indicates successful termination;|ExitFailureInt-- ^ indicates program failure with an exit code.-- The exact interpretation of the code is-- operating-system dependent. In particular, some values-- may be prohibited (e.g. 0 on a POSIX-compliant system).deriving(ExitCode -> ExitCode -> Bool(ExitCode -> ExitCode -> Bool)-> (ExitCode -> ExitCode -> Bool) -> Eq ExitCodeforall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a$c== :: ExitCode -> ExitCode -> Bool== :: ExitCode -> ExitCode -> Bool$c/= :: ExitCode -> ExitCode -> Bool/= :: ExitCode -> ExitCode -> BoolEq,Eq ExitCodeEq ExitCode =>(ExitCode -> ExitCode -> Ordering)-> (ExitCode -> ExitCode -> Bool)-> (ExitCode -> ExitCode -> Bool)-> (ExitCode -> ExitCode -> Bool)-> (ExitCode -> ExitCode -> Bool)-> (ExitCode -> ExitCode -> ExitCode)-> (ExitCode -> ExitCode -> ExitCode)-> Ord ExitCodeExitCode -> ExitCode -> BoolExitCode -> ExitCode -> OrderingExitCode -> ExitCode -> ExitCodeforall a.Eq a =>(a -> a -> Ordering)-> (a -> a -> Bool)-> (a -> a -> Bool)-> (a -> a -> Bool)-> (a -> a -> Bool)-> (a -> a -> a)-> (a -> a -> a)-> Ord a$ccompare :: ExitCode -> ExitCode -> Orderingcompare :: ExitCode -> ExitCode -> Ordering$c< :: ExitCode -> ExitCode -> Bool< :: ExitCode -> ExitCode -> Bool$c<= :: ExitCode -> ExitCode -> Bool<= :: ExitCode -> ExitCode -> Bool$c> :: ExitCode -> ExitCode -> Bool> :: ExitCode -> ExitCode -> Bool$c>= :: ExitCode -> ExitCode -> Bool>= :: ExitCode -> ExitCode -> Bool$cmax :: ExitCode -> ExitCode -> ExitCodemax :: ExitCode -> ExitCode -> ExitCode$cmin :: ExitCode -> ExitCode -> ExitCodemin :: ExitCode -> ExitCode -> ExitCodeOrd,ReadPrec [ExitCode]ReadPrec ExitCodeInt -> ReadS ExitCodeReadS [ExitCode](Int -> ReadS ExitCode)-> ReadS [ExitCode]-> ReadPrec ExitCode-> ReadPrec [ExitCode]-> Read ExitCodeforall a.(Int -> ReadS a)-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a$creadsPrec :: Int -> ReadS ExitCodereadsPrec :: Int -> ReadS ExitCode$creadList :: ReadS [ExitCode]readList :: ReadS [ExitCode]$creadPrec :: ReadPrec ExitCodereadPrec :: ReadPrec ExitCode$creadListPrec :: ReadPrec [ExitCode]readListPrec :: ReadPrec [ExitCode]Read,Int -> ExitCode -> ShowS[ExitCode] -> ShowSExitCode -> String(Int -> ExitCode -> ShowS)-> (ExitCode -> String) -> ([ExitCode] -> ShowS) -> Show ExitCodeforall a.(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a$cshowsPrec :: Int -> ExitCode -> ShowSshowsPrec :: Int -> ExitCode -> ShowS$cshow :: ExitCode -> Stringshow :: ExitCode -> String$cshowList :: [ExitCode] -> ShowSshowList :: [ExitCode] -> ShowSShow,(forall x. ExitCode -> Rep ExitCode x)-> (forall x. Rep ExitCode x -> ExitCode) -> Generic ExitCodeforall x. Rep ExitCode x -> ExitCodeforall x. ExitCode -> Rep ExitCode xforall a.(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a$cfrom :: forall x. ExitCode -> Rep ExitCode xfrom :: forall x. ExitCode -> Rep ExitCode x$cto :: forall x. Rep ExitCode x -> ExitCodeto :: forall x. Rep ExitCode x -> ExitCodeGeneric)-- | @since 4.1.0.0instanceExceptionExitCodeioException::IOException->IOaioException :: forall a. IOException -> IO aioExceptionIOExceptionerr=IOException -> IO aforall e a. Exception e => e -> IO athrowIOIOExceptionerr-- | Raise an 'IOError' in the 'IO' monad.ioError::IOError->IOaioError :: forall a. IOException -> IO aioError=IOException -> IO aforall a. IOException -> IO aioException-- ----------------------------------------------------------------------------- IOError type-- | The Haskell 2010 type for exceptions in the 'IO' monad.-- Any I\/O operation may raise an 'IOError' instead of returning a result.-- For a more general type of exception, including also those that arise-- in pure code, see 'Control.Exception.Exception'.---- In Haskell 2010, this is an opaque type.typeIOError=IOException-- |Exceptions that occur in the @IO@ monad.-- An @IOException@ records a more specific error type, a descriptive-- string and maybe the handle that was used when the error was-- flagged.dataIOException=IOError{IOException -> Maybe Handleioe_handle::MaybeHandle,-- the handle used by the action flagging-- the error.IOException -> IOErrorTypeioe_type::IOErrorType,-- what it was.IOException -> Stringioe_location::String,-- location.IOException -> Stringioe_description::String,-- error type specific information.IOException -> Maybe CIntioe_errno::MaybeCInt,-- errno leading to this error, if any.IOException -> Maybe Stringioe_filename::MaybeFilePath-- filename the error is related to.}-- | @since 4.1.0.0instanceExceptionIOException-- | @since 4.1.0.0instanceEqIOExceptionwhere(IOErrorMaybe Handleh1IOErrorTypee1Stringloc1Stringstr1Maybe CInten1Maybe Stringfn1)== :: IOException -> IOException -> Bool==(IOErrorMaybe Handleh2IOErrorTypee2Stringloc2Stringstr2Maybe CInten2Maybe Stringfn2)=IOErrorTypee1IOErrorType -> IOErrorType -> Boolforall a. Eq a => a -> a -> Bool==IOErrorTypee2Bool -> Bool -> Bool&&Stringstr1String -> String -> Boolforall a. Eq a => a -> a -> Bool==Stringstr2Bool -> Bool -> Bool&&Maybe Handleh1Maybe Handle -> Maybe Handle -> Boolforall a. Eq a => a -> a -> Bool==Maybe Handleh2Bool -> Bool -> Bool&&Stringloc1String -> String -> Boolforall a. Eq a => a -> a -> Bool==Stringloc2Bool -> Bool -> Bool&&Maybe CInten1Maybe CInt -> Maybe CInt -> Boolforall a. Eq a => a -> a -> Bool==Maybe CInten2Bool -> Bool -> Bool&&Maybe Stringfn1Maybe String -> Maybe String -> Boolforall a. Eq a => a -> a -> Bool==Maybe Stringfn2-- | An abstract type that contains a value for each variant of 'IOError'.dataIOErrorType-- Haskell 2010:=AlreadyExists|NoSuchThing|ResourceBusy|ResourceExhausted|EOF|IllegalOperation|PermissionDenied|UserError-- GHC only:|UnsatisfiedConstraints|SystemError|ProtocolError|OtherError|InvalidArgument|InappropriateType|HardwareFault|UnsupportedOperation|TimeExpired|ResourceVanished|Interrupted-- | @since 4.1.0.0instanceEqIOErrorTypewhereIOErrorTypex== :: IOErrorType -> IOErrorType -> Bool==IOErrorTypey=Int# -> BoolisTrue#(IOErrorType -> Int#forall a. a -> Int#getTagIOErrorTypexInt# -> Int# -> Int#==#IOErrorType -> Int#forall a. a -> Int#getTagIOErrorTypey)-- | @since 4.1.0.0instanceShowIOErrorTypewhereshowsPrec :: Int -> IOErrorType -> ShowSshowsPrecInt_IOErrorTypee=String -> ShowSshowString(String -> ShowS) -> String -> ShowSforall a b. (a -> b) -> a -> b$caseIOErrorTypeeofIOErrorTypeAlreadyExists->String"already exists"IOErrorTypeNoSuchThing->String"does not exist"IOErrorTypeResourceBusy->String"resource busy"IOErrorTypeResourceExhausted->String"resource exhausted"IOErrorTypeEOF->String"end of file"IOErrorTypeIllegalOperation->String"illegal operation"IOErrorTypePermissionDenied->String"permission denied"IOErrorTypeUserError->String"user error"IOErrorTypeHardwareFault->String"hardware fault"IOErrorTypeInappropriateType->String"inappropriate type"IOErrorTypeInterrupted->String"interrupted"IOErrorTypeInvalidArgument->String"invalid argument"IOErrorTypeOtherError->String"failed"IOErrorTypeProtocolError->String"protocol error"IOErrorTypeResourceVanished->String"resource vanished"IOErrorTypeSystemError->String"system error"IOErrorTypeTimeExpired->String"timeout"IOErrorTypeUnsatisfiedConstraints->String"unsatisfied constraints"-- ultra-precise!IOErrorTypeUnsupportedOperation->String"unsupported operation"-- | Construct an 'IOError' value with a string describing the error.-- The 'fail' method of the 'IO' instance of the 'Monad' class raises a-- 'userError', thus:---- > instance Monad IO where-- > ...-- > fail s = ioError (userError s)--userError::String->IOErroruserError :: String -> IOExceptionuserErrorStringstr=Maybe Handle-> IOErrorType-> String-> String-> Maybe CInt-> Maybe String-> IOExceptionIOErrorMaybe Handleforall a. Maybe aNothingIOErrorTypeUserErrorString""StringstrMaybe CIntforall a. Maybe aNothingMaybe Stringforall a. Maybe aNothing-- ----------------------------------------------------------------------------- Showing IOErrors-- | @since 4.1.0.0instanceShowIOExceptionwhereshowsPrec :: Int -> IOException -> ShowSshowsPrecIntp(IOErrorMaybe HandlehdlIOErrorTypeiotStringlocStringsMaybe CInt_Maybe Stringfn)=(caseMaybe StringfnofMaybe StringNothing->caseMaybe HandlehdlofMaybe HandleNothing->ShowSforall a. a -> aidJustHandleh->Int -> Handle -> ShowSforall a. Show a => Int -> a -> ShowSshowsPrecIntpHandlehShowS -> ShowS -> ShowSforall b c a. (b -> c) -> (a -> b) -> a -> c.String -> ShowSshowStringString": "JustStringname->String -> ShowSshowStringStringnameShowS -> ShowS -> ShowSforall b c a. (b -> c) -> (a -> b) -> a -> c.String -> ShowSshowStringString": ")ShowS -> ShowS -> ShowSforall b c a. (b -> c) -> (a -> b) -> a -> c.(caseStringlocofString""->ShowSforall a. a -> aidString_->String -> ShowSshowStringStringlocShowS -> ShowS -> ShowSforall b c a. (b -> c) -> (a -> b) -> a -> c.String -> ShowSshowStringString": ")ShowS -> ShowS -> ShowSforall b c a. (b -> c) -> (a -> b) -> a -> c.Int -> IOErrorType -> ShowSforall a. Show a => Int -> a -> ShowSshowsPrecIntpIOErrorTypeiotShowS -> ShowS -> ShowSforall b c a. (b -> c) -> (a -> b) -> a -> c.(caseStringsofString""->ShowSforall a. a -> aidString_->String -> ShowSshowStringString" ("ShowS -> ShowS -> ShowSforall b c a. (b -> c) -> (a -> b) -> a -> c.String -> ShowSshowStringStringsShowS -> ShowS -> ShowSforall b c a. (b -> c) -> (a -> b) -> a -> c.String -> ShowSshowStringString")")-- Note the use of "lazy". This means that-- assert False (throw e)-- will throw the assertion failure rather than e. See trac #5561.assertError::(?callStack::CallStack)=>Bool->a->aassertError :: forall a. (?callStack::CallStack) => Bool -> a -> aassertErrorBoolpredicateav|Boolpredicate=a -> aforall a. a -> alazyav|Boolotherwise=IO a -> aforall a. IO a -> aunsafeDupablePerformIO(IO a -> a) -> IO a -> aforall a b. (a -> b) -> a -> b$do[String]ccsStack<-IO [String]currentCallStackletimplicitParamCallStack :: [String]implicitParamCallStack=CallStack -> [String]prettyCallStackLines?callStack::CallStackCallStack?callStackccsCallStack :: [String]ccsCallStack=[String] -> [String]showCCSStack[String]ccsStackstack :: Stringstack=String -> [String] -> Stringforall a. [a] -> [[a]] -> [a]intercalateString"\n"([String] -> String) -> [String] -> Stringforall a b. (a -> b) -> a -> b$[String]implicitParamCallStack[String] -> [String] -> [String]forall a. [a] -> [a] -> [a]++[String]ccsCallStackAssertionFailed -> IO aforall e a. Exception e => e -> IO athrowIO(String -> AssertionFailedAssertionFailed(String"Assertion failed\n"String -> ShowSforall a. [a] -> [a] -> [a]++Stringstack))unsupportedOperation::IOErrorunsupportedOperation :: IOExceptionunsupportedOperation=(Maybe Handle-> IOErrorType-> String-> String-> Maybe CInt-> Maybe String-> IOExceptionIOErrorMaybe Handleforall a. Maybe aNothingIOErrorTypeUnsupportedOperationString""String"Operation is not supported"Maybe CIntforall a. Maybe aNothingMaybe Stringforall a. Maybe aNothing){-(untangle coded message) expects "coded" to be of the form "location|details"It prints location message details-}untangle::Addr#->String->Stringuntangle :: Addr# -> ShowSuntangleAddr#codedStringmessage=StringlocationString -> ShowSforall a. [a] -> [a] -> [a]++String": "String -> ShowSforall a. [a] -> [a] -> [a]++StringmessageString -> ShowSforall a. [a] -> [a] -> [a]++StringdetailsString -> ShowSforall a. [a] -> [a] -> [a]++String"\n"wherecoded_str :: Stringcoded_str=Addr# -> StringunpackCStringUtf8#Addr#coded(Stringlocation,Stringdetails)=case((Char -> Bool) -> String -> (String, String)forall a. (a -> Bool) -> [a] -> ([a], [a])spanChar -> Boolnot_barStringcoded_str)of{(Stringloc,Stringrest)->caseStringrestof(Char'|':Stringdet)->(Stringloc,Char' 'Char -> ShowSforall a. a -> [a] -> [a]:Stringdet)String_->(Stringloc,String"")}not_bar :: Char -> Boolnot_barCharc=CharcChar -> Char -> Boolforall a. Eq a => a -> a -> Bool/=Char'|'
[8]ページ先頭