ghc-lib-parser-9.8.2.20240223: The GHC API, decoupled from GHC versions
Safe HaskellSafe-Inferred
LanguageHaskell2010

GHC.Unit.Module.Warnings

Description

Warnings for a module

Synopsis

Documentation

newtype WarningCategory Source #

Instances

Instances details
Data WarningCategory Source # 
Instance details

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 Source # 
Instance details

Defined in GHC.Unit.Module.Warnings

NFData WarningCategory Source # 
Instance details

Defined in GHC.Unit.Module.Warnings

Methods

rnf :: WarningCategory -> () #

Uniquable WarningCategory Source # 
Instance details

Defined in GHC.Unit.Module.Warnings

Binary WarningCategory Source # 
Instance details

Defined in GHC.Unit.Module.Warnings

Outputable WarningCategory Source # 
Instance details

Defined in GHC.Unit.Module.Warnings

Eq WarningCategory Source # 
Instance details

Defined in GHC.Unit.Module.Warnings

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 Source #

Instances

Instances details
Data InWarningCategory Source # 
Instance details

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 Source # 
Instance details

Defined in GHC.Unit.Module.Warnings

Eq InWarningCategory Source # 
Instance details

Defined in GHC.Unit.Module.Warnings

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.

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.

data Warnings pass Source #

Warning information from a module

Constructors

WarnSome 

Fields

WarnAll (WarningTxt pass)

Whole module deprecated

Instances

Instances details
Eq (IdP pass) => Eq (Warnings pass) Source # 
Instance details

Defined in GHC.Unit.Module.Warnings

Methods

(==) :: Warnings pass -> Warnings pass -> Bool #

(/=) :: Warnings pass -> Warnings pass -> Bool #

data WarningTxt pass Source #

Warning Text

reason/explanation from a WARNING or DEPRECATED pragma

Constructors

WarningTxt 

Fields

DeprecatedTxt (Located SourceText) [Located (WithHsDocIdentifiers StringLiteral pass)] 

Instances

Instances details
(Data pass, Data (IdP pass)) => Data (WarningTxt pass) Source # 
Instance details

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) Source # 
Instance details

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) Source # 
Instance details

Defined in GHC.Unit.Module.Warnings

Methods

ppr :: WarningTxt pass -> SDoc Source #

(Eq (HsToken "in"), Eq (IdP pass)) => Eq (WarningTxt pass) Source # 
Instance details

Defined in GHC.Unit.Module.Warnings

Methods

(==) :: WarningTxt pass -> WarningTxt pass -> Bool #

(/=) :: WarningTxt pass -> WarningTxt pass -> Bool #

type Rep (WarningTxt pass) Source # 
Instance details

Defined in GHC.Unit.Module.Warnings

type DeclWarnOccNames pass = [(OccName, WarningTxt pass)] Source #

Deprecated declarations

type ExportWarnNames pass = [(Name, WarningTxt pass)] Source #

Names that are deprecated as exports

warningTxtCategory :: WarningTxt pass -> WarningCategory Source #

To which warning category does this WARNING or DEPRECATED pragma belong? See Note [Warning categories].

warningTxtMessage :: WarningTxt p -> [Located (WithHsDocIdentifiers StringLiteral p)] Source #

The message that the WarningTxt was specified to output

warningTxtSame :: WarningTxt p1 -> WarningTxt p2 -> Bool Source #

True if the 2 WarningTxts have the same category and messages

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

insertWarnDecls Source #

Arguments

:: Warnings p

Existing warnings

-> [(OccName, WarningTxt p)]

New declaration deprecations

-> Warnings p

Updated warnings

insertWarnExports Source #

Arguments

:: Warnings p

Existing warnings

-> [(Name, WarningTxt p)]

New export deprecations

-> Warnings p

Updated warnings