How is ExitCode handled?
Tom Ellis
tom-lists-haskell-cafe-2023 at jaguarpaw.co.uk
Sun Oct 20 12:06:01 UTC 2024
Hello all,
I'm not sure I understand how an `ExitCode` exception is used to
terminate a running program. Can anyone clarify?
When we call `exitWith`, what we're doing is `throw`ing an `ExitCode`
exception:
https://www.stackage.org/haddock/lts-22.38/base-4.18.2.1/src/System.Exit.html#exitWith
That exception must be caught somewhere, and used to cause the running
program to exit with the exit code in question. But where?
It's not in the default `uncaughtExceptionHandler`:
https://hackage.haskell.org/package/base-4.20.0.0/docs/src/GHC-Conc-Sync.html#setUncaughtExceptionHandler
That doesn't do anything special with exit code. It seems like
real_handler does:
https://hackage.haskell.org/package/ghc-internal-9.1001.0/docs/src/GHC.Internal.TopHandler.html#topHandler
>From my experiements with a small program (below) I conclude that the
default handler is installed on every thread, and real_handler is
installed *on the main thread only* *below* the default handler, so
that if an `ExitCode` exception is thrown the default handler never
gets a chance to see it.
Is that right?
Thanks,
Tom
{-# LANGUAGE GHC2021 #-}
{-# LANGUAGE LambdaCase #-}
import System.Environment (getArgs)
import System.Exit (ExitCode (ExitFailure))
import Control.Exception
(Exception, SomeException (SomeException), throw)
import GHC.Conc
(forkIO, setUncaughtExceptionHandler, threadDelay)
data MyEx = MyEx
deriving Show
instance Exception MyEx
myHandler (SomeException e) =
putStrLn $ "In myHandler: " <> show e
run f = do
setUncaughtExceptionHandler myHandler
f
main = do
getArgs >>= \case
-- Exits with exit code 1
["1"] -> run (throw (ExitFailure 1))
-- Print: In myHandler: MyEx
-- Exits with exit code 1
["2"] -> run (throw MyEx)
-- Print: In myHandler: ExitFailure 1
-- Exits with exit code 0
["3"] -> run (forkIO (throw (ExitFailure 1)))
-- Print: In myHandler: MyEx
-- Exits with exit code 0
["4"] -> run (forkIO (throw MyEx))
_ -> error "Need an argument"
threadDelay (1000 * 1000)
More information about the ghc-devs
mailing list