ghc-6.12.3: The GHC APISource codeContentsIndex
HsUtils
Documentation
mkHsPar :: LHsExpr id -> LHsExpr idSource
mkSimpleMatch :: [LPat id] -> LHsExpr id -> LMatch idSource
unguardedGRHSs :: LHsExpr id -> GRHSs idSource
unguardedRHS :: LHsExpr id -> [LGRHS id]Source
mkHsAppTy :: LHsType name -> LHsType name -> LHsType nameSource
mkHsApp :: LHsExpr name -> LHsExpr name -> LHsExpr nameSource
nlHsTyApp :: name -> [Type] -> LHsExpr nameSource
mkLHsWrap :: HsWrapper -> LHsExpr id -> LHsExpr idSource
mkHsWrap :: HsWrapper -> HsExpr id -> HsExpr idSource
mkHsWrapCoI :: CoercionI -> HsExpr id -> HsExpr idSource
coiToHsWrapper :: CoercionI -> HsWrapperSource
mkHsLam :: [LPat id] -> LHsExpr id -> LHsExpr idSource
mkMatchGroup :: [LMatch id] -> MatchGroup idSource
mkHsDictLet :: LHsBinds Id -> LHsExpr Id -> LHsExpr IdSource
mkHsConApp :: DataCon -> [Type] -> [HsExpr Id] -> LHsExpr IdSource
mkSimpleHsAlt :: LPat id -> LHsExpr id -> LMatch idSource
mkHsIntegral :: Integer -> PostTcType -> HsOverLit idSource
mkHsFractional :: Rational -> PostTcType -> HsOverLit idSource
mkHsIsString :: FastString -> PostTcType -> HsOverLit idSource
mkHsDo :: HsStmtContext Name -> [LStmt id] -> LHsExpr id -> HsExpr idSource
mkNPat :: HsOverLit id -> Maybe (SyntaxExpr id) -> Pat idSource
mkNPlusKPat :: Located id -> HsOverLit id -> Pat idSource
mkTransformStmt :: [LStmt idL] -> LHsExpr idR -> StmtLR idL idRSource
mkTransformByStmt :: [LStmt idL] -> LHsExpr idR -> LHsExpr idR -> StmtLR idL idRSource
mkGroupUsingStmt :: [LStmt idL] -> LHsExpr idR -> StmtLR idL idRSource
mkGroupByStmt :: [LStmt idL] -> LHsExpr idR -> StmtLR idL idRSource
mkGroupByUsingStmt :: [LStmt idL] -> LHsExpr idR -> LHsExpr idR -> StmtLR idL idRSource
mkExprStmt :: LHsExpr idR -> StmtLR idL idRSource
mkBindStmt :: LPat idL -> LHsExpr idR -> StmtLR idL idRSource
emptyRecStmt :: StmtLR idL idRSource
mkRecStmt :: [LStmtLR idL idR] -> StmtLR idL idRSource
noRebindableInfo :: BoolSource
mkHsOpApp :: LHsExpr id -> id -> LHsExpr id -> HsExpr idSource
mkHsSplice :: LHsExpr RdrName -> HsSplice RdrNameSource
unqualSplice :: RdrNameSource
mkHsQuasiQuote :: RdrName -> SrcSpan -> FastString -> HsQuasiQuote RdrNameSource
unqualQuasiQuote :: RdrNameSource
mkHsString :: String -> HsLitSource
userHsTyVarBndrs :: [Located name] -> [Located (HsTyVarBndr name)]Source
nlHsVar :: id -> LHsExpr idSource
nlHsLit :: HsLit -> LHsExpr idSource
nlVarPat :: id -> LPat idSource
nlLitPat :: HsLit -> LPat idSource
nlHsApp :: LHsExpr id -> LHsExpr id -> LHsExpr idSource
nlHsIntLit :: Integer -> LHsExpr idSource
nlHsApps :: id -> [LHsExpr id] -> LHsExpr idSource
nlHsVarApps :: id -> [id] -> LHsExpr idSource
nlConVarPat :: id -> [id] -> LPat idSource
nlInfixConPat :: id -> LPat id -> LPat id -> LPat idSource
nlConPat :: id -> [LPat id] -> LPat idSource
nlNullaryConPat :: id -> LPat idSource
nlWildConPat :: DataCon -> LPat RdrNameSource
nlWildPat :: LPat idSource
nlHsDo :: HsStmtContext Name -> [LStmt id] -> LHsExpr id -> LHsExpr idSource
nlHsOpApp :: LHsExpr id -> id -> LHsExpr id -> LHsExpr idSource
nlHsLam :: LMatch id -> LHsExpr idSource
nlHsPar :: LHsExpr id -> LHsExpr idSource
nlHsIf :: LHsExpr id -> LHsExpr id -> LHsExpr id -> LHsExpr idSource
nlHsCase :: LHsExpr id -> [LMatch id] -> LHsExpr idSource
nlList :: [LHsExpr id] -> LHsExpr idSource
nlHsAppTy :: LHsType name -> LHsType name -> LHsType nameSource
nlHsTyVar :: name -> LHsType nameSource
nlHsFunTy :: LHsType name -> LHsType name -> LHsType nameSource
nlHsTyConApp :: name -> [LHsType name] -> LHsType nameSource
mkLHsTupleExpr :: [LHsExpr a] -> LHsExpr aSource
mkLHsVarTuple :: [a] -> LHsExpr aSource
nlTuplePat :: [LPat id] -> Boxity -> LPat idSource
missingTupArg :: HsTupArg aSource
mkFunBind :: Located id -> [LMatch id] -> HsBind idSource
mkVarBind :: SrcSpan -> id -> LHsExpr id -> LHsBind idSource
mk_easy_FunBind :: SrcSpan -> id -> [LPat id] -> LHsExpr id -> LHsBind idSource
mk_FunBind :: SrcSpan -> id -> [([LPat id], LHsExpr id)] -> LHsBind idSource
mkMatch :: [LPat id] -> LHsExpr id -> HsLocalBinds id -> LMatch idSource
collectLocalBinders :: HsLocalBindsLR idL idR -> [Located idL]Source
collectHsValBinders :: HsValBindsLR idL idR -> [Located idL]Source
collectAcc :: HsBindLR idL idR -> [Located idL] -> [Located idL]Source
collectHsBindBinders :: LHsBindsLR idL idR -> [idL]Source
collectHsBindLocatedBinders :: LHsBindsLR idL idR -> [Located idL]Source
collectLStmtsBinders :: [LStmtLR idL idR] -> [Located idL]Source
collectStmtsBinders :: [StmtLR idL idR] -> [Located idL]Source
collectLStmtBinders :: LStmtLR idL idR -> [Located idL]Source
collectStmtBinders :: StmtLR idL idR -> [Located idL]Source
collectPatBinders :: LPat a -> [a]Source
collectLocatedPatBinders :: LPat a -> [Located a]Source
collectPatsBinders :: [LPat a] -> [a]Source
collectLocatedPatsBinders :: [LPat a] -> [Located a]Source
collectl :: LPat name -> [Located name] -> [Located name]Source
collectSigTysFromPats :: [InPat name] -> [LHsType name]Source
collectSigTysFromPat :: InPat name -> [LHsType name]Source
collect_lpat :: InPat name -> [LHsType name] -> [LHsType name]Source
collect_pat :: Pat name -> [LHsType name] -> [LHsType name]Source
Produced by Haddock version 2.6.1