ghc-lib-0.20210331: The GHC API, decoupled from GHC versions
Safe HaskellNone
LanguageHaskell2010

GHC.Rename.HsType

Synopsis

Documentation

rnHsType :: HsDocContext -> HsType GhcPs -> RnM (HsType GhcRn, FreeVars) Source #

rnLHsType :: HsDocContext -> LHsType GhcPs -> RnM (LHsType GhcRn, FreeVars) Source #

rnLHsTypes :: HsDocContext -> [LHsType GhcPs] -> RnM ([LHsType GhcRn], FreeVars) Source #

rnContext :: HsDocContext -> Maybe (LHsContext GhcPs) -> RnM (Maybe (LHsContext GhcRn), FreeVars) Source #

rnHsKind :: HsDocContext -> HsKind GhcPs -> RnM (HsKind GhcRn, FreeVars) Source #

rnLHsKind :: HsDocContext -> LHsKind GhcPs -> RnM (LHsKind 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 #

Constructors

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 b into scope.

RULES can also use AlwaysBind, such as in the following example:

{-# 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 is used instead. See also Note [Pattern signature binders and scoping] in GHC.Hs.Type.

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 forall a. implies that the free variables in the types of the term variable binders x and y are not bound. In the example above, there are no such free variables, but if the user had written (y :: b) instead of y in the term variable binders, then b would be rejected for being out of scope. See also Note [Pattern signature binders and scoping] in GHC.Hs.Type.

rnHsSigWcType :: HsDocContext -> LHsSigWcType GhcPs -> RnM (LHsSigWcType GhcRn, FreeVars) Source #

rnHsPatSigType :: HsPatSigTypeScoping -> HsDocContext -> HsPatSigType GhcPs -> (HsPatSigType GhcRn -> RnM (a, FreeVars)) -> RnM (a, FreeVars) Source #

newTyVarNameRn :: Maybe a -> LocatedN RdrName -> RnM Name Source #

rnConDeclFields :: HsDocContext -> [FieldLabel] -> [LConDeclField GhcPs] -> RnM ([LConDeclField GhcRn], FreeVars) Source #

lookupField :: FastStringEnv FieldLabel -> FieldOcc GhcPs -> FieldOcc GhcRn Source #

rnLTyVar :: LocatedN RdrName -> RnM (LocatedN Name) Source #

rnScaledLHsType :: HsDocContext -> HsScaled GhcPs (LHsType GhcPs) -> RnM (HsScaled GhcRn (LHsType GhcRn), FreeVars) Source #

mkOpAppRn :: 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 #

mkConOpPatRn :: LocatedN Name -> Fixity -> LPat GhcRn -> LPat GhcRn -> RnM (Pat GhcRn) Source #

checkPrecMatch :: Name -> MatchGroup GhcRn body -> RnM () Source #

checkSectionPrec :: FixityDirection -> HsExpr GhcPs -> LHsExpr GhcRn -> LHsExpr GhcRn -> RnM () Source #

bindHsOuterTyVarBndrs Source #

Arguments

:: OutputableBndrFlag flag 'Renamed 
=> HsDocContext 
-> Maybe assoc

Just _ => an associated type decl

-> 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

Instances details
Outputable WarnUnusedForalls Source # 
Instance details

Defined in GHC.Rename.HsType

Methods

ppr :: WarnUnusedForalls -> SDoc

rnImplicitTvOccs Source #

Arguments

:: Maybe assoc

Just _ => an associated type decl

-> 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.

bindSigTyVarsFV :: [Name] -> RnM (a, FreeVars) -> RnM (a, FreeVars) Source #

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 foralls 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.

extractRdrKindSigVars :: LFamilyResultSig GhcPs -> FreeKiTyVars Source #

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 #

nubN :: Eq a => [LocatedN a] -> [LocatedN a] Source #