Safe Haskell | None |
---|
- mkHsPar :: LHsExpr id -> LHsExpr id
- mkHsApp :: LHsExpr name -> LHsExpr name -> LHsExpr name
- mkHsConApp :: DataCon -> [Type] -> [HsExpr Id] -> LHsExpr Id
- mkSimpleHsAlt :: LPat id -> LHsExpr id -> LMatch id
- mkSimpleMatch :: [LPat id] -> LHsExpr id -> LMatch id
- unguardedGRHSs :: LHsExpr id -> GRHSs id
- unguardedRHS :: LHsExpr id -> [LGRHS id]
- mkMatchGroup :: [LMatch id] -> MatchGroup id
- mkMatch :: [LPat id] -> LHsExpr id -> HsLocalBinds id -> LMatch id
- mkHsLam :: [LPat id] -> LHsExpr id -> LHsExpr id
- mkHsIf :: LHsExpr id -> LHsExpr id -> LHsExpr id -> HsExpr id
- mkHsWrap :: HsWrapper -> HsExpr id -> HsExpr id
- mkLHsWrap :: HsWrapper -> LHsExpr id -> LHsExpr id
- mkHsWrapCo :: TcCoercion -> HsExpr id -> HsExpr id
- mkLHsWrapCo :: TcCoercion -> LHsExpr id -> LHsExpr id
- coToHsWrapper :: TcCoercion -> HsWrapper
- mkHsDictLet :: TcEvBinds -> LHsExpr Id -> LHsExpr Id
- mkHsLams :: [TyVar] -> [EvVar] -> LHsExpr Id -> LHsExpr Id
- mkHsOpApp :: LHsExpr id -> id -> LHsExpr id -> HsExpr id
- mkHsDo :: HsStmtContext Name -> [LStmt id] -> HsExpr id
- mkHsComp :: HsStmtContext Name -> [LStmt id] -> LHsExpr id -> HsExpr id
- mkHsWrapPat :: HsWrapper -> Pat id -> Type -> Pat id
- mkHsWrapPatCo :: TcCoercion -> Pat id -> Type -> Pat id
- mkLHsPar :: LHsExpr name -> LHsExpr name
- nlHsTyApp :: name -> [Type] -> LHsExpr name
- nlHsVar :: id -> LHsExpr id
- nlHsLit :: HsLit -> LHsExpr id
- nlHsApp :: LHsExpr id -> LHsExpr id -> LHsExpr id
- nlHsApps :: id -> [LHsExpr id] -> LHsExpr id
- nlHsIntLit :: Integer -> LHsExpr id
- nlHsVarApps :: id -> [id] -> LHsExpr id
- nlHsDo :: HsStmtContext Name -> [LStmt id] -> LHsExpr id
- nlHsOpApp :: LHsExpr id -> id -> LHsExpr id -> LHsExpr id
- nlHsLam :: LMatch id -> LHsExpr id
- nlHsPar :: LHsExpr id -> LHsExpr id
- nlHsIf :: LHsExpr id -> LHsExpr id -> LHsExpr id -> LHsExpr id
- nlHsCase :: LHsExpr id -> [LMatch id] -> LHsExpr id
- nlList :: [LHsExpr id] -> LHsExpr id
- mkLHsTupleExpr :: [LHsExpr a] -> LHsExpr a
- mkLHsVarTuple :: [a] -> LHsExpr a
- missingTupArg :: HsTupArg a
- mkFunBind :: Located RdrName -> [LMatch 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 :: Located Name -> [LMatch Name] -> HsBind Name
- mkHsIntegral :: Integer -> PostTcType -> HsOverLit id
- mkHsFractional :: FractionalLit -> PostTcType -> HsOverLit id
- mkHsIsString :: FastString -> PostTcType -> HsOverLit id
- mkHsString :: String -> HsLit
- mkNPat :: HsOverLit id -> Maybe (SyntaxExpr id) -> Pat id
- mkNPlusKPat :: Located id -> HsOverLit id -> Pat id
- nlVarPat :: id -> LPat id
- nlLitPat :: HsLit -> LPat id
- nlConVarPat :: id -> [id] -> LPat id
- nlConPat :: id -> [LPat id] -> LPat id
- nlInfixConPat :: id -> LPat id -> LPat id -> LPat id
- nlNullaryConPat :: id -> LPat id
- nlWildConPat :: DataCon -> LPat RdrName
- nlWildPat :: LPat id
- nlTuplePat :: [LPat id] -> Boxity -> LPat id
- mkParPat :: LPat name -> LPat name
- mkHsAppTy :: LHsType name -> LHsType name -> LHsType name
- userHsTyVarBndrs :: SrcSpan -> [name] -> [Located (HsTyVarBndr name)]
- 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 :: [LStmt idL] -> LHsExpr idR -> StmtLR idL idR
- mkTransformByStmt :: [LStmt idL] -> LHsExpr idR -> LHsExpr idR -> StmtLR idL idR
- mkExprStmt :: LHsExpr idR -> StmtLR idL idR
- mkBindStmt :: LPat idL -> LHsExpr idR -> StmtLR idL idR
- mkLastStmt :: LHsExpr idR -> StmtLR idL idR
- emptyTransStmt :: StmtLR idL idR
- mkGroupUsingStmt :: [LStmt idL] -> LHsExpr idR -> StmtLR idL idR
- mkGroupByUsingStmt :: [LStmt idL] -> LHsExpr idR -> LHsExpr idR -> StmtLR idL idR
- emptyRecStmt :: StmtLR idL idR
- mkRecStmt :: [LStmtLR idL idR] -> StmtLR idL idR
- unqualSplice :: RdrName
- mkHsSpliceTy :: LHsExpr RdrName -> HsType RdrName
- mkHsSplice :: LHsExpr RdrName -> HsSplice RdrName
- mkHsQuasiQuote :: RdrName -> SrcSpan -> FastString -> HsQuasiQuote RdrName
- unqualQuasiQuote :: RdrName
- noRebindableInfo :: Bool
- collectLocalBinders :: HsLocalBindsLR idL idR -> [idL]
- collectHsValBinders :: HsValBindsLR idL idR -> [idL]
- collectHsBindListBinders :: [LHsBindLR 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] -> [idL]
- collectStmtsBinders :: [StmtLR idL idR] -> [idL]
- collectLStmtBinders :: LStmtLR idL idR -> [idL]
- collectStmtBinders :: StmtLR idL idR -> [idL]
- hsLTyClDeclBinders :: Eq name => Located (TyClDecl name) -> [Located name]
- hsTyClDeclBinders :: Eq name => TyClDecl name -> [Located name]
- hsTyClDeclsBinders :: [[LTyClDecl Name]] -> [Located (InstDecl Name)] -> [Name]
- hsForeignDeclsBinders :: [LForeignDecl Name] -> [Name]
- hsGroupBinders :: HsGroup Name -> [Name]
- hsFamInstBinders :: Eq name => FamInstDecl name -> [Located name]
- lStmtsImplicits :: [LStmtLR Name idR] -> NameSet
- hsValBindsImplicits :: HsValBindsLR Name idR -> NameSet
- lPatImplicits :: LPat Name -> NameSet
Documentation
mkSimpleHsAlt :: LPat id -> LHsExpr id -> LMatch idSource
mkSimpleMatch :: [LPat id] -> LHsExpr id -> LMatch idSource
unguardedGRHSs :: LHsExpr id -> GRHSs idSource
unguardedRHS :: LHsExpr id -> [LGRHS id]Source
mkMatchGroup :: [LMatch id] -> MatchGroup idSource
mkHsWrapCo :: TcCoercion -> HsExpr id -> HsExpr idSource
mkLHsWrapCo :: TcCoercion -> LHsExpr id -> LHsExpr idSource
mkHsWrapPatCo :: TcCoercion -> Pat id -> Type -> Pat idSource
nlHsIntLit :: Integer -> LHsExpr idSource
nlHsVarApps :: id -> [id] -> LHsExpr idSource
mkLHsTupleExpr :: [LHsExpr a] -> LHsExpr aSource
mkLHsVarTuple :: [a] -> LHsExpr aSource
mkHsIntegral :: Integer -> PostTcType -> HsOverLit idSource
mkHsFractional :: FractionalLit -> PostTcType -> HsOverLit idSource
mkHsIsString :: FastString -> PostTcType -> HsOverLit idSource
mkHsString :: String -> HsLitSource
mkNPlusKPat :: Located id -> HsOverLit id -> Pat idSource
nlConVarPat :: id -> [id] -> LPat idSource
nlInfixConPat :: id -> LPat id -> LPat id -> LPat idSource
nlNullaryConPat :: id -> LPat idSource
nlWildConPat :: DataCon -> LPat RdrNameSource
nlTuplePat :: [LPat id] -> Boxity -> LPat idSource
userHsTyVarBndrs :: SrcSpan -> [name] -> [Located (HsTyVarBndr name)]Source
nlHsTyConApp :: name -> [LHsType name] -> LHsType nameSource
mkTransformStmt :: [LStmt idL] -> LHsExpr idR -> StmtLR idL idRSource
mkExprStmt :: LHsExpr idR -> StmtLR idL idRSource
mkBindStmt :: LPat idL -> LHsExpr idR -> StmtLR idL idRSource
mkLastStmt :: LHsExpr idR -> StmtLR idL idRSource
emptyTransStmt :: StmtLR idL idRSource
mkGroupUsingStmt :: [LStmt idL] -> LHsExpr idR -> StmtLR idL idRSource
emptyRecStmt :: StmtLR idL idRSource
mkHsQuasiQuote :: RdrName -> SrcSpan -> FastString -> HsQuasiQuote RdrNameSource
collectLocalBinders :: HsLocalBindsLR idL idR -> [idL]Source
collectHsValBinders :: HsValBindsLR idL idR -> [idL]Source
collectHsBindListBinders :: [LHsBindLR 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] -> [idL]Source
collectStmtsBinders :: [StmtLR idL idR] -> [idL]Source
collectLStmtBinders :: LStmtLR idL idR -> [idL]Source
collectStmtBinders :: StmtLR idL idR -> [idL]Source
hsLTyClDeclBinders :: Eq name => Located (TyClDecl name) -> [Located name]Source
Returns all the binding names of the decl, along with their SrcLocs. The first one is guaranteed to be the name of the decl. For record fields mentioned in multiple constructors, the SrcLoc will be from the first occurence. We use the equality to filter out duplicate field names
hsTyClDeclBinders :: Eq name => TyClDecl name -> [Located name]Source
hsForeignDeclsBinders :: [LForeignDecl Name] -> [Name]Source
hsGroupBinders :: HsGroup Name -> [Name]Source
hsFamInstBinders :: Eq name => FamInstDecl name -> [Located name]Source
lStmtsImplicits :: [LStmtLR Name idR] -> NameSetSource
hsValBindsImplicits :: HsValBindsLR Name idR -> NameSetSource
lPatImplicits :: LPat Name -> NameSetSource