never executed always true always false
1 -- | Source errors
2 module GHC.Types.SourceError
3 ( SourceError (..)
4 , mkSrcErr
5 , srcErrorMessages
6 , throwErrors
7 , throwOneError
8 , handleSourceError
9 )
10 where
11
12 import GHC.Prelude
13 import GHC.Types.Error
14 import GHC.Utils.Monad
15 import GHC.Utils.Panic
16 import GHC.Utils.Exception
17 import GHC.Utils.Error (pprMsgEnvelopeBagWithLoc)
18 import GHC.Utils.Outputable
19
20 import GHC.Driver.Errors.Ppr () -- instance Diagnostic GhcMessage
21 import GHC.Driver.Errors.Types
22
23 import Control.Monad.Catch as MC (MonadCatch, catch)
24
25 mkSrcErr :: Messages GhcMessage -> SourceError
26 mkSrcErr = SourceError
27
28 srcErrorMessages :: SourceError -> Messages GhcMessage
29 srcErrorMessages (SourceError msgs) = msgs
30
31 throwErrors :: MonadIO io => Messages GhcMessage -> io a
32 throwErrors = liftIO . throwIO . mkSrcErr
33
34 throwOneError :: MonadIO io => MsgEnvelope GhcMessage -> io a
35 throwOneError = throwErrors . singleMessage
36
37 -- | A source error is an error that is caused by one or more errors in the
38 -- source code. A 'SourceError' is thrown by many functions in the
39 -- compilation pipeline. Inside GHC these errors are merely printed via
40 -- 'log_action', but API clients may treat them differently, for example,
41 -- insert them into a list box. If you want the default behaviour, use the
42 -- idiom:
43 --
44 -- > handleSourceError printExceptionAndWarnings $ do
45 -- > ... api calls that may fail ...
46 --
47 -- The 'SourceError's error messages can be accessed via 'srcErrorMessages'.
48 -- This list may be empty if the compiler failed due to @-Werror@
49 -- ('Opt_WarnIsError').
50 --
51 -- See 'printExceptionAndWarnings' for more information on what to take care
52 -- of when writing a custom error handler.
53 newtype SourceError = SourceError (Messages GhcMessage)
54
55 instance Show SourceError where
56 -- We implement 'Show' because it's required by the 'Exception' instance, but diagnostics
57 -- shouldn't be shown via the 'Show' typeclass, but rather rendered using the ppr functions.
58 -- This also explains why there is no 'Show' instance for a 'MsgEnvelope'.
59 show (SourceError msgs) =
60 renderWithContext defaultSDocContext
61 . vcat
62 . pprMsgEnvelopeBagWithLoc
63 . getMessages
64 $ msgs
65
66 instance Exception SourceError
67
68 -- | Perform the given action and call the exception handler if the action
69 -- throws a 'SourceError'. See 'SourceError' for more information.
70 handleSourceError :: (MonadCatch m) =>
71 (SourceError -> m a) -- ^ exception handler
72 -> m a -- ^ action to perform
73 -> m a
74 handleSourceError handler act =
75 MC.catch act (\(e :: SourceError) -> handler e)
76