Safe Haskell | None |
---|---|
Language | Haskell2010 |
Types used through-out pattern match checking. This module is mostly there to be imported from TcRnTypes. The exposed API is that of GHC.HsToCore.PmCheck.Oracle and GHC.HsToCore.PmCheck.
Synopsis
- data PmLit = PmLit {}
- data PmLitValue
- data PmAltCon
- pmLitType :: PmLit -> Type
- pmAltConType :: PmAltCon -> [Type] -> Type
- data PmEquality
- eqPmAltCon :: PmAltCon -> PmAltCon -> PmEquality
- literalToPmLit :: Type -> Literal -> Maybe PmLit
- negatePmLit :: PmLit -> Maybe PmLit
- overloadPmLit :: Type -> PmLit -> Maybe PmLit
- pmLitAsStringLit :: PmLit -> Maybe FastString
- coreExprAsPmLit :: CoreExpr -> Maybe PmLit
- type ConLikeSet = UniqDSet ConLike
- data PossibleMatches
- = PM (NonEmpty ConLikeSet)
- | NoPM
- data Shared a
- newtype SharedDIdEnv a = SDIE {}
- emptySDIE :: SharedDIdEnv a
- lookupSDIE :: SharedDIdEnv a -> Id -> Maybe a
- sameRepresentativeSDIE :: SharedDIdEnv a -> Id -> Id -> Bool
- setIndirectSDIE :: SharedDIdEnv a -> Id -> Id -> SharedDIdEnv a
- setEntrySDIE :: SharedDIdEnv a -> Id -> a -> SharedDIdEnv a
- traverseSDIE :: Applicative f => (a -> f b) -> SharedDIdEnv a -> f (SharedDIdEnv b)
- data VarInfo = VI {}
- data TmState = TmSt {}
- newtype TyState = TySt (Bag EvVar)
- data Delta = MkDelta {}
- initDelta :: Delta
Representations for Literals and AltCons
Literals (simple and overloaded ones) for pattern match checking.
See Note [Undecidable Equality for PmAltCons]
PmLit | |
|
data PmLitValue Source #
PmLitInt Integer | |
PmLitRat Rational | |
PmLitChar Char | |
PmLitString FastString | |
PmLitOverInt Int Integer | |
PmLitOverRat Int Rational | |
PmLitOverString FastString |
Instances
Outputable PmLitValue Source # | |
Defined in GHC.HsToCore.PmCheck.Types |
Equality on PmAltCon
s
data PmEquality Source #
Undecidable semantic equality result. See Note [Undecidable Equality for PmAltCons]
Instances
Eq PmEquality Source # | |
Defined in GHC.HsToCore.PmCheck.Types (==) :: PmEquality -> PmEquality -> Bool # (/=) :: PmEquality -> PmEquality -> Bool # | |
Show PmEquality Source # | |
Defined in GHC.HsToCore.PmCheck.Types showsPrec :: Int -> PmEquality -> ShowS # show :: PmEquality -> String # showList :: [PmEquality] -> ShowS # | |
Outputable PmEquality Source # | |
Defined in GHC.HsToCore.PmCheck.Types |
eqPmAltCon :: PmAltCon -> PmAltCon -> PmEquality Source #
We can't in general decide whether two PmAltCon
s match the same set of
values. In addition to the reasons in eqPmLit
and eqConLike
, a
PmAltConLike
might or might not represent the same value as a PmAltLit
.
See Note [Undecidable Equality for PmAltCons].
Just True
==> Surely equalJust False
==> Surely different (non-overlapping, even!)Nothing
==> Equality relation undecidable
Examples (omitting some constructor wrapping):
eqPmAltCon (LitInt 42) (LitInt 1) == Just False
: Lit equality is decidableeqPmAltCon (DataCon A) (DataCon B) == Just False
: DataCon equality is decidableeqPmAltCon (LitOverInt 42) (LitOverInt 1) == Nothing
: OverLit equality is undecidableeqPmAltCon (PatSyn PA) (PatSyn PB) == Nothing
: PatSyn equality is undecidableeqPmAltCon (DataCon I#) (LitInt 1) == Nothing
: DataCon to Lit comparisons are undecidable without reasoning about the wrappedInt#
eqPmAltCon (LitOverInt 1) (LitOverInt 1) == Just True
: We assume reflexivity for overloaded literalseqPmAltCon (PatSyn PA) (PatSyn PA) == Just True
: We assume reflexivity for Pattern Synonyms
Operations on PmLit
pmLitAsStringLit :: PmLit -> Maybe FastString Source #
Caching partially matched COMPLETE sets
type ConLikeSet = UniqDSet ConLike Source #
data PossibleMatches Source #
A data type caching the results of completeMatchConLikes
with support for
deletion of constructors that were already matched on.
PM (NonEmpty ConLikeSet) | Each ConLikeSet is a (subset of) the constructors in a COMPLETE set
|
NoPM | No COMPLETE set for this type (yet). Think of overloaded literals. |
Instances
Outputable PossibleMatches Source # | |
Defined in GHC.HsToCore.PmCheck.Types |
A DIdEnv
where entries may be shared
Either Indirect x
, meaning the value is represented by that of x
, or
an Entry
containing containing the actual value it represents.
Instances
newtype SharedDIdEnv a Source #
A DIdEnv
in which entries can be shared by multiple Id
s.
Merge equivalence classes of two Ids by setIndirectSDIE
and set the entry
of an Id with setEntrySDIE
.
Instances
emptySDIE :: SharedDIdEnv a Source #
lookupSDIE :: SharedDIdEnv a -> Id -> Maybe a Source #
sameRepresentativeSDIE :: SharedDIdEnv a -> Id -> Id -> Bool Source #
Check if two variables are part of the same equivalence class.
setIndirectSDIE :: SharedDIdEnv a -> Id -> Id -> SharedDIdEnv a Source #
setIndirectSDIE env x y
sets x
's Entry
to Indirect y
, thereby
merging x
's equivalence class into y
's. This will discard all info on
x
!
setEntrySDIE :: SharedDIdEnv a -> Id -> a -> SharedDIdEnv a Source #
setEntrySDIE env x a
sets the Entry
x
is associated with to a
,
thereby modifying its whole equivalence class.
traverseSDIE :: Applicative f => (a -> f b) -> SharedDIdEnv a -> f (SharedDIdEnv b) Source #
The pattern match oracle
Information about an Id
. Stores positive (vi_pos
) facts, like x ~ Just 42
,
and negative (vi_neg
) facts, like "x is not (:)".
Also caches the type (vi_ty
), the PossibleMatches
of a COMPLETE set
(vi_cache
).
Subject to Note [The Pos/Neg invariant] in PmOracle.
VI | |
|
The term oracle state. Stores VarInfo
for encountered Id
s. These
entries are possibly shared when we figure out that two variables must be
equal, thus represent the same set of values.
See Note [TmState invariants] in Oracle.
TmSt | |
|
The type oracle state. A poor man's InsertSet
: The invariant is
that all constraints in there are mutually compatible.
Term and type constraints to accompany each value vector abstraction. For efficiency, we store the term oracle state instead of the term constraints.