Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
GHC.Unit.Module.Warnings
Description
Warnings for a module
Synopsis
- data Warnings pass
- = NoWarnings
- | WarnAll (WarningTxt pass)
- | WarnSome [(OccName, WarningTxt pass)]
- data WarningTxt pass
- = WarningTxt (Located SourceText) [Located (WithHsDocIdentifiers StringLiteral pass)]
- | DeprecatedTxt (Located SourceText) [Located (WithHsDocIdentifiers StringLiteral pass)]
- pprWarningTxtForMsg :: WarningTxt p -> SDoc
- mkIfaceWarnCache :: Warnings p -> OccName -> Maybe (WarningTxt p)
- emptyIfaceWarnCache :: OccName -> Maybe (WarningTxt p)
- plusWarns :: Warnings p -> Warnings p -> Warnings p
Documentation
Warning information for a module
Constructors
NoWarnings | Nothing deprecated |
WarnAll (WarningTxt pass) | Whole module deprecated |
WarnSome [(OccName, WarningTxt pass)] | Some specific things deprecated |
data WarningTxt pass Source #
Warning Text
reason/explanation from a WARNING or DEPRECATED pragma
Constructors
WarningTxt (Located SourceText) [Located (WithHsDocIdentifiers StringLiteral pass)] | |
DeprecatedTxt (Located SourceText) [Located (WithHsDocIdentifiers StringLiteral pass)] |
Instances
(Data pass, Data (IdP pass)) => Data (WarningTxt pass) Source # | |
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 # | |
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 # | |
Binary (WarningTxt GhcRn) Source # | |
Defined in GHC.Unit.Module.Warnings | |
Outputable (WarningTxt pass) Source # | |
Defined in GHC.Unit.Module.Warnings Methods ppr :: WarningTxt pass -> SDoc Source # | |
Eq (IdP pass) => Eq (WarningTxt pass) Source # | |
Defined in GHC.Unit.Module.Warnings Methods (==) :: WarningTxt pass -> WarningTxt pass -> Bool # (/=) :: WarningTxt pass -> WarningTxt pass -> Bool # | |
type Rep (WarningTxt pass) Source # | |
Defined in GHC.Unit.Module.Warnings type Rep (WarningTxt pass) = D1 ('MetaData "WarningTxt" "GHC.Unit.Module.Warnings" "ghc-lib-parser-9.6.2.20230523-71LAxQKBNbw8ebo0dFJz0z" 'False) (C1 ('MetaCons "WarningTxt" '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)])) :+: 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)]))) |
pprWarningTxtForMsg :: WarningTxt p -> SDoc Source #
mkIfaceWarnCache :: Warnings p -> OccName -> Maybe (WarningTxt p) Source #
Constructs the cache for the mi_warn_fn
field of a ModIface
emptyIfaceWarnCache :: OccName -> Maybe (WarningTxt p) Source #