{-# LANGUAGE CPP #-}
{-# LANGUAGE MagicHash #-}
{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE Trustworthy #-}
{-# LANGUAGE UnliftedFFITypes #-}
{-# OPTIONS_HADDOCK not-home #-}
module GHC.Internal.TopHandler (
        runMainIO, runIO, runIOFastExit, runNonIO,
        topHandler, topHandlerFastExit,
        reportStackOverflow, reportError,
        flushStdHandles
    ) where
#include <ghcplatform.h>
#include "HsBaseConfig.h"
import GHC.Internal.Control.Exception
import GHC.Internal.Data.Maybe
import GHC.Internal.Foreign.C.Error
import GHC.Internal.Foreign.C.Types
import GHC.Internal.Foreign.C.String
import GHC.Internal.Base
import GHC.Internal.Conc.Sync hiding (throwTo)
import GHC.Internal.Real
import GHC.Internal.IO
import GHC.Internal.IO.Handle
import GHC.Internal.IO.StdHandles
import GHC.Internal.IO.Exception
import GHC.Internal.Weak
#if defined(mingw32_HOST_OS)
import GHC.Internal.ConsoleHandler as GHC.ConsoleHandler
#elif defined(javascript_HOST_ARCH)
#else
import GHC.Internal.Ptr
import GHC.Internal.Conc.Signal
import GHC.Internal.Data.Dynamic (toDyn)
#endif
foreign import ccall unsafe "rts_setMainThread"
  setMainThread :: Weak# ThreadId -> IO ()
runMainIO :: IO a -> IO a
runMainIO :: forall a. IO a -> IO a
runMainIO IO a
main =
    do
      main_thread_id <- IO ThreadId
myThreadId
      weak_tid <- mkWeakThreadId main_thread_id
      
      
      
      case weak_tid of (Weak Weak# ThreadId
w) -> Weak# ThreadId -> IO ()
setMainThread Weak# ThreadId
w
      install_interrupt_handler $ do
           m <- deRefWeak weak_tid
           case m of
               Maybe ThreadId
Nothing  -> () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
               Just ThreadId
tid -> ThreadId -> SomeException -> IO ()
forall e. Exception e => ThreadId -> e -> IO ()
throwTo ThreadId
tid (AsyncException -> SomeException
forall e. Exception e => e -> SomeException
toException AsyncException
UserInterrupt)
      main 
    IO a -> (SomeException -> IO a) -> IO a
forall e a. Exception e => IO a -> (e -> IO a) -> IO a
`catch`
      SomeException -> IO a
forall a. SomeException -> IO a
topHandler
install_interrupt_handler :: IO () -> IO ()
#if defined(javascript_HOST_ARCH)
install_interrupt_handler _ = return ()
#elif defined(mingw32_HOST_OS)
install_interrupt_handler handler = do
  _ <- GHC.ConsoleHandler.installHandler $
     Catch $ \event ->
        case event of
           ControlC -> handler
           Break    -> handler
           Close    -> handler
           _ -> return ()
  return ()
#elif !defined(HAVE_SIGNAL_H)
install_interrupt_handler _ = pure ()
#else
#include "rts/Signals.h"
install_interrupt_handler :: IO () -> IO ()
install_interrupt_handler IO ()
handler = do
   let sig :: CInt
sig = CONST_SIGINT :: CInt
   _ <- CInt
-> Maybe (HandlerFun, Dynamic) -> IO (Maybe (HandlerFun, Dynamic))
setHandler CInt
sig ((HandlerFun, Dynamic) -> Maybe (HandlerFun, Dynamic)
forall a. a -> Maybe a
Just (IO () -> HandlerFun
forall a b. a -> b -> a
const IO ()
handler, IO () -> Dynamic
forall a. Typeable a => a -> Dynamic
toDyn IO ()
handler))
   _ <- stg_sig_install sig STG_SIG_RST nullPtr
     
     
   return ()
foreign import ccall unsafe
  stg_sig_install
        :: CInt                         
        -> CInt                         
        -> Ptr ()                       
        -> IO CInt                      
#endif
runIO :: IO a -> IO a
runIO :: forall a. IO a -> IO a
runIO IO a
main = IO a -> (SomeException -> IO a) -> IO a
forall e a. Exception e => IO a -> (e -> IO a) -> IO a
catch IO a
main SomeException -> IO a
forall a. SomeException -> IO a
topHandler
runIOFastExit :: IO a -> IO a
runIOFastExit :: forall a. IO a -> IO a
runIOFastExit IO a
main = IO a -> (SomeException -> IO a) -> IO a
forall e a. Exception e => IO a -> (e -> IO a) -> IO a
catch IO a
main SomeException -> IO a
forall a. SomeException -> IO a
topHandlerFastExit
        
runNonIO :: a -> IO a
runNonIO :: forall a. a -> IO a
runNonIO a
a = IO a -> (SomeException -> IO a) -> IO a
forall e a. Exception e => IO a -> (e -> IO a) -> IO a
catch (a
a a -> IO a -> IO a
forall a b. a -> b -> b
`seq` a -> IO a
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return a
a) SomeException -> IO a
forall a. SomeException -> IO a
topHandler
topHandler :: SomeException -> IO a
topHandler :: forall a. SomeException -> IO a
topHandler SomeException
err = IO a -> (SomeException -> IO a) -> IO a
forall e a. Exception e => IO a -> (e -> IO a) -> IO a
catch ((Int -> IO a) -> SomeException -> IO a
forall a. (Int -> IO a) -> SomeException -> IO a
real_handler Int -> IO a
forall a. Int -> IO a
safeExit SomeException
err) SomeException -> IO a
forall a. SomeException -> IO a
topHandler
topHandlerFastExit :: SomeException -> IO a
topHandlerFastExit :: forall a. SomeException -> IO a
topHandlerFastExit SomeException
err =
  IO a -> (SomeException -> IO a) -> IO a
forall e a. Exception e => IO a -> (e -> IO a) -> IO a
catchException ((Int -> IO a) -> SomeException -> IO a
forall a. (Int -> IO a) -> SomeException -> IO a
real_handler Int -> IO a
forall a. Int -> IO a
fastExit SomeException
err) SomeException -> IO a
forall a. SomeException -> IO a
topHandlerFastExit
real_handler :: (Int -> IO a) -> SomeException -> IO a
real_handler :: forall a. (Int -> IO a) -> SomeException -> IO a
real_handler Int -> IO a
exit SomeException
se = do
  IO ()
flushStdHandles 
  case SomeException -> Maybe AsyncException
forall e. Exception e => SomeException -> Maybe e
fromException SomeException
se of
      Just AsyncException
StackOverflow -> do
           IO ()
reportStackOverflow
           Int -> IO a
exit Int
2
      Just AsyncException
UserInterrupt -> IO a
forall a. IO a
exitInterrupted
      Just AsyncException
HeapOverflow -> do
           IO ()
reportHeapOverflow
           Int -> IO a
exit Int
251
      Maybe AsyncException
_ -> case SomeException -> Maybe ExitCode
forall e. Exception e => SomeException -> Maybe e
fromException SomeException
se of
           
           Just ExitCode
ExitSuccess     -> Int -> IO a
exit Int
0
           Just (ExitFailure Int
n) -> Int -> IO a
exit Int
n
           
           Maybe ExitCode
_ -> IO a -> (IOException -> IO a) -> IO a
forall e a. Exception e => IO a -> (e -> IO a) -> IO a
catch (case SomeException -> Maybe IOException
forall e. Exception e => SomeException -> Maybe e
fromException SomeException
se of
                Just IOError{ ioe_type :: IOException -> IOErrorType
ioe_type = IOErrorType
ResourceVanished,
                              ioe_errno :: IOException -> Maybe CInt
ioe_errno = Just CInt
ioe,
                              ioe_handle :: IOException -> Maybe Handle
ioe_handle = Just Handle
hdl }
                   | CInt -> Errno
Errno CInt
ioe Errno -> Errno -> Bool
forall a. Eq a => a -> a -> Bool
== Errno
ePIPE, Handle
hdl Handle -> Handle -> Bool
forall a. Eq a => a -> a -> Bool
== Handle
stdout -> Int -> IO a
exit Int
0
                Maybe IOException
_ -> do SomeException -> IO ()
reportError SomeException
se
                        Int -> IO a
exit Int
1
                ) ((Int -> IO a) -> IOException -> IO a
forall a. (Int -> IO a) -> IOException -> IO a
disasterHandler Int -> IO a
exit) 
foreign import ccall unsafe "HsBase.h errorBelch2"
    c_errorBelch :: CString -> CString -> IO ()
errorBelch :: String -> IO ()
errorBelch :: String -> IO ()
errorBelch String
msg =
    String -> (CString -> IO ()) -> IO ()
forall a. String -> (CString -> IO a) -> IO a
withCAString String
"%s" ((CString -> IO ()) -> IO ()) -> (CString -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \CString
fmt ->
      String -> (CString -> IO ()) -> IO ()
forall a. String -> (CString -> IO a) -> IO a
withCAString String
msg ((CString -> IO ()) -> IO ()) -> (CString -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \CString
msg' ->
          CString -> CString -> IO ()
c_errorBelch CString
fmt CString
msg'
disasterHandler :: (Int -> IO a) -> IOError -> IO a
disasterHandler :: forall a. (Int -> IO a) -> IOException -> IO a
disasterHandler Int -> IO a
exit IOException
_ =
    String -> IO ()
errorBelch String
msgStr IO () -> IO a -> IO a
forall a b. IO a -> IO b -> IO b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Int -> IO a
exit Int
1
  where
    msgStr :: String
msgStr =
        String
"encountered an exception while trying to report an exception.\n" String -> String -> String
forall a. [a] -> [a] -> [a]
++
        String
"One possible reason for this is that we failed while trying to " String -> String -> String
forall a. [a] -> [a] -> [a]
++
        String
"encode an error message. Check that your locale is configured " String -> String -> String
forall a. [a] -> [a] -> [a]
++
        String
"properly."
flushStdHandles :: IO ()
flushStdHandles :: IO ()
flushStdHandles = do
  Handle -> IO ()
hFlush Handle
stdout IO () -> (SomeException -> IO ()) -> IO ()
forall e a. Exception e => IO a -> (e -> IO a) -> IO a
`catchException` SomeException -> IO ()
handleExc
  
  
  
  Handle -> IO ()
hFlush Handle
stderr IO () -> (SomeException -> IO ()) -> IO ()
forall e a. Exception e => IO a -> (e -> IO a) -> IO a
`catchException` SomeException -> IO ()
handleExc
  where
    
    
    
    
    
    
    handleExc :: SomeException -> IO ()
handleExc SomeException
se = do
      handleFinalizerExc <- IO (SomeException -> IO ())
getFinalizerExceptionHandler
      
      handleFinalizerExc se `catchException` (\(SomeException e
_) -> () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ())
safeExit, fastExit :: Int -> IO a
safeExit :: forall a. Int -> IO a
safeExit = CInt -> Int -> IO a
forall a. CInt -> Int -> IO a
exitHelper CInt
useSafeExit
fastExit :: forall a. Int -> IO a
fastExit = CInt -> Int -> IO a
forall a. CInt -> Int -> IO a
exitHelper CInt
useFastExit
unreachable :: IO a
unreachable :: forall a. IO a
unreachable = String -> IO a
forall a. String -> IO a
failIO String
"If you can read this, shutdownHaskellAndExit did not exit."
exitHelper :: CInt -> Int -> IO a
#if defined(mingw32_HOST_OS) || defined(javascript_HOST_ARCH)
exitHelper exitKind r =
  shutdownHaskellAndExit (fromIntegral r) exitKind >> unreachable
#else
exitHelper :: forall a. CInt -> Int -> IO a
exitHelper CInt
exitKind Int
r
  | Int
r Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Int
0 Bool -> Bool -> Bool
&& Int
r Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= Int
255
  = CInt -> CInt -> IO ()
shutdownHaskellAndExit   (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral   Int
r)  CInt
exitKind IO () -> IO a -> IO a
forall a b. IO a -> IO b -> IO b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> IO a
forall a. IO a
unreachable
  | Int
r Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= -Int
127 Bool -> Bool -> Bool
&& Int
r Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= -Int
1
  = CInt -> CInt -> IO ()
shutdownHaskellAndSignal (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (-Int
r)) CInt
exitKind IO () -> IO a -> IO a
forall a b. IO a -> IO b -> IO b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> IO a
forall a. IO a
unreachable
  | Bool
otherwise
  = CInt -> CInt -> IO ()
shutdownHaskellAndExit   CInt
0xff                CInt
exitKind IO () -> IO a -> IO a
forall a b. IO a -> IO b -> IO b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> IO a
forall a. IO a
unreachable
#if !defined(HAVE_SIGNAL_H)
shutdownHaskellAndSignal :: CInt -> CInt -> IO ()
shutdownHaskellAndSignal = shutdownHaskellAndExit
#else
foreign import ccall "shutdownHaskellAndSignal"
  shutdownHaskellAndSignal :: CInt -> CInt -> IO ()
#endif
#endif
exitInterrupted :: IO a
exitInterrupted :: forall a. IO a
exitInterrupted =
#if defined(mingw32_HOST_OS) || defined(javascript_HOST_ARCH)
  safeExit 252
#elif !defined(HAVE_SIGNAL_H)
  safeExit 1
#else
  
  
  Int -> IO a
forall a. Int -> IO a
safeExit (-CONST_SIGINT)
#endif
foreign import ccall "Rts.h shutdownHaskellAndExit"
  shutdownHaskellAndExit :: CInt -> CInt -> IO ()
useFastExit, useSafeExit :: CInt
useFastExit :: CInt
useFastExit = CInt
1
useSafeExit :: CInt
useSafeExit = CInt
0