{-# LANGUAGE Trustworthy #-} ----------------------------------------------------------------------------- -- | -- Module : System.Exit -- Copyright : (c) The University of Glasgow 2001 -- License : BSD-style (see the file libraries/base/LICENSE) -- -- Maintainer : libraries@haskell.org -- Stability : provisional -- Portability : portable -- -- Exiting the program. -- ----------------------------------------------------------------------------- module System.Exit ( ExitCode(ExitSuccess,ExitFailure) , exitWith , exitFailure , exitSuccess , die ) where import System.IO import GHC.IO import GHC.IO.Exception -- --------------------------------------------------------------------------- -- exitWith -- | Computation 'exitWith' @code@ throws 'ExitCode' @code@. -- Normally this terminates the program, returning @code@ to the -- program's caller. -- -- On program termination, the standard 'Handle's 'stdout' and -- 'stderr' are flushed automatically; any other buffered 'Handle's -- need to be flushed manually, otherwise the buffered data will be -- discarded. -- -- A program that fails in any other way is treated as if it had -- called 'exitFailure'. -- A program that terminates successfully without calling 'exitWith' -- explicitly is treated as if it had called 'exitWith' 'ExitSuccess'. -- -- As an 'ExitCode' is not an 'IOError', 'exitWith' bypasses -- the error handling in the 'IO' monad and cannot be intercepted by -- 'catch' from the "Prelude". However it is a 'Control.Exception.SomeException', and can -- be caught using the functions of "Control.Exception". This means -- that cleanup computations added with 'Control.Exception.bracket' -- (from "Control.Exception") are also executed properly on 'exitWith'. -- -- Note: in GHC, 'exitWith' should be called from the main program -- thread in order to exit the process. When called from another -- thread, 'exitWith' will throw an 'ExitException' as normal, but the -- exception will not cause the process itself to exit. -- exitWith :: ExitCode -> IO a exitWith :: forall a. ExitCode -> IO a exitWith ExitCode ExitSuccess = ExitCode -> IO a forall e a. Exception e => e -> IO a throwIO ExitCode ExitSuccess exitWith code :: ExitCode code@(ExitFailure Int n) | Int n Int -> Int -> Bool forall a. Eq a => a -> a -> Bool /= Int 0 = ExitCode -> IO a forall e a. Exception e => e -> IO a throwIO ExitCode code | Bool otherwise = IOError -> IO a forall a. IOError -> IO a ioError (Maybe Handle -> IOErrorType -> String -> String -> Maybe CInt -> Maybe String -> IOError IOError Maybe Handle forall a. Maybe a Nothing IOErrorType InvalidArgument String "exitWith" String "ExitFailure 0" Maybe CInt forall a. Maybe a Nothing Maybe String forall a. Maybe a Nothing) -- | The computation 'exitFailure' is equivalent to -- 'exitWith' @(@'ExitFailure' /exitfail/@)@, -- where /exitfail/ is implementation-dependent. exitFailure :: IO a exitFailure :: forall a. IO a exitFailure = ExitCode -> IO a forall a. ExitCode -> IO a exitWith (Int -> ExitCode ExitFailure Int 1) -- | The computation 'exitSuccess' is equivalent to -- 'exitWith' 'ExitSuccess', It terminates the program -- successfully. exitSuccess :: IO a exitSuccess :: forall a. IO a exitSuccess = ExitCode -> IO a forall a. ExitCode -> IO a exitWith ExitCode ExitSuccess -- | Write given error message to `stderr` and terminate with `exitFailure`. -- -- @since 4.8.0.0 die :: String -> IO a die :: forall a. String -> IO a die String err = Handle -> String -> IO () hPutStrLn Handle stderr String err 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 exitFailure