| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
GHC.Rename.Utils
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 ()
- warnForallIdentifier :: LocatedN RdrName -> RnM ()
- checkUnusedRecordWildcard :: SrcSpan -> FreeVars -> Maybe [Name] -> RnM ()
- badQualBndrErr :: RdrName -> TcRnMessage
- typeAppErr :: TypeOrKind -> LHsType GhcPs -> TcRnMessage
- badFieldConErr :: Name -> FieldLabelString -> TcRnMessage
- wrapGenSpan :: a -> LocatedAn an a
- genHsVar :: Name -> HsExpr GhcRn
- genLHsVar :: Name -> LHsExpr GhcRn
- genHsApp :: HsExpr GhcRn -> LHsExpr GhcRn -> HsExpr GhcRn
- genHsApps :: Name -> [LHsExpr GhcRn] -> HsExpr GhcRn
- genLHsApp :: HsExpr GhcRn -> LHsExpr GhcRn -> LHsExpr GhcRn
- genAppType :: HsExpr GhcRn -> HsType (NoGhcTc GhcRn) -> HsExpr GhcRn
- genLHsLit :: HsLit GhcRn -> LocatedAn an (HsExpr GhcRn)
- genHsIntegralLit :: 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
- 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 ()
- isIrrefutableHsPatRn :: forall (p :: Pass). OutputableBndrId p => DynFlags -> LPat (GhcPass p) -> Bool
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 #
checkUnusedRecordWildcard :: SrcSpan -> FreeVars -> Maybe [Name] -> 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 :: a -> LocatedAn an a Source #
genHsIntegralLit :: IntegralLit -> LocatedAn an (HsExpr GhcRn) Source #
genHsTyLit :: FastString -> HsType GhcRn Source #
genWildPat :: LPat GhcRn Source #
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 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_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 rnClsIntDeclandrnSrcDerivDeclin GHC.Rename.Module andrenameSigin 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.
isIrrefutableHsPatRn :: forall (p :: Pass). OutputableBndrId p => DynFlags -> LPat (GhcPass p) -> Bool Source #