| Safe Haskell | None |
|---|---|
| Language | GHC2024 |
GHC.Unit.Module.Warnings
Contents
Description
Warnings for a module
Synopsis
- newtype WarningCategory = WarningCategory FastString
- mkWarningCategory :: FastString -> WarningCategory
- defaultWarningCategory :: WarningCategory
- validWarningCategory :: WarningCategory -> Bool
- data InWarningCategory pass
- = InWarningCategory {
- iwc_st :: XInWarningCategory pass
- iwc_wc :: XRec pass WarningCategory
- | XInWarningCategory !(XXInWarningCategory pass)
- = InWarningCategory {
- fromWarningCategory :: HasAnnotation (Anno WarningCategory) => WarningCategory -> InWarningCategory (GhcPass p)
- data WarningCategorySet
- emptyWarningCategorySet :: WarningCategorySet
- completeWarningCategorySet :: WarningCategorySet
- nullWarningCategorySet :: WarningCategorySet -> Bool
- elemWarningCategorySet :: WarningCategory -> WarningCategorySet -> Bool
- insertWarningCategorySet :: WarningCategory -> WarningCategorySet -> WarningCategorySet
- deleteWarningCategorySet :: WarningCategory -> WarningCategorySet -> WarningCategorySet
- data Warnings pass
- = WarnSome (DeclWarnOccNames pass) (ExportWarnNames pass)
- | WarnAll (WarningTxt pass)
- data WarningTxt pass
- = DeprecatedTxt (XDeprecatedTxt pass) [XRec pass (WithHsDocIdentifiers StringLiteral pass)]
- | WarningTxt (XWarningTxt pass) (Maybe (XRec pass (InWarningCategory pass))) [XRec pass (WithHsDocIdentifiers StringLiteral pass)]
- | XWarningTxt !(XXWarningTxt pass)
- type LWarningTxt pass = XRec pass (WarningTxt pass)
- type DeclWarnOccNames pass = [(OccName, WarningTxt pass)]
- type ExportWarnNames pass = [(Name, WarningTxt pass)]
- warningTxtCategory :: WarningTxt (GhcPass p) -> WarningCategory
- warningTxtMessage :: WarningTxt (GhcPass p) -> [LocatedE (WithHsDocIdentifiers StringLiteral (GhcPass p))]
- warningTxtSame :: WarningTxt (GhcPass p) -> WarningTxt (GhcPass p) -> Bool
- pprWarningTxtForMsg :: WarningTxt (GhcPass pass) -> SDoc
- emptyWarn :: Warnings p
- mkIfaceDeclWarnCache :: Warnings p -> OccName -> Maybe (WarningTxt p)
- mkIfaceExportWarnCache :: Warnings p -> Name -> Maybe (WarningTxt p)
- emptyIfaceWarnCache :: name -> Maybe (WarningTxt p)
- insertWarnDecls :: Warnings p -> [(OccName, WarningTxt p)] -> Warnings p
- insertWarnExports :: Warnings p -> [(Name, WarningTxt p)] -> Warnings p
Documentation
newtype WarningCategory Source #
Constructors
| WarningCategory FastString |
Instances
defaultWarningCategory :: WarningCategory Source #
The deprecations category is used for all DEPRECATED pragmas and for
WARNING pragmas that do not specify a category.
validWarningCategory :: WarningCategory -> Bool Source #
Is this warning category allowed to appear in user-defined WARNING pragmas?
It must either be the known category deprecations, or be a custom category
that begins with x- and contains only valid characters (letters, numbers,
apostrophes and dashes).
data InWarningCategory pass Source #
Constructors
| InWarningCategory | |
Fields
| |
| XInWarningCategory !(XXInWarningCategory pass) | |
Instances
fromWarningCategory :: HasAnnotation (Anno WarningCategory) => WarningCategory -> InWarningCategory (GhcPass p) Source #
data WarningCategorySet Source #
A finite or infinite set of warning categories.
Unlike WarningFlag, there are (in principle) infinitely many warning
categories, so we cannot necessarily enumerate all of them. However the set
is constructed by adding or removing categories one at a time, so we can
represent it as either a finite set of categories, or a cofinite set (where
we store the complement).
emptyWarningCategorySet :: WarningCategorySet Source #
The empty set of warning categories.
completeWarningCategorySet :: WarningCategorySet Source #
The set consisting of all possible warning categories.
nullWarningCategorySet :: WarningCategorySet -> Bool Source #
Is this set empty?
elemWarningCategorySet :: WarningCategory -> WarningCategorySet -> Bool Source #
Does this warning category belong to the set?
insertWarningCategorySet :: WarningCategory -> WarningCategorySet -> WarningCategorySet Source #
Insert an element into a warning category set.
deleteWarningCategorySet :: WarningCategory -> WarningCategorySet -> WarningCategorySet Source #
Delete an element from a warning category set.
Warning information from a module
Constructors
| WarnSome | |
Fields
| |
| WarnAll (WarningTxt pass) | Whole module deprecated |
data WarningTxt pass Source #
Warning Text
reason/explanation from a WARNING or DEPRECATED pragma
Constructors
| DeprecatedTxt (XDeprecatedTxt pass) [XRec pass (WithHsDocIdentifiers StringLiteral pass)] | |
| WarningTxt | |
Fields
| |
| XWarningTxt !(XXWarningTxt pass) | |
Instances
type LWarningTxt pass = XRec pass (WarningTxt pass) Source #
type DeclWarnOccNames pass = [(OccName, WarningTxt pass)] Source #
Deprecated declarations
type ExportWarnNames pass = [(Name, WarningTxt pass)] Source #
Names that are deprecated as exports
warningTxtCategory :: WarningTxt (GhcPass p) -> WarningCategory Source #
To which warning category does this WARNING or DEPRECATED pragma belong? See Note [Warning categories].
warningTxtMessage :: WarningTxt (GhcPass p) -> [LocatedE (WithHsDocIdentifiers StringLiteral (GhcPass p))] Source #
The message that the WarningTxt was specified to output
warningTxtSame :: WarningTxt (GhcPass p) -> WarningTxt (GhcPass p) -> Bool Source #
True if the 2 WarningTxts have the same category and messages
pprWarningTxtForMsg :: WarningTxt (GhcPass pass) -> SDoc Source #
mkIfaceDeclWarnCache :: Warnings p -> OccName -> Maybe (WarningTxt p) Source #
Constructs the cache for the mi_decl_warn_fn field of a ModIface
mkIfaceExportWarnCache :: Warnings p -> Name -> Maybe (WarningTxt p) Source #
Constructs the cache for the mi_export_warn_fn field of a ModIface
emptyIfaceWarnCache :: name -> Maybe (WarningTxt p) Source #
Arguments
| :: Warnings p | Existing warnings |
| -> [(OccName, WarningTxt p)] | New declaration deprecations |
| -> Warnings p | Updated warnings |
Arguments
| :: Warnings p | Existing warnings |
| -> [(Name, WarningTxt p)] | New export deprecations |
| -> Warnings p | Updated warnings |
Orphan instances
| Uniquable WarningCategory Source # | |
Methods getUnique :: WarningCategory -> Unique Source # | |
| Binary WarningCategory Source # | |
Methods put_ :: WriteBinHandle -> WarningCategory -> IO () Source # put :: WriteBinHandle -> WarningCategory -> IO (Bin WarningCategory) Source # get :: ReadBinHandle -> IO WarningCategory Source # | |
| Outputable WarningCategory Source # | |
Methods ppr :: WarningCategory -> SDoc Source # | |
| Outputable (InWarningCategory (GhcPass pass)) Source # | |
| Outputable (WarningTxt (GhcPass pass)) Source # | |
| Eq (InWarningCategory GhcPs) Source # | |
Methods (==) :: InWarningCategory GhcPs -> InWarningCategory GhcPs -> Bool Source # (/=) :: InWarningCategory GhcPs -> InWarningCategory GhcPs -> Bool Source # | |
| Eq (InWarningCategory GhcRn) Source # | |
Methods (==) :: InWarningCategory GhcRn -> InWarningCategory GhcRn -> Bool Source # (/=) :: InWarningCategory GhcRn -> InWarningCategory GhcRn -> Bool Source # | |
| Eq (InWarningCategory GhcTc) Source # | |
Methods (==) :: InWarningCategory GhcTc -> InWarningCategory GhcTc -> Bool Source # (/=) :: InWarningCategory GhcTc -> InWarningCategory GhcTc -> Bool Source # | |
| Eq (WarningTxt GhcPs) Source # | |
Methods (==) :: WarningTxt GhcPs -> WarningTxt GhcPs -> Bool Source # (/=) :: WarningTxt GhcPs -> WarningTxt GhcPs -> Bool Source # | |
| Eq (WarningTxt GhcRn) Source # | |
Methods (==) :: WarningTxt GhcRn -> WarningTxt GhcRn -> Bool Source # (/=) :: WarningTxt GhcRn -> WarningTxt GhcRn -> Bool Source # | |
| Eq (WarningTxt GhcTc) Source # | |
Methods (==) :: WarningTxt GhcTc -> WarningTxt GhcTc -> Bool Source # (/=) :: WarningTxt GhcTc -> WarningTxt GhcTc -> Bool Source # | |