Safe Haskell | None |
---|---|
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 -> LHsContext GhcPs -> RnM (LHsContext GhcRn, FreeVars)
- rnHsKind :: HsDocContext -> HsKind GhcPs -> RnM (HsKind GhcRn, FreeVars)
- rnLHsKind :: HsDocContext -> LHsKind GhcPs -> RnM (LHsKind GhcRn, FreeVars)
- rnHsSigType :: HsDocContext -> LHsSigType GhcPs -> RnM (LHsSigType GhcRn, FreeVars)
- rnHsWcType :: HsDocContext -> LHsWcType GhcPs -> RnM (LHsWcType GhcRn, FreeVars)
- rnHsSigWcType :: HsDocContext -> LHsSigWcType GhcPs -> RnM (LHsSigWcType GhcRn, FreeVars)
- rnHsSigWcTypeScoped :: HsDocContext -> LHsSigWcType GhcPs -> (LHsSigWcType GhcRn -> RnM (a, FreeVars)) -> RnM (a, FreeVars)
- rnLHsInstType :: SDoc -> LHsSigType GhcPs -> RnM (LHsSigType GhcRn, FreeVars)
- newTyVarNameRn :: Maybe a -> Located RdrName -> RnM Name
- collectAnonWildCards :: LHsType GhcRn -> [Name]
- rnConDeclFields :: HsDocContext -> [FieldLabel] -> [LConDeclField GhcPs] -> RnM ([LConDeclField GhcRn], FreeVars)
- rnLTyVar :: Located RdrName -> RnM (Located Name)
- mkOpAppRn :: LHsExpr GhcRn -> LHsExpr GhcRn -> Fixity -> LHsExpr GhcRn -> RnM (HsExpr GhcRn)
- mkNegAppRn :: LHsExpr (GhcPass id) -> SyntaxExpr (GhcPass id) -> RnM (HsExpr (GhcPass id))
- mkOpFormRn :: LHsCmdTop GhcRn -> LHsExpr GhcRn -> Fixity -> LHsCmdTop GhcRn -> RnM (HsCmd GhcRn)
- mkConOpPatRn :: Located Name -> Fixity -> LPat GhcRn -> LPat GhcRn -> RnM (Pat GhcRn)
- checkPrecMatch :: Name -> MatchGroup GhcRn body -> RnM ()
- checkSectionPrec :: FixityDirection -> HsExpr GhcPs -> LHsExpr GhcRn -> LHsExpr GhcRn -> RnM ()
- bindLHsTyVarBndr :: HsDocContext -> Maybe a -> LHsTyVarBndr GhcPs -> (LHsTyVarBndr GhcRn -> RnM (b, FreeVars)) -> RnM (b, FreeVars)
- bindLHsTyVarBndrs :: HsDocContext -> Maybe SDoc -> Maybe a -> [LHsTyVarBndr GhcPs] -> ([LHsTyVarBndr GhcRn] -> RnM (b, FreeVars)) -> RnM (b, FreeVars)
- rnImplicitBndrs :: Bool -> FreeKiTyVarsWithDups -> ([Name] -> RnM (a, FreeVars)) -> RnM (a, FreeVars)
- bindSigTyVarsFV :: [Name] -> RnM (a, FreeVars) -> RnM (a, FreeVars)
- bindHsQTyVars :: forall a b. HsDocContext -> Maybe SDoc -> Maybe a -> [Located RdrName] -> LHsQTyVars GhcPs -> (LHsQTyVars GhcRn -> Bool -> RnM (b, FreeVars)) -> RnM (b, FreeVars)
- bindLRdrNames :: [Located RdrName] -> ([Name] -> RnM (a, FreeVars)) -> RnM (a, FreeVars)
- extractFilteredRdrTyVars :: LHsType GhcPs -> RnM FreeKiTyVarsNoDups
- extractFilteredRdrTyVarsDups :: LHsType GhcPs -> RnM FreeKiTyVarsWithDups
- extractHsTyRdrTyVars :: LHsType GhcPs -> RnM FreeKiTyVarsNoDups
- extractHsTyRdrTyVarsKindVars :: LHsType GhcPs -> RnM [Located RdrName]
- extractHsTyRdrTyVarsDups :: LHsType GhcPs -> RnM FreeKiTyVarsWithDups
- extractHsTysRdrTyVars :: [LHsType GhcPs] -> RnM FreeKiTyVarsNoDups
- extractHsTysRdrTyVarsDups :: [LHsType GhcPs] -> RnM FreeKiTyVarsWithDups
- rmDupsInRdrTyVars :: FreeKiTyVarsWithDups -> FreeKiTyVarsNoDups
- extractRdrKindSigVars :: LFamilyResultSig GhcPs -> RnM [Located RdrName]
- extractDataDefnKindVars :: HsDataDefn GhcPs -> RnM [Located RdrName]
- extractHsTvBndrs :: [LHsTyVarBndr GhcPs] -> FreeKiTyVarsWithDups -> RnM FreeKiTyVarsWithDups
- freeKiTyVarsAllVars :: FreeKiTyVars -> [Located RdrName]
- freeKiTyVarsKindVars :: FreeKiTyVars -> [Located RdrName]
- freeKiTyVarsTypeVars :: FreeKiTyVars -> [Located RdrName]
- elemRdr :: Located RdrName -> [Located RdrName] -> Bool
Documentation
rnLHsTypes :: HsDocContext -> [LHsType GhcPs] -> RnM ([LHsType GhcRn], FreeVars) Source #
rnContext :: HsDocContext -> LHsContext GhcPs -> RnM (LHsContext GhcRn, FreeVars) Source #
rnHsSigType :: HsDocContext -> LHsSigType GhcPs -> RnM (LHsSigType GhcRn, FreeVars) Source #
rnHsWcType :: HsDocContext -> LHsWcType GhcPs -> RnM (LHsWcType GhcRn, FreeVars) Source #
rnHsSigWcType :: HsDocContext -> LHsSigWcType GhcPs -> RnM (LHsSigWcType GhcRn, FreeVars) Source #
rnHsSigWcTypeScoped :: HsDocContext -> LHsSigWcType GhcPs -> (LHsSigWcType GhcRn -> RnM (a, FreeVars)) -> RnM (a, FreeVars) Source #
rnLHsInstType :: SDoc -> LHsSigType GhcPs -> RnM (LHsSigType GhcRn, FreeVars) Source #
rnConDeclFields :: HsDocContext -> [FieldLabel] -> [LConDeclField GhcPs] -> RnM ([LConDeclField GhcRn], FreeVars) Source #
mkOpAppRn :: LHsExpr GhcRn -> LHsExpr GhcRn -> Fixity -> LHsExpr GhcRn -> RnM (HsExpr GhcRn) Source #
mkNegAppRn :: LHsExpr (GhcPass id) -> SyntaxExpr (GhcPass id) -> RnM (HsExpr (GhcPass id)) 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 #
bindLHsTyVarBndr :: HsDocContext -> Maybe a -> LHsTyVarBndr GhcPs -> (LHsTyVarBndr GhcRn -> RnM (b, FreeVars)) -> RnM (b, FreeVars) Source #
bindLHsTyVarBndrs :: HsDocContext -> Maybe SDoc -> Maybe a -> [LHsTyVarBndr GhcPs] -> ([LHsTyVarBndr GhcRn] -> RnM (b, FreeVars)) -> RnM (b, FreeVars) Source #
rnImplicitBndrs :: Bool -> FreeKiTyVarsWithDups -> ([Name] -> RnM (a, FreeVars)) -> RnM (a, FreeVars) Source #
bindHsQTyVars :: forall a b. HsDocContext -> Maybe SDoc -> Maybe a -> [Located RdrName] -> LHsQTyVars GhcPs -> (LHsQTyVars GhcRn -> Bool -> RnM (b, FreeVars)) -> RnM (b, FreeVars) Source #
bindLRdrNames :: [Located RdrName] -> ([Name] -> RnM (a, FreeVars)) -> RnM (a, FreeVars) Source #
Simply bring a bunch of RdrNames into scope. No checking for validity, at all. The binding location is taken from the location on each name.
extractFilteredRdrTyVars :: LHsType GhcPs -> RnM FreeKiTyVarsNoDups Source #
Finds free type and kind variables in a type, without duplicates, and without variables that are already in scope in LocalRdrEnv NB: this includes named wildcards, which look like perfectly ordinary type variables at this point
extractFilteredRdrTyVarsDups :: LHsType GhcPs -> RnM FreeKiTyVarsWithDups Source #
Finds free type and kind variables in a type, with duplicates, but without variables that are already in scope in LocalRdrEnv NB: this includes named wildcards, which look like perfectly ordinary type variables at this point
extractHsTyRdrTyVars :: LHsType GhcPs -> RnM FreeKiTyVarsNoDups Source #
extractHsTyRdrTyVars
finds the
free (kind, type) variables of an HsType
or the free (sort, kind) variables of an HsKind
.
It's used when making the forall
s explicit.
Does not return any wildcards.
When the same name occurs multiple times in the types, only the first
occurrence is returned.
See Note [Kind and type-variable binders]
extractHsTyRdrTyVarsKindVars :: LHsType GhcPs -> RnM [Located RdrName] Source #
Extracts the free kind variables (but not the type variables) of an
HsType
. Does not return any wildcards.
When the same name occurs multiple times in the type, only the first
occurrence is returned.
See Note [Kind and type-variable binders]
extractHsTyRdrTyVarsDups :: LHsType GhcPs -> RnM FreeKiTyVarsWithDups Source #
extractHsTyRdrTyVarsDups
find the
free (kind, type) variables of an HsType
or the free (sort, kind) variables of an HsKind
.
It's used when making the forall
s explicit.
Does not return any wildcards.
When the same name occurs multiple times in the types, all occurrences
are returned.
extractHsTysRdrTyVars :: [LHsType GhcPs] -> RnM FreeKiTyVarsNoDups Source #
Extracts free type and kind variables from types in a list. When the same name occurs multiple times in the types, only the first occurrence is returned and the rest is filtered out. See Note [Kind and type-variable binders]
extractHsTysRdrTyVarsDups :: [LHsType GhcPs] -> RnM FreeKiTyVarsWithDups 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.
rmDupsInRdrTyVars :: FreeKiTyVarsWithDups -> FreeKiTyVarsNoDups Source #
Removes multiple occurrences of the same name from FreeKiTyVars. If a variable occurs as both a kind and a type variable, only keep the occurrence as a kind variable. See also Note [Kind and type-variable binders]
extractHsTvBndrs :: [LHsTyVarBndr GhcPs] -> FreeKiTyVarsWithDups -> RnM FreeKiTyVarsWithDups Source #
freeKiTyVarsAllVars :: FreeKiTyVars -> [Located RdrName] Source #
freeKiTyVarsKindVars :: FreeKiTyVars -> [Located RdrName] Source #
freeKiTyVarsTypeVars :: FreeKiTyVars -> [Located RdrName] Source #