| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
ErrUtils
Contents
Synopsis
- data Validity
- andValid :: Validity -> Validity -> Validity
- allValid :: [Validity] -> Validity
- isValid :: Validity -> Bool
- getInvalids :: [Validity] -> [MsgDoc]
- orValid :: Validity -> Validity -> Validity
- data Severity
- data ErrMsg
- errMsgDoc :: ErrMsg -> ErrDoc
- errMsgSeverity :: ErrMsg -> Severity
- errMsgReason :: ErrMsg -> WarnReason
- data ErrDoc
- errDoc :: [MsgDoc] -> [MsgDoc] -> [MsgDoc] -> ErrDoc
- errDocImportant :: ErrDoc -> [MsgDoc]
- errDocContext :: ErrDoc -> [MsgDoc]
- errDocSupplementary :: ErrDoc -> [MsgDoc]
- type WarnMsg = ErrMsg
- type MsgDoc = SDoc
- type Messages = (WarningMessages, ErrorMessages)
- type ErrorMessages = Bag ErrMsg
- type WarningMessages = Bag WarnMsg
- unionMessages :: Messages -> Messages -> Messages
- errMsgSpan :: ErrMsg -> SrcSpan
- errMsgContext :: ErrMsg -> PrintUnqualified
- errorsFound :: DynFlags -> Messages -> Bool
- isEmptyMessages :: Messages -> Bool
- isWarnMsgFatal :: DynFlags -> WarnMsg -> Maybe (Maybe WarningFlag)
- warningsToMessages :: DynFlags -> WarningMessages -> Messages
- pprMessageBag :: Bag MsgDoc -> SDoc
- pprErrMsgBagWithLoc :: Bag ErrMsg -> [SDoc]
- pprLocErrMsg :: ErrMsg -> SDoc
- printBagOfErrors :: DynFlags -> Bag ErrMsg -> IO ()
- formatErrDoc :: DynFlags -> ErrDoc -> SDoc
- emptyMessages :: Messages
- mkLocMessage :: Severity -> SrcSpan -> MsgDoc -> MsgDoc
- mkLocMessageAnn :: Maybe String -> Severity -> SrcSpan -> MsgDoc -> MsgDoc
- makeIntoWarning :: WarnReason -> ErrMsg -> ErrMsg
- mkErrMsg :: DynFlags -> SrcSpan -> PrintUnqualified -> MsgDoc -> ErrMsg
- mkPlainErrMsg :: DynFlags -> SrcSpan -> MsgDoc -> ErrMsg
- mkErrDoc :: DynFlags -> SrcSpan -> PrintUnqualified -> ErrDoc -> ErrMsg
- mkLongErrMsg :: DynFlags -> SrcSpan -> PrintUnqualified -> MsgDoc -> MsgDoc -> ErrMsg
- mkWarnMsg :: DynFlags -> SrcSpan -> PrintUnqualified -> MsgDoc -> ErrMsg
- mkPlainWarnMsg :: DynFlags -> SrcSpan -> MsgDoc -> ErrMsg
- mkLongWarnMsg :: DynFlags -> SrcSpan -> PrintUnqualified -> MsgDoc -> MsgDoc -> ErrMsg
- doIfSet :: Bool -> IO () -> IO ()
- doIfSet_dyn :: DynFlags -> GeneralFlag -> IO () -> IO ()
- getCaretDiagnostic :: Severity -> SrcSpan -> IO MsgDoc
- dumpIfSet :: DynFlags -> Bool -> String -> SDoc -> IO ()
- dumpIfSet_dyn :: DynFlags -> DumpFlag -> String -> DumpFormat -> SDoc -> IO ()
- dumpIfSet_dyn_printer :: PrintUnqualified -> DynFlags -> DumpFlag -> String -> DumpFormat -> SDoc -> IO ()
- dumpOptionsFromFlag :: DumpFlag -> DumpOptions
- data DumpOptions = DumpOptions {}
- data DumpFormat
- type DumpAction = DynFlags -> PprStyle -> DumpOptions -> String -> DumpFormat -> SDoc -> IO ()
- dumpAction :: DumpAction
- defaultDumpAction :: DumpAction
- type TraceAction = forall a. DynFlags -> String -> SDoc -> a -> a
- traceAction :: TraceAction
- defaultTraceAction :: TraceAction
- touchDumpFile :: DynFlags -> DumpOptions -> IO ()
- putMsg :: DynFlags -> MsgDoc -> IO ()
- printInfoForUser :: DynFlags -> PrintUnqualified -> MsgDoc -> IO ()
- printOutputForUser :: DynFlags -> PrintUnqualified -> MsgDoc -> IO ()
- logInfo :: DynFlags -> PprStyle -> MsgDoc -> IO ()
- logOutput :: DynFlags -> PprStyle -> MsgDoc -> IO ()
- errorMsg :: DynFlags -> MsgDoc -> IO ()
- warningMsg :: DynFlags -> MsgDoc -> IO ()
- fatalErrorMsg :: DynFlags -> MsgDoc -> IO ()
- fatalErrorMsg'' :: FatalMessager -> String -> IO ()
- compilationProgressMsg :: DynFlags -> String -> IO ()
- showPass :: DynFlags -> String -> IO ()
- withTiming :: MonadIO m => DynFlags -> SDoc -> (a -> ()) -> m a -> m a
- withTimingSilent :: MonadIO m => DynFlags -> SDoc -> (a -> ()) -> m a -> m a
- withTimingD :: (MonadIO m, HasDynFlags m) => SDoc -> (a -> ()) -> m a -> m a
- withTimingSilentD :: (MonadIO m, HasDynFlags m) => SDoc -> (a -> ()) -> m a -> m a
- debugTraceMsg :: DynFlags -> Int -> MsgDoc -> IO ()
- ghcExit :: DynFlags -> Int -> IO ()
- prettyPrintGhcErrors :: ExceptionMonad m => DynFlags -> m a -> m a
- traceCmd :: DynFlags -> String -> String -> IO a -> IO a
Basic types
getInvalids :: [Validity] -> [MsgDoc] Source #
Constructors
| SevOutput | |
| SevFatal | |
| SevInteractive | |
| SevDump | Log message intended for compiler developers No filelinecolumn stuff | 
| SevInfo | Log messages intended for end users. No filelinecolumn stuff. | 
| SevWarning | |
| SevError | SevWarning and SevError are used for warnings and errors o The message has a filelinecolumn heading, plus "warning:" or "error:", added by mkLocMessags o Output is intended for end users | 
Messages
errMsgSeverity :: ErrMsg -> Severity Source #
errMsgReason :: ErrMsg -> WarnReason 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 ...".
type Messages = (WarningMessages, ErrorMessages) Source #
type ErrorMessages = Bag ErrMsg Source #
type WarningMessages = Bag WarnMsg Source #
errMsgSpan :: ErrMsg -> SrcSpan Source #
isEmptyMessages :: Messages -> Bool Source #
isWarnMsgFatal :: DynFlags -> WarnMsg -> Maybe (Maybe WarningFlag) Source #
Checks if given WarnMsg is a fatal warning.
warningsToMessages :: DynFlags -> WarningMessages -> Messages Source #
Formatting
pprLocErrMsg :: ErrMsg -> SDoc Source #
Construction
mkLocMessage :: Severity -> SrcSpan -> MsgDoc -> MsgDoc Source #
Make an unannotated error message with location info.
Arguments
| :: Maybe String | optional annotation | 
| -> Severity | severity | 
| -> SrcSpan | location | 
| -> MsgDoc | message | 
| -> MsgDoc | 
Make a possibly annotated error message with location info.
makeIntoWarning :: WarnReason -> ErrMsg -> ErrMsg Source #
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_dyn :: DynFlags -> GeneralFlag -> 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
| Eq DumpFormat Source # | |
| Defined in ErrUtils | |
| Show DumpFormat Source # | |
| Defined in ErrUtils Methods showsPrec :: Int -> DumpFormat -> ShowS # show :: DumpFormat -> String # showList :: [DumpFormat] -> ShowS # | |
type DumpAction = DynFlags -> PprStyle -> DumpOptions -> String -> DumpFormat -> SDoc -> IO () Source #
dumpAction :: DumpAction Source #
Helper for dump_action
defaultDumpAction :: DumpAction Source #
Default action for dumpAction hook
traceAction :: TraceAction Source #
Helper for trace_action
defaultTraceAction :: TraceAction Source #
Default action for traceAction hook
touchDumpFile :: DynFlags -> DumpOptions -> IO () Source #
Ensure that a dump file is created even if it stays empty
Issuing messages during compilation
printInfoForUser :: DynFlags -> PrintUnqualified -> MsgDoc -> IO () Source #
printOutputForUser :: DynFlags -> PrintUnqualified -> MsgDoc -> IO () Source #
fatalErrorMsg'' :: FatalMessager -> String -> IO () Source #
Arguments
| :: MonadIO m | |
| => 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 | |
| => 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.
Arguments
| :: (MonadIO m, HasDynFlags m) | |
| => 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 | 
Like withTiming but get DynFlags from the Monad.
Arguments
| :: (MonadIO m, HasDynFlags m) | |
| => 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)
   and gets the DynFlags from the given Monad.
See Note [withTiming] for more.
prettyPrintGhcErrors :: ExceptionMonad m => DynFlags -> m a -> m a Source #