Copyright | disco team and contributors |
---|---|
License | BSD-3-Clause |
Maintainer | byorgey@gmail.com |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
Disco.Exhaustiveness.Constraint
Description
The heart of the Lower Your Guards algorithm. Functions for converting constraints detailing pattern matches into a normalized description of everything that is left uncovered.
Synopsis
- data Constraint where
- CMatch :: DataCon -> [TypedVar] -> Constraint
- CNot :: DataCon -> Constraint
- CWasOriginally :: TypedVar -> Constraint
- posMatch :: [Constraint] -> Maybe (DataCon, [TypedVar])
- negMatches :: [Constraint] -> [DataCon]
- type ConstraintFor = (TypedVar, Constraint)
- lookupVar :: TypedVar -> [ConstraintFor] -> TypedVar
- alistLookup :: Eq a => a -> [(a, b)] -> [b]
- onVar :: TypedVar -> [ConstraintFor] -> [Constraint]
- type NormRefType = [ConstraintFor]
- addConstraints :: Members '[Fresh, Reader TyDefCtx] r => NormRefType -> [ConstraintFor] -> MaybeT (Sem r) NormRefType
- addConstraint :: Members '[Fresh, Reader TyDefCtx] r => NormRefType -> ConstraintFor -> MaybeT (Sem r) NormRefType
- addConstraintHelper :: Members '[Fresh, Reader TyDefCtx] r => NormRefType -> ConstraintFor -> MaybeT (Sem r) NormRefType
- breakIf :: Alternative f => Bool -> f ()
- conflictsWith :: Constraint -> Constraint -> Bool
- getConstructorArgs :: DataCon -> [Constraint] -> Maybe [TypedVar]
- substituteVarIDs :: TypedVar -> TypedVar -> [ConstraintFor] -> [ConstraintFor]
- inhabited :: Members '[Fresh, Reader TyDefCtx] r => NormRefType -> TypedVar -> Sem r Bool
- instantiate :: Members '[Fresh, Reader TyDefCtx] r => NormRefType -> TypedVar -> DataCon -> Sem r Bool
Documentation
data Constraint where Source #
Constructors
CMatch :: DataCon -> [TypedVar] -> Constraint | |
CNot :: DataCon -> Constraint | |
CWasOriginally :: TypedVar -> Constraint |
Instances
Show Constraint Source # | |
Defined in Disco.Exhaustiveness.Constraint Methods showsPrec :: Int -> Constraint -> ShowS # show :: Constraint -> String # showList :: [Constraint] -> ShowS # | |
Eq Constraint Source # | |
Defined in Disco.Exhaustiveness.Constraint | |
Ord Constraint Source # | |
Defined in Disco.Exhaustiveness.Constraint Methods compare :: Constraint -> Constraint -> Ordering # (<) :: Constraint -> Constraint -> Bool # (<=) :: Constraint -> Constraint -> Bool # (>) :: Constraint -> Constraint -> Bool # (>=) :: Constraint -> Constraint -> Bool # max :: Constraint -> Constraint -> Constraint # min :: Constraint -> Constraint -> Constraint # |
negMatches :: [Constraint] -> [DataCon] Source #
type ConstraintFor = (TypedVar, Constraint) Source #
alistLookup :: Eq a => a -> [(a, b)] -> [b] Source #
onVar :: TypedVar -> [ConstraintFor] -> [Constraint] Source #
type NormRefType = [ConstraintFor] Source #
addConstraints :: Members '[Fresh, Reader TyDefCtx] r => NormRefType -> [ConstraintFor] -> MaybeT (Sem r) NormRefType Source #
addConstraint :: Members '[Fresh, Reader TyDefCtx] r => NormRefType -> ConstraintFor -> MaybeT (Sem r) NormRefType Source #
addConstraintHelper :: Members '[Fresh, Reader TyDefCtx] r => NormRefType -> ConstraintFor -> MaybeT (Sem r) NormRefType Source #
breakIf :: Alternative f => Bool -> f () Source #
conflictsWith :: Constraint -> Constraint -> Bool Source #
Returns a predicate that returns true if another constraint conflicts with the one given. This alone is not sufficient to test if a constraint can be added, but it filters out the easy negatives early on
getConstructorArgs :: DataCon -> [Constraint] -> Maybe [TypedVar] Source #
Search for a MatchDataCon that is matching on k specifically (there should be at most one, see I4 in section 3.4) and if it exists, return the variable ids of its arguments
substituteVarIDs :: TypedVar -> TypedVar -> [ConstraintFor] -> [ConstraintFor] Source #
substituting y *for* x ie replace the second with the first, replace x with y
inhabited :: Members '[Fresh, Reader TyDefCtx] r => NormRefType -> TypedVar -> Sem r Bool Source #
Deals with I2 from section 3.4 if a variable in the context has a resolvable type, there must be at least one constructor which can be instantiated without contradiction of the refinement type This function tests if this is true
instantiate :: Members '[Fresh, Reader TyDefCtx] r => NormRefType -> TypedVar -> DataCon -> Sem r Bool Source #
Attempts to "instantiate" a match of the dataconstructor k on x If we can add the MatchDataCon constraint to the normalized refinement type without contradiction (a Nothing value), then x is inhabited by k and we return true