ghc-9.0.2: The GHC API
Safe HaskellSafe-Inferred
LanguageHaskell2010

GHC.Utils.Error

Synopsis

Basic types

data Validity Source #

Constructors

IsValid

Everything is fine

NotValid MsgDoc

A problem, and some indication of why

allValid :: [Validity] -> Validity Source #

If they aren't all valid, return the first

data Severity Source #

Constructors

SevOutput 
SevFatal 
SevInteractive 
SevDump

Log message intended for compiler developers No file/line/column stuff

SevInfo

Log messages intended for end users. No file/line/column stuff.

SevWarning 
SevError

SevWarning and SevError are used for warnings and errors o The message has a file/line/column heading, plus "warning:" or "error:", added by mkLocMessags o Output is intended for end users

Instances

Instances details
Show Severity Source # 
Instance details

Defined in GHC.Utils.Error

ToJson Severity Source # 
Instance details

Defined in GHC.Utils.Error

Messages

data ErrMsg Source #

Instances

Instances details
Show ErrMsg Source # 
Instance details

Defined in GHC.Utils.Error

data ErrDoc Source #

Categorise error msgs by their importance. This is so each section can be rendered visually distinct. See Note [Error report] for where these come from.

errDocImportant :: ErrDoc -> [MsgDoc] Source #

Primary error msg.

errDocContext :: ErrDoc -> [MsgDoc] Source #

Context e.g. "In the second argument of ...".

errDocSupplementary :: ErrDoc -> [MsgDoc] Source #

Supplementary information, e.g. "Relevant bindings include ...".

isWarnMsgFatal :: DynFlags -> WarnMsg -> Maybe (Maybe WarningFlag) Source #

Checks if given WarnMsg is a fatal warning.

Formatting

Construction

mkLocMessage :: Severity -> SrcSpan -> MsgDoc -> MsgDoc Source #

Make an unannotated error message with location info.

mkLocMessageAnn Source #

Arguments

:: Maybe String

optional annotation

-> Severity

severity

-> SrcSpan

location

-> MsgDoc

message

-> MsgDoc 

Make a possibly annotated error message with location info.

mkErrMsg :: DynFlags -> SrcSpan -> PrintUnqualified -> MsgDoc -> ErrMsg Source #

A short (one-line) error message

mkPlainErrMsg :: DynFlags -> SrcSpan -> MsgDoc -> ErrMsg Source #

Variant that doesn't care about qualified/unqualified names

mkLongErrMsg :: DynFlags -> SrcSpan -> PrintUnqualified -> MsgDoc -> MsgDoc -> ErrMsg Source #

A long (multi-line) error message

mkWarnMsg :: DynFlags -> SrcSpan -> PrintUnqualified -> MsgDoc -> ErrMsg Source #

A short (one-line) error message

mkPlainWarnMsg :: DynFlags -> SrcSpan -> MsgDoc -> ErrMsg Source #

Variant that doesn't care about qualified/unqualified names

mkLongWarnMsg :: DynFlags -> SrcSpan -> PrintUnqualified -> MsgDoc -> MsgDoc -> ErrMsg Source #

A long (multi-line) error message

Utilities

doIfSet :: Bool -> IO () -> IO () Source #

Dump files

dumpIfSet_dyn :: DynFlags -> DumpFlag -> String -> DumpFormat -> SDoc -> IO () Source #

A wrapper around dumpAction. First check whether the dump flag is set Do nothing if it is unset

dumpIfSet_dyn_printer :: PrintUnqualified -> DynFlags -> DumpFlag -> String -> DumpFormat -> SDoc -> IO () Source #

A wrapper around dumpAction. First check whether the dump flag is set Do nothing if it is unset

Unlike dumpIfSet_dyn, has a printer argument

dumpOptionsFromFlag :: DumpFlag -> DumpOptions Source #

Create dump options from a DumpFlag

data DumpOptions Source #

Dump options

Dumps are printed on stdout by default except when the dumpForcedToFile field is set to True.

When dumpForcedToFile is True or when `-ddump-to-file` is set, dumps are written into a file whose suffix is given in the dumpSuffix field.

Constructors

DumpOptions 

Fields

data DumpFormat Source #

Format of a dump

Dump formats are loosely defined: dumps may contain various additional headers and annotations and they may be partial. DumpFormat is mainly a hint (e.g. for syntax highlighters).

Constructors

FormatHaskell

Haskell

FormatCore

Core

FormatSTG

STG

FormatByteCode

ByteCode

FormatCMM

Cmm

FormatASM

Assembly code

FormatC

C code/header

FormatLLVM

LLVM bytecode

FormatText

Unstructured dump

Instances

Instances details
Show DumpFormat Source # 
Instance details

Defined in GHC.Utils.Error

Eq DumpFormat Source # 
Instance details

Defined in GHC.Utils.Error

defaultDumpAction :: DumpAction Source #

Default action for dumpAction hook

type TraceAction = forall a. DynFlags -> String -> SDoc -> a -> a Source #

touchDumpFile :: DynFlags -> DumpOptions -> IO () Source #

Ensure that a dump file is created even if it stays empty

Issuing messages during compilation

logOutput :: DynFlags -> MsgDoc -> IO () Source #

Like logInfo but with SevOutput rather then SevInfo

withTiming Source #

Arguments

:: MonadIO m 
=> DynFlags

DynFlags

-> SDoc

The name of the phase

-> (a -> ())

A function to force the result (often either const () or rnf)

-> 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 result r 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.

withTimingSilent Source #

Arguments

:: MonadIO m 
=> DynFlags

DynFlags

-> SDoc

The name of the phase

-> (a -> ())

A function to force the result (often either const () or rnf)

-> 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.

withTimingD Source #

Arguments

:: (MonadIO m, HasDynFlags m) 
=> SDoc

The name of the phase

-> (a -> ())

A function to force the result (often either const () or rnf)

-> m a

The body of the phase to be timed

-> m a 

Like withTiming but get DynFlags from the Monad.

withTimingSilentD Source #

Arguments

:: (MonadIO m, HasDynFlags m) 
=> SDoc

The name of the phase

-> (a -> ())

A function to force the result (often either const () or rnf)

-> 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) and gets the DynFlags from the given Monad.

See Note [withTiming] for more.

traceCmd :: DynFlags -> String -> String -> IO a -> IO a Source #