ghc-9.10.1: The GHC API
Safe HaskellNone
LanguageGHC2021

GHC.Rename.Utils

Synopsis

Documentation

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.

addFvRn :: FreeVars -> RnM (thing, FreeVars) -> RnM (thing, FreeVars) Source #

mapFvRn :: Traversable f => (a -> RnM (b, FreeVars)) -> f a -> RnM (f b, FreeVars) Source #

mapMaybeFvRn :: (a -> RnM (b, FreeVars)) -> Maybe a -> RnM (Maybe b, FreeVars) 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)

checkUnusedRecordWildcard :: SrcSpan -> FreeVars -> Maybe [ImplicitFieldBinders] -> RnM () Source #

Checks to see if we need to warn for -Wunused-record-wildcards or -Wredundant-record-wildcards

wrapGenSpan :: NoAnn an => a -> LocatedAn an a Source #

genHsApps' :: LocatedN Name -> [LHsExpr GhcRn] -> HsExpr GhcRn Source #

Keeps the span given to the Name for the application head only

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 #

delLocalNames :: [Name] -> RnM a -> RnM a 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 foralls 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 Just err_msg if such a forall or context is found, and returns Nothing otherwise.

This is currently used in the following places:

  • In GADT constructor types (in rnConDecl). See Note [GADT abstract syntax] (Wrinkle: No nested foralls or contexts) in GHC.Hs.Type.
  • In instance declaration types (in rnClsIntDecl and rnSrcDerivDecl in GHC.Rename.Module and renameSig in GHC.Rename.Bind). See Note [No nested foralls or contexts in instance types] in GHC.Hs.Type.