Safe Haskell | None |
---|---|
Language | GHC2021 |
Synopsis
- checkDupRdrNames :: [LocatedN RdrName] -> RnM ()
- checkShadowedRdrNames :: [LocatedN RdrName] -> RnM ()
- checkDupNames :: [Name] -> RnM ()
- checkDupAndShadowedNames :: (GlobalRdrEnv, LocalRdrEnv) -> [Name] -> RnM ()
- dupNamesErr :: NonEmpty SrcSpan -> NonEmpty RdrName -> RnM ()
- checkTupSize :: Int -> TcM ()
- checkCTupSize :: Int -> TcM ()
- addFvRn :: FreeVars -> RnM (thing, FreeVars) -> RnM (thing, FreeVars)
- mapFvRn :: Traversable f => (a -> RnM (b, FreeVars)) -> f a -> RnM (f b, FreeVars)
- mapMaybeFvRn :: (a -> RnM (b, FreeVars)) -> Maybe a -> RnM (Maybe b, FreeVars)
- warnUnusedMatches :: [Name] -> FreeVars -> RnM ()
- warnUnusedTypePatterns :: [Name] -> FreeVars -> RnM ()
- warnUnusedTopBinds :: [GlobalRdrElt] -> RnM ()
- warnUnusedLocalBinds :: [Name] -> FreeVars -> RnM ()
- data DeprecationWarnings
- warnIfDeprecated :: DeprecationWarnings -> [GlobalRdrElt] -> RnM ()
- checkUnusedRecordWildcard :: SrcSpan -> FreeVars -> Maybe [ImplicitFieldBinders] -> RnM ()
- badQualBndrErr :: RdrName -> TcRnMessage
- typeAppErr :: TypeOrKind -> LHsType GhcPs -> TcRnMessage
- badFieldConErr :: Name -> FieldLabelString -> TcRnMessage
- wrapGenSpan :: HasAnnotation an => a -> GenLocated an a
- genHsVar :: Name -> HsExpr GhcRn
- genLHsVar :: Name -> LHsExpr GhcRn
- genHsApp :: HsExpr GhcRn -> LHsExpr GhcRn -> HsExpr GhcRn
- genHsApps :: Name -> [LHsExpr GhcRn] -> HsExpr GhcRn
- genHsApps' :: LocatedN Name -> [LHsExpr GhcRn] -> HsExpr GhcRn
- genHsExpApps :: HsExpr GhcRn -> [LHsExpr GhcRn] -> HsExpr GhcRn
- genLHsApp :: HsExpr GhcRn -> LHsExpr GhcRn -> LHsExpr GhcRn
- genAppType :: HsExpr GhcRn -> HsType (NoGhcTc GhcRn) -> HsExpr GhcRn
- genLHsLit :: NoAnn an => HsLit GhcRn -> LocatedAn an (HsExpr GhcRn)
- genHsIntegralLit :: NoAnn an => IntegralLit -> LocatedAn an (HsExpr GhcRn)
- genHsTyLit :: FastString -> HsType GhcRn
- genSimpleConPat :: Name -> [LPat GhcRn] -> LPat GhcRn
- genVarPat :: Name -> LPat GhcRn
- genWildPat :: LPat GhcRn
- genSimpleFunBind :: Name -> [LPat GhcRn] -> LHsExpr GhcRn -> LHsBind GhcRn
- genFunBind :: LocatedN Name -> [LMatch GhcRn (LHsExpr GhcRn)] -> HsBind GhcRn
- genHsLamDoExp :: forall (p :: Pass). (IsPass p, XMG (GhcPass p) (LHsExpr (GhcPass p)) ~ Origin) => HsDoFlavour -> [LPat (GhcPass p)] -> LHsExpr (GhcPass p) -> LHsExpr (GhcPass p)
- genHsCaseAltDoExp :: forall (p :: Pass) body. (Anno (GRHS (GhcPass p) (LocatedA (body (GhcPass p)))) ~ EpAnnCO, Anno (Match (GhcPass p) (LocatedA (body (GhcPass p)))) ~ SrcSpanAnnA) => HsDoFlavour -> LPat (GhcPass p) -> LocatedA (body (GhcPass p)) -> LMatch (GhcPass p) (LocatedA (body (GhcPass p)))
- genSimpleMatch :: forall (p :: Pass) body. (Anno (Match (GhcPass p) (LocatedA (body (GhcPass p)))) ~ SrcSpanAnnA, Anno (GRHS (GhcPass p) (LocatedA (body (GhcPass p)))) ~ EpAnnCO) => HsMatchContext (LIdP (NoGhcTc (GhcPass p))) -> [LPat (GhcPass p)] -> LocatedA (body (GhcPass p)) -> LMatch (GhcPass p) (LocatedA (body (GhcPass p)))
- genHsLet :: HsLocalBindsLR GhcRn GhcRn -> LHsExpr GhcRn -> HsExpr GhcRn
- mkRnSyntaxExpr :: Name -> SyntaxExprRn
- newLocalBndrRn :: LocatedN RdrName -> RnM Name
- newLocalBndrsRn :: [LocatedN RdrName] -> RnM [Name]
- bindLocalNames :: [Name] -> RnM a -> RnM a
- bindLocalNamesFV :: [Name] -> RnM (a, FreeVars) -> RnM (a, FreeVars)
- delLocalNames :: [Name] -> RnM a -> RnM a
- addNameClashErrRn :: RdrName -> NonEmpty GlobalRdrElt -> RnM ()
- mkNameClashErr :: GlobalRdrEnv -> RdrName -> NonEmpty GlobalRdrElt -> TcRnMessage
- checkInferredVars :: HsDocContext -> LHsSigType GhcPs -> RnM ()
- noNestedForallsContextsErr :: NestedForallsContextsIn -> LHsType GhcRn -> Maybe (SrcSpan, TcRnMessage)
- addNoNestedForallsContextsErr :: HsDocContext -> NestedForallsContextsIn -> LHsType GhcRn -> RnM ()
Documentation
checkDupNames :: [Name] -> RnM () Source #
checkDupAndShadowedNames :: (GlobalRdrEnv, LocalRdrEnv) -> [Name] -> RnM () Source #
checkTupSize :: Int -> TcM () Source #
Ensure that a boxed or unboxed tuple has arity no larger than
mAX_TUPLE_SIZE
.
checkCTupSize :: Int -> TcM () Source #
Ensure that a constraint tuple has arity no larger than mAX_CTUPLE_SIZE
.
warnUnusedTopBinds :: [GlobalRdrElt] -> RnM () Source #
data DeprecationWarnings Source #
Whether to report deprecation warnings when registering a used GRE
There is no option to only emit declaration warnings since everywhere we emit the declaration warnings we also emit export warnings (See Note [Handling of deprecations] for details)
warnIfDeprecated :: DeprecationWarnings -> [GlobalRdrElt] -> RnM () Source #
checkUnusedRecordWildcard :: SrcSpan -> FreeVars -> Maybe [ImplicitFieldBinders] -> RnM () Source #
Checks to see if we need to warn for -Wunused-record-wildcards or -Wredundant-record-wildcards
badQualBndrErr :: RdrName -> TcRnMessage Source #
typeAppErr :: TypeOrKind -> LHsType GhcPs -> TcRnMessage Source #
badFieldConErr :: Name -> FieldLabelString -> TcRnMessage Source #
wrapGenSpan :: HasAnnotation an => a -> GenLocated an a Source #
genHsApps' :: LocatedN Name -> [LHsExpr GhcRn] -> HsExpr GhcRn Source #
Keeps the span given to the Name
for the application head only
genHsIntegralLit :: NoAnn an => IntegralLit -> LocatedAn an (HsExpr GhcRn) Source #
genHsTyLit :: FastString -> HsType GhcRn Source #
genWildPat :: LPat GhcRn Source #
genHsLamDoExp :: forall (p :: Pass). (IsPass p, XMG (GhcPass p) (LHsExpr (GhcPass p)) ~ Origin) => HsDoFlavour -> [LPat (GhcPass p)] -> LHsExpr (GhcPass p) -> LHsExpr (GhcPass p) Source #
genHsCaseAltDoExp :: forall (p :: Pass) body. (Anno (GRHS (GhcPass p) (LocatedA (body (GhcPass p)))) ~ EpAnnCO, Anno (Match (GhcPass p) (LocatedA (body (GhcPass p)))) ~ SrcSpanAnnA) => HsDoFlavour -> LPat (GhcPass p) -> LocatedA (body (GhcPass p)) -> LMatch (GhcPass p) (LocatedA (body (GhcPass p))) Source #
genSimpleMatch :: forall (p :: Pass) body. (Anno (Match (GhcPass p) (LocatedA (body (GhcPass p)))) ~ SrcSpanAnnA, Anno (GRHS (GhcPass p) (LocatedA (body (GhcPass p)))) ~ EpAnnCO) => HsMatchContext (LIdP (NoGhcTc (GhcPass p))) -> [LPat (GhcPass p)] -> LocatedA (body (GhcPass p)) -> LMatch (GhcPass p) (LocatedA (body (GhcPass p))) Source #
mkRnSyntaxExpr :: Name -> SyntaxExprRn Source #
Make a SyntaxExpr
from a Name
(the "rn" is because this is used in the
renamer).
addNameClashErrRn :: RdrName -> NonEmpty GlobalRdrElt -> RnM () Source #
mkNameClashErr :: GlobalRdrEnv -> RdrName -> NonEmpty GlobalRdrElt -> TcRnMessage Source #
checkInferredVars :: HsDocContext -> LHsSigType GhcPs -> RnM () Source #
Throw an error message if a user attempts to quantify an inferred type
variable in a place where specificity cannot be observed. For example,
forall {a}. [a] -> [a]
would be rejected to the inferred type variable
{a}
, but forall a. [a] -> [a]
would be accepted.
See Note [Unobservably inferred type variables]
.
noNestedForallsContextsErr :: NestedForallsContextsIn -> LHsType GhcRn -> Maybe (SrcSpan, TcRnMessage) Source #
Examines a non-outermost type for forall
s or contexts, which are assumed
to be nested. For example, in the following declaration:
instance forall a. forall b. C (Either a b)
The outermost forall a
is fine, but the nested forall b
is not. We
invoke noNestedForallsContextsErr
on the type forall b. C (Either a b)
to catch the nested forall
and create a suitable error message.
noNestedForallsContextsErr
returns
if such a Just
err_msgforall
or
context is found, and returns Nothing
otherwise.
This is currently used in the following places:
- In GADT constructor types (in
rnConDecl
). SeeNote [GADT abstract syntax] (Wrinkle: No nested foralls or contexts)
in GHC.Hs.Type. - In instance declaration types (in
rnClsIntDecl
andrnSrcDerivDecl
in GHC.Rename.Module andrenameSig
in GHC.Rename.Bind). SeeNote [No nested foralls or contexts in instance types]
in GHC.Hs.Type.
addNoNestedForallsContextsErr :: HsDocContext -> NestedForallsContextsIn -> LHsType GhcRn -> RnM () Source #
A common way to invoke noNestedForallsContextsErr
.