Safe Haskell | None |
---|---|
Language | Haskell2010 |
Utility functions for constructing Core syntax, principally for desugaring
Synopsis
- data EquationInfo = EqnInfo {}
- firstPat :: EquationInfo -> Pat GhcTc
- shiftEqns :: [EquationInfo] -> [EquationInfo]
- data MatchResult = MatchResult CanItFail (CoreExpr -> DsM CoreExpr)
- data CanItFail
- data CaseAlt a = MkCaseAlt {
- alt_pat :: a
- alt_bndrs :: [Var]
- alt_wrapper :: HsWrapper
- alt_result :: MatchResult
- cantFailMatchResult :: CoreExpr -> MatchResult
- alwaysFailMatchResult :: MatchResult
- extractMatchResult :: MatchResult -> CoreExpr -> DsM CoreExpr
- combineMatchResults :: MatchResult -> MatchResult -> MatchResult
- adjustMatchResult :: DsWrapper -> MatchResult -> MatchResult
- adjustMatchResultDs :: (CoreExpr -> DsM CoreExpr) -> MatchResult -> MatchResult
- mkCoLetMatchResult :: CoreBind -> MatchResult -> MatchResult
- mkViewMatchResult :: Id -> CoreExpr -> MatchResult -> MatchResult
- mkGuardedMatchResult :: CoreExpr -> MatchResult -> MatchResult
- matchCanFail :: MatchResult -> Bool
- mkEvalMatchResult :: Id -> Type -> MatchResult -> MatchResult
- mkCoPrimCaseMatchResult :: Id -> Type -> [(Literal, MatchResult)] -> MatchResult
- mkCoAlgCaseMatchResult :: Id -> Type -> [CaseAlt DataCon] -> MatchResult
- mkCoSynCaseMatchResult :: Id -> Type -> CaseAlt PatSyn -> MatchResult
- wrapBind :: Var -> Var -> CoreExpr -> CoreExpr
- wrapBinds :: [(Var, Var)] -> CoreExpr -> CoreExpr
- mkErrorAppDs :: Id -> Type -> SDoc -> DsM CoreExpr
- mkCoreAppDs :: SDoc -> CoreExpr -> CoreExpr -> CoreExpr
- mkCoreAppsDs :: SDoc -> CoreExpr -> [CoreExpr] -> CoreExpr
- mkCastDs :: CoreExpr -> Coercion -> CoreExpr
- seqVar :: Var -> CoreExpr -> CoreExpr
- mkLHsPatTup :: [LPat GhcTc] -> LPat GhcTc
- mkVanillaTuplePat :: [OutPat GhcTc] -> Boxity -> Pat GhcTc
- mkBigLHsVarTupId :: [Id] -> LHsExpr GhcTc
- mkBigLHsTupId :: [LHsExpr GhcTc] -> LHsExpr GhcTc
- mkBigLHsVarPatTupId :: [Id] -> LPat GhcTc
- mkBigLHsPatTupId :: [LPat GhcTc] -> LPat GhcTc
- mkSelectorBinds :: [[Tickish Id]] -> LPat GhcTc -> CoreExpr -> DsM (Id, [(Id, CoreExpr)])
- selectSimpleMatchVarL :: LPat GhcTc -> DsM Id
- selectMatchVars :: [Pat GhcTc] -> DsM [Id]
- selectMatchVar :: Pat GhcTc -> DsM Id
- mkOptTickBox :: [Tickish Id] -> CoreExpr -> CoreExpr
- mkBinaryTickBox :: Int -> Int -> CoreExpr -> DsM CoreExpr
- decideBangHood :: DynFlags -> LPat GhcTc -> LPat GhcTc
- addBang :: LPat GhcTc -> LPat GhcTc
- isTrueLHsExpr :: LHsExpr GhcTc -> Maybe (CoreExpr -> DsM CoreExpr)
Documentation
shiftEqns :: [EquationInfo] -> [EquationInfo] Source #
data MatchResult Source #
MkCaseAlt | |
|
extractMatchResult :: MatchResult -> CoreExpr -> DsM CoreExpr Source #
adjustMatchResult :: DsWrapper -> MatchResult -> MatchResult Source #
adjustMatchResultDs :: (CoreExpr -> DsM CoreExpr) -> MatchResult -> MatchResult Source #
mkCoLetMatchResult :: CoreBind -> MatchResult -> MatchResult Source #
mkViewMatchResult :: Id -> CoreExpr -> MatchResult -> MatchResult Source #
matchCanFail :: MatchResult -> Bool Source #
mkEvalMatchResult :: Id -> Type -> MatchResult -> MatchResult Source #
mkCoPrimCaseMatchResult :: Id -> Type -> [(Literal, MatchResult)] -> MatchResult Source #
mkCoAlgCaseMatchResult :: Id -> Type -> [CaseAlt DataCon] -> MatchResult Source #
mkCoSynCaseMatchResult :: Id -> Type -> CaseAlt PatSyn -> MatchResult Source #
Use -XStrict to add a ! or remove a ~ See Note [decideBangHood]
Unconditionally make a Pat
strict.