Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- mkHsPar :: LHsExpr id -> LHsExpr id
- mkHsApp :: LHsExpr name -> LHsExpr name -> LHsExpr name
- mkHsAppType :: LHsExpr name -> LHsWcType name -> LHsExpr name
- mkHsAppTypes :: LHsExpr name -> [LHsWcType name] -> LHsExpr name
- mkHsAppTypeOut :: LHsExpr GhcTc -> LHsWcType GhcRn -> LHsExpr GhcTc
- mkHsCaseAlt :: LPat id -> Located (body id) -> LMatch id (Located (body id))
- mkSimpleMatch :: HsMatchContext (NameOrRdrName (IdP id)) -> [LPat id] -> Located (body id) -> LMatch id (Located (body id))
- unguardedGRHSs :: Located (body id) -> GRHSs id (Located (body id))
- unguardedRHS :: SrcSpan -> Located (body id) -> [LGRHS id (Located (body id))]
- mkMatchGroup :: PostTc name Type ~ PlaceHolder => Origin -> [LMatch name (Located (body name))] -> MatchGroup name (Located (body name))
- mkMatch :: HsMatchContext (NameOrRdrName (IdP p)) -> [LPat p] -> LHsExpr p -> Located (HsLocalBinds p) -> LMatch p (LHsExpr p)
- mkPrefixFunRhs :: Located id -> HsMatchContext id
- mkHsLam :: [LPat GhcPs] -> LHsExpr GhcPs -> LHsExpr GhcPs
- mkHsIf :: SourceTextX p => LHsExpr p -> LHsExpr p -> LHsExpr p -> HsExpr p
- mkHsWrap :: HsWrapper -> HsExpr id -> HsExpr id
- mkLHsWrap :: HsWrapper -> LHsExpr id -> LHsExpr id
- mkHsWrapCo :: TcCoercionN -> HsExpr id -> HsExpr id
- mkHsWrapCoR :: TcCoercionR -> HsExpr id -> HsExpr id
- mkLHsWrapCo :: TcCoercionN -> LHsExpr id -> LHsExpr id
- mkHsDictLet :: TcEvBinds -> LHsExpr GhcTc -> LHsExpr GhcTc
- mkHsLams :: [TyVar] -> [EvVar] -> LHsExpr GhcTc -> LHsExpr GhcTc
- mkHsOpApp :: LHsExpr id -> IdP id -> LHsExpr id -> HsExpr id
- mkHsDo :: HsStmtContext Name -> [ExprLStmt GhcPs] -> HsExpr GhcPs
- mkHsComp :: HsStmtContext Name -> [ExprLStmt GhcPs] -> LHsExpr GhcPs -> HsExpr GhcPs
- mkHsWrapPat :: HsWrapper -> Pat id -> Type -> Pat id
- mkHsWrapPatCo :: TcCoercionN -> Pat id -> Type -> Pat id
- mkLHsPar :: LHsExpr name -> LHsExpr name
- mkHsCmdWrap :: HsWrapper -> HsCmd id -> HsCmd id
- mkLHsCmdWrap :: HsWrapper -> LHsCmd id -> LHsCmd id
- nlHsTyApp :: IdP name -> [Type] -> LHsExpr name
- nlHsTyApps :: IdP name -> [Type] -> [LHsExpr name] -> LHsExpr name
- nlHsVar :: IdP id -> LHsExpr id
- nlHsDataCon :: DataCon -> LHsExpr GhcTc
- nlHsLit :: HsLit p -> LHsExpr p
- nlHsApp :: LHsExpr id -> LHsExpr id -> LHsExpr id
- nlHsApps :: IdP id -> [LHsExpr id] -> LHsExpr id
- nlHsSyntaxApps :: SyntaxExpr id -> [LHsExpr id] -> LHsExpr id
- nlHsIntLit :: HasDefaultX p => Integer -> LHsExpr p
- nlHsVarApps :: IdP id -> [IdP id] -> LHsExpr id
- nlHsDo :: HsStmtContext Name -> [LStmt GhcPs (LHsExpr GhcPs)] -> LHsExpr GhcPs
- nlHsOpApp :: LHsExpr id -> IdP id -> LHsExpr id -> LHsExpr id
- nlHsLam :: LMatch GhcPs (LHsExpr GhcPs) -> LHsExpr GhcPs
- nlHsPar :: LHsExpr id -> LHsExpr id
- nlHsIf :: LHsExpr id -> LHsExpr id -> LHsExpr id -> LHsExpr id
- nlHsCase :: LHsExpr GhcPs -> [LMatch GhcPs (LHsExpr GhcPs)] -> LHsExpr GhcPs
- nlList :: [LHsExpr GhcPs] -> LHsExpr GhcPs
- mkLHsTupleExpr :: [LHsExpr a] -> LHsExpr a
- mkLHsVarTuple :: [IdP a] -> LHsExpr a
- missingTupArg :: HsTupArg GhcPs
- typeToLHsType :: Type -> LHsType GhcPs
- mkChunkified :: ([a] -> a) -> [a] -> a
- chunkify :: [a] -> [[a]]
- mkFunBind :: Located RdrName -> [LMatch GhcPs (LHsExpr GhcPs)] -> HsBind GhcPs
- mkVarBind :: IdP p -> LHsExpr p -> LHsBind p
- mkHsVarBind :: SrcSpan -> RdrName -> LHsExpr GhcPs -> LHsBind GhcPs
- mk_easy_FunBind :: SrcSpan -> RdrName -> [LPat GhcPs] -> LHsExpr GhcPs -> LHsBind GhcPs
- mkTopFunBind :: Origin -> Located Name -> [LMatch GhcRn (LHsExpr GhcRn)] -> HsBind GhcRn
- mkPatSynBind :: Located RdrName -> HsPatSynDetails (Located RdrName) -> LPat GhcPs -> HsPatSynDir GhcPs -> HsBind GhcPs
- isInfixFunBind :: HsBindLR id1 id2 -> Bool
- mkHsIntegral :: IntegralLit -> PostTc GhcPs Type -> HsOverLit GhcPs
- mkHsFractional :: FractionalLit -> PostTc GhcPs Type -> HsOverLit GhcPs
- mkHsIsString :: SourceText -> FastString -> PostTc GhcPs Type -> HsOverLit GhcPs
- mkHsString :: SourceTextX p => String -> HsLit p
- mkHsStringPrimLit :: SourceTextX p => FastString -> HsLit p
- mkNPat :: Located (HsOverLit GhcPs) -> Maybe (SyntaxExpr GhcPs) -> Pat GhcPs
- mkNPlusKPat :: Located RdrName -> Located (HsOverLit GhcPs) -> Pat GhcPs
- nlVarPat :: IdP id -> LPat id
- nlLitPat :: HsLit p -> LPat p
- nlConVarPat :: RdrName -> [RdrName] -> LPat GhcPs
- nlConVarPatName :: Name -> [Name] -> LPat GhcRn
- nlConPat :: RdrName -> [LPat GhcPs] -> LPat GhcPs
- nlConPatName :: Name -> [LPat GhcRn] -> LPat GhcRn
- nlInfixConPat :: IdP id -> LPat id -> LPat id -> LPat id
- nlNullaryConPat :: IdP id -> LPat id
- nlWildConPat :: DataCon -> LPat GhcPs
- nlWildPat :: LPat GhcPs
- nlWildPatName :: LPat GhcRn
- nlWildPatId :: LPat GhcTc
- nlTuplePat :: [LPat id] -> Boxity -> LPat id
- mkParPat :: LPat name -> LPat name
- nlParPat :: LPat name -> LPat name
- mkBigLHsVarTup :: [IdP id] -> LHsExpr id
- mkBigLHsTup :: [LHsExpr id] -> LHsExpr id
- mkBigLHsVarPatTup :: [IdP id] -> LPat id
- mkBigLHsPatTup :: [LPat id] -> LPat id
- mkHsAppTy :: LHsType pass -> LHsType pass -> LHsType pass
- mkHsAppTys :: LHsType pass -> [LHsType pass] -> LHsType pass
- userHsTyVarBndrs :: SrcSpan -> [IdP name] -> [LHsTyVarBndr name]
- userHsLTyVarBndrs :: SrcSpan -> [Located (IdP name)] -> [LHsTyVarBndr name]
- mkLHsSigType :: LHsType GhcPs -> LHsSigType GhcPs
- mkLHsSigWcType :: LHsType GhcPs -> LHsSigWcType GhcPs
- mkClassOpSigs :: [LSig GhcPs] -> [LSig GhcPs]
- mkHsSigEnv :: forall a. (LSig GhcRn -> Maybe ([Located Name], a)) -> [LSig GhcRn] -> NameEnv a
- nlHsAppTy :: LHsType name -> LHsType name -> LHsType name
- nlHsTyVar :: IdP name -> LHsType name
- nlHsFunTy :: LHsType name -> LHsType name -> LHsType name
- nlHsParTy :: LHsType name -> LHsType name
- nlHsTyConApp :: IdP name -> [LHsType name] -> LHsType name
- mkTransformStmt :: (SourceTextX idR, PostTc idR Type ~ PlaceHolder) => [ExprLStmt idL] -> LHsExpr idR -> StmtLR idL idR (LHsExpr idL)
- mkTransformByStmt :: (SourceTextX idR, PostTc idR Type ~ PlaceHolder) => [ExprLStmt idL] -> LHsExpr idR -> LHsExpr idR -> StmtLR idL idR (LHsExpr idL)
- mkBodyStmt :: Located (bodyR GhcPs) -> StmtLR idL GhcPs (Located (bodyR GhcPs))
- mkBindStmt :: (SourceTextX idR, PostTc idR Type ~ PlaceHolder) => LPat idL -> Located (bodyR idR) -> StmtLR idL idR (Located (bodyR idR))
- mkTcBindStmt :: LPat GhcTc -> Located (bodyR GhcTc) -> StmtLR GhcTc GhcTc (Located (bodyR GhcTc))
- mkLastStmt :: SourceTextX idR => Located (bodyR idR) -> StmtLR idL idR (Located (bodyR idR))
- emptyTransStmt :: (SourceTextX idR, PostTc idR Type ~ PlaceHolder) => StmtLR idL idR (LHsExpr idR)
- mkGroupUsingStmt :: (SourceTextX idR, PostTc idR Type ~ PlaceHolder) => [ExprLStmt idL] -> LHsExpr idR -> StmtLR idL idR (LHsExpr idL)
- mkGroupByUsingStmt :: (SourceTextX idR, PostTc idR Type ~ PlaceHolder) => [ExprLStmt idL] -> LHsExpr idR -> LHsExpr idR -> StmtLR idL idR (LHsExpr idL)
- emptyRecStmt :: StmtLR idL GhcPs bodyR
- emptyRecStmtName :: StmtLR GhcRn GhcRn bodyR
- emptyRecStmtId :: StmtLR GhcTc GhcTc bodyR
- mkRecStmt :: [LStmtLR idL GhcPs bodyR] -> StmtLR idL GhcPs bodyR
- mkHsSpliceTy :: SpliceDecoration -> LHsExpr GhcPs -> HsType GhcPs
- mkHsSpliceE :: SpliceDecoration -> LHsExpr GhcPs -> HsExpr GhcPs
- mkHsSpliceTE :: SpliceDecoration -> LHsExpr GhcPs -> HsExpr GhcPs
- mkUntypedSplice :: SpliceDecoration -> LHsExpr GhcPs -> HsSplice GhcPs
- mkHsQuasiQuote :: RdrName -> SrcSpan -> FastString -> HsSplice GhcPs
- unqualQuasiQuote :: RdrName
- noRebindableInfo :: PlaceHolder
- isUnliftedHsBind :: HsBind GhcTc -> Bool
- isBangedHsBind :: HsBind GhcTc -> Bool
- collectLocalBinders :: HsLocalBindsLR idL idR -> [IdP idL]
- collectHsValBinders :: HsValBindsLR idL idR -> [IdP idL]
- collectHsBindListBinders :: [LHsBindLR idL idR] -> [IdP idL]
- collectHsIdBinders :: HsValBindsLR idL idR -> [IdP idL]
- collectHsBindsBinders :: LHsBindsLR idL idR -> [IdP idL]
- collectHsBindBinders :: HsBindLR idL idR -> [IdP idL]
- collectMethodBinders :: LHsBindsLR GhcPs idR -> [Located RdrName]
- collectPatBinders :: LPat a -> [IdP a]
- collectPatsBinders :: [LPat a] -> [IdP a]
- collectLStmtsBinders :: [LStmtLR idL idR body] -> [IdP idL]
- collectStmtsBinders :: [StmtLR idL idR body] -> [IdP idL]
- collectLStmtBinders :: LStmtLR idL idR body -> [IdP idL]
- collectStmtBinders :: StmtLR idL idR body -> [IdP idL]
- hsLTyClDeclBinders :: Located (TyClDecl pass) -> ([Located (IdP pass)], [LFieldOcc pass])
- hsTyClForeignBinders :: [TyClGroup GhcRn] -> [LForeignDecl GhcRn] -> [Name]
- hsPatSynSelectors :: HsValBinds p -> [IdP p]
- getPatSynBinds :: [(RecFlag, LHsBinds id)] -> [PatSynBind id id]
- hsForeignDeclsBinders :: [LForeignDecl pass] -> [Located (IdP pass)]
- hsGroupBinders :: HsGroup GhcRn -> [Name]
- hsDataFamInstBinders :: DataFamInstDecl pass -> ([Located (IdP pass)], [LFieldOcc pass])
- hsDataDefnBinders :: HsDataDefn pass -> ([Located (IdP pass)], [LFieldOcc pass])
- lStmtsImplicits :: [LStmtLR GhcRn idR (Located (body idR))] -> NameSet
- hsValBindsImplicits :: HsValBindsLR GhcRn idR -> NameSet
- lPatImplicits :: LPat GhcRn -> NameSet
Documentation
mkHsCaseAlt :: LPat id -> Located (body id) -> LMatch id (Located (body id)) Source #
A simple case alternative with a single pattern, no binds, no guards; pre-typechecking
mkSimpleMatch :: HsMatchContext (NameOrRdrName (IdP id)) -> [LPat id] -> Located (body id) -> LMatch id (Located (body id)) Source #
mkMatchGroup :: PostTc name Type ~ PlaceHolder => Origin -> [LMatch name (Located (body name))] -> MatchGroup name (Located (body name)) Source #
mkMatch :: HsMatchContext (NameOrRdrName (IdP p)) -> [LPat p] -> LHsExpr p -> Located (HsLocalBinds p) -> LMatch p (LHsExpr p) Source #
mkPrefixFunRhs :: Located id -> HsMatchContext id Source #
Make a prefix, non-strict function HsMatchContext
mkHsWrapCo :: TcCoercionN -> HsExpr id -> HsExpr id Source #
mkHsWrapCoR :: TcCoercionR -> HsExpr id -> HsExpr id Source #
mkLHsWrapCo :: TcCoercionN -> LHsExpr id -> LHsExpr id Source #
mkHsWrapPatCo :: TcCoercionN -> Pat id -> Type -> Pat id Source #
nlHsSyntaxApps :: SyntaxExpr id -> [LHsExpr id] -> LHsExpr id Source #
nlHsIntLit :: HasDefaultX p => Integer -> LHsExpr p Source #
mkLHsTupleExpr :: [LHsExpr a] -> LHsExpr a Source #
mkLHsVarTuple :: [IdP a] -> LHsExpr a Source #
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.
:: ([a] -> a) | "Small" constructor function, of maximum input arity |
-> [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
mkPatSynBind :: Located RdrName -> HsPatSynDetails (Located RdrName) -> LPat GhcPs -> HsPatSynDir GhcPs -> HsBind GhcPs Source #
isInfixFunBind :: HsBindLR id1 id2 -> Bool Source #
mkHsIntegral :: IntegralLit -> PostTc GhcPs Type -> HsOverLit GhcPs Source #
mkHsFractional :: FractionalLit -> PostTc GhcPs Type -> HsOverLit GhcPs Source #
mkHsIsString :: SourceText -> FastString -> PostTc GhcPs Type -> HsOverLit GhcPs Source #
mkHsString :: SourceTextX p => String -> HsLit p Source #
mkHsStringPrimLit :: SourceTextX p => FastString -> HsLit p Source #
nlNullaryConPat :: IdP id -> LPat id Source #
nlWildPatId :: LPat GhcTc Source #
mkBigLHsVarTup :: [IdP id] -> LHsExpr id Source #
mkBigLHsTup :: [LHsExpr id] -> LHsExpr id Source #
mkBigLHsVarPatTup :: [IdP id] -> LPat id Source #
mkBigLHsPatTup :: [LPat id] -> LPat id Source #
userHsTyVarBndrs :: SrcSpan -> [IdP name] -> [LHsTyVarBndr name] Source #
userHsLTyVarBndrs :: SrcSpan -> [Located (IdP name)] -> [LHsTyVarBndr name] Source #
mkLHsSigType :: LHsType GhcPs -> LHsSigType GhcPs Source #
mkHsSigEnv :: forall a. (LSig GhcRn -> Maybe ([Located Name], a)) -> [LSig GhcRn] -> NameEnv a Source #
mkTransformStmt :: (SourceTextX idR, PostTc idR Type ~ PlaceHolder) => [ExprLStmt idL] -> LHsExpr idR -> StmtLR idL idR (LHsExpr idL) Source #
mkTransformByStmt :: (SourceTextX idR, PostTc idR Type ~ PlaceHolder) => [ExprLStmt idL] -> LHsExpr idR -> LHsExpr idR -> StmtLR idL idR (LHsExpr idL) Source #
mkBindStmt :: (SourceTextX idR, PostTc idR Type ~ PlaceHolder) => LPat idL -> Located (bodyR idR) -> StmtLR idL idR (Located (bodyR idR)) Source #
mkTcBindStmt :: LPat GhcTc -> Located (bodyR GhcTc) -> StmtLR GhcTc GhcTc (Located (bodyR GhcTc)) Source #
mkLastStmt :: SourceTextX idR => Located (bodyR idR) -> StmtLR idL idR (Located (bodyR idR)) Source #
emptyTransStmt :: (SourceTextX idR, PostTc idR Type ~ PlaceHolder) => StmtLR idL idR (LHsExpr idR) Source #
mkGroupUsingStmt :: (SourceTextX idR, PostTc idR Type ~ PlaceHolder) => [ExprLStmt idL] -> LHsExpr idR -> StmtLR idL idR (LHsExpr idL) Source #
mkGroupByUsingStmt :: (SourceTextX idR, PostTc idR Type ~ PlaceHolder) => [ExprLStmt idL] -> LHsExpr idR -> LHsExpr idR -> StmtLR idL idR (LHsExpr idL) Source #
emptyRecStmt :: StmtLR idL GhcPs bodyR Source #
mkHsSpliceTy :: SpliceDecoration -> LHsExpr GhcPs -> HsType GhcPs Source #
mkHsSpliceE :: SpliceDecoration -> LHsExpr GhcPs -> HsExpr GhcPs Source #
mkHsSpliceTE :: SpliceDecoration -> LHsExpr GhcPs -> HsExpr GhcPs Source #
mkUntypedSplice :: SpliceDecoration -> LHsExpr GhcPs -> HsSplice GhcPs Source #
mkHsQuasiQuote :: RdrName -> SrcSpan -> FastString -> HsSplice GhcPs Source #
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 = ...
)?
collectLocalBinders :: HsLocalBindsLR idL idR -> [IdP idL] Source #
collectHsValBinders :: HsValBindsLR idL idR -> [IdP idL] Source #
collectHsBindListBinders :: [LHsBindLR idL idR] -> [IdP idL] Source #
collectHsIdBinders :: HsValBindsLR idL idR -> [IdP idL] Source #
collectHsBindsBinders :: LHsBindsLR idL idR -> [IdP idL] Source #
collectHsBindBinders :: HsBindLR idL idR -> [IdP idL] Source #
collectMethodBinders :: LHsBindsLR GhcPs idR -> [Located RdrName] Source #
collectPatBinders :: LPat a -> [IdP a] Source #
collectPatsBinders :: [LPat a] -> [IdP a] Source #
collectLStmtsBinders :: [LStmtLR idL idR body] -> [IdP idL] Source #
collectStmtsBinders :: [StmtLR idL idR body] -> [IdP idL] Source #
collectLStmtBinders :: LStmtLR idL idR body -> [IdP idL] Source #
collectStmtBinders :: StmtLR idL idR body -> [IdP idL] Source #
hsLTyClDeclBinders :: Located (TyClDecl pass) -> ([Located (IdP pass)], [LFieldOcc pass]) 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]
hsTyClForeignBinders :: [TyClGroup GhcRn] -> [LForeignDecl GhcRn] -> [Name] Source #
hsPatSynSelectors :: HsValBinds p -> [IdP p] Source #
getPatSynBinds :: [(RecFlag, LHsBinds id)] -> [PatSynBind id id] Source #
hsForeignDeclsBinders :: [LForeignDecl pass] -> [Located (IdP pass)] Source #
hsDataFamInstBinders :: DataFamInstDecl pass -> ([Located (IdP pass)], [LFieldOcc pass]) Source #
hsDataDefnBinders :: HsDataDefn pass -> ([Located (IdP pass)], [LFieldOcc pass]) Source #
hsValBindsImplicits :: HsValBindsLR GhcRn idR -> NameSet Source #