| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
GHC.Utils.Error
Synopsis
- data Validity
- andValid :: Validity -> Validity -> Validity
- allValid :: [Validity] -> Validity
- isValid :: Validity -> Bool
- getInvalids :: [Validity] -> [SDoc]
- orValid :: Validity -> Validity -> Validity
- data Severity
- type WarnMsg = MsgEnvelope DecoratedSDoc
- data MsgEnvelope e = MsgEnvelope {}
- data SDoc
- data DecoratedSDoc
- data Messages e
- type ErrorMessages = Bag (MsgEnvelope DecoratedSDoc)
- type WarningMessages = Bag (MsgEnvelope DecoratedSDoc)
- unionMessages :: Messages e -> Messages e -> Messages e
- errorsFound :: Messages e -> Bool
- isEmptyMessages :: Messages e -> Bool
- pprMessageBag :: Bag SDoc -> SDoc
- pprMsgEnvelopeBagWithLoc :: Bag (MsgEnvelope DecoratedSDoc) -> [SDoc]
- pprLocMsgEnvelope :: RenderableDiagnostic e => MsgEnvelope e -> SDoc
- formatBulleted :: SDocContext -> DecoratedSDoc -> SDoc
- emptyMessages :: Messages e
- mkDecorated :: [SDoc] -> DecoratedSDoc
- mkLocMessage :: Severity -> SrcSpan -> SDoc -> SDoc
- mkLocMessageAnn :: Maybe String -> Severity -> SrcSpan -> SDoc -> SDoc
- makeIntoWarning :: WarnReason -> MsgEnvelope e -> MsgEnvelope e
- mkMsgEnvelope :: SrcSpan -> PrintUnqualified -> SDoc -> MsgEnvelope DecoratedSDoc
- mkPlainMsgEnvelope :: SrcSpan -> SDoc -> MsgEnvelope DecoratedSDoc
- mkErr :: SrcSpan -> PrintUnqualified -> e -> MsgEnvelope e
- mkLongMsgEnvelope :: SrcSpan -> PrintUnqualified -> SDoc -> SDoc -> MsgEnvelope DecoratedSDoc
- mkWarnMsg :: SrcSpan -> PrintUnqualified -> SDoc -> MsgEnvelope DecoratedSDoc
- mkPlainWarnMsg :: SrcSpan -> SDoc -> MsgEnvelope DecoratedSDoc
- mkLongWarnMsg :: SrcSpan -> PrintUnqualified -> SDoc -> SDoc -> MsgEnvelope DecoratedSDoc
- doIfSet :: Bool -> IO () -> IO ()
- doIfSet_dyn :: DynFlags -> GeneralFlag -> IO () -> IO ()
- getCaretDiagnostic :: Severity -> SrcSpan -> IO SDoc
- putMsg :: Logger -> DynFlags -> SDoc -> IO ()
- printInfoForUser :: Logger -> DynFlags -> PrintUnqualified -> SDoc -> IO ()
- printOutputForUser :: Logger -> DynFlags -> PrintUnqualified -> SDoc -> IO ()
- logInfo :: Logger -> DynFlags -> SDoc -> IO ()
- logOutput :: Logger -> DynFlags -> SDoc -> IO ()
- errorMsg :: Logger -> DynFlags -> SDoc -> IO ()
- warningMsg :: Logger -> DynFlags -> SDoc -> IO ()
- fatalErrorMsg :: Logger -> DynFlags -> SDoc -> IO ()
- fatalErrorMsg'' :: FatalMessager -> String -> IO ()
- compilationProgressMsg :: Logger -> DynFlags -> SDoc -> IO ()
- showPass :: Logger -> DynFlags -> String -> IO ()
- withTiming :: MonadIO m => Logger -> DynFlags -> SDoc -> (a -> ()) -> m a -> m a
- withTimingSilent :: MonadIO m => Logger -> DynFlags -> SDoc -> (a -> ()) -> m a -> m a
- debugTraceMsg :: Logger -> DynFlags -> Int -> SDoc -> IO ()
- ghcExit :: Logger -> DynFlags -> Int -> IO ()
- prettyPrintGhcErrors :: ExceptionMonad m => DynFlags -> m a -> m a
- traceCmd :: Logger -> DynFlags -> String -> String -> IO a -> IO a
- sortMsgBag :: Maybe DynFlags -> Bag (MsgEnvelope e) -> [MsgEnvelope e]
Basic types
getInvalids :: [Validity] -> [SDoc] 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 | 
Messages
type WarnMsg = MsgEnvelope DecoratedSDoc Source #
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, its severity, etc.
 Finally, multiple MsgEnvelopes are aggregated into Messages that are returned to the user.
Constructors
| MsgEnvelope | |
| Fields 
 | |
Instances
| Functor MsgEnvelope Source # | |
| Defined in GHC.Types.Error Methods fmap :: (a -> b) -> MsgEnvelope a -> MsgEnvelope b # (<$) :: a -> MsgEnvelope b -> MsgEnvelope a # | |
| Show (MsgEnvelope DecoratedSDoc) Source # | |
| Defined in GHC.Types.Error Methods showsPrec :: Int -> MsgEnvelope DecoratedSDoc -> ShowS # show :: MsgEnvelope DecoratedSDoc -> String # showList :: [MsgEnvelope DecoratedSDoc] -> ShowS # | |
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 Methods fromString :: String -> SDoc # | |
| Outputable SDoc Source # | |
| OutputableP env SDoc Source # | |
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.
Instances
| RenderableDiagnostic DecoratedSDoc Source # | |
| Defined in GHC.Types.Error Methods | |
| Show (MsgEnvelope DecoratedSDoc) Source # | |
| Defined in GHC.Types.Error Methods showsPrec :: Int -> MsgEnvelope DecoratedSDoc -> ShowS # show :: MsgEnvelope DecoratedSDoc -> String # showList :: [MsgEnvelope DecoratedSDoc] -> ShowS # | |
A collection of messages emitted by GHC during error reporting. A diagnostic message is typically a warning or an error. See Note [Messages].
type ErrorMessages = Bag (MsgEnvelope DecoratedSDoc) Source #
type WarningMessages = Bag (MsgEnvelope DecoratedSDoc) Source #
unionMessages :: Messages e -> Messages e -> Messages e Source #
Joins two collections of messages together.
errorsFound :: Messages e -> Bool Source #
isEmptyMessages :: Messages e -> Bool Source #
Formatting
pprMsgEnvelopeBagWithLoc :: Bag (MsgEnvelope DecoratedSDoc) -> [SDoc] Source #
pprLocMsgEnvelope :: RenderableDiagnostic 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
emptyMessages :: Messages e Source #
mkDecorated :: [SDoc] -> DecoratedSDoc Source #
Creates a new DecoratedSDoc out of a list of SDoc.
mkLocMessage :: Severity -> SrcSpan -> SDoc -> SDoc Source #
Make an unannotated error message with location info.
Arguments
| :: Maybe String | optional annotation | 
| -> Severity | severity | 
| -> SrcSpan | location | 
| -> SDoc | message | 
| -> SDoc | 
Make a possibly annotated error message with location info.
makeIntoWarning :: WarnReason -> MsgEnvelope e -> MsgEnvelope e Source #
mkMsgEnvelope :: SrcSpan -> PrintUnqualified -> SDoc -> MsgEnvelope DecoratedSDoc Source #
A short (one-line) error message
mkPlainMsgEnvelope :: SrcSpan -> SDoc -> MsgEnvelope DecoratedSDoc Source #
Variant that doesn't care about qualified/unqualified names
mkErr :: SrcSpan -> PrintUnqualified -> e -> MsgEnvelope e Source #
mkLongMsgEnvelope :: SrcSpan -> PrintUnqualified -> SDoc -> SDoc -> MsgEnvelope DecoratedSDoc Source #
A long (multi-line) error message
mkWarnMsg :: SrcSpan -> PrintUnqualified -> SDoc -> MsgEnvelope DecoratedSDoc Source #
A short (one-line) error message
mkPlainWarnMsg :: SrcSpan -> SDoc -> MsgEnvelope DecoratedSDoc Source #
Variant that doesn't care about qualified/unqualified names
mkLongWarnMsg :: SrcSpan -> PrintUnqualified -> SDoc -> SDoc -> MsgEnvelope DecoratedSDoc Source #
A long (multi-line) error message
Utilities
doIfSet_dyn :: DynFlags -> GeneralFlag -> IO () -> IO () Source #
Issuing messages during compilation
printInfoForUser :: Logger -> DynFlags -> PrintUnqualified -> SDoc -> IO () Source #
printOutputForUser :: Logger -> DynFlags -> PrintUnqualified -> SDoc -> IO () Source #
fatalErrorMsg'' :: FatalMessager -> String -> IO () Source #
Arguments
| :: MonadIO m | |
| => Logger | |
| -> DynFlags | DynFlags | 
| -> 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 passto a resultrin WHNF
- The cost of evaluating force rto 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.
Arguments
| :: MonadIO m | |
| => Logger | |
| -> DynFlags | DynFlags | 
| -> 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 => DynFlags -> m a -> m a Source #
sortMsgBag :: Maybe DynFlags -> Bag (MsgEnvelope e) -> [MsgEnvelope e] Source #