| Safe Haskell | Safe-Inferred | 
|---|---|
| Language | Haskell2010 | 
GHC.HsToCore.Utils
Description
Utility functions for constructing Core syntax, principally for desugaring
Synopsis
- data EquationInfo = EqnInfo {}
- firstPat :: EquationInfo -> Pat GhcTc
- shiftEqns :: Functor f => f EquationInfo -> f EquationInfo
- data MatchResult a- = MR_Infallible (DsM a)
- | MR_Fallible (CoreExpr -> DsM a)
 
- data CaseAlt a = MkCaseAlt {- alt_pat :: a
- alt_bndrs :: [Var]
- alt_wrapper :: HsWrapper
- alt_result :: MatchResult CoreExpr
 
- cantFailMatchResult :: CoreExpr -> MatchResult CoreExpr
- alwaysFailMatchResult :: MatchResult CoreExpr
- extractMatchResult :: MatchResult CoreExpr -> CoreExpr -> DsM CoreExpr
- combineMatchResults :: MatchResult CoreExpr -> MatchResult CoreExpr -> MatchResult CoreExpr
- adjustMatchResultDs :: (a -> DsM b) -> MatchResult a -> MatchResult b
- shareFailureHandler :: MatchResult CoreExpr -> MatchResult CoreExpr
- dsHandleMonadicFailure :: HsDoFlavour -> LPat GhcTc -> MatchResult CoreExpr -> FailOperator GhcTc -> DsM CoreExpr
- mkCoLetMatchResult :: CoreBind -> MatchResult CoreExpr -> MatchResult CoreExpr
- mkViewMatchResult :: Id -> CoreExpr -> MatchResult CoreExpr -> MatchResult CoreExpr
- mkGuardedMatchResult :: CoreExpr -> MatchResult CoreExpr -> MatchResult CoreExpr
- matchCanFail :: MatchResult a -> Bool
- mkEvalMatchResult :: Id -> Type -> MatchResult CoreExpr -> MatchResult CoreExpr
- mkCoPrimCaseMatchResult :: Id -> Type -> [(Literal, MatchResult CoreExpr)] -> MatchResult CoreExpr
- mkCoAlgCaseMatchResult :: Id -> Type -> NonEmpty (CaseAlt DataCon) -> MatchResult CoreExpr
- mkCoSynCaseMatchResult :: Id -> Type -> CaseAlt PatSyn -> MatchResult CoreExpr
- 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
- mkFailExpr :: HsMatchContext GhcRn -> Type -> DsM CoreExpr
- seqVar :: Var -> CoreExpr -> CoreExpr
- mkLHsPatTup :: [LPat GhcTc] -> LPat GhcTc
- mkVanillaTuplePat :: [LPat GhcTc] -> Boxity -> Pat GhcTc
- mkBigLHsVarTupId :: [Id] -> LHsExpr GhcTc
- mkBigLHsTupId :: [LHsExpr GhcTc] -> LHsExpr GhcTc
- mkBigLHsVarPatTupId :: [Id] -> LPat GhcTc
- mkBigLHsPatTupId :: [LPat GhcTc] -> LPat GhcTc
- mkSelectorBinds :: [[CoreTickish]] -> LPat GhcTc -> CoreExpr -> DsM (Id, [(Id, CoreExpr)])
- selectSimpleMatchVarL :: Mult -> LPat GhcTc -> DsM Id
- selectMatchVars :: [(Mult, Pat GhcTc)] -> DsM [Id]
- selectMatchVar :: Mult -> Pat GhcTc -> DsM Id
- mkOptTickBox :: [CoreTickish] -> CoreExpr -> CoreExpr
- mkBinaryTickBox :: Int -> Int -> CoreExpr -> DsM CoreExpr
- decideBangHood :: DynFlags -> LPat GhcTc -> LPat GhcTc
- isTrueLHsExpr :: LHsExpr GhcTc -> Maybe (CoreExpr -> DsM CoreExpr)
Documentation
data EquationInfo Source #
Constructors
| EqnInfo | |
| Fields 
 | |
Instances
| Outputable EquationInfo Source # | |
| Defined in GHC.HsToCore.Monad Methods ppr :: EquationInfo -> SDoc # | |
shiftEqns :: Functor f => f EquationInfo -> f EquationInfo Source #
data MatchResult a Source #
This is a value of type a with potentially a CoreExpr-shaped hole in it. This is used to deal with cases where we are potentially handling pattern match failure, and want to later specify how failure is handled.
Constructors
| MR_Infallible (DsM a) | We represent the case where there is no hole without a function from
  | 
| MR_Fallible (CoreExpr -> DsM a) | 
Instances
| Applicative MatchResult Source # | Product is an "or" on fallibility---the combined match result is infallible only if the left and right argument match results both were. This is useful for combining a bunch of alternatives together and then
 getting the overall fallibility of the entire group. See  | 
| Defined in GHC.HsToCore.Monad Methods pure :: a -> MatchResult a # (<*>) :: MatchResult (a -> b) -> MatchResult a -> MatchResult b # liftA2 :: (a -> b -> c) -> MatchResult a -> MatchResult b -> MatchResult c # (*>) :: MatchResult a -> MatchResult b -> MatchResult b # (<*) :: MatchResult a -> MatchResult b -> MatchResult a # | |
| Functor MatchResult Source # | |
| Defined in GHC.HsToCore.Monad Methods fmap :: (a -> b) -> MatchResult a -> MatchResult b # (<$) :: a -> MatchResult b -> MatchResult a # | |
Constructors
| MkCaseAlt | |
| Fields 
 | |
extractMatchResult :: MatchResult CoreExpr -> CoreExpr -> DsM CoreExpr Source #
combineMatchResults :: MatchResult CoreExpr -> MatchResult CoreExpr -> MatchResult CoreExpr Source #
adjustMatchResultDs :: (a -> DsM b) -> MatchResult a -> MatchResult b Source #
dsHandleMonadicFailure :: HsDoFlavour -> LPat GhcTc -> MatchResult CoreExpr -> FailOperator GhcTc -> DsM CoreExpr Source #
mkViewMatchResult :: Id -> CoreExpr -> MatchResult CoreExpr -> MatchResult CoreExpr Source #
matchCanFail :: MatchResult a -> Bool Source #
mkEvalMatchResult :: Id -> Type -> MatchResult CoreExpr -> MatchResult CoreExpr Source #
mkCoPrimCaseMatchResult :: Id -> Type -> [(Literal, MatchResult CoreExpr)] -> MatchResult CoreExpr Source #
mkCoSynCaseMatchResult :: Id -> Type -> CaseAlt PatSyn -> MatchResult CoreExpr Source #
mkFailExpr :: HsMatchContext GhcRn -> Type -> DsM CoreExpr Source #
Arguments
| :: [[CoreTickish]] | ticks to add, possibly | 
| -> LPat GhcTc | The pattern | 
| -> CoreExpr | Expression to which the pattern is bound | 
| -> DsM (Id, [(Id, CoreExpr)]) | Id the rhs is bound to, for desugaring strict binds (see Note [Desugar Strict binds] in GHC.HsToCore.Binds) and all the desugared binds | 
mkOptTickBox :: [CoreTickish] -> CoreExpr -> CoreExpr Source #
Use -XStrict to add a ! or remove a ~ See Note [decideBangHood]