ghc-9.8.2: The GHC API
Copyright(c) The University of Glasgow 1992-2006
Safe HaskellNone
LanguageHaskell2010

GHC.Hs.Utils

Description

Here we collect a variety of helper functions that construct or analyse HsSyn. All these functions deal with generic HsSyn; functions which deal with the instantiated versions are located elsewhere:

Parameterised by Module ---------------- ------------- GhcPs/RdrName GHC.Parser.PostProcess GhcRn/Name GHC.Rename.* GhcTc/Id GHC.Tc.Zonk.Type

The mk* functions attempt to construct a not-completely-useless SrcSpan from their components, compared with the nl* functions which just attach noSrcSpan to everything.

Synopsis

Terms

mkHsPar :: forall (id :: Pass). LHsExpr (GhcPass id) -> LHsExpr (GhcPass id) Source #

e => (e)

mkHsApp :: forall (id :: Pass). LHsExpr (GhcPass id) -> LHsExpr (GhcPass id) -> LHsExpr (GhcPass id) Source #

mkHsAppWith :: forall (id :: Pass). (LHsExpr (GhcPass id) -> LHsExpr (GhcPass id) -> HsExpr (GhcPass id) -> LHsExpr (GhcPass id)) -> LHsExpr (GhcPass id) -> LHsExpr (GhcPass id) -> LHsExpr (GhcPass id) Source #

mkHsApps :: forall (id :: Pass). LHsExpr (GhcPass id) -> [LHsExpr (GhcPass id)] -> LHsExpr (GhcPass id) Source #

mkHsAppsWith :: forall (id :: Pass). (LHsExpr (GhcPass id) -> LHsExpr (GhcPass id) -> HsExpr (GhcPass id) -> LHsExpr (GhcPass id)) -> LHsExpr (GhcPass id) -> [LHsExpr (GhcPass id)] -> LHsExpr (GhcPass id) Source #

mkHsCaseAlt :: forall (p :: Pass) body. (Anno (GRHS (GhcPass p) (LocatedA (body (GhcPass p)))) ~ SrcAnn NoEpAnns, Anno (Match (GhcPass p) (LocatedA (body (GhcPass p)))) ~ SrcSpanAnnA) => LPat (GhcPass p) -> LocatedA (body (GhcPass p)) -> LMatch (GhcPass p) (LocatedA (body (GhcPass p))) Source #

A simple case alternative with a single pattern, no binds, no guards; pre-typechecking

mkSimpleMatch :: forall (p :: Pass) body. (Anno (Match (GhcPass p) (LocatedA (body (GhcPass p)))) ~ SrcSpanAnnA, Anno (GRHS (GhcPass p) (LocatedA (body (GhcPass p)))) ~ SrcAnn NoEpAnns) => HsMatchContext (GhcPass p) -> [LPat (GhcPass p)] -> LocatedA (body (GhcPass p)) -> LMatch (GhcPass p) (LocatedA (body (GhcPass p))) Source #

unguardedGRHSs :: forall (p :: Pass) body. Anno (GRHS (GhcPass p) (LocatedA (body (GhcPass p)))) ~ SrcAnn NoEpAnns => SrcSpan -> LocatedA (body (GhcPass p)) -> EpAnn GrhsAnn -> GRHSs (GhcPass p) (LocatedA (body (GhcPass p))) Source #

unguardedRHS :: forall (p :: Pass) body. Anno (GRHS (GhcPass p) (LocatedA (body (GhcPass p)))) ~ SrcAnn NoEpAnns => EpAnn GrhsAnn -> SrcSpan -> LocatedA (body (GhcPass p)) -> [LGRHS (GhcPass p) (LocatedA (body (GhcPass p)))] Source #

mkMatchGroup :: forall (p :: Pass) body. AnnoBody p body => Origin -> LocatedL [LocatedA (Match (GhcPass p) (LocatedA (body (GhcPass p))))] -> MatchGroup (GhcPass p) (LocatedA (body (GhcPass p))) Source #

mkLamCaseMatchGroup :: forall (p :: Pass) body. AnnoBody p body => Origin -> LamCaseVariant -> LocatedL [LocatedA (Match (GhcPass p) (LocatedA (body (GhcPass p))))] -> MatchGroup (GhcPass p) (LocatedA (body (GhcPass p))) Source #

mkMatch :: forall (p :: Pass). IsPass p => HsMatchContext (GhcPass p) -> [LPat (GhcPass p)] -> LHsExpr (GhcPass p) -> HsLocalBinds (GhcPass p) -> LMatch (GhcPass p) (LHsExpr (GhcPass p)) Source #

mkPrefixFunRhs :: LIdP (NoGhcTc p) -> HsMatchContext p Source #

Make a prefix, non-strict function HsMatchContext

mkHsLam :: forall (p :: Pass). (IsPass p, XMG (GhcPass p) (LHsExpr (GhcPass p)) ~ Origin) => [LPat (GhcPass p)] -> LHsExpr (GhcPass p) -> LHsExpr (GhcPass p) Source #

mkHsOpApp :: LHsExpr GhcPs -> IdP GhcPs -> LHsExpr GhcPs -> HsExpr GhcPs Source #

A useful function for building OpApps. The operator is always a variable, and we don't know the fixity yet.

mkLHsPar :: forall (id :: Pass). IsPass id => LHsExpr (GhcPass id) -> LHsExpr (GhcPass id) Source #

Wrap in parens if hsExprNeedsParens appPrec says it needs them So f x becomes (f x), but 3 stays as 3.

nlHsVar :: forall (p :: Pass) a. IsSrcSpanAnn p a => IdP (GhcPass p) -> LHsExpr (GhcPass p) Source #

nl_HsVar :: forall (p :: Pass) a. IsSrcSpanAnn p a => IdP (GhcPass p) -> HsExpr (GhcPass p) Source #

nlHsLit :: forall (p :: Pass). HsLit (GhcPass p) -> LHsExpr (GhcPass p) Source #

nlHsApp :: forall (id :: Pass). IsPass id => LHsExpr (GhcPass id) -> LHsExpr (GhcPass id) -> LHsExpr (GhcPass id) Source #

nlHsApps :: forall (p :: Pass) a. IsSrcSpanAnn p a => IdP (GhcPass p) -> [LHsExpr (GhcPass p)] -> LHsExpr (GhcPass p) Source #

nlHsIntLit :: forall (p :: Pass). Integer -> LHsExpr (GhcPass p) Source #

nlHsVarApps :: forall (p :: Pass) a. IsSrcSpanAnn p a => IdP (GhcPass p) -> [IdP (GhcPass p)] -> LHsExpr (GhcPass p) Source #

nlHsPar :: forall (id :: Pass). LHsExpr (GhcPass id) -> LHsExpr (GhcPass id) Source #

mkLHsVarTuple :: forall (p :: Pass) a. IsSrcSpanAnn p a => [IdP (GhcPass p)] -> XExplicitTuple (GhcPass p) -> LHsExpr (GhcPass p) Source #

Bindings

mkFunBind :: Origin -> LocatedN RdrName -> [LMatch GhcPs (LHsExpr GhcPs)] -> HsBind GhcPs Source #

Not infix, with place holders for coercion and free vars

mkSimpleGeneratedFunBind :: SrcSpan -> RdrName -> [LPat GhcPs] -> LHsExpr GhcPs -> LHsBind GhcPs Source #

Convenience function using mkFunBind. This is for generated bindings only, do not use for user-written code.

mkTopFunBind :: Origin -> LocatedN Name -> [LMatch GhcRn (LHsExpr GhcRn)] -> HsBind GhcRn Source #

In Name-land, with empty bind_fvs

isInfixFunBind :: forall id1 id2. UnXRec id2 => HsBindLR id1 id2 -> Bool Source #

If any of the matches in the FunBind are infix, the FunBind is considered infix.

spanHsLocaLBinds :: forall (p :: Pass). HsLocalBinds (GhcPass p) -> SrcSpan Source #

Return the SrcSpan encompassing the contents of any enclosed binds

Literals

mkHsString :: forall (p :: Pass). String -> HsLit (GhcPass p) Source #

mkHsStringFS :: forall (p :: Pass). FastString -> HsLit (GhcPass p) Source #

mkHsCharPrimLit :: forall (p :: Pass). Char -> HsLit (GhcPass p) Source #

Patterns

nlVarPat :: forall (p :: Pass) a. IsSrcSpanAnn p a => IdP (GhcPass p) -> LPat (GhcPass p) Source #

nlWildPat :: LPat GhcPs Source #

Wildcard pattern - after parsing

nlWildPatName :: LPat GhcRn Source #

Wildcard pattern - after renaming

mkParPat :: forall (p :: Pass). IsPass p => LPat (GhcPass p) -> LPat (GhcPass p) Source #

nlParPat :: forall (name :: Pass). LPat (GhcPass name) -> LPat (GhcPass name) Source #

mkBigLHsVarTup :: forall (p :: Pass) a. IsSrcSpanAnn p a => [IdP (GhcPass p)] -> XExplicitTuple (GhcPass p) -> LHsExpr (GhcPass p) Source #

The Big equivalents for the source tuple expressions

mkBigLHsTup :: forall (id :: Pass). [LHsExpr (GhcPass id)] -> XExplicitTuple (GhcPass id) -> LHsExpr (GhcPass id) Source #

mkBigLHsVarPatTup :: [IdP GhcRn] -> LPat GhcRn Source #

The Big equivalents for the source tuple patterns

Types

mkHsAppTy :: forall (p :: Pass). LHsType (GhcPass p) -> LHsType (GhcPass p) -> LHsType (GhcPass p) Source #

mkHsAppKindTy :: forall (p :: Pass). LHsType (GhcPass p) -> LHsToken "@" (GhcPass p) -> LHsType (GhcPass p) -> LHsType (GhcPass p) Source #

mkClassOpSigs :: [LSig GhcPs] -> [LSig GhcPs] Source #

Convert TypeSig to ClassOpSig. The former is what is parsed, but the latter is what we need in class/instance declarations

nlHsAppTy :: forall (p :: Pass). LHsType (GhcPass p) -> LHsType (GhcPass p) -> LHsType (GhcPass p) Source #

nlHsAppKindTy :: forall (p :: Pass). LHsType (GhcPass p) -> LHsKind (GhcPass p) -> LHsType (GhcPass p) Source #

nlHsTyVar :: forall (p :: Pass) a. IsSrcSpanAnn p a => PromotionFlag -> IdP (GhcPass p) -> LHsType (GhcPass p) Source #

nlHsFunTy :: forall (p :: Pass). LHsType (GhcPass p) -> LHsType (GhcPass p) -> LHsType (GhcPass p) Source #

nlHsParTy :: forall (p :: Pass). LHsType (GhcPass p) -> LHsType (GhcPass p) Source #

Stmts

mkBodyStmt :: forall bodyR (idL :: Pass). LocatedA (bodyR GhcPs) -> StmtLR (GhcPass idL) GhcPs (LocatedA (bodyR GhcPs)) Source #

mkLastStmt :: forall (idR :: Pass) bodyR (idL :: Pass). IsPass idR => LocatedA (bodyR (GhcPass idR)) -> StmtLR (GhcPass idL) (GhcPass idR) (LocatedA (bodyR (GhcPass idR))) Source #

emptyRecStmt :: forall (idL :: Pass) bodyR. Anno [GenLocated (Anno (StmtLR (GhcPass idL) GhcPs bodyR)) (StmtLR (GhcPass idL) GhcPs bodyR)] ~ SrcSpanAnnL => StmtLR (GhcPass idL) GhcPs bodyR Source #

mkRecStmt :: forall (idL :: Pass) bodyR. Anno [GenLocated (Anno (StmtLR (GhcPass idL) GhcPs bodyR)) (StmtLR (GhcPass idL) GhcPs bodyR)] ~ SrcSpanAnnL => EpAnn AnnList -> LocatedL [LStmtLR (GhcPass idL) GhcPs bodyR] -> StmtLR (GhcPass idL) GhcPs bodyR Source #

Collecting binders

isUnliftedHsBind :: HsBind GhcTc -> Bool Source #

Should we treat this as an unlifted bind? This will be true for any bind that binds an unlifted variable, but we must be careful around AbsBinds. See Note [isUnliftedHsBind]. For usage information, see Note [Strict binds checks] is GHC.HsToCore.Binds.

isBangedHsBind :: HsBind GhcTc -> Bool Source #

Is a binding a strict variable or pattern bind (e.g. !x = ...)?

collectLocalBinders :: forall (idL :: Pass) (idR :: Pass). CollectPass (GhcPass idL) => CollectFlag (GhcPass idL) -> HsLocalBindsLR (GhcPass idL) (GhcPass idR) -> [IdP (GhcPass idL)] Source #

collectHsValBinders :: forall (idL :: Pass) idR. CollectPass (GhcPass idL) => CollectFlag (GhcPass idL) -> HsValBindsLR (GhcPass idL) idR -> [IdP (GhcPass idL)] Source #

collectHsBindListBinders :: CollectPass p => CollectFlag p -> [LHsBindLR p idR] -> [IdP p] Source #

Same as collectHsBindsBinders, but works over a list of bindings

collectHsIdBinders :: forall (idL :: Pass) (idR :: Pass). CollectPass (GhcPass idL) => CollectFlag (GhcPass idL) -> HsValBindsLR (GhcPass idL) (GhcPass idR) -> [IdP (GhcPass idL)] Source #

Collect Id binders only, or Ids + pattern synonyms, respectively

collectHsBindBinders :: CollectPass p => CollectFlag p -> HsBindLR p idR -> [IdP p] Source #

Collect both Ids and pattern-synonym binders

collectMethodBinders :: UnXRec idL => LHsBindsLR idL idR -> [LIdP idL] Source #

Used exclusively for the bindings of an instance decl which are all FunBinds

collectLStmtsBinders :: forall (idL :: Pass) (idR :: Pass) body. CollectPass (GhcPass idL) => CollectFlag (GhcPass idL) -> [LStmtLR (GhcPass idL) (GhcPass idR) body] -> [IdP (GhcPass idL)] Source #

collectStmtsBinders :: forall (idL :: Pass) (idR :: Pass) body. CollectPass (GhcPass idL) => CollectFlag (GhcPass idL) -> [StmtLR (GhcPass idL) (GhcPass idR) body] -> [IdP (GhcPass idL)] Source #

collectLStmtBinders :: forall (idL :: Pass) (idR :: Pass) body. CollectPass (GhcPass idL) => CollectFlag (GhcPass idL) -> LStmtLR (GhcPass idL) (GhcPass idR) body -> [IdP (GhcPass idL)] Source #

collectStmtBinders :: forall (idL :: Pass) (idR :: Pass) body. CollectPass (GhcPass idL) => CollectFlag (GhcPass idL) -> StmtLR (GhcPass idL) (GhcPass idR) body -> [IdP (GhcPass idL)] Source #

class UnXRec p => CollectPass p where Source #

This class specifies how to collect variable identifiers from extension patterns in the given pass. Consumers of the GHC API that define their own passes should feel free to implement instances in order to make use of functions which depend on it.

In particular, Haddock already makes use of this, with an instance for its DocNameI pass so that it can reuse the code in GHC for collecting binders.

Methods

collectXXPat :: CollectFlag p -> XXPat p -> [IdP p] -> [IdP p] Source #

collectXXHsBindsLR :: XXHsBindsLR p pR -> [IdP p] -> [IdP p] Source #

collectXSplicePat :: CollectFlag p -> XSplicePat p -> [IdP p] -> [IdP p] Source #

Instances

Instances details
IsPass p => CollectPass (GhcPass p) Source # 
Instance details

Defined in GHC.Hs.Utils

data CollectFlag p where Source #

Indicate if evidence binders have to be collected.

This type is used as a boolean (should we collect evidence binders or not?) but also to pass an evidence that the AST has been typechecked when we do want to collect evidence binders, otherwise these binders are not available.

See Note [Dictionary binders in ConPatOut]

Constructors

CollNoDictBinders :: forall p. CollectFlag p

Don't collect evidence binders

CollWithDictBinders :: CollectFlag (GhcPass 'Typechecked)

Collect evidence binders

data LConsWithFields (p :: Pass) Source #

A mapping from constructors to all of their fields.

See Note [Collecting record fields in data declarations].

hsLTyClDeclBinders :: forall (p :: Pass). (IsPass p, OutputableBndrId p) => LocatedA (TyClDecl (GhcPass p)) -> TyDeclBinders p Source #

Returns all the binding names of the decl. The first one is guaranteed to be the name of the decl. The first component represents all binding names except record fields; the second represents field occurrences. For record fields mentioned in multiple constructors, the SrcLoc will be from the first occurrence.

Each returned (Located name) has a SrcSpan for the whole declaration. See Note [SrcSpan for binders]

hsPatSynSelectors :: forall (p :: Pass). IsPass p => HsValBinds (GhcPass p) -> [FieldOcc (GhcPass p)] Source #

Collects record pattern-synonym selectors only; the pattern synonym names are collected by collectHsValBinders.

hsForeignDeclsBinders :: forall (p :: Pass) a. (UnXRec (GhcPass p), IsSrcSpanAnn p a) => [LForeignDecl (GhcPass p)] -> [LIdP (GhcPass p)] Source #

See Note [SrcSpan for binders]

hsDataFamInstBinders :: forall (p :: Pass). (IsPass p, OutputableBndrId p) => DataFamInstDecl (GhcPass p) -> LConsWithFields p Source #

the SrcLoc returned are for the whole declarations, not just the names

Collecting implicit binders

lStmtsImplicits :: forall (idR :: Pass) (body :: Type -> Type). [LStmtLR GhcRn (GhcPass idR) (LocatedA (body (GhcPass idR)))] -> [(SrcSpan, [Name])] Source #

hsValBindsImplicits :: forall (idR :: Pass). HsValBindsLR GhcRn (GhcPass idR) -> [(SrcSpan, [Name])] Source #