Safe Haskell | None |
---|---|
Language | Haskell2010 |
- mkHsPar :: LHsExpr id -> LHsExpr id
- mkHsApp :: LHsExpr name -> LHsExpr name -> LHsExpr name
- mkHsAppType :: LHsExpr name -> LHsWcType name -> LHsExpr name
- mkHsAppTypeOut :: LHsExpr Id -> LHsWcType Name -> LHsExpr Id
- mkHsConApp :: DataCon -> [Type] -> [HsExpr Id] -> LHsExpr Id
- mkSimpleHsAlt :: LPat id -> Located (body id) -> LMatch id (Located (body id))
- mkSimpleMatch :: [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 :: Origin -> [LMatch RdrName (Located (body RdrName))] -> MatchGroup RdrName (Located (body RdrName))
- mkMatchGroupName :: Origin -> [LMatch Name (Located (body Name))] -> MatchGroup Name (Located (body Name))
- mkMatch :: [LPat id] -> LHsExpr id -> Located (HsLocalBinds id) -> LMatch id (LHsExpr id)
- mkHsLam :: [LPat RdrName] -> LHsExpr RdrName -> LHsExpr RdrName
- mkHsIf :: LHsExpr id -> LHsExpr id -> LHsExpr id -> HsExpr id
- 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 Id -> LHsExpr Id
- mkHsLams :: [TyVar] -> [EvVar] -> LHsExpr Id -> LHsExpr Id
- mkHsOpApp :: LHsExpr id -> id -> LHsExpr id -> HsExpr id
- mkHsDo :: HsStmtContext Name -> [ExprLStmt RdrName] -> HsExpr RdrName
- mkHsComp :: HsStmtContext Name -> [ExprLStmt RdrName] -> LHsExpr RdrName -> HsExpr RdrName
- 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 :: name -> [Type] -> LHsExpr name
- nlHsTyApps :: name -> [Type] -> [LHsExpr name] -> LHsExpr name
- nlHsVar :: id -> LHsExpr id
- nlHsLit :: HsLit -> LHsExpr id
- nlHsApp :: LHsExpr id -> LHsExpr id -> LHsExpr id
- nlHsApps :: id -> [LHsExpr id] -> LHsExpr id
- nlHsSyntaxApps :: SyntaxExpr id -> [LHsExpr id] -> LHsExpr id
- nlHsIntLit :: Integer -> LHsExpr id
- nlHsVarApps :: id -> [id] -> LHsExpr id
- nlHsDo :: HsStmtContext Name -> [LStmt RdrName (LHsExpr RdrName)] -> LHsExpr RdrName
- nlHsOpApp :: LHsExpr id -> id -> LHsExpr id -> LHsExpr id
- nlHsLam :: LMatch RdrName (LHsExpr RdrName) -> LHsExpr RdrName
- nlHsPar :: LHsExpr id -> LHsExpr id
- nlHsIf :: LHsExpr id -> LHsExpr id -> LHsExpr id -> LHsExpr id
- nlHsCase :: LHsExpr RdrName -> [LMatch RdrName (LHsExpr RdrName)] -> LHsExpr RdrName
- nlList :: [LHsExpr RdrName] -> LHsExpr RdrName
- mkLHsTupleExpr :: [LHsExpr a] -> LHsExpr a
- mkLHsVarTuple :: [a] -> LHsExpr a
- missingTupArg :: HsTupArg RdrName
- toLHsSigWcType :: Type -> LHsSigWcType RdrName
- mkChunkified :: ([a] -> a) -> [a] -> a
- chunkify :: [a] -> [[a]]
- mkFunBind :: Located RdrName -> [LMatch RdrName (LHsExpr RdrName)] -> HsBind RdrName
- mkVarBind :: id -> LHsExpr id -> LHsBind id
- mkHsVarBind :: SrcSpan -> RdrName -> LHsExpr RdrName -> LHsBind RdrName
- mk_easy_FunBind :: SrcSpan -> RdrName -> [LPat RdrName] -> LHsExpr RdrName -> LHsBind RdrName
- mkTopFunBind :: Origin -> Located Name -> [LMatch Name (LHsExpr Name)] -> HsBind Name
- mkPatSynBind :: Located RdrName -> HsPatSynDetails (Located RdrName) -> LPat RdrName -> HsPatSynDir RdrName -> HsBind RdrName
- isInfixFunBind :: HsBindLR id1 id2 -> Bool
- mkHsIntegral :: String -> Integer -> PostTc RdrName Type -> HsOverLit RdrName
- mkHsFractional :: FractionalLit -> PostTc RdrName Type -> HsOverLit RdrName
- mkHsIsString :: String -> FastString -> PostTc RdrName Type -> HsOverLit RdrName
- mkHsString :: String -> HsLit
- mkHsStringPrimLit :: FastString -> HsLit
- mkNPat :: Located (HsOverLit RdrName) -> Maybe (SyntaxExpr RdrName) -> Pat RdrName
- mkNPlusKPat :: Located RdrName -> Located (HsOverLit RdrName) -> Pat RdrName
- nlVarPat :: id -> LPat id
- nlLitPat :: HsLit -> LPat id
- nlConVarPat :: RdrName -> [RdrName] -> LPat RdrName
- nlConVarPatName :: Name -> [Name] -> LPat Name
- nlConPat :: RdrName -> [LPat RdrName] -> LPat RdrName
- nlConPatName :: Name -> [LPat Name] -> LPat Name
- nlInfixConPat :: id -> LPat id -> LPat id -> LPat id
- nlNullaryConPat :: id -> LPat id
- nlWildConPat :: DataCon -> LPat RdrName
- nlWildPat :: LPat RdrName
- nlWildPatName :: LPat Name
- nlWildPatId :: LPat Id
- nlTuplePat :: [LPat id] -> Boxity -> LPat id
- mkParPat :: LPat name -> LPat name
- mkBigLHsVarTup :: [id] -> LHsExpr id
- mkBigLHsTup :: [LHsExpr id] -> LHsExpr id
- mkBigLHsVarPatTup :: [id] -> LPat id
- mkBigLHsPatTup :: [LPat id] -> LPat id
- mkHsAppTy :: LHsType name -> LHsType name -> LHsType name
- mkHsAppTys :: LHsType name -> [LHsType name] -> LHsType name
- userHsTyVarBndrs :: SrcSpan -> [name] -> [LHsTyVarBndr name]
- userHsLTyVarBndrs :: SrcSpan -> [Located name] -> [LHsTyVarBndr name]
- mkLHsSigType :: LHsType RdrName -> LHsSigType RdrName
- mkLHsSigWcType :: LHsType RdrName -> LHsSigWcType RdrName
- mkClassOpSigs :: [LSig RdrName] -> [LSig RdrName]
- nlHsAppTy :: LHsType name -> LHsType name -> LHsType name
- nlHsTyVar :: name -> LHsType name
- nlHsFunTy :: LHsType name -> LHsType name -> LHsType name
- nlHsTyConApp :: name -> [LHsType name] -> LHsType name
- mkTransformStmt :: PostTc idR Type ~ PlaceHolder => [ExprLStmt idL] -> LHsExpr idR -> StmtLR idL idR (LHsExpr idL)
- mkTransformByStmt :: PostTc idR Type ~ PlaceHolder => [ExprLStmt idL] -> LHsExpr idR -> LHsExpr idR -> StmtLR idL idR (LHsExpr idL)
- mkBodyStmt :: Located (bodyR RdrName) -> StmtLR idL RdrName (Located (bodyR RdrName))
- mkBindStmt :: PostTc idR Type ~ PlaceHolder => LPat idL -> Located (bodyR idR) -> StmtLR idL idR (Located (bodyR idR))
- mkTcBindStmt :: LPat Id -> Located (bodyR Id) -> StmtLR Id Id (Located (bodyR Id))
- mkLastStmt :: Located (bodyR idR) -> StmtLR idL idR (Located (bodyR idR))
- emptyTransStmt :: PostTc idR Type ~ PlaceHolder => StmtLR idL idR (LHsExpr idR)
- mkGroupUsingStmt :: PostTc idR Type ~ PlaceHolder => [ExprLStmt idL] -> LHsExpr idR -> StmtLR idL idR (LHsExpr idL)
- mkGroupByUsingStmt :: PostTc idR Type ~ PlaceHolder => [ExprLStmt idL] -> LHsExpr idR -> LHsExpr idR -> StmtLR idL idR (LHsExpr idL)
- emptyRecStmt :: StmtLR idL RdrName bodyR
- emptyRecStmtName :: StmtLR Name Name bodyR
- emptyRecStmtId :: StmtLR Id Id bodyR
- mkRecStmt :: [LStmtLR idL RdrName bodyR] -> StmtLR idL RdrName bodyR
- mkHsSpliceTy :: LHsExpr RdrName -> HsType RdrName
- mkHsSpliceE :: LHsExpr RdrName -> HsExpr RdrName
- mkHsSpliceTE :: LHsExpr RdrName -> HsExpr RdrName
- mkUntypedSplice :: LHsExpr RdrName -> HsSplice RdrName
- mkHsQuasiQuote :: RdrName -> SrcSpan -> FastString -> HsSplice RdrName
- unqualQuasiQuote :: RdrName
- noRebindableInfo :: PlaceHolder
- collectLocalBinders :: HsLocalBindsLR idL idR -> [idL]
- collectHsValBinders :: HsValBindsLR idL idR -> [idL]
- collectHsBindListBinders :: [LHsBindLR idL idR] -> [idL]
- collectHsIdBinders :: HsValBindsLR idL idR -> [idL]
- collectHsBindsBinders :: LHsBindsLR idL idR -> [idL]
- collectHsBindBinders :: HsBindLR idL idR -> [idL]
- collectMethodBinders :: LHsBindsLR RdrName idR -> [Located RdrName]
- collectPatBinders :: LPat a -> [a]
- collectPatsBinders :: [LPat a] -> [a]
- collectLStmtsBinders :: [LStmtLR idL idR body] -> [idL]
- collectStmtsBinders :: [StmtLR idL idR body] -> [idL]
- collectLStmtBinders :: LStmtLR idL idR body -> [idL]
- collectStmtBinders :: StmtLR idL idR body -> [idL]
- hsLTyClDeclBinders :: Located (TyClDecl name) -> ([Located name], [LFieldOcc name])
- hsTyClForeignBinders :: [TyClGroup Name] -> [LInstDecl Name] -> [LForeignDecl Name] -> [Name]
- hsPatSynBinders :: HsValBinds RdrName -> ([Located RdrName], [Located RdrName])
- hsForeignDeclsBinders :: [LForeignDecl name] -> [Located name]
- hsGroupBinders :: HsGroup Name -> [Name]
- hsDataFamInstBinders :: DataFamInstDecl name -> ([Located name], [LFieldOcc name])
- lStmtsImplicits :: [LStmtLR Name idR (Located (body idR))] -> NameSet
- hsValBindsImplicits :: HsValBindsLR Name idR -> NameSet
- lPatImplicits :: LPat Name -> NameSet
Documentation
mkMatchGroup :: Origin -> [LMatch RdrName (Located (body RdrName))] -> MatchGroup RdrName (Located (body RdrName)) Source #
mkMatchGroupName :: Origin -> [LMatch Name (Located (body Name))] -> MatchGroup Name (Located (body Name)) Source #
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 :: Integer -> LHsExpr id Source #
nlHsVarApps :: id -> [id] -> LHsExpr id Source #
mkLHsTupleExpr :: [LHsExpr a] -> LHsExpr a Source #
mkLHsVarTuple :: [a] -> LHsExpr a 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
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
mk_easy_FunBind :: SrcSpan -> RdrName -> [LPat RdrName] -> LHsExpr RdrName -> LHsBind RdrName Source #
mkPatSynBind :: Located RdrName -> HsPatSynDetails (Located RdrName) -> LPat RdrName -> HsPatSynDir RdrName -> HsBind RdrName Source #
isInfixFunBind :: HsBindLR id1 id2 -> Bool Source #
mkHsFractional :: FractionalLit -> PostTc RdrName Type -> HsOverLit RdrName Source #
mkHsIsString :: String -> FastString -> PostTc RdrName Type -> HsOverLit RdrName Source #
mkHsString :: String -> HsLit Source #
mkHsStringPrimLit :: FastString -> HsLit Source #
nlNullaryConPat :: id -> LPat id Source #
nlWildPatName :: LPat Name Source #
nlWildPatId :: LPat Id Source #
mkBigLHsVarTup :: [id] -> LHsExpr id Source #
mkBigLHsTup :: [LHsExpr id] -> LHsExpr id Source #
mkBigLHsVarPatTup :: [id] -> LPat id Source #
mkBigLHsPatTup :: [LPat id] -> LPat id Source #
userHsTyVarBndrs :: SrcSpan -> [name] -> [LHsTyVarBndr name] Source #
userHsLTyVarBndrs :: SrcSpan -> [Located name] -> [LHsTyVarBndr name] Source #
nlHsTyConApp :: name -> [LHsType name] -> LHsType name Source #
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 #
emptyTransStmt :: PostTc idR Type ~ PlaceHolder => StmtLR idL idR (LHsExpr 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 #
emptyRecStmt :: StmtLR idL RdrName bodyR Source #
mkHsQuasiQuote :: RdrName -> SrcSpan -> FastString -> HsSplice RdrName Source #
collectLocalBinders :: HsLocalBindsLR idL idR -> [idL] Source #
collectHsValBinders :: HsValBindsLR idL idR -> [idL] Source #
collectHsBindListBinders :: [LHsBindLR idL idR] -> [idL] Source #
collectHsIdBinders :: HsValBindsLR idL idR -> [idL] Source #
collectHsBindsBinders :: LHsBindsLR idL idR -> [idL] Source #
collectHsBindBinders :: HsBindLR idL idR -> [idL] Source #
collectMethodBinders :: LHsBindsLR RdrName idR -> [Located RdrName] Source #
collectPatBinders :: LPat a -> [a] Source #
collectPatsBinders :: [LPat a] -> [a] 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]
hsTyClForeignBinders :: [TyClGroup Name] -> [LInstDecl Name] -> [LForeignDecl Name] -> [Name] Source #
hsPatSynBinders :: HsValBinds RdrName -> ([Located RdrName], [Located RdrName]) Source #
hsForeignDeclsBinders :: [LForeignDecl name] -> [Located name] Source #
hsDataFamInstBinders :: DataFamInstDecl name -> ([Located name], [LFieldOcc name]) Source #
hsValBindsImplicits :: HsValBindsLR Name idR -> NameSet Source #