Hannes Siebenhandl pushed to branch wip/fendor/backtraces-decoders at Glasgow Haskell Compiler / GHC

Commits:

24 changed files:

Changes:

  • libraries/ghc-experimental/src/GHC/Exception/Backtrace/Experimental.hs
    1
    +{-
    
    2
    +Module      :  GHC.Exception.Backtrace.Experimental
    
    3
    +Copyright   :  (c) The GHC Team
    
    4
    +License     :  see libraries/ghc-experimental/LICENSE
    
    5
    +
    
    6
    +Maintainer  :  ghc-devs@haskell.org
    
    7
    +Stability   :  experimental
    
    8
    +Portability :  non-portable (GHC extensions)
    
    9
    +
    
    10
    +This module exposes experimental extensions to the Backtrace mechanism of GHC.
    
    11
    +-}
    
    12
    +module GHC.Exception.Backtrace.Experimental (
    
    13
    +  -- * Collecting exception annotations (like backtraces)
    
    14
    +  CollectExceptionAnnotationMechanism,
    
    15
    +  getCollectExceptionAnnotationMechanism,
    
    16
    +  setCollectExceptionAnnotation,
    
    17
    +  collectExceptionAnnotation,
    
    18
    +  ) where
    
    19
    +
    
    20
    +import GHC.Internal.Exception.Backtrace

  • libraries/ghc-internal/src/GHC/Internal/Exception.hs
    ... ... @@ -70,7 +70,8 @@ import GHC.Internal.Show
    70 70
     import GHC.Internal.Stack.Types
    
    71 71
     import GHC.Internal.IO.Unsafe
    
    72 72
     import {-# SOURCE #-} GHC.Internal.Stack (prettyCallStackLines, prettyCallStack, prettySrcLoc, withFrozenCallStack)
    
    73
    -import {-# SOURCE #-} GHC.Internal.Exception.Backtrace (collectBacktraces)
    
    73
    +import {-# SOURCE #-} GHC.Internal.Exception.Backtrace (collectExceptionAnnotation)
    
    74
    +import GHC.Internal.Exception.Context (SomeExceptionAnnotation(..))
    
    74 75
     import GHC.Internal.Exception.Type
    
    75 76
     
    
    76 77
     -- | Throw an exception.  Exceptions may be thrown from purely
    
    ... ... @@ -166,8 +167,8 @@ toExceptionWithBacktrace :: (HasCallStack, Exception e)
    166 167
                              => e -> IO SomeException
    
    167 168
     toExceptionWithBacktrace e
    
    168 169
       | backtraceDesired e = do
    
    169
    -      bt <- collectBacktraces
    
    170
    -      return (addExceptionContext bt (toException e))
    
    170
    +      SomeExceptionAnnotation ea <- collectExceptionAnnotation
    
    171
    +      return (addExceptionContext ea (toException e))
    
    171 172
       | otherwise = return (toException e)
    
    172 173
     
    
    173 174
     -- | This is thrown when the user calls 'error'. The @String@ is the
    

  • libraries/ghc-internal/src/GHC/Internal/Exception/Backtrace.hs
    ... ... @@ -12,7 +12,7 @@ import GHC.Internal.IO.Unsafe (unsafePerformIO)
    12 12
     import GHC.Internal.Exception.Context
    
    13 13
     import GHC.Internal.Ptr
    
    14 14
     import GHC.Internal.Data.Maybe (fromMaybe)
    
    15
    -import GHC.Internal.Stack.Types as GHC.Stack (CallStack)
    
    15
    +import GHC.Internal.Stack.Types as GHC.Stack (CallStack, HasCallStack)
    
    16 16
     import qualified GHC.Internal.Stack as HCS
    
    17 17
     import qualified GHC.Internal.ExecutionStack.Internal as ExecStack
    
    18 18
     import qualified GHC.Internal.Stack.CloneStack as CloneStack
    
    ... ... @@ -86,6 +86,37 @@ setBacktraceMechanismState bm enabled = do
    86 86
         _ <- atomicModifyIORef'_ enabledBacktraceMechanismsRef (setBacktraceMechanismEnabled bm enabled)
    
    87 87
         return ()
    
    88 88
     
    
    89
    +-- | How to collect 'ExceptionAnnotation's on throwing 'Exception's.
    
    90
    +--
    
    91
    +data CollectExceptionAnnotationMechanism = CollectExceptionAnnotationMechanism
    
    92
    +  { ceaCollectExceptionAnnotationMechanism :: HasCallStack => IO SomeExceptionAnnotation
    
    93
    +  }
    
    94
    +
    
    95
    +defaultCollectExceptionAnnotationMechanism :: CollectExceptionAnnotationMechanism
    
    96
    +defaultCollectExceptionAnnotationMechanism = CollectExceptionAnnotationMechanism
    
    97
    +  { ceaCollectExceptionAnnotationMechanism = SomeExceptionAnnotation `fmap` collectBacktraces
    
    98
    +  }
    
    99
    +
    
    100
    +collectExceptionAnnotationMechanismRef :: IORef CollectExceptionAnnotationMechanism
    
    101
    +collectExceptionAnnotationMechanismRef =
    
    102
    +    unsafePerformIO $ newIORef defaultCollectExceptionAnnotationMechanism
    
    103
    +{-# NOINLINE collectExceptionAnnotationMechanismRef #-}
    
    104
    +
    
    105
    +-- | Returns the current callback for collecting 'ExceptionAnnotation's on throwing 'Exception's.
    
    106
    +--
    
    107
    +getCollectExceptionAnnotationMechanism :: IO CollectExceptionAnnotationMechanism
    
    108
    +getCollectExceptionAnnotationMechanism = readIORef collectExceptionAnnotationMechanismRef
    
    109
    +
    
    110
    +-- | Set the callback for collecting an 'ExceptionAnnotation'.
    
    111
    +--
    
    112
    +setCollectExceptionAnnotation :: ExceptionAnnotation a => (HasCallStack => IO a) -> IO ()
    
    113
    +setCollectExceptionAnnotation collector = do
    
    114
    +  let cea = CollectExceptionAnnotationMechanism
    
    115
    +        { ceaCollectExceptionAnnotationMechanism = fmap SomeExceptionAnnotation collector
    
    116
    +        }
    
    117
    +  _ <- atomicModifyIORef'_ collectExceptionAnnotationMechanismRef (const cea)
    
    118
    +  return ()
    
    119
    +
    
    89 120
     -- | A collection of backtraces.
    
    90 121
     data Backtraces =
    
    91 122
         Backtraces {
    
    ... ... @@ -124,6 +155,14 @@ displayBacktraces bts = concat
    124 155
     instance ExceptionAnnotation Backtraces where
    
    125 156
         displayExceptionAnnotation = displayBacktraces
    
    126 157
     
    
    158
    +-- | Collect 'SomeExceptionAnnotation' based on the configuration of the
    
    159
    +-- global 'CollectExceptionAnnotationMechanism'.
    
    160
    +--
    
    161
    +collectExceptionAnnotation :: HasCallStack => IO SomeExceptionAnnotation
    
    162
    +collectExceptionAnnotation = HCS.withFrozenCallStack $ do
    
    163
    +  cea <- getCollectExceptionAnnotationMechanism
    
    164
    +  ceaCollectExceptionAnnotationMechanism cea
    
    165
    +
    
    127 166
     -- | Collect a set of 'Backtraces'.
    
    128 167
     collectBacktraces :: (?callStack :: CallStack) => IO Backtraces
    
    129 168
     collectBacktraces = HCS.withFrozenCallStack $ do
    

  • libraries/ghc-internal/src/GHC/Internal/Exception/Backtrace.hs-boot
    ... ... @@ -5,11 +5,7 @@ module GHC.Internal.Exception.Backtrace where
    5 5
     
    
    6 6
     import GHC.Internal.Base (IO)
    
    7 7
     import GHC.Internal.Stack.Types (HasCallStack)
    
    8
    -import GHC.Internal.Exception.Context (ExceptionAnnotation)
    
    9
    -
    
    10
    -data Backtraces
    
    11
    -
    
    12
    -instance ExceptionAnnotation Backtraces
    
    8
    +import GHC.Internal.Exception.Context (SomeExceptionAnnotation)
    
    13 9
     
    
    14 10
     -- For GHC.Exception
    
    15
    -collectBacktraces :: HasCallStack => IO Backtraces
    11
    +collectExceptionAnnotation :: HasCallStack => IO SomeExceptionAnnotation

  • testsuite/tests/arrows/should_compile/T21301.stderr
    ... ... @@ -4,7 +4,7 @@ T21301.hs:(8,7)-(10,6): Non-exhaustive patterns in case
    4 4
     
    
    5 5
     
    
    6 6
     HasCallStack backtrace:
    
    7
    -  collectBacktraces, called at libraries/ghc-internal/src/GHC/Internal/Exception.hs:92:13 in ghc-internal:GHC.Internal.Exception
    
    8
    -  toExceptionWithBacktrace, called at libraries/ghc-internal/src/GHC/Internal/Exception.hs:84:32 in ghc-internal:GHC.Internal.Exception
    
    7
    +  collectExceptionAnnotation, called at libraries/ghc-internal/src/GHC/Internal/Exception.hs:169:13 in ghc-internal:GHC.Internal.Exception
    
    8
    +  toExceptionWithBacktrace, called at libraries/ghc-internal/src/GHC/Internal/Exception.hs:89:42 in ghc-internal:GHC.Internal.Exception
    
    9 9
       throw, called at libraries/ghc-internal/src/GHC/Internal/Control/Exception/Base.hs:434:30 in ghc-internal:GHC.Internal.Control.Exception.Base
    
    10 10
     

  • testsuite/tests/deSugar/should_fail/DsStrictFail.stderr
    ... ... @@ -4,7 +4,7 @@ DsStrictFail.hs:4:12-23: Non-exhaustive patterns in False
    4 4
     
    
    5 5
     
    
    6 6
     HasCallStack backtrace:
    
    7
    -  collectBacktraces, called at libraries/ghc-internal/src/GHC/Internal/Exception.hs:92:13 in ghc-internal:GHC.Internal.Exception
    
    8
    -  toExceptionWithBacktrace, called at libraries/ghc-internal/src/GHC/Internal/Exception.hs:84:32 in ghc-internal:GHC.Internal.Exception
    
    7
    +  collectExceptionAnnotation, called at libraries/ghc-internal/src/GHC/Internal/Exception.hs:169:13 in ghc-internal:GHC.Internal.Exception
    
    8
    +  toExceptionWithBacktrace, called at libraries/ghc-internal/src/GHC/Internal/Exception.hs:89:42 in ghc-internal:GHC.Internal.Exception
    
    9 9
       throw, called at libraries/ghc-internal/src/GHC/Internal/Control/Exception/Base.hs:434:30 in ghc-internal:GHC.Internal.Control.Exception.Base
    
    10 10
     

  • testsuite/tests/deSugar/should_run/T20024.stderr
    ... ... @@ -4,7 +4,7 @@ T20024.hs:2:12-32: Non-exhaustive guards in pattern binding
    4 4
     
    
    5 5
     
    
    6 6
     HasCallStack backtrace:
    
    7
    -  collectBacktraces, called at libraries/ghc-internal/src/GHC/Internal/Exception.hs:92:13 in ghc-internal:GHC.Internal.Exception
    
    8
    -  toExceptionWithBacktrace, called at libraries/ghc-internal/src/GHC/Internal/Exception.hs:84:32 in ghc-internal:GHC.Internal.Exception
    
    7
    +  collectExceptionAnnotation, called at libraries/ghc-internal/src/GHC/Internal/Exception.hs:169:13 in ghc-internal:GHC.Internal.Exception
    
    8
    +  toExceptionWithBacktrace, called at libraries/ghc-internal/src/GHC/Internal/Exception.hs:89:42 in ghc-internal:GHC.Internal.Exception
    
    9 9
       throw, called at libraries/ghc-internal/src/GHC/Internal/Control/Exception/Base.hs:431:30 in ghc-internal:GHC.Internal.Control.Exception.Base
    
    10 10
     

  • testsuite/tests/deSugar/should_run/dsrun005.stderr
    ... ... @@ -4,7 +4,7 @@ dsrun005.hs:42:1-18: Non-exhaustive patterns in function f
    4 4
     
    
    5 5
     
    
    6 6
     HasCallStack backtrace:
    
    7
    -  collectBacktraces, called at libraries/ghc-internal/src/GHC/Internal/Exception.hs:92:13 in ghc-internal:GHC.Internal.Exception
    
    8
    -  toExceptionWithBacktrace, called at libraries/ghc-internal/src/GHC/Internal/Exception.hs:84:32 in ghc-internal:GHC.Internal.Exception
    
    7
    +  collectExceptionAnnotation, called at libraries/ghc-internal/src/GHC/Internal/Exception.hs:169:13 in ghc-internal:GHC.Internal.Exception
    
    8
    +  toExceptionWithBacktrace, called at libraries/ghc-internal/src/GHC/Internal/Exception.hs:89:42 in ghc-internal:GHC.Internal.Exception
    
    9 9
       throw, called at libraries/ghc-internal/src/GHC/Internal/Control/Exception/Base.hs:434:30 in ghc-internal:GHC.Internal.Control.Exception.Base
    
    10 10
     

  • testsuite/tests/deSugar/should_run/dsrun007.stderr
    ... ... @@ -4,7 +4,7 @@ dsrun007.hs:5:23-25: Missing field in record construction
    4 4
     
    
    5 5
     
    
    6 6
     HasCallStack backtrace:
    
    7
    -  collectBacktraces, called at libraries/ghc-internal/src/GHC/Internal/Exception.hs:92:13 in ghc-internal:GHC.Internal.Exception
    
    8
    -  toExceptionWithBacktrace, called at libraries/ghc-internal/src/GHC/Internal/Exception.hs:84:32 in ghc-internal:GHC.Internal.Exception
    
    7
    +  collectExceptionAnnotation, called at libraries/ghc-internal/src/GHC/Internal/Exception.hs:169:13 in ghc-internal:GHC.Internal.Exception
    
    8
    +  toExceptionWithBacktrace, called at libraries/ghc-internal/src/GHC/Internal/Exception.hs:89:42 in ghc-internal:GHC.Internal.Exception
    
    9 9
       throw, called at libraries/ghc-internal/src/GHC/Internal/Control/Exception/Base.hs:432:30 in ghc-internal:GHC.Internal.Control.Exception.Base
    
    10 10
     

  • testsuite/tests/deSugar/should_run/dsrun008.stderr
    ... ... @@ -4,7 +4,7 @@ dsrun008.hs:2:32-36: Non-exhaustive patterns in (2, x)
    4 4
     
    
    5 5
     
    
    6 6
     HasCallStack backtrace:
    
    7
    -  collectBacktraces, called at libraries/ghc-internal/src/GHC/Internal/Exception.hs:92:13 in ghc-internal:GHC.Internal.Exception
    
    8
    -  toExceptionWithBacktrace, called at libraries/ghc-internal/src/GHC/Internal/Exception.hs:84:32 in ghc-internal:GHC.Internal.Exception
    
    7
    +  collectExceptionAnnotation, called at libraries/ghc-internal/src/GHC/Internal/Exception.hs:169:13 in ghc-internal:GHC.Internal.Exception
    
    8
    +  toExceptionWithBacktrace, called at libraries/ghc-internal/src/GHC/Internal/Exception.hs:89:42 in ghc-internal:GHC.Internal.Exception
    
    9 9
       throw, called at libraries/ghc-internal/src/GHC/Internal/Control/Exception/Base.hs:434:30 in ghc-internal:GHC.Internal.Control.Exception.Base
    
    10 10
     

  • testsuite/tests/deriving/should_run/T9576.stderr
    ... ... @@ -13,7 +13,7 @@ T9576.hs:6:31: error: [GHC-39999]
    13 13
     (deferred type error)
    
    14 14
     
    
    15 15
     HasCallStack backtrace:
    
    16
    -  collectBacktraces, called at libraries/ghc-internal/src/GHC/Internal/Exception.hs:92:13 in ghc-internal:GHC.Internal.Exception
    
    17
    -  toExceptionWithBacktrace, called at libraries/ghc-internal/src/GHC/Internal/Exception.hs:84:32 in ghc-internal:GHC.Internal.Exception
    
    16
    +  collectExceptionAnnotation, called at libraries/ghc-internal/src/GHC/Internal/Exception.hs:169:13 in ghc-internal:GHC.Internal.Exception
    
    17
    +  toExceptionWithBacktrace, called at libraries/ghc-internal/src/GHC/Internal/Exception.hs:89:42 in ghc-internal:GHC.Internal.Exception
    
    18 18
       throw, called at libraries/ghc-internal/src/GHC/Internal/Control/Exception/Base.hs:435:30 in ghc-internal:GHC.Internal.Control.Exception.Base
    
    19 19
     

  • testsuite/tests/ghci/scripts/Defer02.stderr
    ... ... @@ -71,8 +71,8 @@ Defer01.hs:49:5: warning: [GHC-83865] [-Wdeferred-type-errors (in -Wdefault)]
    71 71
     (deferred type error)
    
    72 72
     
    
    73 73
     HasCallStack backtrace:
    
    74
    -  collectBacktraces, called at libraries/ghc-internal/src/GHC/Internal/Exception.hs:168:13 in ghc-internal:GHC.Internal.Exception
    
    75
    -  toExceptionWithBacktrace, called at libraries/ghc-internal/src/GHC/Internal/Exception.hs:88:42 in ghc-internal:GHC.Internal.Exception
    
    74
    +  collectExceptionAnnotation, called at libraries/ghc-internal/src/GHC/Internal/Exception.hs:169:13 in ghc-internal:GHC.Internal.Exception
    
    75
    +  toExceptionWithBacktrace, called at libraries/ghc-internal/src/GHC/Internal/Exception.hs:89:42 in ghc-internal:GHC.Internal.Exception
    
    76 76
       throw, called at libraries/ghc-internal/src/GHC/Internal/Control/Exception/Base.hs:435:30 in ghc-internal:GHC.Internal.Control.Exception.Base
    
    77 77
     
    
    78 78
     *** Exception: Defer01.hs:13:5: error: [GHC-83865]
    
    ... ... @@ -82,8 +82,8 @@ HasCallStack backtrace:
    82 82
     (deferred type error)
    
    83 83
     
    
    84 84
     HasCallStack backtrace:
    
    85
    -  collectBacktraces, called at libraries/ghc-internal/src/GHC/Internal/Exception.hs:168:13 in ghc-internal:GHC.Internal.Exception
    
    86
    -  toExceptionWithBacktrace, called at libraries/ghc-internal/src/GHC/Internal/Exception.hs:88:42 in ghc-internal:GHC.Internal.Exception
    
    85
    +  collectExceptionAnnotation, called at libraries/ghc-internal/src/GHC/Internal/Exception.hs:169:13 in ghc-internal:GHC.Internal.Exception
    
    86
    +  toExceptionWithBacktrace, called at libraries/ghc-internal/src/GHC/Internal/Exception.hs:89:42 in ghc-internal:GHC.Internal.Exception
    
    87 87
       throw, called at libraries/ghc-internal/src/GHC/Internal/Control/Exception/Base.hs:435:30 in ghc-internal:GHC.Internal.Control.Exception.Base
    
    88 88
     
    
    89 89
     *** Exception: Defer01.hs:17:9: error: [GHC-39999]
    
    ... ... @@ -93,8 +93,8 @@ HasCallStack backtrace:
    93 93
     (deferred type error)
    
    94 94
     
    
    95 95
     HasCallStack backtrace:
    
    96
    -  collectBacktraces, called at libraries/ghc-internal/src/GHC/Internal/Exception.hs:168:13 in ghc-internal:GHC.Internal.Exception
    
    97
    -  toExceptionWithBacktrace, called at libraries/ghc-internal/src/GHC/Internal/Exception.hs:88:42 in ghc-internal:GHC.Internal.Exception
    
    96
    +  collectExceptionAnnotation, called at libraries/ghc-internal/src/GHC/Internal/Exception.hs:169:13 in ghc-internal:GHC.Internal.Exception
    
    97
    +  toExceptionWithBacktrace, called at libraries/ghc-internal/src/GHC/Internal/Exception.hs:89:42 in ghc-internal:GHC.Internal.Exception
    
    98 98
       throw, called at libraries/ghc-internal/src/GHC/Internal/Control/Exception/Base.hs:435:30 in ghc-internal:GHC.Internal.Control.Exception.Base
    
    99 99
     
    
    100 100
     <interactive>:10:11: error: [GHC-83865]
    
    ... ... @@ -113,8 +113,8 @@ HasCallStack backtrace:
    113 113
     (deferred type error)
    
    114 114
     
    
    115 115
     HasCallStack backtrace:
    
    116
    -  collectBacktraces, called at libraries/ghc-internal/src/GHC/Internal/Exception.hs:168:13 in ghc-internal:GHC.Internal.Exception
    
    117
    -  toExceptionWithBacktrace, called at libraries/ghc-internal/src/GHC/Internal/Exception.hs:88:42 in ghc-internal:GHC.Internal.Exception
    
    116
    +  collectExceptionAnnotation, called at libraries/ghc-internal/src/GHC/Internal/Exception.hs:169:13 in ghc-internal:GHC.Internal.Exception
    
    117
    +  toExceptionWithBacktrace, called at libraries/ghc-internal/src/GHC/Internal/Exception.hs:89:42 in ghc-internal:GHC.Internal.Exception
    
    118 118
       throw, called at libraries/ghc-internal/src/GHC/Internal/Control/Exception/Base.hs:435:30 in ghc-internal:GHC.Internal.Control.Exception.Base
    
    119 119
     
    
    120 120
     *** Exception: Defer01.hs:30:5: error: [GHC-83865]
    
    ... ... @@ -127,8 +127,8 @@ HasCallStack backtrace:
    127 127
     (deferred type error)
    
    128 128
     
    
    129 129
     HasCallStack backtrace:
    
    130
    -  collectBacktraces, called at libraries/ghc-internal/src/GHC/Internal/Exception.hs:168:13 in ghc-internal:GHC.Internal.Exception
    
    131
    -  toExceptionWithBacktrace, called at libraries/ghc-internal/src/GHC/Internal/Exception.hs:88:42 in ghc-internal:GHC.Internal.Exception
    
    130
    +  collectExceptionAnnotation, called at libraries/ghc-internal/src/GHC/Internal/Exception.hs:169:13 in ghc-internal:GHC.Internal.Exception
    
    131
    +  toExceptionWithBacktrace, called at libraries/ghc-internal/src/GHC/Internal/Exception.hs:89:42 in ghc-internal:GHC.Internal.Exception
    
    132 132
       throw, called at libraries/ghc-internal/src/GHC/Internal/Control/Exception/Base.hs:435:30 in ghc-internal:GHC.Internal.Control.Exception.Base
    
    133 133
     
    
    134 134
     *** Exception: Defer01.hs:33:8: error: [GHC-25897]
    
    ... ... @@ -146,8 +146,8 @@ HasCallStack backtrace:
    146 146
     (deferred type error)
    
    147 147
     
    
    148 148
     HasCallStack backtrace:
    
    149
    -  collectBacktraces, called at libraries/ghc-internal/src/GHC/Internal/Exception.hs:168:13 in ghc-internal:GHC.Internal.Exception
    
    150
    -  toExceptionWithBacktrace, called at libraries/ghc-internal/src/GHC/Internal/Exception.hs:88:42 in ghc-internal:GHC.Internal.Exception
    
    149
    +  collectExceptionAnnotation, called at libraries/ghc-internal/src/GHC/Internal/Exception.hs:169:13 in ghc-internal:GHC.Internal.Exception
    
    150
    +  toExceptionWithBacktrace, called at libraries/ghc-internal/src/GHC/Internal/Exception.hs:89:42 in ghc-internal:GHC.Internal.Exception
    
    151 151
       throw, called at libraries/ghc-internal/src/GHC/Internal/Control/Exception/Base.hs:435:30 in ghc-internal:GHC.Internal.Control.Exception.Base
    
    152 152
     
    
    153 153
     *** Exception: Defer01.hs:38:17: error: [GHC-83865]
    
    ... ... @@ -161,8 +161,8 @@ HasCallStack backtrace:
    161 161
     (deferred type error)
    
    162 162
     
    
    163 163
     HasCallStack backtrace:
    
    164
    -  collectBacktraces, called at libraries/ghc-internal/src/GHC/Internal/Exception.hs:168:13 in ghc-internal:GHC.Internal.Exception
    
    165
    -  toExceptionWithBacktrace, called at libraries/ghc-internal/src/GHC/Internal/Exception.hs:88:42 in ghc-internal:GHC.Internal.Exception
    
    164
    +  collectExceptionAnnotation, called at libraries/ghc-internal/src/GHC/Internal/Exception.hs:169:13 in ghc-internal:GHC.Internal.Exception
    
    165
    +  toExceptionWithBacktrace, called at libraries/ghc-internal/src/GHC/Internal/Exception.hs:89:42 in ghc-internal:GHC.Internal.Exception
    
    166 166
       throw, called at libraries/ghc-internal/src/GHC/Internal/Control/Exception/Base.hs:435:30 in ghc-internal:GHC.Internal.Control.Exception.Base
    
    167 167
     
    
    168 168
     *** Exception: Defer01.hs:42:5: error: [GHC-39999]
    
    ... ... @@ -172,8 +172,8 @@ HasCallStack backtrace:
    172 172
     (deferred type error)
    
    173 173
     
    
    174 174
     HasCallStack backtrace:
    
    175
    -  collectBacktraces, called at libraries/ghc-internal/src/GHC/Internal/Exception.hs:168:13 in ghc-internal:GHC.Internal.Exception
    
    176
    -  toExceptionWithBacktrace, called at libraries/ghc-internal/src/GHC/Internal/Exception.hs:88:42 in ghc-internal:GHC.Internal.Exception
    
    175
    +  collectExceptionAnnotation, called at libraries/ghc-internal/src/GHC/Internal/Exception.hs:169:13 in ghc-internal:GHC.Internal.Exception
    
    176
    +  toExceptionWithBacktrace, called at libraries/ghc-internal/src/GHC/Internal/Exception.hs:89:42 in ghc-internal:GHC.Internal.Exception
    
    177 177
       throw, called at libraries/ghc-internal/src/GHC/Internal/Control/Exception/Base.hs:435:30 in ghc-internal:GHC.Internal.Control.Exception.Base
    
    178 178
     
    
    179 179
     <interactive>:16:8: error: [GHC-18872]
    
    ... ... @@ -192,7 +192,7 @@ HasCallStack backtrace:
    192 192
     (deferred type error)
    
    193 193
     
    
    194 194
     HasCallStack backtrace:
    
    195
    -  collectBacktraces, called at libraries/ghc-internal/src/GHC/Internal/Exception.hs:168:13 in ghc-internal:GHC.Internal.Exception
    
    196
    -  toExceptionWithBacktrace, called at libraries/ghc-internal/src/GHC/Internal/Exception.hs:88:42 in ghc-internal:GHC.Internal.Exception
    
    195
    +  collectExceptionAnnotation, called at libraries/ghc-internal/src/GHC/Internal/Exception.hs:169:13 in ghc-internal:GHC.Internal.Exception
    
    196
    +  toExceptionWithBacktrace, called at libraries/ghc-internal/src/GHC/Internal/Exception.hs:89:42 in ghc-internal:GHC.Internal.Exception
    
    197 197
       throw, called at libraries/ghc-internal/src/GHC/Internal/Control/Exception/Base.hs:435:30 in ghc-internal:GHC.Internal.Control.Exception.Base
    
    198 198
     

  • testsuite/tests/ghci/scripts/T15325.stderr
    ... ... @@ -24,7 +24,7 @@ T15325.hs:11:9: warning: [GHC-39999] [-Wdeferred-type-errors (in -Wdefault)]
    24 24
     (deferred type error)
    
    25 25
     
    
    26 26
     HasCallStack backtrace:
    
    27
    -  collectBacktraces, called at libraries/ghc-internal/src/GHC/Internal/Exception.hs:168:13 in ghc-internal:GHC.Internal.Exception
    
    28
    -  toExceptionWithBacktrace, called at libraries/ghc-internal/src/GHC/Internal/Exception.hs:88:42 in ghc-internal:GHC.Internal.Exception
    
    27
    +  collectExceptionAnnotation, called at libraries/ghc-internal/src/GHC/Internal/Exception.hs:169:13 in ghc-internal:GHC.Internal.Exception
    
    28
    +  toExceptionWithBacktrace, called at libraries/ghc-internal/src/GHC/Internal/Exception.hs:89:42 in ghc-internal:GHC.Internal.Exception
    
    29 29
       throw, called at libraries/ghc-internal/src/GHC/Internal/Control/Exception/Base.hs:435:30 in ghc-internal:GHC.Internal.Control.Exception.Base
    
    30 30
     

  • testsuite/tests/patsyn/should_run/ghci.stderr
    ... ... @@ -2,7 +2,7 @@
    2 2
     
    
    3 3
     
    
    4 4
     HasCallStack backtrace:
    
    5
    -  collectBacktraces, called at libraries/ghc-internal/src/GHC/Internal/Exception.hs:168:13 in ghc-internal:GHC.Internal.Exception
    
    6
    -  toExceptionWithBacktrace, called at libraries/ghc-internal/src/GHC/Internal/Exception.hs:88:42 in ghc-internal:GHC.Internal.Exception
    
    5
    +  collectExceptionAnnotation, called at libraries/ghc-internal/src/GHC/Internal/Exception.hs:169:13 in ghc-internal:GHC.Internal.Exception
    
    6
    +  toExceptionWithBacktrace, called at libraries/ghc-internal/src/GHC/Internal/Exception.hs:89:42 in ghc-internal:GHC.Internal.Exception
    
    7 7
       throw, called at libraries/ghc-internal/src/GHC/Internal/Control/Exception/Base.hs:434:30 in ghc-internal:GHC.Internal.Control.Exception.Base
    
    8 8
     

  • testsuite/tests/quotes/LiftErrMsgDefer.stderr
    ... ... @@ -11,7 +11,7 @@ LiftErrMsgDefer.hs:14:12: warning: [GHC-28914] [-Wdeferred-type-errors (in -Wdef
    11 11
     (deferred type error)
    
    12 12
     
    
    13 13
     HasCallStack backtrace:
    
    14
    -  collectBacktraces, called at libraries/ghc-internal/src/GHC/Internal/Exception.hs:169:13 in ghc-internal:GHC.Internal.Exception
    
    14
    +  collectExceptionAnnotation, called at libraries/ghc-internal/src/GHC/Internal/Exception.hs:169:13 in ghc-internal:GHC.Internal.Exception
    
    15 15
       toExceptionWithBacktrace, called at libraries/ghc-internal/src/GHC/Internal/Exception.hs:89:42 in ghc-internal:GHC.Internal.Exception
    
    16 16
       throw, called at libraries/ghc-internal/src/GHC/Internal/Control/Exception/Base.hs:435:30 in ghc-internal:GHC.Internal.Control.Exception.Base
    
    17 17
     

  • testsuite/tests/safeHaskell/safeLanguage/SafeLang15.stderr
    ... ... @@ -4,7 +4,7 @@ SafeLang15.hs:22:9-37: Non-exhaustive patterns in Just p'
    4 4
     
    
    5 5
     
    
    6 6
     HasCallStack backtrace:
    
    7
    -  collectBacktraces, called at libraries/ghc-internal/src/GHC/Internal/Exception.hs:92:13 in ghc-internal:GHC.Internal.Exception
    
    8
    -  toExceptionWithBacktrace, called at libraries/ghc-internal/src/GHC/Internal/Exception.hs:84:32 in ghc-internal:GHC.Internal.Exception
    
    7
    +  collectExceptionAnnotation, called at libraries/ghc-internal/src/GHC/Internal/Exception.hs:169:13 in ghc-internal:GHC.Internal.Exception
    
    8
    +  toExceptionWithBacktrace, called at libraries/ghc-internal/src/GHC/Internal/Exception.hs:89:42 in ghc-internal:GHC.Internal.Exception
    
    9 9
       throw, called at libraries/ghc-internal/src/GHC/Internal/Control/Exception/Base.hs:434:30 in ghc-internal:GHC.Internal.Control.Exception.Base
    
    10 10
     

  • testsuite/tests/type-data/should_run/T22332a.stderr
    ... ... @@ -4,7 +4,7 @@ T22332a.hs:18:1-35: Non-exhaustive patterns in Just eq
    4 4
     
    
    5 5
     
    
    6 6
     HasCallStack backtrace:
    
    7
    -  collectBacktraces, called at libraries/ghc-internal/src/GHC/Internal/Exception.hs:92:13 in ghc-internal:GHC.Internal.Exception
    
    8
    -  toExceptionWithBacktrace, called at libraries/ghc-internal/src/GHC/Internal/Exception.hs:84:32 in ghc-internal:GHC.Internal.Exception
    
    7
    +  collectExceptionAnnotation, called at libraries/ghc-internal/src/GHC/Internal/Exception.hs:169:13 in ghc-internal:GHC.Internal.Exception
    
    8
    +  toExceptionWithBacktrace, called at libraries/ghc-internal/src/GHC/Internal/Exception.hs:89:42 in ghc-internal:GHC.Internal.Exception
    
    9 9
       throw, called at libraries/ghc-internal/src/GHC/Internal/Control/Exception/Base.hs:434:30 in ghc-internal:GHC.Internal.Control.Exception.Base
    
    10 10
     

  • testsuite/tests/typecheck/should_run/T10284.stderr
    ... ... @@ -7,7 +7,7 @@ T10284.hs:7:5: error: [GHC-83865]
    7 7
     (deferred type error)
    
    8 8
     
    
    9 9
     HasCallStack backtrace:
    
    10
    -  collectBacktraces, called at libraries/ghc-internal/src/GHC/Internal/Exception.hs:92:13 in ghc-internal:GHC.Internal.Exception
    
    11
    -  toExceptionWithBacktrace, called at libraries/ghc-internal/src/GHC/Internal/Exception.hs:84:32 in ghc-internal:GHC.Internal.Exception
    
    10
    +  collectExceptionAnnotation, called at libraries/ghc-internal/src/GHC/Internal/Exception.hs:169:13 in ghc-internal:GHC.Internal.Exception
    
    11
    +  toExceptionWithBacktrace, called at libraries/ghc-internal/src/GHC/Internal/Exception.hs:89:42 in ghc-internal:GHC.Internal.Exception
    
    12 12
       throw, called at libraries/ghc-internal/src/GHC/Internal/Control/Exception/Base.hs:435:30 in ghc-internal:GHC.Internal.Control.Exception.Base
    
    13 13
     

  • testsuite/tests/typecheck/should_run/T13838.stderr
    1
    -T13838.exe: Uncaught exception ghc-internal:GHC.Internal.Control.Exception.Base.TypeError:
    
    1
    +T13838: Uncaught exception ghc-internal:GHC.Internal.Control.Exception.Base.TypeError:
    
    2 2
     
    
    3 3
     T13838.hs:6:1: error: [GHC-83865]
    
    4 4
         • Couldn't match expected type: IO t0
    
    ... ... @@ -9,7 +9,7 @@ T13838.hs:6:1: error: [GHC-83865]
    9 9
     (deferred type error)
    
    10 10
     
    
    11 11
     HasCallStack backtrace:
    
    12
    -  collectBacktraces, called at libraries\ghc-internal\src\GHC\Internal\Exception.hs:169:13 in ghc-internal:GHC.Internal.Exception
    
    13
    -  toExceptionWithBacktrace, called at libraries\ghc-internal\src\GHC\Internal\Exception.hs:89:42 in ghc-internal:GHC.Internal.Exception
    
    14
    -  throw, called at libraries\ghc-internal\src\GHC\Internal\Control\Exception\Base.hs:435:30 in ghc-internal:GHC.Internal.Control.Exception.Base
    
    12
    +  collectExceptionAnnotation, called at libraries/ghc-internal/src/GHC/Internal/Exception.hs:169:13 in ghc-internal:GHC.Internal.Exception
    
    13
    +  toExceptionWithBacktrace, called at libraries/ghc-internal/src/GHC/Internal/Exception.hs:89:42 in ghc-internal:GHC.Internal.Exception
    
    14
    +  throw, called at libraries/ghc-internal/src/GHC/Internal/Control/Exception/Base.hs:435:30 in ghc-internal:GHC.Internal.Control.Exception.Base
    
    15 15
     

  • testsuite/tests/typecheck/should_run/T9497a-run.stderr
    ... ... @@ -19,7 +19,7 @@ T9497a-run.hs:2:8: error: [GHC-88464]
    19 19
     (deferred type error)
    
    20 20
     
    
    21 21
     HasCallStack backtrace:
    
    22
    -  collectBacktraces, called at libraries/ghc-internal/src/GHC/Internal/Exception.hs:92:13 in ghc-internal:GHC.Internal.Exception
    
    23
    -  toExceptionWithBacktrace, called at libraries/ghc-internal/src/GHC/Internal/Exception.hs:84:32 in ghc-internal:GHC.Internal.Exception
    
    22
    +  collectExceptionAnnotation, called at libraries/ghc-internal/src/GHC/Internal/Exception.hs:169:13 in ghc-internal:GHC.Internal.Exception
    
    23
    +  toExceptionWithBacktrace, called at libraries/ghc-internal/src/GHC/Internal/Exception.hs:89:42 in ghc-internal:GHC.Internal.Exception
    
    24 24
       throw, called at libraries/ghc-internal/src/GHC/Internal/Control/Exception/Base.hs:435:30 in ghc-internal:GHC.Internal.Control.Exception.Base
    
    25 25
     

  • testsuite/tests/typecheck/should_run/T9497b-run.stderr
    ... ... @@ -19,7 +19,7 @@ T9497b-run.hs:2:8: error: [GHC-88464]
    19 19
     (deferred type error)
    
    20 20
     
    
    21 21
     HasCallStack backtrace:
    
    22
    -  collectBacktraces, called at libraries/ghc-internal/src/GHC/Internal/Exception.hs:92:13 in ghc-internal:GHC.Internal.Exception
    
    23
    -  toExceptionWithBacktrace, called at libraries/ghc-internal/src/GHC/Internal/Exception.hs:84:32 in ghc-internal:GHC.Internal.Exception
    
    22
    +  collectExceptionAnnotation, called at libraries/ghc-internal/src/GHC/Internal/Exception.hs:169:13 in ghc-internal:GHC.Internal.Exception
    
    23
    +  toExceptionWithBacktrace, called at libraries/ghc-internal/src/GHC/Internal/Exception.hs:89:42 in ghc-internal:GHC.Internal.Exception
    
    24 24
       throw, called at libraries/ghc-internal/src/GHC/Internal/Control/Exception/Base.hs:435:30 in ghc-internal:GHC.Internal.Control.Exception.Base
    
    25 25
     

  • testsuite/tests/typecheck/should_run/T9497c-run.stderr
    ... ... @@ -19,7 +19,7 @@ T9497c-run.hs:2:8: error: [GHC-88464]
    19 19
     (deferred type error)
    
    20 20
     
    
    21 21
     HasCallStack backtrace:
    
    22
    -  collectBacktraces, called at libraries/ghc-internal/src/GHC/Internal/Exception.hs:92:13 in ghc-internal:GHC.Internal.Exception
    
    23
    -  toExceptionWithBacktrace, called at libraries/ghc-internal/src/GHC/Internal/Exception.hs:84:32 in ghc-internal:GHC.Internal.Exception
    
    22
    +  collectExceptionAnnotation, called at libraries/ghc-internal/src/GHC/Internal/Exception.hs:169:13 in ghc-internal:GHC.Internal.Exception
    
    23
    +  toExceptionWithBacktrace, called at libraries/ghc-internal/src/GHC/Internal/Exception.hs:89:42 in ghc-internal:GHC.Internal.Exception
    
    24 24
       throw, called at libraries/ghc-internal/src/GHC/Internal/Control/Exception/Base.hs:435:30 in ghc-internal:GHC.Internal.Control.Exception.Base
    
    25 25
     

  • testsuite/tests/unsatisfiable/T23816.stderr
    ... ... @@ -8,7 +8,7 @@ T23816.hs:18:15: error: [GHC-22250]
    8 8
     (deferred type error)
    
    9 9
     
    
    10 10
     HasCallStack backtrace:
    
    11
    -  collectBacktraces, called at libraries/ghc-internal/src/GHC/Internal/Exception.hs:92:13 in ghc-internal:GHC.Internal.Exception
    
    12
    -  toExceptionWithBacktrace, called at libraries/ghc-internal/src/GHC/Internal/Exception.hs:84:32 in ghc-internal:GHC.Internal.Exception
    
    11
    +  collectExceptionAnnotation, called at libraries/ghc-internal/src/GHC/Internal/Exception.hs:169:13 in ghc-internal:GHC.Internal.Exception
    
    12
    +  toExceptionWithBacktrace, called at libraries/ghc-internal/src/GHC/Internal/Exception.hs:89:42 in ghc-internal:GHC.Internal.Exception
    
    13 13
       throw, called at libraries/ghc-internal/src/GHC/Internal/Control/Exception/Base.hs:435:30 in ghc-internal:GHC.Internal.Control.Exception.Base
    
    14 14
     

  • testsuite/tests/unsatisfiable/UnsatDefer.stderr
    ... ... @@ -7,7 +7,7 @@ UnsatDefer.hs:20:7: error: [GHC-22250]
    7 7
     (deferred type error)
    
    8 8
     
    
    9 9
     HasCallStack backtrace:
    
    10
    -  collectBacktraces, called at libraries/ghc-internal/src/GHC/Internal/Exception.hs:92:13 in ghc-internal:GHC.Internal.Exception
    
    11
    -  toExceptionWithBacktrace, called at libraries/ghc-internal/src/GHC/Internal/Exception.hs:84:32 in ghc-internal:GHC.Internal.Exception
    
    10
    +  collectExceptionAnnotation, called at libraries/ghc-internal/src/GHC/Internal/Exception.hs:169:13 in ghc-internal:GHC.Internal.Exception
    
    11
    +  toExceptionWithBacktrace, called at libraries/ghc-internal/src/GHC/Internal/Exception.hs:89:42 in ghc-internal:GHC.Internal.Exception
    
    12 12
       throw, called at libraries/ghc-internal/src/GHC/Internal/Control/Exception/Base.hs:435:30 in ghc-internal:GHC.Internal.Control.Exception.Base
    
    13 13