{-# LANGUAGE Trustworthy #-}
{-# LANGUAGE DeriveGeneric, NoImplicitPrelude, MagicHash,
ExistentialQuantification, ImplicitParams #-}
{-# OPTIONS_GHC -funbox-strict-fields #-}
{-# OPTIONS_HADDOCK not-home #-}
module GHC.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,
) where
import GHC.Base
import GHC.Generics
import GHC.List
import GHC.IO
import GHC.Show
import GHC.Read
import GHC.Exception
import GHC.IO.Handle.Types
import GHC.OldList ( intercalate )
import {-# SOURCE #-} GHC.Stack.CCS
import Foreign.C.Types
import Data.Typeable ( cast )
data BlockedIndefinitelyOnMVar = BlockedIndefinitelyOnMVar
instance Exception BlockedIndefinitelyOnMVar
instance Show BlockedIndefinitelyOnMVar where
showsPrec :: Int -> BlockedIndefinitelyOnMVar -> ShowS
showsPrec _ BlockedIndefinitelyOnMVar = String -> ShowS
showString "thread blocked indefinitely in an MVar operation"
blockedIndefinitelyOnMVar :: SomeException
blockedIndefinitelyOnMVar :: SomeException
blockedIndefinitelyOnMVar = BlockedIndefinitelyOnMVar -> SomeException
forall e. Exception e => e -> SomeException
toException BlockedIndefinitelyOnMVar
BlockedIndefinitelyOnMVar
data BlockedIndefinitelyOnSTM = BlockedIndefinitelyOnSTM
instance Exception BlockedIndefinitelyOnSTM
instance Show BlockedIndefinitelyOnSTM where
showsPrec :: Int -> BlockedIndefinitelyOnSTM -> ShowS
showsPrec _ BlockedIndefinitelyOnSTM = String -> ShowS
showString "thread blocked indefinitely in an STM transaction"
blockedIndefinitelyOnSTM :: SomeException
blockedIndefinitelyOnSTM :: SomeException
blockedIndefinitelyOnSTM = BlockedIndefinitelyOnSTM -> SomeException
forall e. Exception e => e -> SomeException
toException BlockedIndefinitelyOnSTM
BlockedIndefinitelyOnSTM
data Deadlock = Deadlock
instance Exception Deadlock
instance Show Deadlock where
showsPrec :: Int -> Deadlock -> ShowS
showsPrec _ Deadlock = String -> ShowS
showString "<<deadlock>>"
data AllocationLimitExceeded = AllocationLimitExceeded
instance Exception AllocationLimitExceeded where
toException :: 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
instance Show AllocationLimitExceeded where
showsPrec :: Int -> AllocationLimitExceeded -> ShowS
showsPrec _ AllocationLimitExceeded =
String -> ShowS
showString "allocation limit exceeded"
allocationLimitExceeded :: SomeException
allocationLimitExceeded :: SomeException
allocationLimitExceeded = AllocationLimitExceeded -> SomeException
forall e. Exception e => e -> SomeException
toException AllocationLimitExceeded
AllocationLimitExceeded
newtype CompactionFailed = CompactionFailed String
instance Exception CompactionFailed where
instance Show CompactionFailed where
showsPrec :: Int -> CompactionFailed -> ShowS
showsPrec _ (CompactionFailed why :: String
why) =
String -> ShowS
showString ("compaction failed: " String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
why)
cannotCompactFunction :: SomeException
cannotCompactFunction :: SomeException
cannotCompactFunction =
CompactionFailed -> SomeException
forall e. Exception e => e -> SomeException
toException (String -> CompactionFailed
CompactionFailed "cannot compact functions")
cannotCompactPinned :: SomeException
cannotCompactPinned :: SomeException
cannotCompactPinned =
CompactionFailed -> SomeException
forall e. Exception e => e -> SomeException
toException (String -> CompactionFailed
CompactionFailed "cannot compact pinned objects")
cannotCompactMutable :: SomeException
cannotCompactMutable :: SomeException
cannotCompactMutable =
CompactionFailed -> SomeException
forall e. Exception e => e -> SomeException
toException (String -> CompactionFailed
CompactionFailed "cannot compact mutable objects")
newtype AssertionFailed = AssertionFailed String
instance Exception AssertionFailed
instance Show AssertionFailed where
showsPrec :: Int -> AssertionFailed -> ShowS
showsPrec _ (AssertionFailed err :: String
err) = String -> ShowS
showString String
err
data SomeAsyncException = forall e . Exception e => SomeAsyncException e
instance Show SomeAsyncException where
show :: SomeAsyncException -> String
show (SomeAsyncException e :: e
e) = e -> String
forall a. Show a => a -> String
show e
e
instance Exception SomeAsyncException
asyncExceptionToException :: Exception e => e -> SomeException
asyncExceptionToException :: 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
asyncExceptionFromException :: Exception e => SomeException -> Maybe e
asyncExceptionFromException :: SomeException -> Maybe e
asyncExceptionFromException x :: SomeException
x = do
SomeAsyncException a :: 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
data AsyncException
= StackOverflow
| HeapOverflow
| ThreadKilled
| UserInterrupt
deriving ( Eq
, Ord
)
instance Exception AsyncException where
toException :: 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
data ArrayException
= IndexOutOfBounds String
| UndefinedElement String
deriving ( Eq
, Ord
)
instance Exception ArrayException
stackOverflow, 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
instance Show AsyncException where
showsPrec :: Int -> AsyncException -> ShowS
showsPrec _ StackOverflow = String -> ShowS
showString "stack overflow"
showsPrec _ HeapOverflow = String -> ShowS
showString "heap overflow"
showsPrec _ ThreadKilled = String -> ShowS
showString "thread killed"
showsPrec _ UserInterrupt = String -> ShowS
showString "user interrupt"
instance Show ArrayException where
showsPrec :: Int -> ArrayException -> ShowS
showsPrec _ (IndexOutOfBounds s :: String
s)
= String -> ShowS
showString "array index out of range"
ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (if Bool -> Bool
not (String -> Bool
forall a. [a] -> Bool
null String
s) then String -> ShowS
showString ": " ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> ShowS
showString String
s
else ShowS
forall a. a -> a
id)
showsPrec _ (UndefinedElement s :: String
s)
= String -> ShowS
showString "undefined array element"
ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (if Bool -> Bool
not (String -> Bool
forall a. [a] -> Bool
null String
s) then String -> ShowS
showString ": " ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> ShowS
showString String
s
else ShowS
forall a. a -> a
id)
data FixIOException = FixIOException
instance Exception FixIOException
instance Show FixIOException where
showsPrec :: Int -> FixIOException -> ShowS
showsPrec _ FixIOException = String -> ShowS
showString "cyclic evaluation in fixIO"
data ExitCode
= ExitSuccess
| ExitFailure Int
deriving (ExitCode -> ExitCode -> Bool
(ExitCode -> ExitCode -> Bool)
-> (ExitCode -> ExitCode -> Bool) -> Eq ExitCode
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ExitCode -> ExitCode -> Bool
$c/= :: ExitCode -> ExitCode -> Bool
== :: ExitCode -> ExitCode -> Bool
$c== :: 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
min :: ExitCode -> ExitCode -> ExitCode
$cmin :: ExitCode -> ExitCode -> ExitCode
max :: ExitCode -> ExitCode -> ExitCode
$cmax :: ExitCode -> ExitCode -> ExitCode
>= :: ExitCode -> ExitCode -> Bool
$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
compare :: ExitCode -> ExitCode -> Ordering
$ccompare :: ExitCode -> ExitCode -> Ordering
$cp1Ord :: Eq 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
readListPrec :: ReadPrec [ExitCode]
$creadListPrec :: ReadPrec [ExitCode]
readPrec :: ReadPrec ExitCode
$creadPrec :: ReadPrec ExitCode
readList :: ReadS [ExitCode]
$creadList :: ReadS [ExitCode]
readsPrec :: Int -> ReadS ExitCode
$creadsPrec :: Int -> ReadS 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
showList :: [ExitCode] -> ShowS
$cshowList :: [ExitCode] -> ShowS
show :: ExitCode -> String
$cshow :: ExitCode -> String
showsPrec :: Int -> ExitCode -> ShowS
$cshowsPrec :: Int -> 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
$cto :: forall x. Rep ExitCode x -> ExitCode
$cfrom :: forall x. ExitCode -> Rep ExitCode x
Generic)
instance Exception ExitCode
ioException :: IOException -> IO a
ioException :: IOException -> IO a
ioException err :: IOException
err = IOException -> IO a
forall e a. Exception e => e -> IO a
throwIO IOException
err
ioError :: IOError -> IO a
ioError :: IOException -> IO a
ioError = IOException -> IO a
forall a. IOException -> IO a
ioException
type IOError = IOException
data IOException
= IOError {
IOException -> Maybe Handle
ioe_handle :: Maybe Handle,
IOException -> IOErrorType
ioe_type :: IOErrorType,
IOException -> String
ioe_location :: String,
IOException -> String
ioe_description :: String,
IOException -> Maybe CInt
ioe_errno :: Maybe CInt,
IOException -> Maybe String
ioe_filename :: Maybe FilePath
}
instance Exception IOException
instance Eq IOException where
(IOError h1 :: Maybe Handle
h1 e1 :: IOErrorType
e1 loc1 :: String
loc1 str1 :: String
str1 en1 :: Maybe CInt
en1 fn1 :: Maybe String
fn1) == :: IOException -> IOException -> Bool
== (IOError h2 :: Maybe Handle
h2 e2 :: IOErrorType
e2 loc2 :: String
loc2 str2 :: String
str2 en2 :: Maybe CInt
en2 fn2 :: Maybe String
fn2) =
IOErrorType
e1IOErrorType -> IOErrorType -> Bool
forall a. Eq a => a -> a -> Bool
==IOErrorType
e2 Bool -> Bool -> Bool
&& String
str1String -> String -> Bool
forall a. Eq a => a -> a -> Bool
==String
str2 Bool -> Bool -> Bool
&& Maybe Handle
h1Maybe Handle -> Maybe Handle -> Bool
forall a. Eq a => a -> a -> Bool
==Maybe Handle
h2 Bool -> Bool -> Bool
&& String
loc1String -> String -> Bool
forall a. Eq a => a -> a -> Bool
==String
loc2 Bool -> Bool -> Bool
&& Maybe CInt
en1Maybe CInt -> Maybe CInt -> Bool
forall a. Eq a => a -> a -> Bool
==Maybe CInt
en2 Bool -> Bool -> Bool
&& Maybe String
fn1Maybe String -> Maybe String -> Bool
forall a. Eq a => a -> a -> Bool
==Maybe String
fn2
data IOErrorType
= AlreadyExists
| NoSuchThing
| ResourceBusy
| ResourceExhausted
| EOF
| IllegalOperation
| PermissionDenied
| UserError
| UnsatisfiedConstraints
| SystemError
| ProtocolError
| OtherError
| InvalidArgument
| InappropriateType
| HardwareFault
| UnsupportedOperation
| TimeExpired
| ResourceVanished
| Interrupted
instance Eq IOErrorType where
x :: IOErrorType
x == :: IOErrorType -> IOErrorType -> Bool
== y :: 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)
instance Show IOErrorType where
showsPrec :: Int -> IOErrorType -> ShowS
showsPrec _ e :: IOErrorType
e =
String -> ShowS
showString (String -> ShowS) -> String -> ShowS
forall a b. (a -> b) -> a -> b
$
case IOErrorType
e of
AlreadyExists -> "already exists"
NoSuchThing -> "does not exist"
ResourceBusy -> "resource busy"
ResourceExhausted -> "resource exhausted"
EOF -> "end of file"
IllegalOperation -> "illegal operation"
PermissionDenied -> "permission denied"
UserError -> "user error"
HardwareFault -> "hardware fault"
InappropriateType -> "inappropriate type"
Interrupted -> "interrupted"
InvalidArgument -> "invalid argument"
OtherError -> "failed"
ProtocolError -> "protocol error"
ResourceVanished -> "resource vanished"
SystemError -> "system error"
TimeExpired -> "timeout"
UnsatisfiedConstraints -> "unsatisfied constraints"
UnsupportedOperation -> "unsupported operation"
userError :: String -> IOError
userError :: String -> IOException
userError str :: String
str = Maybe Handle
-> IOErrorType
-> String
-> String
-> Maybe CInt
-> Maybe String
-> IOException
IOError Maybe Handle
forall a. Maybe a
Nothing IOErrorType
UserError "" String
str Maybe CInt
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing
instance Show IOException where
showsPrec :: Int -> IOException -> ShowS
showsPrec p :: Int
p (IOError hdl :: Maybe Handle
hdl iot :: IOErrorType
iot loc :: String
loc s :: String
s _ fn :: Maybe String
fn) =
(case Maybe String
fn of
Nothing -> case Maybe Handle
hdl of
Nothing -> ShowS
forall a. a -> a
id
Just h :: 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 ": "
Just name :: String
name -> String -> ShowS
showString String
name ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> ShowS
showString ": ") ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
(case String
loc of
"" -> ShowS
forall a. a -> a
id
_ -> String -> ShowS
showString String
loc ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> ShowS
showString ": ") 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
.
(case String
s of
"" -> ShowS
forall a. a -> a
id
_ -> String -> ShowS
showString " (" 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 ")")
assertError :: (?callStack :: CallStack) => Bool -> a -> a
assertError :: Bool -> a -> a
assertError predicate :: Bool
predicate v :: 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
let
implicitParamCallStack :: [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 "\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 ("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 ""
"Operation is not supported" Maybe CInt
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing)
untangle :: Addr# -> String -> String
untangle :: Addr# -> ShowS
untangle coded :: Addr#
coded message :: String
message
= String
location
String -> ShowS
forall a. [a] -> [a] -> [a]
++ ": "
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]
++ "\n"
where
coded_str :: String
coded_str = Addr# -> String
unpackCStringUtf8# Addr#
coded
(location :: String
location, details :: String
details)
= case ((Char -> Bool) -> String -> (String, String)
forall a. (a -> Bool) -> [a] -> ([a], [a])
span Char -> Bool
not_bar String
coded_str) of { (loc :: String
loc, rest :: String
rest) ->
case String
rest of
('|':det :: String
det) -> (String
loc, ' ' Char -> ShowS
forall a. a -> [a] -> [a]
: String
det)
_ -> (String
loc, "")
}
not_bar :: Char -> Bool
not_bar c :: Char
c = Char
c Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
/= '|'