Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC

Commits:

1 changed file:

Changes:

  • compiler/GHC/Utils/Panic/Plain.hs
    ... ... @@ -116,9 +116,17 @@ assertPanic file line =
    116 116
       Exception.throw (Exception.AssertionFailed
    
    117 117
                ("ASSERT failed! file " ++ file ++ ", line " ++ show line))
    
    118 118
     
    
    119
    -
    
    119
    +-- | Throw a failed assertion exception taking the location information
    
    120
    +-- from 'HasCallStack' evidence.
    
    120 121
     assertPanic' :: HasCallStack => a
    
    121
    -assertPanic' = Exception.throw (Exception.AssertionFailed "ASSERT failed!")
    
    122
    +assertPanic' =
    
    123
    +    Exception.throw
    
    124
    +      $ Exception.AssertionFailed
    
    125
    +      $ "ASSERT failed!\n" ++ withFrozenCallStack doc
    
    126
    +  where
    
    127
    +    -- TODO: Drop CallStack when exception backtrace functionality
    
    128
    +    -- can be assumed of bootstrap compiler.
    
    129
    +    doc = unlines $ fmap ("  "++) $ lines (prettyCallStack callStack)
    
    122 130
     
    
    123 131
     assert :: HasCallStack => Bool -> a -> a
    
    124 132
     {-# INLINE assert #-}