Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Synopsis
- data Validity' a
- type Validity = Validity' SDoc
- andValid :: Validity' a -> Validity' a -> Validity' a
- allValid :: [Validity' a] -> Validity' a
- getInvalids :: [Validity' a] -> [a]
- data Severity
- class Diagnostic a where
- type DiagnosticOpts a
- defaultDiagnosticOpts :: DiagnosticOpts a
- diagnosticMessage :: DiagnosticOpts a -> a -> DecoratedSDoc
- diagnosticReason :: a -> DiagnosticReason
- diagnosticHints :: a -> [GhcHint]
- diagnosticCode :: a -> Maybe DiagnosticCode
- data MsgEnvelope e = MsgEnvelope {}
- data MessageClass
- data SDoc
- data DecoratedSDoc
- data Messages e
- mkMessages :: Bag (MsgEnvelope e) -> Messages e
- unionMessages :: Messages e -> Messages e -> Messages e
- errorsFound :: Diagnostic e => Messages e -> Bool
- isEmptyMessages :: Messages e -> Bool
- pprMessageBag :: Bag SDoc -> SDoc
- pprMsgEnvelopeBagWithLoc :: Diagnostic e => DiagnosticOpts e -> Bag (MsgEnvelope e) -> [SDoc]
- pprMsgEnvelopeBagWithLocDefault :: forall e. Diagnostic e => Bag (MsgEnvelope e) -> [SDoc]
- pprMessages :: Diagnostic e => DiagnosticOpts e -> Messages e -> SDoc
- pprLocMsgEnvelope :: Diagnostic e => DiagnosticOpts e -> MsgEnvelope e -> SDoc
- pprLocMsgEnvelopeDefault :: forall e. Diagnostic e => MsgEnvelope e -> SDoc
- formatBulleted :: SDocContext -> DecoratedSDoc -> SDoc
- data DiagOpts = DiagOpts {}
- diag_wopt :: WarningFlag -> DiagOpts -> Bool
- diag_fatal_wopt :: WarningFlag -> DiagOpts -> Bool
- emptyMessages :: Messages e
- mkDecorated :: [SDoc] -> DecoratedSDoc
- mkLocMessage :: MessageClass -> SrcSpan -> SDoc -> SDoc
- mkMsgEnvelope :: Diagnostic e => DiagOpts -> SrcSpan -> NamePprCtx -> e -> MsgEnvelope e
- mkPlainMsgEnvelope :: Diagnostic e => DiagOpts -> SrcSpan -> e -> MsgEnvelope e
- mkPlainErrorMsgEnvelope :: Diagnostic e => SrcSpan -> e -> MsgEnvelope e
- mkErrorMsgEnvelope :: Diagnostic e => SrcSpan -> NamePprCtx -> e -> MsgEnvelope e
- mkMCDiagnostic :: DiagOpts -> DiagnosticReason -> Maybe DiagnosticCode -> MessageClass
- errorDiagnostic :: MessageClass
- diagReasonSeverity :: DiagOpts -> DiagnosticReason -> Severity
- mkPlainError :: [GhcHint] -> SDoc -> DiagnosticMessage
- mkPlainDiagnostic :: DiagnosticReason -> [GhcHint] -> SDoc -> DiagnosticMessage
- mkDecoratedError :: [GhcHint] -> [SDoc] -> DiagnosticMessage
- mkDecoratedDiagnostic :: DiagnosticReason -> [GhcHint] -> [SDoc] -> DiagnosticMessage
- noHints :: [GhcHint]
- getCaretDiagnostic :: MessageClass -> SrcSpan -> IO SDoc
- putMsg :: Logger -> SDoc -> IO ()
- printInfoForUser :: Logger -> NamePprCtx -> SDoc -> IO ()
- printOutputForUser :: Logger -> NamePprCtx -> SDoc -> IO ()
- logInfo :: Logger -> SDoc -> IO ()
- logOutput :: Logger -> SDoc -> IO ()
- errorMsg :: Logger -> SDoc -> IO ()
- fatalErrorMsg :: Logger -> SDoc -> IO ()
- compilationProgressMsg :: Logger -> SDoc -> IO ()
- showPass :: Logger -> String -> IO ()
- withTiming :: MonadIO m => Logger -> SDoc -> (a -> ()) -> m a -> m a
- withTimingSilent :: MonadIO m => Logger -> SDoc -> (a -> ()) -> m a -> m a
- debugTraceMsg :: Logger -> Int -> SDoc -> IO ()
- ghcExit :: Logger -> Int -> IO ()
- prettyPrintGhcErrors :: ExceptionMonad m => Logger -> m a -> m a
- traceCmd :: Logger -> String -> String -> IO a -> IO a
- traceSystoolCommand :: Logger -> String -> IO a -> IO a
- sortMsgBag :: Maybe DiagOpts -> Bag (MsgEnvelope e) -> [MsgEnvelope e]
Basic types
getInvalids :: [Validity' a] -> [a] Source #
Used to describe warnings and errors
o The message has a file/line/column heading,
plus "warning:" or "error:",
added by mkLocMessage
o With SevIgnore
the message is suppressed
o Output is intended for end users
SevIgnore | Ignore this message, for example in case of suppression of warnings users don't want to see. See Note [Suppressing Messages] |
SevWarning | |
SevError |
Messages
class Diagnostic a where Source #
A class identifying a diagnostic. Dictionary.com defines a diagnostic as:
"a message output by a computer diagnosing an error in a computer program, computer system, or component device".
A Diagnostic
carries the actual description of the message (which, in
GHC's case, it can be an error or a warning) and the reason why such
message was generated in the first place.
type DiagnosticOpts a Source #
Type of configuration options for the diagnostic.
defaultDiagnosticOpts :: DiagnosticOpts a Source #
diagnosticMessage :: DiagnosticOpts a -> a -> DecoratedSDoc Source #
Extract the error message text from a Diagnostic
.
diagnosticReason :: a -> DiagnosticReason Source #
Extract the reason for this diagnostic. For warnings,
a DiagnosticReason
includes the warning flag.
diagnosticHints :: a -> [GhcHint] Source #
Extract any hints a user might use to repair their code to avoid this diagnostic.
diagnosticCode :: a -> Maybe DiagnosticCode Source #
Get the DiagnosticCode
associated with this Diagnostic
.
This can return Nothing
for at least two reasons:
- The message might be from a plugin that does not supply codes.
- The message might not yet have been assigned a code. See the
Diagnostic
instance forDiagnosticMessage
.
Ideally, case (2) would not happen, but because some errors in GHC still use the old system of just writing the error message in-place (instead of using a dedicated error type and constructor), we do not have error codes for all errors. #18516 tracks our progress toward this goal.
Instances
data MsgEnvelope e Source #
An envelope for GHC's facts about a running program, parameterised over the domain-specific (i.e. parsing, typecheck-renaming, etc) diagnostics.
To say things differently, GHC emits diagnostics about the running
program, each of which is wrapped into a MsgEnvelope
that carries
specific information like where the error happened, etc. Finally, multiple
MsgEnvelope
s are aggregated into Messages
that are returned to the
user.
MsgEnvelope | |
|
Instances
data MessageClass Source #
The class for a diagnostic message. The main purpose is to classify a
message within GHC, to distinguish it from a debug/dump message vs a proper
diagnostic, for which we include a DiagnosticReason
.
MCOutput | |
MCFatal | |
MCInteractive | |
MCDump | Log message intended for compiler developers No file/line/column stuff |
MCInfo | Log messages intended for end users. No file/line/column stuff. |
MCDiagnostic Severity DiagnosticReason (Maybe DiagnosticCode) | Diagnostics from the compiler. This constructor is very powerful as
it allows the construction of a The |
Instances
ToJson MessageClass Source # | |
Defined in GHC.Types.Error json :: MessageClass -> JsonDoc Source # |
Represents a pretty-printable document.
To display an SDoc
, use printSDoc
, printSDocLn
, bufLeftRenderSDoc
,
or renderWithContext
. Avoid calling runSDoc
directly as it breaks the
abstraction layer.
Instances
IsString SDoc Source # | |
Defined in GHC.Utils.Outputable fromString :: String -> SDoc Source # | |
IsDoc SDoc Source # | |
IsLine SDoc Source # | |
Defined in GHC.Utils.Outputable text :: String -> SDoc Source # ftext :: FastString -> SDoc Source # ztext :: FastZString -> SDoc Source # (<>) :: SDoc -> SDoc -> SDoc Source # (<+>) :: SDoc -> SDoc -> SDoc Source # sep :: [SDoc] -> SDoc Source # fsep :: [SDoc] -> SDoc Source # hcat :: [SDoc] -> SDoc Source # | |
IsOutput SDoc Source # | |
Defined in GHC.Utils.Outputable docWithContext :: (SDocContext -> SDoc) -> SDoc Source # | |
Outputable SDoc Source # | |
OutputableP env SDoc Source # | |
type Line SDoc Source # | |
Defined in GHC.Utils.Outputable |
data DecoratedSDoc Source #
A DecoratedSDoc
is isomorphic to a '[SDoc]' but it carries the
invariant that the input '[SDoc]' needs to be rendered decorated into its
final form, where the typical case would be adding bullets between each
elements of the list. The type of decoration depends on the formatting
function used, but in practice GHC uses the formatBulleted
.
A collection of messages emitted by GHC during error reporting. A diagnostic message is typically a warning or an error. See Note [Messages].
INVARIANT: All the messages in this collection must be relevant, i.e.
their Severity
should not be SevIgnore
. The smart constructor
mkMessages
will filter out any message which Severity
is SevIgnore
.
Instances
Foldable Messages Source # | |
Defined in GHC.Types.Error fold :: Monoid m => Messages m -> m Source # foldMap :: Monoid m => (a -> m) -> Messages a -> m Source # foldMap' :: Monoid m => (a -> m) -> Messages a -> m Source # foldr :: (a -> b -> b) -> b -> Messages a -> b Source # foldr' :: (a -> b -> b) -> b -> Messages a -> b Source # foldl :: (b -> a -> b) -> b -> Messages a -> b Source # foldl' :: (b -> a -> b) -> b -> Messages a -> b Source # foldr1 :: (a -> a -> a) -> Messages a -> a Source # foldl1 :: (a -> a -> a) -> Messages a -> a Source # toList :: Messages a -> [a] Source # null :: Messages a -> Bool Source # length :: Messages a -> Int Source # elem :: Eq a => a -> Messages a -> Bool Source # maximum :: Ord a => Messages a -> a Source # minimum :: Ord a => Messages a -> a Source # | |
Traversable Messages Source # | |
Defined in GHC.Types.Error | |
Functor Messages Source # | |
Monoid (Messages e) Source # | |
Semigroup (Messages e) Source # | |
Diagnostic e => Outputable (Messages e) Source # | |
mkMessages :: Bag (MsgEnvelope e) -> Messages e Source #
unionMessages :: Messages e -> Messages e -> Messages e Source #
Joins two collections of messages together. See Note [Discarding Messages].
errorsFound :: Diagnostic e => Messages e -> Bool Source #
Are there any hard errors here? -Werror warnings are not detected. If
you want to check for -Werror warnings, use errorsOrFatalWarningsFound
.
isEmptyMessages :: Messages e -> Bool Source #
Formatting
pprMsgEnvelopeBagWithLoc :: Diagnostic e => DiagnosticOpts e -> Bag (MsgEnvelope e) -> [SDoc] Source #
pprMsgEnvelopeBagWithLocDefault :: forall e. Diagnostic e => Bag (MsgEnvelope e) -> [SDoc] Source #
Print the messages with the suitable default configuration, usually not what you want but sometimes you don't really care about what the configuration is (for example, if the message is in a panic).
pprMessages :: Diagnostic e => DiagnosticOpts e -> Messages e -> SDoc Source #
pprLocMsgEnvelope :: Diagnostic e => DiagnosticOpts e -> MsgEnvelope e -> SDoc Source #
pprLocMsgEnvelopeDefault :: forall e. Diagnostic e => MsgEnvelope e -> SDoc Source #
formatBulleted :: SDocContext -> DecoratedSDoc -> SDoc Source #
Formats the input list of structured document, where each element of the list gets a bullet.
Construction
DiagOpts | |
|
diag_fatal_wopt :: WarningFlag -> DiagOpts -> Bool Source #
emptyMessages :: Messages e Source #
mkDecorated :: [SDoc] -> DecoratedSDoc Source #
Creates a new DecoratedSDoc
out of a list of SDoc
.
:: MessageClass | What kind of message? |
-> SrcSpan | location |
-> SDoc | message |
-> SDoc |
mkMsgEnvelope :: Diagnostic e => DiagOpts -> SrcSpan -> NamePprCtx -> e -> MsgEnvelope e Source #
Wrap a Diagnostic
in a MsgEnvelope
, recording its location.
If you know your Diagnostic
is an error, consider using mkErrorMsgEnvelope
,
which does not require looking at the DiagOpts
mkPlainMsgEnvelope :: Diagnostic e => DiagOpts -> SrcSpan -> e -> MsgEnvelope e Source #
Variant that doesn't care about qualified/unqualified names.
mkPlainErrorMsgEnvelope :: Diagnostic e => SrcSpan -> e -> MsgEnvelope e Source #
Variant of mkPlainMsgEnvelope
which can be used when we are sure we
are constructing a diagnostic with a ErrorWithoutFlag
reason.
mkErrorMsgEnvelope :: Diagnostic e => SrcSpan -> NamePprCtx -> e -> MsgEnvelope e Source #
Wrap a Diagnostic
in a MsgEnvelope
, recording its location.
Precondition: the diagnostic is, in fact, an error. That is,
diagnosticReason msg == ErrorWithoutFlag
.
mkMCDiagnostic :: DiagOpts -> DiagnosticReason -> Maybe DiagnosticCode -> MessageClass Source #
Make a MessageClass
for a given DiagnosticReason
, consulting the
'DiagOpts.
errorDiagnostic :: MessageClass Source #
Varation of mkMCDiagnostic
which can be used when we are sure the
input DiagnosticReason
is ErrorWithoutFlag
and there is no diagnostic code.
diagReasonSeverity :: DiagOpts -> DiagnosticReason -> Severity Source #
Computes the right Severity
for the input DiagnosticReason
out of
the 'DiagOpts. This function has to be called when a diagnostic is constructed,
i.e. with a 'DiagOpts "snapshot" taken as close as possible to where a
particular diagnostic message is built, otherwise the computed Severity
might
not be correct, due to the mutable nature of the DynFlags
in GHC.
mkPlainError :: [GhcHint] -> SDoc -> DiagnosticMessage Source #
Create an error DiagnosticMessage
holding just a single SDoc
mkPlainDiagnostic :: DiagnosticReason -> [GhcHint] -> SDoc -> DiagnosticMessage Source #
mkDecoratedError :: [GhcHint] -> [SDoc] -> DiagnosticMessage Source #
Create an error DiagnosticMessage
from a list of bulleted SDocs
mkDecoratedDiagnostic :: DiagnosticReason -> [GhcHint] -> [SDoc] -> DiagnosticMessage Source #
Create a DiagnosticMessage
from a list of bulleted SDocs and a DiagnosticReason
Helper function to use when no hints can be provided. Currently this function
can be used to construct plain DiagnosticMessage
and add hints to them, but
once #18516 will be fully executed, the main usage of this function would be in
the implementation of the diagnosticHints
typeclass method, to report the fact
that a particular Diagnostic
has no hints.
Utilities
getCaretDiagnostic :: MessageClass -> SrcSpan -> IO SDoc Source #
Issuing messages during compilation
printInfoForUser :: Logger -> NamePprCtx -> SDoc -> IO () Source #
printOutputForUser :: Logger -> NamePprCtx -> SDoc -> IO () Source #
:: MonadIO m | |
=> Logger | |
-> SDoc | The name of the phase |
-> (a -> ()) | A function to force the result
(often either |
-> m a | The body of the phase to be timed |
-> m a |
Time a compilation phase.
When timings are enabled (e.g. with the -v2
flag), the allocations
and CPU time used by the phase will be reported to stderr. Consider
a typical usage:
withTiming getDynFlags (text "simplify") force PrintTimings pass
.
When timings are enabled the following costs are included in the
produced accounting,
- The cost of executing
pass
to a resultr
in WHNF - The cost of evaluating
force r
to WHNF (e.g.()
)
The choice of the force
function depends upon the amount of forcing
desired; the goal here is to ensure that the cost of evaluating the result
is, to the greatest extent possible, included in the accounting provided by
withTiming
. Often the pass already sufficiently forces its result during
construction; in this case const ()
is a reasonable choice.
In other cases, it is necessary to evaluate the result to normal form, in
which case something like Control.DeepSeq.rnf
is appropriate.
To avoid adversely affecting compiler performance when timings are not requested, the result is only forced when timings are enabled.
See Note [withTiming] for more.
:: MonadIO m | |
=> Logger | |
-> SDoc | The name of the phase |
-> (a -> ()) | A function to force the result
(often either |
-> m a | The body of the phase to be timed |
-> m a |
Same as withTiming
, but doesn't print timings in the
console (when given -vN
, N >= 2
or -ddump-timings
).
See Note [withTiming] for more.
prettyPrintGhcErrors :: ExceptionMonad m => Logger -> m a -> m a Source #
traceCmd :: Logger -> String -> String -> IO a -> IO a Source #
Trace a command (when verbosity level >= 3)
traceSystoolCommand :: Logger -> String -> IO a -> IO a Source #
Record in the eventlog when the given tool command starts
and finishes, prepending the given String
with
"systool:", to easily be able to collect and process
all the systool events.
For those events to show up in the eventlog, you need
to run GHC with -v2
or -ddump-timings
.
sortMsgBag :: Maybe DiagOpts -> Bag (MsgEnvelope e) -> [MsgEnvelope e] Source #