{-# 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.Base importGHC.Generics importGHC.List importGHC.IO importGHC.Show importGHC.Read importGHC.Exception importGHC.IO.Handle.Types importGHC.OldList (intercalate )import{-# SOURCE#-}GHC.Stack.CCS importForeign.C.Types importData.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.0instanceException BlockedIndefinitelyOnMVar -- | @since 4.1.0.0instanceShow BlockedIndefinitelyOnMVar whereshowsPrec :: Int -> BlockedIndefinitelyOnMVar -> ShowS showsPrec Int _BlockedIndefinitelyOnMVar BlockedIndefinitelyOnMVar =String -> ShowS showString String "thread blocked indefinitely in an MVar operation"blockedIndefinitelyOnMVar ::SomeException -- for the RTSblockedIndefinitelyOnMVar :: SomeException blockedIndefinitelyOnMVar =BlockedIndefinitelyOnMVar -> SomeException forall e. Exception e => e -> SomeException toException BlockedIndefinitelyOnMVar BlockedIndefinitelyOnMVar ------- |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.0instanceException BlockedIndefinitelyOnSTM -- | @since 4.1.0.0instanceShow BlockedIndefinitelyOnSTM whereshowsPrec :: Int -> BlockedIndefinitelyOnSTM -> ShowS showsPrec Int _BlockedIndefinitelyOnSTM BlockedIndefinitelyOnSTM =String -> ShowS showString String "thread blocked indefinitely in an STM transaction"blockedIndefinitelyOnSTM ::SomeException -- for the RTSblockedIndefinitelyOnSTM :: SomeException blockedIndefinitelyOnSTM =BlockedIndefinitelyOnSTM -> SomeException forall e. Exception e => e -> SomeException toException BlockedIndefinitelyOnSTM BlockedIndefinitelyOnSTM ------- |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.0instanceException Deadlock -- | @since 4.1.0.0instanceShow Deadlock whereshowsPrec :: Int -> Deadlock -> ShowS showsPrec Int _Deadlock Deadlock =String -> ShowS showString String "<<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.0instanceException AllocationLimitExceeded wheretoException :: AllocationLimitExceeded -> SomeException toException =AllocationLimitExceeded -> SomeException forall e. Exception e => e -> SomeException asyncExceptionToException fromException :: SomeException -> Maybe AllocationLimitExceeded fromException =SomeException -> Maybe AllocationLimitExceeded forall e. Exception e => SomeException -> Maybe e asyncExceptionFromException -- | @since 4.7.1.0instanceShow AllocationLimitExceeded whereshowsPrec :: Int -> AllocationLimitExceeded -> ShowS showsPrec Int _AllocationLimitExceeded AllocationLimitExceeded =String -> ShowS showString String "allocation limit exceeded"allocationLimitExceeded ::SomeException -- for the RTSallocationLimitExceeded :: SomeException allocationLimitExceeded =AllocationLimitExceeded -> SomeException forall e. Exception e => e -> SomeException toException AllocationLimitExceeded AllocationLimitExceeded ------- | 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 =CompactionFailed String -- | @since 4.10.0.0instanceException CompactionFailed where-- | @since 4.10.0.0instanceShow CompactionFailed whereshowsPrec :: Int -> CompactionFailed -> ShowS showsPrec Int _(CompactionFailed String why )=String -> ShowS showString (String "compaction failed: "String -> ShowS forall a. [a] -> [a] -> [a] ++ String why )cannotCompactFunction ::SomeException -- for the RTScannotCompactFunction :: SomeException cannotCompactFunction =CompactionFailed -> SomeException forall e. Exception e => e -> SomeException toException (String -> CompactionFailed CompactionFailed String "cannot compact functions")cannotCompactPinned ::SomeException -- for the RTScannotCompactPinned :: SomeException cannotCompactPinned =CompactionFailed -> SomeException forall e. Exception e => e -> SomeException toException (String -> CompactionFailed CompactionFailed String "cannot compact pinned objects")cannotCompactMutable ::SomeException -- for the RTScannotCompactMutable :: SomeException cannotCompactMutable =CompactionFailed -> SomeException forall e. Exception e => e -> SomeException toException (String -> CompactionFailed CompactionFailed String "cannot compact mutable objects")------- |'assert' was applied to 'False'.newtypeAssertionFailed =AssertionFailed String -- | @since 4.1.0.0instanceException AssertionFailed -- | @since 4.1.0.0instanceShow AssertionFailed whereshowsPrec :: Int -> AssertionFailed -> ShowS showsPrec Int _(AssertionFailed String err )=String -> ShowS showString String err ------- |Superclass for asynchronous exceptions.---- @since 4.7.0.0dataSomeAsyncException =foralle .Exception e =>SomeAsyncException e -- | @since 4.7.0.0instanceShow SomeAsyncException whereshowsPrec :: Int -> SomeAsyncException -> ShowS showsPrec Int p (SomeAsyncException e e )=Int -> e -> ShowS forall a. Show a => Int -> a -> ShowS showsPrec Int p e e -- | @since 4.7.0.0instanceException SomeAsyncException -- |@since 4.7.0.0asyncExceptionToException ::Exception e =>e ->SomeException asyncExceptionToException :: forall e. Exception e => e -> SomeException asyncExceptionToException =SomeAsyncException -> SomeException forall e. Exception e => e -> SomeException toException (SomeAsyncException -> SomeException) -> (e -> SomeAsyncException) -> e -> SomeException forall b c a. (b -> c) -> (a -> b) -> a -> c . e -> SomeAsyncException forall e. Exception e => e -> SomeAsyncException SomeAsyncException -- |@since 4.7.0.0asyncExceptionFromException ::Exception e =>SomeException ->Maybe e asyncExceptionFromException :: forall e. Exception e => SomeException -> Maybe e asyncExceptionFromException SomeException x =doSomeAsyncException e a <-SomeException -> Maybe SomeAsyncException forall e. Exception e => SomeException -> Maybe e fromException SomeException x e -> Maybe e forall a b. (Typeable a, Typeable b) => a -> Maybe b cast e a -- |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 AsyncException forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a $c== :: AsyncException -> AsyncException -> Bool == :: AsyncException -> AsyncException -> Bool $c/= :: AsyncException -> AsyncException -> Bool /= :: AsyncException -> AsyncException -> Bool Eq -- ^ @since 4.2.0.0,Eq AsyncException Eq AsyncException => (AsyncException -> AsyncException -> Ordering) -> (AsyncException -> AsyncException -> Bool) -> (AsyncException -> AsyncException -> Bool) -> (AsyncException -> AsyncException -> Bool) -> (AsyncException -> AsyncException -> Bool) -> (AsyncException -> AsyncException -> AsyncException) -> (AsyncException -> AsyncException -> AsyncException) -> Ord AsyncException AsyncException -> AsyncException -> Bool AsyncException -> AsyncException -> Ordering AsyncException -> AsyncException -> AsyncException forall 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 -> Ordering compare :: 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 -> AsyncException max :: AsyncException -> AsyncException -> AsyncException $cmin :: AsyncException -> AsyncException -> AsyncException min :: AsyncException -> AsyncException -> AsyncException Ord -- ^ @since 4.2.0.0)-- | @since 4.7.0.0instanceException AsyncException wheretoException :: AsyncException -> SomeException toException =AsyncException -> SomeException forall e. Exception e => e -> SomeException asyncExceptionToException fromException :: SomeException -> Maybe AsyncException fromException =SomeException -> Maybe AsyncException forall e. Exception e => SomeException -> Maybe e asyncExceptionFromException -- | Exceptions generated by array operationsdataArrayException =IndexOutOfBounds String -- ^An attempt was made to index an array outside-- its declared bounds.|UndefinedElement String -- ^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 ArrayException forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a $c== :: ArrayException -> ArrayException -> Bool == :: ArrayException -> ArrayException -> Bool $c/= :: ArrayException -> ArrayException -> Bool /= :: ArrayException -> ArrayException -> Bool Eq -- ^ @since 4.2.0.0,Eq ArrayException Eq ArrayException => (ArrayException -> ArrayException -> Ordering) -> (ArrayException -> ArrayException -> Bool) -> (ArrayException -> ArrayException -> Bool) -> (ArrayException -> ArrayException -> Bool) -> (ArrayException -> ArrayException -> Bool) -> (ArrayException -> ArrayException -> ArrayException) -> (ArrayException -> ArrayException -> ArrayException) -> Ord ArrayException ArrayException -> ArrayException -> Bool ArrayException -> ArrayException -> Ordering ArrayException -> ArrayException -> ArrayException forall 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 -> Ordering compare :: 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 -> ArrayException max :: ArrayException -> ArrayException -> ArrayException $cmin :: ArrayException -> ArrayException -> ArrayException min :: ArrayException -> ArrayException -> ArrayException Ord -- ^ @since 4.2.0.0)-- | @since 4.1.0.0instanceException ArrayException -- for the RTSstackOverflow ,heapOverflow ::SomeException stackOverflow :: SomeException stackOverflow =AsyncException -> SomeException forall e. Exception e => e -> SomeException toException AsyncException StackOverflow heapOverflow :: SomeException heapOverflow =AsyncException -> SomeException forall e. Exception e => e -> SomeException toException AsyncException HeapOverflow -- | @since 4.1.0.0instanceShow AsyncException whereshowsPrec :: Int -> AsyncException -> ShowS showsPrec Int _AsyncException StackOverflow =String -> ShowS showString String "stack overflow"showsPrec Int _AsyncException HeapOverflow =String -> ShowS showString String "heap overflow"showsPrec Int _AsyncException ThreadKilled =String -> ShowS showString String "thread killed"showsPrec Int _AsyncException UserInterrupt =String -> ShowS showString String "user interrupt"-- | @since 4.1.0.0instanceShow ArrayException whereshowsPrec :: Int -> ArrayException -> ShowS showsPrec Int _(IndexOutOfBounds String s )=String -> ShowS showString String "array index out of range"ShowS -> ShowS -> ShowS forall b c a. (b -> c) -> (a -> b) -> a -> c . (ifBool -> Bool not (String -> Bool forall a. [a] -> Bool null String s )thenString -> ShowS showString String ": "ShowS -> ShowS -> ShowS forall b c a. (b -> c) -> (a -> b) -> a -> c . String -> ShowS showString String s elseShowS forall a. a -> a id )showsPrec Int _(UndefinedElement String s )=String -> ShowS showString String "undefined array element"ShowS -> ShowS -> ShowS forall b c a. (b -> c) -> (a -> b) -> a -> c . (ifBool -> Bool not (String -> Bool forall a. [a] -> Bool null String s )thenString -> ShowS showString String ": "ShowS -> ShowS -> ShowS forall b c a. (b -> c) -> (a -> b) -> a -> c . String -> ShowS showString String s elseShowS forall a. a -> a id )-- | The exception thrown when an infinite cycle is detected in-- 'System.IO.fixIO'.---- @since 4.11.0.0dataFixIOException =FixIOException -- | @since 4.11.0.0instanceException FixIOException -- | @since 4.11.0.0instanceShow FixIOException whereshowsPrec :: Int -> FixIOException -> ShowS showsPrec Int _FixIOException FixIOException =String -> ShowS showString String "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;|ExitFailure Int -- ^ 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 ExitCode forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a $c== :: ExitCode -> ExitCode -> Bool == :: ExitCode -> ExitCode -> Bool $c/= :: ExitCode -> ExitCode -> Bool /= :: ExitCode -> ExitCode -> Bool Eq ,Eq ExitCode Eq ExitCode => (ExitCode -> ExitCode -> Ordering) -> (ExitCode -> ExitCode -> Bool) -> (ExitCode -> ExitCode -> Bool) -> (ExitCode -> ExitCode -> Bool) -> (ExitCode -> ExitCode -> Bool) -> (ExitCode -> ExitCode -> ExitCode) -> (ExitCode -> ExitCode -> ExitCode) -> Ord ExitCode ExitCode -> ExitCode -> Bool ExitCode -> ExitCode -> Ordering ExitCode -> ExitCode -> ExitCode forall 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 -> Ordering compare :: 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 -> ExitCode max :: ExitCode -> ExitCode -> ExitCode $cmin :: ExitCode -> ExitCode -> ExitCode min :: ExitCode -> ExitCode -> ExitCode Ord ,ReadPrec [ExitCode] ReadPrec ExitCode Int -> ReadS ExitCode ReadS [ExitCode] (Int -> ReadS ExitCode) -> ReadS [ExitCode] -> ReadPrec ExitCode -> ReadPrec [ExitCode] -> Read ExitCode forall a. (Int -> ReadS a) -> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a $creadsPrec :: Int -> ReadS ExitCode readsPrec :: Int -> ReadS ExitCode $creadList :: ReadS [ExitCode] readList :: ReadS [ExitCode] $creadPrec :: ReadPrec ExitCode readPrec :: ReadPrec ExitCode $creadListPrec :: ReadPrec [ExitCode] readListPrec :: ReadPrec [ExitCode] Read ,Int -> ExitCode -> ShowS [ExitCode] -> ShowS ExitCode -> String (Int -> ExitCode -> ShowS) -> (ExitCode -> String) -> ([ExitCode] -> ShowS) -> Show ExitCode forall a. (Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a $cshowsPrec :: Int -> ExitCode -> ShowS showsPrec :: Int -> ExitCode -> ShowS $cshow :: ExitCode -> String show :: ExitCode -> String $cshowList :: [ExitCode] -> ShowS showList :: [ExitCode] -> ShowS Show ,(forall x. ExitCode -> Rep ExitCode x) -> (forall x. Rep ExitCode x -> ExitCode) -> Generic ExitCode forall x. Rep ExitCode x -> ExitCode forall x. ExitCode -> Rep ExitCode x forall a. (forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a $cfrom :: forall x. ExitCode -> Rep ExitCode x from :: forall x. ExitCode -> Rep ExitCode x $cto :: forall x. Rep ExitCode x -> ExitCode to :: forall x. Rep ExitCode x -> ExitCode Generic )-- | @since 4.1.0.0instanceException ExitCode ioException ::IOException ->IO a ioException :: forall a. IOException -> IO a ioException IOException err =IOException -> IO a forall e a. Exception e => e -> IO a throwIO IOException err -- | Raise an 'IOError' in the 'IO' monad.ioError ::IOError ->IO a ioError :: forall a. IOException -> IO a ioError =IOException -> IO a forall a. IOException -> IO a ioException -- ----------------------------------------------------------------------------- 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 Handle ioe_handle ::Maybe Handle ,-- the handle used by the action flagging-- the error.IOException -> IOErrorType ioe_type ::IOErrorType ,-- what it was.IOException -> String ioe_location ::String ,-- location.IOException -> String ioe_description ::String ,-- error type specific information.IOException -> Maybe CInt ioe_errno ::Maybe CInt ,-- errno leading to this error, if any.IOException -> Maybe String ioe_filename ::Maybe FilePath -- filename the error is related to.}-- | @since 4.1.0.0instanceException IOException -- | @since 4.1.0.0instanceEq IOException where(IOError Maybe Handle h1 IOErrorType e1 String loc1 String str1 Maybe CInt en1 Maybe String fn1 )== :: IOException -> IOException -> Bool == (IOError Maybe Handle h2 IOErrorType e2 String loc2 String str2 Maybe CInt en2 Maybe String fn2 )=IOErrorType e1 IOErrorType -> IOErrorType -> Bool forall a. Eq a => a -> a -> Bool == IOErrorType e2 Bool -> Bool -> Bool && String str1 String -> String -> Bool forall a. Eq a => a -> a -> Bool == String str2 Bool -> Bool -> Bool && Maybe Handle h1 Maybe Handle -> Maybe Handle -> Bool forall a. Eq a => a -> a -> Bool == Maybe Handle h2 Bool -> Bool -> Bool && String loc1 String -> String -> Bool forall a. Eq a => a -> a -> Bool == String loc2 Bool -> Bool -> Bool && Maybe CInt en1 Maybe CInt -> Maybe CInt -> Bool forall a. Eq a => a -> a -> Bool == Maybe CInt en2 Bool -> Bool -> Bool && Maybe String fn1 Maybe String -> Maybe String -> Bool forall a. Eq a => a -> a -> Bool == Maybe String fn2 -- | 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.0instanceEq IOErrorType whereIOErrorType x == :: IOErrorType -> IOErrorType -> Bool == IOErrorType y =Int# -> Bool isTrue# (IOErrorType -> Int# forall a. a -> Int# getTag IOErrorType x Int# -> Int# -> Int# ==# IOErrorType -> Int# forall a. a -> Int# getTag IOErrorType y )-- | @since 4.1.0.0instanceShow IOErrorType whereshowsPrec :: Int -> IOErrorType -> ShowS showsPrec Int _IOErrorType e =String -> ShowS showString (String -> ShowS) -> String -> ShowS forall a b. (a -> b) -> a -> b $ caseIOErrorType e ofIOErrorType AlreadyExists ->String "already exists"IOErrorType NoSuchThing ->String "does not exist"IOErrorType ResourceBusy ->String "resource busy"IOErrorType ResourceExhausted ->String "resource exhausted"IOErrorType EOF ->String "end of file"IOErrorType IllegalOperation ->String "illegal operation"IOErrorType PermissionDenied ->String "permission denied"IOErrorType UserError ->String "user error"IOErrorType HardwareFault ->String "hardware fault"IOErrorType InappropriateType ->String "inappropriate type"IOErrorType Interrupted ->String "interrupted"IOErrorType InvalidArgument ->String "invalid argument"IOErrorType OtherError ->String "failed"IOErrorType ProtocolError ->String "protocol error"IOErrorType ResourceVanished ->String "resource vanished"IOErrorType SystemError ->String "system error"IOErrorType TimeExpired ->String "timeout"IOErrorType UnsatisfiedConstraints ->String "unsatisfied constraints"-- ultra-precise!IOErrorType UnsupportedOperation ->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 ->IOError userError :: String -> IOException userError String str =Maybe Handle -> IOErrorType -> String -> String -> Maybe CInt -> Maybe String -> IOException IOError Maybe Handle forall a. Maybe a Nothing IOErrorType UserError String ""String str Maybe CInt forall a. Maybe a Nothing Maybe String forall a. Maybe a Nothing -- ----------------------------------------------------------------------------- Showing IOErrors-- | @since 4.1.0.0instanceShow IOException whereshowsPrec :: Int -> IOException -> ShowS showsPrec Int p (IOError Maybe Handle hdl IOErrorType iot String loc String s Maybe CInt _Maybe String fn )=(caseMaybe String fn ofMaybe String Nothing ->caseMaybe Handle hdl ofMaybe Handle Nothing ->ShowS forall a. a -> a id Just Handle h ->Int -> Handle -> ShowS forall a. Show a => Int -> a -> ShowS showsPrec Int p Handle h ShowS -> ShowS -> ShowS forall b c a. (b -> c) -> (a -> b) -> a -> c . String -> ShowS showString String ": "Just String name ->String -> ShowS showString String name ShowS -> ShowS -> ShowS forall b c a. (b -> c) -> (a -> b) -> a -> c . String -> ShowS showString String ": ")ShowS -> ShowS -> ShowS forall b c a. (b -> c) -> (a -> b) -> a -> c . (caseString loc ofString ""->ShowS forall a. a -> a id String _->String -> ShowS showString String loc ShowS -> ShowS -> ShowS forall b c a. (b -> c) -> (a -> b) -> a -> c . String -> ShowS showString String ": ")ShowS -> ShowS -> ShowS forall b c a. (b -> c) -> (a -> b) -> a -> c . Int -> IOErrorType -> ShowS forall a. Show a => Int -> a -> ShowS showsPrec Int p IOErrorType iot ShowS -> ShowS -> ShowS forall b c a. (b -> c) -> (a -> b) -> a -> c . (caseString s ofString ""->ShowS forall a. a -> a id String _->String -> ShowS showString String " ("ShowS -> ShowS -> ShowS forall b c a. (b -> c) -> (a -> b) -> a -> c . String -> ShowS showString String s ShowS -> ShowS -> ShowS forall b c a. (b -> c) -> (a -> b) -> a -> c . String -> ShowS showString String ")")-- 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 ->a assertError :: forall a. (?callStack::CallStack) => Bool -> a -> a assertError Bool predicate a v |Bool predicate =a -> a forall a. a -> a lazy a v |Bool otherwise =IO a -> a forall a. IO a -> a unsafeDupablePerformIO (IO a -> a) -> IO a -> a forall a b. (a -> b) -> a -> b $ do[String] ccsStack <-IO [String] currentCallStack letimplicitParamCallStack :: [String] implicitParamCallStack =CallStack -> [String] prettyCallStackLines ?callStack::CallStack CallStack ?callStack ccsCallStack :: [String] ccsCallStack =[String] -> [String] showCCSStack [String] ccsStack stack :: String stack =String -> [String] -> String forall a. [a] -> [[a]] -> [a] intercalate String "\n"([String] -> String) -> [String] -> String forall a b. (a -> b) -> a -> b $ [String] implicitParamCallStack [String] -> [String] -> [String] forall a. [a] -> [a] -> [a] ++ [String] ccsCallStack AssertionFailed -> IO a forall e a. Exception e => e -> IO a throwIO (String -> AssertionFailed AssertionFailed (String "Assertion failed\n"String -> ShowS forall a. [a] -> [a] -> [a] ++ String stack ))unsupportedOperation ::IOError unsupportedOperation :: IOException unsupportedOperation =(Maybe Handle -> IOErrorType -> String -> String -> Maybe CInt -> Maybe String -> IOException IOError Maybe Handle forall a. Maybe a Nothing IOErrorType UnsupportedOperation String ""String "Operation is not supported"Maybe CInt forall a. Maybe a Nothing Maybe String forall a. Maybe a Nothing ){- (untangle coded message) expects "coded" to be of the form "location|details" It prints location message details -}untangle ::Addr# ->String ->String untangle :: Addr# -> ShowS untangle Addr# coded String message =String location String -> ShowS forall a. [a] -> [a] -> [a] ++ String ": "String -> ShowS forall a. [a] -> [a] -> [a] ++ String message String -> ShowS forall a. [a] -> [a] -> [a] ++ String details String -> ShowS forall a. [a] -> [a] -> [a] ++ String "\n"wherecoded_str :: String coded_str =Addr# -> String unpackCStringUtf8# Addr# coded (String location ,String details )=case((Char -> Bool) -> String -> (String, String) forall a. (a -> Bool) -> [a] -> ([a], [a]) span Char -> Bool not_bar String coded_str )of{(String loc ,String rest )->caseString rest of(Char '|': String det )->(String loc ,Char ' 'Char -> ShowS forall a. a -> [a] -> [a] : String det )String _->(String loc ,String "")}not_bar :: Char -> Bool not_bar Char c =Char c Char -> Char -> Bool forall a. Eq a => a -> a -> Bool /= Char '|'