33{-# LANGUAGE FlexibleContexts #-}
44{-# LANGUAGE FlexibleInstances #-}
55{-# LANGUAGE GADTs #-}
6+ #if MIN_VERSION_base(4,21,0)
7+ {-# LANGUAGE ImplicitParams #-}
8+ #endif
69{-# LANGUAGE InstanceSigs #-}
710{-# LANGUAGE LambdaCase #-}
811{-# LANGUAGE RankNTypes #-}
@@ -39,6 +42,7 @@ module Distribution.Simple.Utils
3942 , dieNoWrap
4043 , topHandler
4144 , topHandlerWith
45+ , isUserException
4246 , warn
4347 , warnError
4448 , notice
@@ -301,6 +305,10 @@ import GitHash
301305 )
302306#endif
303307
308+ #if MIN_VERSION_base(4,21,0)
309+ import Control.Exception.Context
310+ #endif
311+
304312-- We only get our own version number when we're building with ourselves
305313cabalVersion :: Version
306314#if defined(BOOTSTRAPPED_CABAL)
@@ -505,9 +513,22 @@ ioeModifyErrorString = over ioeErrorString
505513ioeErrorString :: Lens' IOError String
506514ioeErrorString f ioe = ioeSetErrorString ioe <$> f (ioeGetErrorString ioe)
507515
516+ -- | Check that the type of the exception matches the given user error type.
517+ isUserException :: forall user_err . Typeable user_err => Proxy user_err -> Exception. SomeException -> Bool
518+ isUserException Proxy (SomeException se) =
519+ case cast se :: Maybe user_err of
520+ Just {} -> True
521+ Nothing -> False
522+
508523{-# NOINLINE topHandlerWith #-}
509- topHandlerWith :: forall a . (Exception. SomeException -> IO a ) -> IO a -> IO a
510- topHandlerWith cont prog = do
524+ topHandlerWith
525+ :: forall a
526+ . (Exception. SomeException -> Bool )
527+ -- ^ Identify when the error is an exception to display to users.
528+ -> (Exception. SomeException -> IO a )
529+ -> IO a
530+ -> IO a
531+ topHandlerWith is_user_exception cont prog = do
511532 -- By default, stderr to a terminal device is NoBuffering. But this
512533 -- is *really slow*
513534 hSetBuffering stderr LineBuffering
@@ -535,7 +556,7 @@ topHandlerWith cont prog = do
535556 cont se
536557
537558 message :: String -> Exception. SomeException -> String
538- message pname (Exception. SomeException se) =
559+ message pname e @ (Exception. SomeException se) =
539560 case cast se :: Maybe Exception. IOException of
540561 Just ioe
541562 | ioeGetVerbatim ioe ->
@@ -550,15 +571,27 @@ topHandlerWith cont prog = do
550571 _ -> " "
551572 detail = ioeGetErrorString ioe
552573 in wrapText $ addErrorPrefix $ pname ++ " : " ++ file ++ detail
553- _ ->
554- displaySomeException se ++ " \n "
574+ -- Don't print a call stack for a "user exception"
575+ _
576+ | is_user_exception e -> displayException e
577+ -- Other errors which have are not intended for user display, print with a callstack.
578+ | otherwise -> displaySomeExceptionWithContext e ++ " \n "
555579
556580-- | BC wrapper around 'Exception.displayException'.
557- displaySomeException :: Exception. Exception e => e -> String
558- displaySomeException se = Exception. displayException se
581+ displaySomeExceptionWithContext :: SomeException -> String
582+ #if MIN_VERSION_base(4,21,0)
583+ displaySomeExceptionWithContext (SomeException e) =
584+ case displayExceptionContext ? exceptionContext of
585+ " " -> msg
586+ dc -> msg ++ " \n\n " ++ dc
587+ where
588+ msg = displayException e
589+ #else
590+ displaySomeExceptionWithContext e = displayException e
591+ #endif
559592
560- topHandler :: IO a -> IO a
561- topHandler prog = topHandlerWith (const $ exitWith (ExitFailure 1 )) prog
593+ topHandler :: ( Exception. SomeException -> Bool ) -> IO a -> IO a
594+ topHandler is_user_exception prog = topHandlerWith is_user_exception (const $ exitWith (ExitFailure 1 )) prog
562595
563596-- | Depending on 'isVerboseStderr', set the output handle to 'stderr' or 'stdout'.
564597verbosityHandle :: Verbosity -> Handle
0 commit comments