ghc-9.2.5: The GHC API
Safe HaskellSafe-Inferred
LanguageHaskell2010

GHC.HsToCore.Pmc.Types

Description

Types used through-out pattern match checking. This module is mostly there to be imported from GHC.HsToCore.Types. The exposed API is that of GHC.HsToCore.Pmc.

These types model the paper Lower Your Guards: A Compositional Pattern-Match Coverage Checker".

Synopsis

LYG syntax

Guard language

newtype SrcInfo Source #

Means by which we identify a source construct for later pretty-printing in a warning message. SDoc for the equation to show, Located for the location.

Constructors

SrcInfo (Located SDoc) 

Instances

Instances details
Outputable SrcInfo Source # 
Instance details

Defined in GHC.HsToCore.Pmc.Types

Methods

ppr :: SrcInfo -> SDoc Source #

data PmGrd Source #

A very simple language for pattern guards. Let bindings, bang patterns, and matching variables against flat constructor patterns. The LYG guard language.

Constructors

PmCon

PmCon x K dicts args corresponds to a K dicts args <- x guard. The args are bound in this construct, the x is just a use. For the arguments' meaning see ConPatOut.

Fields

PmBang

PmBang x corresponds to a seq x True guard. If the extra SrcInfo is present, the bang guard came from a source bang pattern, in which case we might want to report it as redundant. See Note [Dead bang patterns] in GHC.HsToCore.Pmc.Check.

Fields

PmLet

PmLet x expr corresponds to a let x = expr guard. This actually binds x.

Fields

Instances

Instances details
Outputable PmGrd Source #

Should not be user-facing.

Instance details

Defined in GHC.HsToCore.Pmc.Types

Methods

ppr :: PmGrd -> SDoc Source #

newtype GrdVec Source #

A sequence of PmGrds.

Constructors

GrdVec [PmGrd] 

Instances

Instances details
Outputable GrdVec Source #

Format LYG guards as | True <- x, let x = 42, !z

Instance details

Defined in GHC.HsToCore.Pmc.Types

Methods

ppr :: GrdVec -> SDoc Source #

Guard tree language

newtype PmMatchGroup p Source #

A guard tree denoting MatchGroup.

Constructors

PmMatchGroup (NonEmpty (PmMatch p)) 

Instances

Instances details
Outputable p => Outputable (PmMatchGroup p) Source # 
Instance details

Defined in GHC.HsToCore.Pmc.Types

Methods

ppr :: PmMatchGroup p -> SDoc Source #

data PmMatch p Source #

A guard tree denoting Match: A payload describing the pats and a bunch of GRHS.

Constructors

PmMatch 

Fields

Instances

Instances details
Outputable p => Outputable (PmMatch p) Source # 
Instance details

Defined in GHC.HsToCore.Pmc.Types

Methods

ppr :: PmMatch p -> SDoc Source #

data PmGRHSs p Source #

A guard tree denoting GRHSs: A bunch of PmLet guards for local bindings from the GRHSss where clauses and the actual list of GRHS. See Note [Long-distance information for HsLocalBinds] in GHC.HsToCore.Pmc.Desugar.

Constructors

PmGRHSs 

Fields

Instances

Instances details
Outputable p => Outputable (PmGRHSs p) Source # 
Instance details

Defined in GHC.HsToCore.Pmc.Types

Methods

ppr :: PmGRHSs p -> SDoc Source #

data PmGRHS p Source #

A guard tree denoting GRHS: A payload describing the grds and a SrcInfo useful for printing out in warnings messages.

Constructors

PmGRHS 

Fields

Instances

Instances details
Outputable p => Outputable (PmGRHS p) Source # 
Instance details

Defined in GHC.HsToCore.Pmc.Types

Methods

ppr :: PmGRHS p -> SDoc Source #

newtype PmPatBind p Source #

A guard tree denoting a pattern binding.

Constructors

PmPatBind (PmGRHS p) 

Instances

Instances details
Outputable p => Outputable (PmPatBind p) Source # 
Instance details

Defined in GHC.HsToCore.Pmc.Types

Methods

ppr :: PmPatBind p -> SDoc Source #

newtype PmEmptyCase Source #

A guard tree denoting an -XEmptyCase.

Constructors

PmEmptyCase 

Fields

Instances

Instances details
Outputable PmEmptyCase Source # 
Instance details

Defined in GHC.HsToCore.Pmc.Types

Methods

ppr :: PmEmptyCase -> SDoc Source #

Coverage Checking types

data RedSets Source #

Redundancy sets, used to determine redundancy of RHSs and bang patterns (later digested into a CIRB).

Constructors

RedSets 

Fields

  • rs_cov :: !Nablas

    The Covered set; the set of values reaching a particular program point.

  • rs_div :: !Nablas

    The Diverging set; empty if no match can lead to divergence. If it wasn't empty, we have to turn redundancy warnings into inaccessibility warnings for any subclauses.

  • rs_bangs :: !(OrdList (Nablas, SrcInfo))

    If any of the Nablas is empty, the corresponding SrcInfo pin-points a bang pattern in source that is redundant. See Note [Dead bang patterns].

Instances

Instances details
Outputable RedSets Source # 
Instance details

Defined in GHC.HsToCore.Pmc.Types

Methods

ppr :: RedSets -> SDoc Source #

data CheckResult a Source #

Pattern-match coverage check result

Constructors

CheckResult 

Fields

  • cr_ret :: !a

    A hole for redundancy info and covered sets.

  • cr_uncov :: !Nablas

    The set of uncovered values falling out at the bottom. (for -Wincomplete-patterns, but also important state for the algorithm)

  • cr_approx :: !Precision

    A flag saying whether we ran into the maxPmCheckModels limit for the purpose of suggesting to crank it up in the warning message. Writer state.

Instances

Instances details
Functor CheckResult Source # 
Instance details

Defined in GHC.HsToCore.Pmc.Types

Methods

fmap :: (a -> b) -> CheckResult a -> CheckResult b Source #

(<$) :: a -> CheckResult b -> CheckResult a Source #

Outputable a => Outputable (CheckResult a) Source # 
Instance details

Defined in GHC.HsToCore.Pmc.Types

Methods

ppr :: CheckResult a -> SDoc Source #

Pre and post coverage checking synonyms

type Pre = GrdVec Source #

Used as tree payload pre-checking. The LYG guards to check.

type Post = RedSets Source #

Used as tree payload post-checking. The redundancy info we elaborated.

Normalised refinement types