Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
GHC.Unit.Module.Warnings
Description
Warnings for a module
Synopsis
- newtype WarningCategory = WarningCategory FastString
- mkWarningCategory :: FastString -> WarningCategory
- defaultWarningCategory :: WarningCategory
- validWarningCategory :: WarningCategory -> Bool
- data InWarningCategory = InWarningCategory {
- iwc_in :: !(Located (HsToken "in"))
- iwc_st :: !SourceText
- iwc_wc :: Located WarningCategory
- fromWarningCategory :: WarningCategory -> InWarningCategory
- 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
- = WarningTxt (Maybe (Located InWarningCategory)) (Located SourceText) [Located (WithHsDocIdentifiers StringLiteral pass)]
- | DeprecatedTxt (Located SourceText) [Located (WithHsDocIdentifiers StringLiteral pass)]
- type DeclWarnOccNames pass = [(OccName, WarningTxt pass)]
- type ExportWarnNames pass = [(Name, WarningTxt pass)]
- warningTxtCategory :: WarningTxt pass -> WarningCategory
- warningTxtMessage :: WarningTxt p -> [Located (WithHsDocIdentifiers StringLiteral p)]
- warningTxtSame :: WarningTxt p1 -> WarningTxt p2 -> Bool
- pprWarningTxtForMsg :: WarningTxt p -> 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 #
Constructors
WarningCategory FastString |
Instances
Data WarningCategory # | |
Defined in GHC.Unit.Module.Warnings Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> WarningCategory -> c WarningCategory gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c WarningCategory toConstr :: WarningCategory -> Constr dataTypeOf :: WarningCategory -> DataType dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c WarningCategory) dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c WarningCategory) gmapT :: (forall b. Data b => b -> b) -> WarningCategory -> WarningCategory gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> WarningCategory -> r gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> WarningCategory -> r gmapQ :: (forall d. Data d => d -> u) -> WarningCategory -> [u] gmapQi :: Int -> (forall d. Data d => d -> u) -> WarningCategory -> u gmapM :: Monad m => (forall d. Data d => d -> m d) -> WarningCategory -> m WarningCategory gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> WarningCategory -> m WarningCategory gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> WarningCategory -> m WarningCategory | |
Show WarningCategory # | |
Defined in GHC.Unit.Module.Warnings Methods showsPrec :: Int -> WarningCategory -> ShowS # show :: WarningCategory -> String # showList :: [WarningCategory] -> ShowS # | |
NFData WarningCategory # | |
Defined in GHC.Unit.Module.Warnings Methods rnf :: WarningCategory -> () | |
Uniquable WarningCategory # | |
Defined in GHC.Unit.Module.Warnings Methods getUnique :: WarningCategory -> Unique # | |
Binary WarningCategory # | |
Defined in GHC.Unit.Module.Warnings Methods put_ :: BinHandle -> WarningCategory -> IO () # put :: BinHandle -> WarningCategory -> IO (Bin WarningCategory) # get :: BinHandle -> IO WarningCategory # | |
Outputable WarningCategory # | |
Defined in GHC.Unit.Module.Warnings Methods ppr :: WarningCategory -> SDoc # | |
Eq WarningCategory # | |
Defined in GHC.Unit.Module.Warnings Methods (==) :: WarningCategory -> WarningCategory -> Bool # (/=) :: WarningCategory -> WarningCategory -> Bool # |
defaultWarningCategory :: WarningCategory #
The deprecations
category is used for all DEPRECATED pragmas and for
WARNING pragmas that do not specify a category.
validWarningCategory :: WarningCategory -> Bool #
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 #
Constructors
InWarningCategory | |
Fields
|
Instances
Data InWarningCategory # | |
Defined in GHC.Unit.Module.Warnings Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> InWarningCategory -> c InWarningCategory gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c InWarningCategory toConstr :: InWarningCategory -> Constr dataTypeOf :: InWarningCategory -> DataType dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c InWarningCategory) dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c InWarningCategory) gmapT :: (forall b. Data b => b -> b) -> InWarningCategory -> InWarningCategory gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> InWarningCategory -> r gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> InWarningCategory -> r gmapQ :: (forall d. Data d => d -> u) -> InWarningCategory -> [u] gmapQi :: Int -> (forall d. Data d => d -> u) -> InWarningCategory -> u gmapM :: Monad m => (forall d. Data d => d -> m d) -> InWarningCategory -> m InWarningCategory gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> InWarningCategory -> m InWarningCategory gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> InWarningCategory -> m InWarningCategory | |
Outputable InWarningCategory # | |
Defined in GHC.Unit.Module.Warnings Methods ppr :: InWarningCategory -> SDoc # | |
Eq InWarningCategory # | |
Defined in GHC.Unit.Module.Warnings Methods (==) :: InWarningCategory -> InWarningCategory -> Bool # (/=) :: InWarningCategory -> InWarningCategory -> Bool # |
data WarningCategorySet #
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 #
The empty set of warning categories.
completeWarningCategorySet :: WarningCategorySet #
The set consisting of all possible warning categories.
nullWarningCategorySet :: WarningCategorySet -> Bool #
Is this set empty?
elemWarningCategorySet :: WarningCategory -> WarningCategorySet -> Bool #
Does this warning category belong to the set?
insertWarningCategorySet :: WarningCategory -> WarningCategorySet -> WarningCategorySet #
Insert an element into a warning category set.
deleteWarningCategorySet :: WarningCategory -> WarningCategorySet -> WarningCategorySet #
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 #
Warning Text
reason/explanation from a WARNING or DEPRECATED pragma
Constructors
WarningTxt | |
Fields
| |
DeprecatedTxt (Located SourceText) [Located (WithHsDocIdentifiers StringLiteral pass)] |
Instances
(Data pass, Data (IdP pass)) => Data (WarningTxt pass) # | |
Defined in GHC.Unit.Module.Warnings Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> WarningTxt pass -> c (WarningTxt pass) gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (WarningTxt pass) toConstr :: WarningTxt pass -> Constr dataTypeOf :: WarningTxt pass -> DataType dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (WarningTxt pass)) dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (WarningTxt pass)) gmapT :: (forall b. Data b => b -> b) -> WarningTxt pass -> WarningTxt pass gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> WarningTxt pass -> r gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> WarningTxt pass -> r gmapQ :: (forall d. Data d => d -> u) -> WarningTxt pass -> [u] gmapQi :: Int -> (forall d. Data d => d -> u) -> WarningTxt pass -> u gmapM :: Monad m => (forall d. Data d => d -> m d) -> WarningTxt pass -> m (WarningTxt pass) gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> WarningTxt pass -> m (WarningTxt pass) gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> WarningTxt pass -> m (WarningTxt pass) | |
Generic (WarningTxt pass) # | |
Defined in GHC.Unit.Module.Warnings Associated Types type Rep (WarningTxt pass) :: Type -> Type Methods from :: WarningTxt pass -> Rep (WarningTxt pass) x to :: Rep (WarningTxt pass) x -> WarningTxt pass | |
Outputable (WarningTxt pass) # | |
Defined in GHC.Unit.Module.Warnings Methods ppr :: WarningTxt pass -> SDoc # | |
(Eq (HsToken "in"), Eq (IdP pass)) => Eq (WarningTxt pass) # | |
Defined in GHC.Unit.Module.Warnings Methods (==) :: WarningTxt pass -> WarningTxt pass -> Bool # (/=) :: WarningTxt pass -> WarningTxt pass -> Bool # | |
type Rep (WarningTxt pass) # | |
Defined in GHC.Unit.Module.Warnings type Rep (WarningTxt pass) = D1 ('MetaData "WarningTxt" "GHC.Unit.Module.Warnings" "ghc-lib-parser-9.8.1.20231009-9t39cZJXFk0KTfEG3WLPuF" 'False) (C1 ('MetaCons "WarningTxt" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (Located InWarningCategory))) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Located SourceText)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Located (WithHsDocIdentifiers StringLiteral pass)]))) :+: C1 ('MetaCons "DeprecatedTxt" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Located SourceText)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Located (WithHsDocIdentifiers StringLiteral pass)]))) |
type DeclWarnOccNames pass = [(OccName, WarningTxt pass)] #
Deprecated declarations
type ExportWarnNames pass = [(Name, WarningTxt pass)] #
Names that are deprecated as exports
warningTxtCategory :: WarningTxt pass -> WarningCategory #
To which warning category does this WARNING or DEPRECATED pragma belong? See Note [Warning categories].
warningTxtMessage :: WarningTxt p -> [Located (WithHsDocIdentifiers StringLiteral p)] #
The message that the WarningTxt was specified to output
warningTxtSame :: WarningTxt p1 -> WarningTxt p2 -> Bool #
True if the 2 WarningTxts have the same category and messages
pprWarningTxtForMsg :: WarningTxt p -> SDoc #
mkIfaceDeclWarnCache :: Warnings p -> OccName -> Maybe (WarningTxt p) #
Constructs the cache for the mi_decl_warn_fn
field of a ModIface
mkIfaceExportWarnCache :: Warnings p -> Name -> Maybe (WarningTxt p) #
Constructs the cache for the mi_export_warn_fn
field of a ModIface
emptyIfaceWarnCache :: name -> Maybe (WarningTxt p) #
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 |