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