ghc-lib-0.20201101: The GHC API, decoupled from GHC versions
Safe HaskellNone
LanguageHaskell2010

GHC.HsToCore.Utils

Description

Utility functions for constructing Core syntax, principally for desugaring

Synopsis

Documentation

data EquationInfo Source #

Constructors

EqnInfo 

Fields

  • eqn_pats :: [Pat GhcTc]

    The patterns for an equation

    NB: We have already applied decideBangHood to these patterns. See Note [decideBangHood] in GHC.HsToCore.Utils

  • eqn_orig :: Origin

    Was this equation present in the user source?

    This helps us avoid warnings on patterns that GHC elaborated.

    For instance, the pattern -1 :: Word gets desugared into W# :: Word, but we shouldn't warn about an overflowed literal for both of these cases.

  • eqn_rhs :: MatchResult CoreExpr

    What to do after match

Instances

Instances details
Outputable EquationInfo Source # 
Instance details

Defined in GHC.HsToCore.Monad

Methods

ppr :: EquationInfo -> SDoc

firstPat :: EquationInfo -> Pat GhcTc 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 CoreExpr, like this, because sometimes we have nothing to put in the hole and so want to be sure there is in fact no hole.

MR_Fallible (CoreExpr -> DsM a) 

Instances

Instances details
Functor MatchResult Source # 
Instance details

Defined in GHC.HsToCore.Monad

Methods

fmap :: (a -> b) -> MatchResult a -> MatchResult b #

(<$) :: a -> MatchResult b -> MatchResult a #

Applicative MatchResult Source #

Product is an "or" on falliblity---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 falliblity of the entire group. See mkDataConCase for an example.

Instance details

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 #

data CaseAlt a Source #

Constructors

MkCaseAlt 

Fields

cantFailMatchResult :: CoreExpr -> MatchResult CoreExpr Source #

extractMatchResult :: MatchResult CoreExpr -> CoreExpr -> DsM CoreExpr Source #

combineMatchResults :: MatchResult CoreExpr -> MatchResult CoreExpr -> MatchResult CoreExpr Source #

dsHandleMonadicFailure :: HsStmtContext GhcRn -> LPat GhcTc -> MatchResult CoreExpr -> FailOperator GhcTc -> DsM CoreExpr Source #

mkCoLetMatchResult :: CoreBind -> MatchResult CoreExpr -> MatchResult CoreExpr Source #

mkViewMatchResult :: Id -> CoreExpr -> MatchResult CoreExpr -> MatchResult CoreExpr Source #

mkGuardedMatchResult :: CoreExpr -> MatchResult CoreExpr -> MatchResult CoreExpr Source #

mkEvalMatchResult :: Id -> Type -> MatchResult CoreExpr -> MatchResult CoreExpr Source #

mkCoPrimCaseMatchResult :: Id -> Type -> [(Literal, MatchResult CoreExpr)] -> MatchResult CoreExpr Source #

mkCoAlgCaseMatchResult Source #

Arguments

:: Id

Scrutinee

-> Type

Type of exp

-> NonEmpty (CaseAlt DataCon)

Alternatives (bndrs *include* tyvars, dicts)

-> MatchResult CoreExpr 

wrapBind :: Var -> Var -> CoreExpr -> CoreExpr Source #

wrapBinds :: [(Var, Var)] -> CoreExpr -> CoreExpr Source #

mkErrorAppDs :: Id -> Type -> SDoc -> DsM CoreExpr Source #

mkCoreAppDs :: SDoc -> CoreExpr -> CoreExpr -> CoreExpr Source #

mkCoreAppsDs :: SDoc -> CoreExpr -> [CoreExpr] -> CoreExpr Source #

mkCastDs :: CoreExpr -> Coercion -> CoreExpr Source #

seqVar :: Var -> CoreExpr -> CoreExpr Source #

mkLHsPatTup :: [LPat GhcTc] -> LPat GhcTc Source #

mkVanillaTuplePat :: [LPat GhcTc] -> Boxity -> Pat GhcTc Source #

mkBigLHsVarTupId :: [Id] -> LHsExpr GhcTc Source #

mkBigLHsTupId :: [LHsExpr GhcTc] -> LHsExpr GhcTc Source #

mkBigLHsVarPatTupId :: [Id] -> LPat GhcTc Source #

mkBigLHsPatTupId :: [LPat GhcTc] -> LPat GhcTc Source #

mkSelectorBinds Source #

Arguments

:: [[Tickish Id]]

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

selectSimpleMatchVarL :: Mult -> LPat GhcTc -> DsM Id Source #

selectMatchVars :: [(Mult, Pat GhcTc)] -> DsM [Id] Source #

selectMatchVar :: Mult -> Pat GhcTc -> DsM Id Source #

mkOptTickBox :: [Tickish Id] -> CoreExpr -> CoreExpr Source #

mkBinaryTickBox :: Int -> Int -> CoreExpr -> DsM CoreExpr Source #

decideBangHood Source #

Arguments

:: DynFlags 
-> LPat GhcTc

Original pattern

-> LPat GhcTc 

Use -XStrict to add a ! or remove a ~ See Note [decideBangHood]

isTrueLHsExpr :: LHsExpr GhcTc -> Maybe (CoreExpr -> DsM CoreExpr) Source #