Skip to content
GitLab
Menu
Projects
Groups
Snippets
Help
Help
Support
Community forum
Keyboard shortcuts
?
Submit feedback
Sign in / Register
Toggle navigation
Menu
Open sidebar
Glasgow Haskell Compiler
GHC
Commits
2de63e5a
Commit
2de63e5a
authored
Jun 11, 2012
by
Ian Lynagh
Browse files
Make Ppr* versions of the Sorry and PgmError exceptions too
parent
fa362ab5
Changes
3
Hide whitespace changes
Inline
Side-by-side
compiler/main/ErrUtils.lhs
View file @
2de63e5a
...
...
@@ -338,6 +338,10 @@ prettyPrintGhcErrors :: ExceptionMonad m => m a -> m a
prettyPrintGhcErrors = ghandle $ \e -> case e of
PprPanic str doc ->
pprDebugAndThen panic str doc
PprSorry str doc ->
pprDebugAndThen sorry str doc
PprProgramError str doc ->
pprDebugAndThen pgmError str doc
_ ->
throw e
\end{code}
...
...
compiler/utils/Outputable.lhs
View file @
2de63e5a
...
...
@@ -909,12 +909,12 @@ pprPanic = panicDoc
pprSorry :: String -> SDoc -> a
-- ^ Throw an exception saying "this isn't finished yet"
pprSorry =
pprDebugAndThen
sorry
pprSorry = sorry
Doc
pprPgmError :: String -> SDoc -> a
-- ^ Throw an exception saying "bug in pgm being compiled" (used for unusual program errors)
pprPgmError =
pprDebugAndThen
pgmError
pprPgmError = pgmError
Doc
pprTrace :: String -> SDoc -> a -> a
...
...
compiler/utils/Panic.lhs
View file @
2de63e5a
...
...
@@ -14,7 +14,7 @@ module Panic (
pgmError,
panic, sorry, panicFastInt, assertPanic, trace,
panicDoc,
panicDoc,
sorryDoc, pgmErrorDoc,
Exception.Exception(..), showException, safeShowException, try, tryMost, throwTo,
...
...
@@ -87,12 +87,14 @@ data GhcException
-- | The user tickled something that's known not to work yet,
-- but we're not counting it as a bug.
| Sorry String
| PprSorry String SDoc
-- | An installation problem.
| InstallationError String
-- | An error in the user's code, probably.
| ProgramError String
| ProgramError String
| PprProgramError String SDoc
deriving (Typeable)
instance Exception GhcException
...
...
@@ -144,6 +146,8 @@ showGhcException exception
showString ")"
CmdLineError str -> showString str
PprProgramError str _ ->
showGhcException (ProgramError (str ++ "\n<<details unavailable>>"))
ProgramError str -> showString str
InstallationError str -> showString str
Signal n -> showString "signal: " . shows n
...
...
@@ -157,6 +161,8 @@ showGhcException exception
++ s ++ "\n\n"
++ "Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug\n"
PprSorry s _ ->
showGhcException (Sorry (s ++ "\n<<details unavailable>>"))
Sorry s
-> showString $
"sorry! (unimplemented feature or known bug)\n"
...
...
@@ -192,12 +198,14 @@ panic x = unsafeDupablePerformIO $ do
panic x = throwGhcException (Panic x)
#endif
panicDoc :: String -> SDoc -> a
panicDoc x doc = throwGhcException (PprPanic x doc)
sorry x = throwGhcException (Sorry x)
pgmError x = throwGhcException (ProgramError x)
panicDoc, sorryDoc, pgmErrorDoc :: String -> SDoc -> a
panicDoc x doc = throwGhcException (PprPanic x doc)
sorryDoc x doc = throwGhcException (PprSorry x doc)
pgmErrorDoc x doc = throwGhcException (PprProgramError x doc)
-- | Panic while pretending to return an unboxed int.
-- You can't use the regular panic functions in expressions
...
...
Write
Preview
Supports
Markdown
0%
Try again
or
attach a new file
.
Attach a file
Cancel
You are about to add
0
people
to the discussion. Proceed with caution.
Finish editing this message first!
Cancel
Please
register
or
sign in
to comment