ghc-8.10.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 ---------------- ------------- GhcPsRdrName parserRdrHsSyn GhcRnName renameRnHsSyn GhcTcId typecheckTcHsSyn

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 :: LHsExpr (GhcPass id) -> LHsExpr (GhcPass id) Source #

e => (e)

mkHsCaseAlt :: LPat (GhcPass p) -> Located (body (GhcPass p)) -> LMatch (GhcPass p) (Located (body (GhcPass p))) Source #

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

unguardedGRHSs :: Located (body (GhcPass p)) -> GRHSs (GhcPass p) (Located (body (GhcPass p))) Source #

unguardedRHS :: SrcSpan -> Located (body (GhcPass p)) -> [LGRHS (GhcPass p) (Located (body (GhcPass p)))] Source #

mkMatchGroup :: XMG name (Located (body name)) ~ NoExtField => Origin -> [LMatch name (Located (body name))] -> MatchGroup name (Located (body name)) Source #

mkPrefixFunRhs :: Located id -> HsMatchContext id Source #

Make a prefix, non-strict function HsMatchContext

mkHsWrap :: HsWrapper -> HsExpr (GhcPass id) -> HsExpr (GhcPass id) Source #

Avoid (HsWrap co (HsWrap co' _)). See Note [Detecting forced eta expansion] in DsExpr

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

nlHsTyApps :: IdP (GhcPass id) -> [Type] -> [LHsExpr (GhcPass id)] -> LHsExpr (GhcPass id) Source #

nlHsDataCon :: DataCon -> LHsExpr GhcTc Source #

NB: Only for LHsExpr **Id**

nlHsIf :: LHsExpr (GhcPass id) -> LHsExpr (GhcPass id) -> LHsExpr (GhcPass id) -> LHsExpr (GhcPass id) Source #

Note [Rebindable nlHsIf] nlHsIf should generate if-expressions which are NOT subject to RebindableSyntax, so the first field of HsIf is Nothing. (#12080)

typeToLHsType :: Type -> LHsType GhcPs Source #

Converting a Type to an HsType RdrName This is needed to implement GeneralizedNewtypeDeriving.

Note that we use getRdrName extensively, which generates Exact RdrNames rather than strings.

Constructing general big tuples

GHCs built in tuples can only go up to mAX_TUPLE_SIZE in arity, but we might concievably want to build such a massive tuple as part of the output of a desugaring stage (notably that for list comprehensions).

We call tuples above this size "big tuples", and emulate them by creating and pattern matching on >nested< tuples that are expressible by GHC.

Nesting policy: it's better to have a 2-tuple of 10-tuples (3 objects) than a 10-tuple of 2-tuples (11 objects), so we want the leaves of any construction to be big.

If you just use the mkBigCoreTup, mkBigCoreVarTupTy, mkTupleSelector and mkTupleCase functions to do all your work with tuples you should be fine, and not have to worry about the arity limitation at all.

mkChunkified Source #

Arguments

:: ([a] -> a)

"Small" constructor function, of maximum input arity mAX_TUPLE_SIZE

-> [a]

Possible "big" list of things to construct from

-> a

Constructed thing made possible by recursive decomposition

Lifts a "small" constructor into a "big" constructor by recursive decompositon

chunkify :: [a] -> [[a]] Source #

Split a list into lists that are small enough to have a corresponding tuple arity. The sub-lists of the result all have length <= mAX_TUPLE_SIZE But there may be more than mAX_TUPLE_SIZE sub-lists

Bindings

mkFunBind :: Origin -> Located 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 -> Located Name -> [LMatch GhcRn (LHsExpr GhcRn)] -> HsBind GhcRn Source #

In Name-land, with empty bind_fvs

isInfixFunBind :: HsBindLR id1 id2 -> Bool Source #

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

Literals

Patterns

nlWildPat :: LPat GhcPs Source #

Wildcard pattern - after parsing

nlWildPatName :: LPat GhcRn Source #

Wildcard pattern - after renaming

mkParPat :: LPat (GhcPass name) -> LPat (GhcPass name) Source #

nlParPat :: LPat (GhcPass name) -> LPat (GhcPass name) Source #

mkBigLHsVarTup :: [IdP (GhcPass id)] -> LHsExpr (GhcPass id) Source #

The Big equivalents for the source tuple expressions

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

The Big equivalents for the source tuple patterns

Types

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

mkHsSigEnv :: forall a. (LSig GhcRn -> Maybe ([Located Name], a)) -> [LSig GhcRn] -> NameEnv a Source #

Stmts

mkBindStmt :: XBindStmt (GhcPass idL) (GhcPass idR) (Located (bodyR (GhcPass idR))) ~ NoExtField => LPat (GhcPass idL) -> Located (bodyR (GhcPass idR)) -> StmtLR (GhcPass idL) (GhcPass idR) (Located (bodyR (GhcPass idR))) Source #

mkLastStmt :: Located (bodyR (GhcPass idR)) -> StmtLR (GhcPass idL) (GhcPass idR) (Located (bodyR (GhcPass idR))) Source #

mkRecStmt :: [LStmtLR (GhcPass idL) GhcPs bodyR] -> StmtLR (GhcPass idL) GhcPs bodyR Source #

Template Haskell

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 [Unlifted id check in isUnliftedHsBind]. For usage information, see Note [Strict binds check] is DsBinds.

isBangedHsBind :: HsBind GhcTc -> Bool Source #

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

collectHsValBinders :: HsValBindsLR (GhcPass idL) (GhcPass idR) -> [IdP (GhcPass idL)] Source #

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

collectHsBindListBinders :: [LHsBindLR (GhcPass p) idR] -> [IdP (GhcPass p)] Source #

Same as collectHsBindsBinders, but works over a list of bindings

collectHsIdBinders :: HsValBindsLR (GhcPass idL) (GhcPass idR) -> [IdP (GhcPass idL)] Source #

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

collectHsBindBinders :: (SrcSpanLess (LPat p) ~ Pat p, HasSrcSpan (LPat p)) => HsBindLR p idR -> [IdP p] Source #

Collect both Ids and pattern-synonym binders

collectMethodBinders :: LHsBindsLR idL idR -> [Located (IdP idL)] Source #

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

collectLStmtsBinders :: [LStmtLR (GhcPass idL) (GhcPass idR) body] -> [IdP (GhcPass idL)] Source #

collectStmtsBinders :: [StmtLR (GhcPass idL) (GhcPass idR) body] -> [IdP (GhcPass idL)] Source #

collectLStmtBinders :: LStmtLR (GhcPass idL) (GhcPass idR) body -> [IdP (GhcPass idL)] Source #

collectStmtBinders :: StmtLR (GhcPass idL) (GhcPass idR) body -> [IdP (GhcPass idL)] Source #

hsLTyClDeclBinders :: Located (TyClDecl (GhcPass p)) -> ([Located (IdP (GhcPass p))], [LFieldOcc (GhcPass 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 :: HsValBinds (GhcPass p) -> [IdP (GhcPass p)] Source #

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

hsForeignDeclsBinders :: [LForeignDecl pass] -> [Located (IdP pass)] Source #

See Note [SrcSpan for binders]

hsDataFamInstBinders :: DataFamInstDecl (GhcPass p) -> ([Located (IdP (GhcPass p))], [LFieldOcc (GhcPass p)]) Source #

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

Collecting implicit binders

lStmtsImplicits :: [LStmtLR GhcRn (GhcPass idR) (Located (body (GhcPass idR)))] -> [(SrcSpan, [Name])] Source #