{-# LANGUAGE ScopedTypeVariables, LambdaCase #-}
module GHC.Utils.Panic.Plain
( PlainGhcException(..)
, showPlainGhcException
, panic, sorry, pgmError
, cmdLineError, cmdLineErrorIO
, assertPanic
, assert, assertM, massert
) where
import GHC.Settings.Config
import GHC.Utils.Constants
import GHC.Utils.Exception as Exception
import GHC.Stack
import GHC.Prelude.Basic
import System.IO.Unsafe
data PlainGhcException
= PlainSignal Int
| PlainUsageError String
| PlainCmdLineError String
| PlainPanic String
| PlainSorry String
| PlainInstallationError String
| PlainProgramError String
instance Exception PlainGhcException
instance Show PlainGhcException where
showsPrec :: Int -> PlainGhcException -> ShowS
showsPrec Int
_ PlainGhcException
e = PlainGhcException -> ShowS
showPlainGhcException PlainGhcException
e
short_usage :: String
short_usage :: String
short_usage = String
"Usage: For basic information, try the `--help' option."
showPlainGhcException :: PlainGhcException -> ShowS
showPlainGhcException :: PlainGhcException -> ShowS
showPlainGhcException =
\case
PlainSignal Int
n -> String -> ShowS
showString String
"signal: " forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Show a => a -> ShowS
shows Int
n
PlainUsageError String
str -> String -> ShowS
showString String
str forall b c a. (b -> c) -> (a -> b) -> a -> c
. Char -> ShowS
showChar Char
'\n' forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> ShowS
showString String
short_usage
PlainCmdLineError String
str -> String -> ShowS
showString String
str
PlainPanic String
s -> ShowS -> ShowS
panicMsg (String -> ShowS
showString String
s)
PlainSorry String
s -> ShowS -> ShowS
sorryMsg (String -> ShowS
showString String
s)
PlainInstallationError String
str -> String -> ShowS
showString String
str
PlainProgramError String
str -> String -> ShowS
showString String
str
where
sorryMsg :: ShowS -> ShowS
sorryMsg :: ShowS -> ShowS
sorryMsg ShowS
s =
String -> ShowS
showString String
"sorry! (unimplemented feature or known bug)\n"
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> ShowS
showString (String
" GHC version " forall a. [a] -> [a] -> [a]
++ String
cProjectVersion forall a. [a] -> [a] -> [a]
++ String
":\n\t")
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ShowS
s forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> ShowS
showString String
"\n"
panicMsg :: ShowS -> ShowS
panicMsg :: ShowS -> ShowS
panicMsg ShowS
s =
String -> ShowS
showString String
"panic! (the 'impossible' happened)\n"
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> ShowS
showString (String
" GHC version " forall a. [a] -> [a] -> [a]
++ String
cProjectVersion forall a. [a] -> [a] -> [a]
++ String
":\n\t")
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ShowS
s forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> ShowS
showString String
"\n\n"
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> ShowS
showString String
"Please report this as a GHC bug: https://www.haskell.org/ghc/reportabug\n"
throwPlainGhcException :: PlainGhcException -> a
throwPlainGhcException :: forall a. PlainGhcException -> a
throwPlainGhcException = forall a e. Exception e => e -> a
Exception.throw
panic, sorry, pgmError :: HasCallStack => String -> a
panic :: forall a. HasCallStack => String -> a
panic String
x = forall a. IO a -> a
unsafeDupablePerformIO forall a b. (a -> b) -> a -> b
$ do
[String]
stack <- Ptr CostCentreStack -> IO [String]
ccsToStrings forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< forall dummy. dummy -> IO (Ptr CostCentreStack)
getCurrentCCS String
x
let doc :: String
doc = [String] -> String
unlines forall a b. (a -> b) -> a -> b
$ forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (String
" "forall a. [a] -> [a] -> [a]
++) forall a b. (a -> b) -> a -> b
$ String -> [String]
lines (CallStack -> String
prettyCallStack HasCallStack => CallStack
callStack)
if forall (t :: * -> *) a. Foldable t => t a -> Bool
null [String]
stack
then forall a. PlainGhcException -> a
throwPlainGhcException (String -> PlainGhcException
PlainPanic (String
x forall a. [a] -> [a] -> [a]
++ Char
'\n' forall a. a -> [a] -> [a]
: String
doc))
else forall a. PlainGhcException -> a
throwPlainGhcException (String -> PlainGhcException
PlainPanic (String
x forall a. [a] -> [a] -> [a]
++ Char
'\n' forall a. a -> [a] -> [a]
: [String] -> String
renderStack [String]
stack))
sorry :: forall a. HasCallStack => String -> a
sorry String
x = forall a. PlainGhcException -> a
throwPlainGhcException (String -> PlainGhcException
PlainSorry String
x)
pgmError :: forall a. HasCallStack => String -> a
pgmError String
x = forall a. PlainGhcException -> a
throwPlainGhcException (String -> PlainGhcException
PlainProgramError String
x)
cmdLineError :: String -> a
cmdLineError :: forall a. String -> a
cmdLineError = forall a. IO a -> a
unsafeDupablePerformIO forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. String -> IO a
cmdLineErrorIO
cmdLineErrorIO :: String -> IO a
cmdLineErrorIO :: forall a. String -> IO a
cmdLineErrorIO String
x = do
[String]
stack <- Ptr CostCentreStack -> IO [String]
ccsToStrings forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< forall dummy. dummy -> IO (Ptr CostCentreStack)
getCurrentCCS String
x
if forall (t :: * -> *) a. Foldable t => t a -> Bool
null [String]
stack
then forall a. PlainGhcException -> a
throwPlainGhcException (String -> PlainGhcException
PlainCmdLineError String
x)
else forall a. PlainGhcException -> a
throwPlainGhcException (String -> PlainGhcException
PlainCmdLineError (String
x forall a. [a] -> [a] -> [a]
++ Char
'\n' forall a. a -> [a] -> [a]
: [String] -> String
renderStack [String]
stack))
assertPanic :: String -> Int -> a
assertPanic :: forall a. String -> Int -> a
assertPanic String
file Int
line =
forall a e. Exception e => e -> a
Exception.throw (String -> AssertionFailed
Exception.AssertionFailed
(String
"ASSERT failed! file " forall a. [a] -> [a] -> [a]
++ String
file forall a. [a] -> [a] -> [a]
++ String
", line " forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> String
show Int
line))
assertPanic' :: HasCallStack => a
assertPanic' :: forall a. HasCallStack => a
assertPanic' =
let doc :: String
doc = [String] -> String
unlines forall a b. (a -> b) -> a -> b
$ forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (String
" "forall a. [a] -> [a] -> [a]
++) forall a b. (a -> b) -> a -> b
$ String -> [String]
lines (CallStack -> String
prettyCallStack HasCallStack => CallStack
callStack)
in
forall a e. Exception e => e -> a
Exception.throw (String -> AssertionFailed
Exception.AssertionFailed
(String
"ASSERT failed!\n"
forall a. [a] -> [a] -> [a]
++ forall a. HasCallStack => (HasCallStack => a) -> a
withFrozenCallStack String
doc))
assert :: HasCallStack => Bool -> a -> a
{-# INLINE assert #-}
assert :: forall a. HasCallStack => Bool -> a -> a
assert Bool
cond a
a =
if Bool
debugIsOn Bool -> Bool -> Bool
&& Bool -> Bool
not Bool
cond
then forall a. HasCallStack => (HasCallStack => a) -> a
withFrozenCallStack forall a. HasCallStack => a
assertPanic'
else a
a
massert :: (HasCallStack, Applicative m) => Bool -> m ()
{-# INLINE massert #-}
massert :: forall (m :: * -> *). (HasCallStack, Applicative m) => Bool -> m ()
massert Bool
cond = forall a. HasCallStack => (HasCallStack => a) -> a
withFrozenCallStack (forall a. HasCallStack => Bool -> a -> a
assert Bool
cond (forall (f :: * -> *) a. Applicative f => a -> f a
pure ()))
assertM :: (HasCallStack, Monad m) => m Bool -> m ()
{-# INLINE assertM #-}
assertM :: forall (m :: * -> *). (HasCallStack, Monad m) => m Bool -> m ()
assertM m Bool
mcond = forall a. HasCallStack => (HasCallStack => a) -> a
withFrozenCallStack (m Bool
mcond forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= forall (m :: * -> *). (HasCallStack, Applicative m) => Bool -> m ()
massert)