ghc-8.0.0.20160204: The GHC API

Safe HaskellNone
LanguageHaskell2010

HsUtils

Contents

Synopsis

Documentation

mkHsApp :: LHsExpr name -> LHsExpr name -> LHsExpr name Source

mkSimpleHsAlt :: LPat id -> Located (body id) -> LMatch id (Located (body id)) Source

mkSimpleMatch :: [LPat id] -> Located (body id) -> LMatch id (Located (body id)) Source

unguardedGRHSs :: Located (body id) -> GRHSs id (Located (body id)) Source

unguardedRHS :: SrcSpan -> Located (body id) -> [LGRHS id (Located (body id))] Source

mkMatch :: [LPat id] -> LHsExpr id -> Located (HsLocalBinds id) -> LMatch id (LHsExpr id) Source

mkHsIf :: LHsExpr id -> LHsExpr id -> LHsExpr id -> HsExpr id Source

mkHsOpApp :: LHsExpr id -> id -> LHsExpr id -> HsExpr id Source

mkLHsPar :: LHsExpr name -> LHsExpr name Source

isLHsTypeExpr_maybe :: LHsExpr name -> Maybe (LHsWcType name) Source

Extract a type argument from an HsExpr, with the list of wildcards in the type

isLHsTypeExpr :: LHsExpr name -> Bool Source

Is an expression a visible type application?

nlHsTyApp :: name -> [Type] -> LHsExpr name Source

nlHsTyApps :: name -> [Type] -> [LHsExpr name] -> LHsExpr name Source

nlHsVar :: id -> LHsExpr id Source

nlHsApps :: id -> [LHsExpr id] -> LHsExpr id Source

nlHsVarApps :: id -> [id] -> LHsExpr id Source

nlHsOpApp :: LHsExpr id -> id -> LHsExpr id -> LHsExpr id Source

nlHsIf :: LHsExpr id -> LHsExpr id -> LHsExpr id -> LHsExpr id Source

toLHsSigWcType :: Type -> LHsSigWcType RdrName 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

 

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

mkVarBind :: id -> LHsExpr id -> LHsBind id Source

isInfixFunBind :: HsBindLR id1 id2 -> Bool Source

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

nlVarPat :: id -> LPat id Source

nlInfixConPat :: id -> LPat id -> LPat id -> LPat id Source

nlTuplePat :: [LPat id] -> Boxity -> LPat id Source

mkParPat :: LPat name -> LPat name Source

mkHsAppTy :: LHsType name -> LHsType name -> LHsType name Source

mkHsAppTys :: LHsType name -> [LHsType name] -> LHsType name Source

nlHsAppTy :: LHsType name -> LHsType name -> LHsType name Source

nlHsTyVar :: name -> LHsType name Source

nlHsFunTy :: LHsType name -> LHsType name -> LHsType name Source

nlHsTyConApp :: name -> [LHsType name] -> LHsType name Source

getAppsTyHead_maybe :: [LHsAppType name] -> Maybe (LHsType name, [LHsType name]) Source

Retrieves the head of an HsAppsTy, if this can be done unambiguously, without consulting fixities.

splitHsAppsTy :: [LHsAppType name] -> ([[LHsType name]], [Located name]) Source

Splits a [HsAppType name] (the payload of an HsAppsTy) into regions of prefix types (normal types) and infix operators. If splitHsAppsTy tys = (non_syms, syms), then tys starts with the first element of non_syms followed by the first element of syms followed by the next element of non_syms, etc. It is guaranteed that the non_syms list has one more element than the syms list.

mkTransformStmt :: PostTc idR Type ~ PlaceHolder => [ExprLStmt idL] -> LHsExpr idR -> StmtLR idL idR (LHsExpr idL) Source

mkTransformByStmt :: PostTc idR Type ~ PlaceHolder => [ExprLStmt idL] -> LHsExpr idR -> LHsExpr idR -> StmtLR idL idR (LHsExpr idL) Source

mkBindStmt :: PostTc idR Type ~ PlaceHolder => LPat idL -> Located (bodyR idR) -> StmtLR idL idR (Located (bodyR idR)) Source

mkTcBindStmt :: LPat Id -> Located (bodyR Id) -> StmtLR Id Id (Located (bodyR Id)) Source

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

mkGroupUsingStmt :: PostTc idR Type ~ PlaceHolder => [ExprLStmt idL] -> LHsExpr idR -> StmtLR idL idR (LHsExpr idL) Source

mkGroupByUsingStmt :: PostTc idR Type ~ PlaceHolder => [ExprLStmt idL] -> LHsExpr idR -> LHsExpr idR -> StmtLR idL idR (LHsExpr idL) Source

mkRecStmt :: [LStmtLR idL RdrName bodyR] -> StmtLR idL RdrName bodyR Source

collectLStmtsBinders :: [LStmtLR idL idR body] -> [idL] Source

collectStmtsBinders :: [StmtLR idL idR body] -> [idL] Source

collectLStmtBinders :: LStmtLR idL idR body -> [idL] Source

collectStmtBinders :: StmtLR idL idR body -> [idL] Source

hsLTyClDeclBinders :: Located (TyClDecl name) -> ([Located name], [LFieldOcc name]) 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]