Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Synopsis
- rnHsType :: HsDocContext -> HsType GhcPs -> RnM (HsType GhcRn, FreeVars)
- rnLHsType :: HsDocContext -> LHsType GhcPs -> RnM (LHsType GhcRn, FreeVars)
- rnLHsTypes :: HsDocContext -> [LHsType GhcPs] -> RnM ([LHsType GhcRn], FreeVars)
- rnContext :: HsDocContext -> Maybe (LHsContext GhcPs) -> RnM (Maybe (LHsContext GhcRn), FreeVars)
- rnHsKind :: HsDocContext -> HsKind GhcPs -> RnM (HsKind GhcRn, FreeVars)
- rnLHsKind :: HsDocContext -> LHsKind GhcPs -> RnM (LHsKind GhcRn, FreeVars)
- rnLHsTypeArgs :: HsDocContext -> [LHsTypeArg GhcPs] -> RnM ([LHsTypeArg GhcRn], FreeVars)
- rnHsSigType :: HsDocContext -> TypeOrKind -> LHsSigType GhcPs -> RnM (LHsSigType GhcRn, FreeVars)
- rnHsWcType :: HsDocContext -> LHsWcType GhcPs -> RnM (LHsWcType GhcRn, FreeVars)
- rnHsPatSigTypeBindingVars :: HsDocContext -> HsPatSigType GhcPs -> (HsPatSigType GhcRn -> RnM (r, FreeVars)) -> RnM (r, FreeVars)
- data HsPatSigTypeScoping
- rnHsSigWcType :: HsDocContext -> LHsSigWcType GhcPs -> RnM (LHsSigWcType GhcRn, FreeVars)
- rnHsPatSigType :: HsPatSigTypeScoping -> HsDocContext -> HsPatSigType GhcPs -> (HsPatSigType GhcRn -> RnM (a, FreeVars)) -> RnM (a, FreeVars)
- newTyVarNameRn :: Maybe a -> LocatedN RdrName -> RnM Name
- rnConDeclFields :: HsDocContext -> [FieldLabel] -> [LConDeclField GhcPs] -> RnM ([LConDeclField GhcRn], FreeVars)
- lookupField :: FastStringEnv FieldLabel -> FieldOcc GhcPs -> FieldOcc GhcRn
- rnLTyVar :: LocatedN RdrName -> RnM (LocatedN Name)
- rnScaledLHsType :: HsDocContext -> HsScaled GhcPs (LHsType GhcPs) -> RnM (HsScaled GhcRn (LHsType GhcRn), FreeVars)
- data NegationHandling
- mkOpAppRn :: NegationHandling -> LHsExpr GhcRn -> LHsExpr GhcRn -> Fixity -> LHsExpr GhcRn -> RnM (HsExpr GhcRn)
- mkNegAppRn :: LHsExpr GhcRn -> SyntaxExpr GhcRn -> RnM (HsExpr GhcRn)
- mkOpFormRn :: LHsCmdTop GhcRn -> LHsExpr GhcRn -> Fixity -> LHsCmdTop GhcRn -> RnM (HsCmd GhcRn)
- mkConOpPatRn :: LocatedN Name -> Fixity -> LPat GhcRn -> LPat GhcRn -> RnM (Pat GhcRn)
- checkPrecMatch :: Name -> MatchGroup GhcRn body -> RnM ()
- checkSectionPrec :: FixityDirection -> HsExpr GhcPs -> LHsExpr GhcRn -> LHsExpr GhcRn -> RnM ()
- bindHsOuterTyVarBndrs :: OutputableBndrFlag flag 'Renamed => HsDocContext -> Maybe assoc -> FreeKiTyVars -> HsOuterTyVarBndrs flag GhcPs -> (HsOuterTyVarBndrs flag GhcRn -> RnM (a, FreeVars)) -> RnM (a, FreeVars)
- bindHsForAllTelescope :: HsDocContext -> HsForAllTelescope GhcPs -> (HsForAllTelescope GhcRn -> RnM (a, FreeVars)) -> RnM (a, FreeVars)
- bindLHsTyVarBndr :: HsDocContext -> Maybe a -> LHsTyVarBndr flag GhcPs -> (LHsTyVarBndr flag GhcRn -> RnM (b, FreeVars)) -> RnM (b, FreeVars)
- bindLHsTyVarBndrs :: OutputableBndrFlag flag 'Renamed => HsDocContext -> WarnUnusedForalls -> Maybe a -> [LHsTyVarBndr flag GhcPs] -> ([LHsTyVarBndr flag GhcRn] -> RnM (b, FreeVars)) -> RnM (b, FreeVars)
- data WarnUnusedForalls
- rnImplicitTvOccs :: Maybe assoc -> FreeKiTyVars -> ([Name] -> RnM (a, FreeVars)) -> RnM (a, FreeVars)
- bindSigTyVarsFV :: [Name] -> RnM (a, FreeVars) -> RnM (a, FreeVars)
- bindHsQTyVars :: forall a b. HsDocContext -> Maybe a -> FreeKiTyVars -> LHsQTyVars GhcPs -> (LHsQTyVars GhcRn -> Bool -> RnM (b, FreeVars)) -> RnM (b, FreeVars)
- type FreeKiTyVars = [LocatedN RdrName]
- extractHsTyRdrTyVars :: LHsType GhcPs -> FreeKiTyVars
- extractHsTyRdrTyVarsKindVars :: LHsType GhcPs -> FreeKiTyVars
- extractHsTysRdrTyVars :: [LHsType GhcPs] -> FreeKiTyVars -> FreeKiTyVars
- extractRdrKindSigVars :: LFamilyResultSig GhcPs -> FreeKiTyVars
- extractConDeclGADTDetailsTyVars :: HsConDeclGADTDetails GhcPs -> FreeKiTyVars -> FreeKiTyVars
- extractDataDefnKindVars :: HsDataDefn GhcPs -> FreeKiTyVars
- extractHsOuterTvBndrs :: HsOuterTyVarBndrs flag GhcPs -> FreeKiTyVars -> FreeKiTyVars
- extractHsTyArgRdrKiTyVars :: [LHsTypeArg GhcPs] -> FreeKiTyVars
- nubL :: Eq a => [GenLocated l a] -> [GenLocated l a]
- nubN :: Eq a => [LocatedN a] -> [LocatedN a]
Documentation
rnLHsTypes :: HsDocContext -> [LHsType GhcPs] -> RnM ([LHsType GhcRn], FreeVars) Source #
rnContext :: HsDocContext -> Maybe (LHsContext GhcPs) -> RnM (Maybe (LHsContext GhcRn), FreeVars) Source #
rnLHsTypeArgs :: HsDocContext -> [LHsTypeArg GhcPs] -> RnM ([LHsTypeArg GhcRn], FreeVars) Source #
rnHsSigType :: HsDocContext -> TypeOrKind -> LHsSigType GhcPs -> RnM (LHsSigType GhcRn, FreeVars) Source #
rnHsWcType :: HsDocContext -> LHsWcType GhcPs -> RnM (LHsWcType GhcRn, FreeVars) Source #
rnHsPatSigTypeBindingVars :: HsDocContext -> HsPatSigType GhcPs -> (HsPatSigType GhcRn -> RnM (r, FreeVars)) -> RnM (r, FreeVars) Source #
data HsPatSigTypeScoping Source #
AlwaysBind | Always bind any free tyvars of the given type, regardless of whether we have a forall at the top. For pattern type sigs, we do want to bring those type variables into scope, even if there's a forall at the top which usually stops that happening, e.g: \ (x :: forall a. a -> b) -> e Here we do bring RULES can also use {-# RULES \"f\" forall (x :: forall a. a -> b). f x = ... b ... #-} This only applies to RULES that do not explicitly bind their type
variables. If a RULE explicitly quantifies its type variables, then
|
NeverBind | Never bind any free tyvars. This is used for RULES that have both explicit type and term variable binders, e.g.: {-# RULES \"const\" forall a. forall (x :: a) y. const x y = x #-} The presence of the type variable binder |
rnHsSigWcType :: HsDocContext -> LHsSigWcType GhcPs -> RnM (LHsSigWcType GhcRn, FreeVars) Source #
rnHsPatSigType :: HsPatSigTypeScoping -> HsDocContext -> HsPatSigType GhcPs -> (HsPatSigType GhcRn -> RnM (a, FreeVars)) -> RnM (a, FreeVars) Source #
rnConDeclFields :: HsDocContext -> [FieldLabel] -> [LConDeclField GhcPs] -> RnM ([LConDeclField GhcRn], FreeVars) Source #
lookupField :: FastStringEnv FieldLabel -> FieldOcc GhcPs -> FieldOcc GhcRn Source #
rnScaledLHsType :: HsDocContext -> HsScaled GhcPs (LHsType GhcPs) -> RnM (HsScaled GhcRn (LHsType GhcRn), FreeVars) Source #
mkOpAppRn :: NegationHandling -> LHsExpr GhcRn -> LHsExpr GhcRn -> Fixity -> LHsExpr GhcRn -> RnM (HsExpr GhcRn) Source #
mkNegAppRn :: LHsExpr GhcRn -> SyntaxExpr GhcRn -> RnM (HsExpr GhcRn) Source #
mkOpFormRn :: LHsCmdTop GhcRn -> LHsExpr GhcRn -> Fixity -> LHsCmdTop GhcRn -> RnM (HsCmd GhcRn) Source #
checkPrecMatch :: Name -> MatchGroup GhcRn body -> RnM () Source #
checkSectionPrec :: FixityDirection -> HsExpr GhcPs -> LHsExpr GhcRn -> LHsExpr GhcRn -> RnM () Source #
bindHsOuterTyVarBndrs Source #
:: OutputableBndrFlag flag 'Renamed | |
=> HsDocContext | |
-> Maybe assoc |
|
-> FreeKiTyVars | |
-> HsOuterTyVarBndrs flag GhcPs | |
-> (HsOuterTyVarBndrs flag GhcRn -> RnM (a, FreeVars)) | |
-> RnM (a, FreeVars) |
bindHsForAllTelescope :: HsDocContext -> HsForAllTelescope GhcPs -> (HsForAllTelescope GhcRn -> RnM (a, FreeVars)) -> RnM (a, FreeVars) Source #
bindLHsTyVarBndr :: HsDocContext -> Maybe a -> LHsTyVarBndr flag GhcPs -> (LHsTyVarBndr flag GhcRn -> RnM (b, FreeVars)) -> RnM (b, FreeVars) Source #
bindLHsTyVarBndrs :: OutputableBndrFlag flag 'Renamed => HsDocContext -> WarnUnusedForalls -> Maybe a -> [LHsTyVarBndr flag GhcPs] -> ([LHsTyVarBndr flag GhcRn] -> RnM (b, FreeVars)) -> RnM (b, FreeVars) Source #
data WarnUnusedForalls Source #
Should GHC warn if a quantified type variable goes unused? Usually, the
answer is "yes", but in the particular case of binding LHsQTyVars
, we
avoid emitting warnings.
See Note [Suppress -Wunused-foralls when binding LHsQTyVars]
.
Instances
Outputable WarnUnusedForalls Source # | |
Defined in GHC.Rename.HsType ppr :: WarnUnusedForalls -> SDoc Source # |
:: Maybe assoc |
|
-> FreeKiTyVars | Surface-syntax free vars that we will implicitly bind. May have duplicates, which are removed here. |
-> ([Name] -> RnM (a, FreeVars)) | |
-> RnM (a, FreeVars) |
Create new renamed type variables corresponding to source-level ones. Duplicates are permitted, but will be removed. This is intended especially for the case of handling the implicitly bound free variables of a type signature.
bindHsQTyVars :: forall a b. HsDocContext -> Maybe a -> FreeKiTyVars -> LHsQTyVars GhcPs -> (LHsQTyVars GhcRn -> Bool -> RnM (b, FreeVars)) -> RnM (b, FreeVars) Source #
type FreeKiTyVars = [LocatedN RdrName] Source #
extractHsTyRdrTyVars :: LHsType GhcPs -> FreeKiTyVars Source #
extractHsTyRdrTyVars
finds the type/kind variables
of a HsType/HsKind.
It's used when making the forall
s explicit.
See Note [Kind and type-variable binders]
extractHsTyRdrTyVarsKindVars :: LHsType GhcPs -> FreeKiTyVars Source #
Extracts the free type/kind variables from the kind signature of a HsType.
This is used to implicitly quantify over k
in type T = Nothing :: Maybe k
.
The left-to-right order of variables is preserved.
See Note [Kind and type-variable binders] and
Note [Ordering of implicit variables] and
Note [Implicit quantification in type synonyms].
extractHsTysRdrTyVars :: [LHsType GhcPs] -> FreeKiTyVars -> FreeKiTyVars Source #
Extracts free type and kind variables from types in a list. When the same name occurs multiple times in the types, all occurrences are returned.
extractConDeclGADTDetailsTyVars :: HsConDeclGADTDetails GhcPs -> FreeKiTyVars -> FreeKiTyVars Source #
Extracts free type and kind variables from an argument in a GADT
constructor, returning variable occurrences in left-to-right order.
See Note [Ordering of implicit variables]
.
extractDataDefnKindVars :: HsDataDefn GhcPs -> FreeKiTyVars Source #
Get type/kind variables mentioned in the kind signature, preserving left-to-right order:
- data T a (b :: k1) :: k2 -> k1 -> k2 -> Type -- result: [k2,k1]
- data T a (b :: k1) -- result: []
See Note [Ordering of implicit variables].
extractHsOuterTvBndrs :: HsOuterTyVarBndrs flag GhcPs -> FreeKiTyVars -> FreeKiTyVars Source #
nubL :: Eq a => [GenLocated l a] -> [GenLocated l a] Source #