| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
GHC.Core.Lint
Contents
Synopsis
- data LintPassResultConfig = LintPassResultConfig {
- lpr_diagOpts :: !DiagOpts
 - lpr_platform :: !Platform
 - lpr_makeLintFlags :: !LintFlags
 - lpr_showLintWarnings :: !Bool
 - lpr_passPpr :: !SDoc
 - lpr_localsInScope :: ![Var]
 
 - data LintFlags = LF {}
 - data StaticPtrCheck
 - data LintConfig = LintConfig {
- l_diagOpts :: !DiagOpts
 - l_platform :: !Platform
 - l_flags :: !LintFlags
 - l_vars :: ![Var]
 
 - type WarnsAndErrs = (Bag SDoc, Bag SDoc)
 - lintCoreBindings' :: LintConfig -> CoreProgram -> WarnsAndErrs
 - lintUnfolding :: Bool -> LintConfig -> SrcLoc -> CoreExpr -> Maybe (Bag SDoc)
 - lintPassResult :: Logger -> LintPassResultConfig -> CoreProgram -> IO ()
 - lintExpr :: LintConfig -> CoreExpr -> Maybe (Bag SDoc)
 - lintAnnots :: SDoc -> (ModGuts -> CoreM ModGuts) -> ModGuts -> CoreM ModGuts
 - lintAxioms :: Logger -> LintConfig -> SDoc -> [CoAxiom Branched] -> IO ()
 - data EndPassConfig = EndPassConfig {
- ep_dumpCoreSizes :: !Bool
 - ep_lintPassResult :: !(Maybe LintPassResultConfig)
 - ep_namePprCtx :: !NamePprCtx
 - ep_dumpFlag :: !(Maybe DumpFlag)
 - ep_prettyPass :: !SDoc
 - ep_passDetails :: !SDoc
 
 - endPassIO :: Logger -> EndPassConfig -> CoreProgram -> [CoreRule] -> IO ()
 - displayLintResults :: Logger -> Bool -> SDoc -> SDoc -> WarnsAndErrs -> IO ()
 - dumpPassResult :: Logger -> Bool -> NamePprCtx -> Maybe DumpFlag -> String -> SDoc -> CoreProgram -> [CoreRule] -> IO ()
 
Documentation
data LintPassResultConfig Source #
Constructors
| LintPassResultConfig | |
Fields 
  | |
Constructors
| LF | |
Fields 
  | |
data StaticPtrCheck Source #
Constructors
| AllowAnywhere | Allow   | 
| AllowAtTopLevel | Allow   | 
| RejectEverywhere | Reject any   | 
Instances
| Eq StaticPtrCheck Source # | |
Defined in GHC.Core.Lint Methods (==) :: StaticPtrCheck -> StaticPtrCheck -> Bool # (/=) :: StaticPtrCheck -> StaticPtrCheck -> Bool #  | |
data LintConfig Source #
Constructors
| LintConfig | |
Fields 
  | |
lintCoreBindings' :: LintConfig -> CoreProgram -> WarnsAndErrs Source #
Type-check a CoreProgram. See Note [Core Lint guarantee].
lintPassResult :: Logger -> LintPassResultConfig -> CoreProgram -> IO () Source #
lintAnnots :: SDoc -> (ModGuts -> CoreM ModGuts) -> ModGuts -> CoreM ModGuts Source #
This checks whether a pass correctly looks through debug
 annotations (SourceNote). This works a bit different from other
 consistency checks: We check this by running the given task twice,
 noting all differences between the results.
Debug output
data EndPassConfig Source #
Configuration for boilerplate operations at the end of a compilation pass producing Core.
Constructors
| EndPassConfig | |
Fields 
  | |
endPassIO :: Logger -> EndPassConfig -> CoreProgram -> [CoreRule] -> IO () Source #
dumpPassResult :: Logger -> Bool -> NamePprCtx -> Maybe DumpFlag -> String -> SDoc -> CoreProgram -> [CoreRule] -> IO () Source #