Skip to content
Snippets Groups Projects
Commit 3abf31a4 authored by Rodrigo Mesquita's avatar Rodrigo Mesquita :seedling: Committed by Marge Bot
Browse files

De-duplicate displayContext and displayExceptionContext

The former was unused except for one module where it was essentially
re-defining displayExceptionContext.

Moreover, this commit extends the fix from
bfe600f5 to displayExceptionContext too,
which was missing.
parent 7a74330b
No related branches found
No related tags found
No related merge requests found
......@@ -34,7 +34,8 @@ module GHC.Internal.Exception.Context
, ExceptionAnnotation(..)
) where
import GHC.Internal.Base ((++), return, String, Maybe(..), Semigroup(..), Monoid(..))
import GHC.Internal.Data.OldList (intersperse)
import GHC.Internal.Base (($), map, (++), return, String, Maybe(..), Semigroup(..), Monoid(..))
import GHC.Internal.Show (Show(..))
import GHC.Internal.Data.Typeable.Internal (Typeable, typeRep, eqTypeRep)
import GHC.Internal.Data.Type.Equality ( (:~~:)(HRefl) )
......@@ -92,10 +93,9 @@ mergeExceptionContext (ExceptionContext a) (ExceptionContext b) = ExceptionConte
--
-- @since base-4.20.0.0
displayExceptionContext :: ExceptionContext -> String
displayExceptionContext (ExceptionContext anns0) = go anns0
displayExceptionContext (ExceptionContext anns0) = mconcat $ intersperse "\n" $ map go anns0
where
go (SomeExceptionAnnotation ann : anns) = displayExceptionAnnotation ann ++ "\n" ++ go anns
go [] = "\n"
go (SomeExceptionAnnotation ann) = displayExceptionAnnotation ann
data SomeExceptionAnnotation = forall a. ExceptionAnnotation a => SomeExceptionAnnotation a
......
......@@ -49,7 +49,7 @@ module GHC.Internal.Exception.Type
, underflowException
) where
import GHC.Internal.Data.OldList (intersperse, lines, unlines, null)
import GHC.Internal.Data.OldList (lines, unlines, null)
import GHC.Internal.Data.Maybe
import GHC.Internal.Data.Typeable (Typeable, TypeRep, cast)
import qualified GHC.Internal.Data.Typeable as Typeable
......@@ -252,7 +252,7 @@ instance Exception SomeException where
-- @since base-4.21
displayExceptionWithInfo :: SomeException -> String
displayExceptionWithInfo (SomeException e) =
case displayContext ?exceptionContext of
case displayExceptionContext ?exceptionContext of
"" -> msg
dc -> msg ++ "\n\n" ++ dc
where
......@@ -268,11 +268,6 @@ displayExceptionWithInfo (SomeException e) =
tyMsg = Typeable.tyConPackage tyCon ++ ":" ++ Typeable.tyConModule tyCon ++ "." ++ Typeable.tyConName tyCon
tyCon = Typeable.typeRepTyCon rep
displayContext :: ExceptionContext -> String
displayContext (ExceptionContext anns0) = mconcat $ intersperse "\n" $ map go anns0
where
go (SomeExceptionAnnotation ann) = displayExceptionAnnotation ann
newtype NoBacktrace e = NoBacktrace e
deriving (Show)
......
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment