Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Synopsis
- checkDupRdrNames :: [LocatedN RdrName] -> RnM ()
- checkDupRdrNamesN :: [LocatedN RdrName] -> RnM ()
- checkShadowedRdrNames :: [LocatedN RdrName] -> RnM ()
- checkDupNames :: [Name] -> RnM ()
- checkDupAndShadowedNames :: (GlobalRdrEnv, LocalRdrEnv) -> [Name] -> RnM ()
- dupNamesErr :: Outputable n => (n -> SrcSpan) -> NonEmpty n -> 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 ()
- mkFieldEnv :: GlobalRdrEnv -> NameEnv (FieldLabelString, Parent)
- badQualBndrErr :: RdrName -> TcRnMessage
- typeAppErr :: String -> 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
- genAppType :: HsExpr GhcRn -> HsType (NoGhcTc GhcRn) -> 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)
- addNameClashErrRn :: RdrName -> NonEmpty GlobalRdrElt -> RnM ()
- checkInferredVars :: HsDocContext -> Maybe SDoc -> LHsSigType GhcPs -> RnM ()
- noNestedForallsContextsErr :: SDoc -> LHsType GhcRn -> Maybe (SrcSpan, TcRnMessage)
- addNoNestedForallsContextsErr :: HsDocContext -> SDoc -> LHsType GhcRn -> RnM ()
Documentation
checkDupNames :: [Name] -> RnM () Source #
checkDupAndShadowedNames :: (GlobalRdrEnv, LocalRdrEnv) -> [Name] -> RnM () Source #
dupNamesErr :: Outputable n => (n -> SrcSpan) -> NonEmpty n -> 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
mkFieldEnv :: GlobalRdrEnv -> NameEnv (FieldLabelString, Parent) Source #
Make a map from selector names to field labels and parent tycon names, to be used when reporting unused record fields.
badQualBndrErr :: RdrName -> TcRnMessage Source #
typeAppErr :: String -> 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 #
:: HsDocContext | |
-> Maybe SDoc | The error msg if the signature is not allowed to contain manually written inferred variables. |
-> LHsSigType GhcPs | |
-> RnM () |
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 :: SDoc -> 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 -> SDoc -> LHsType GhcRn -> RnM () Source #
A common way to invoke noNestedForallsContextsErr
.