Copyright | disco team and contributors |
---|---|
License | BSD-3-Clause |
Maintainer | byorgey@gmail.com |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
Disco.Exhaustiveness
Description
Entry point into the exhaustiveness checker. Converts information into a format the checker understands, then pretty prints the results of running it.
Synopsis
- checkClauses :: Members '[Fresh, Reader TyDefCtx, Output (Message ann), Embed IO] r => Name ATerm -> [Type] -> NonEmpty [APattern] -> Sem r ()
- prettyPrintExample :: ExamplePat -> Sem r (Doc ann)
- prettyPrintPattern :: Members '[Reader PA, LFresh] r => Pattern -> Sem r (Doc ann)
- exampleToDiscoPattern :: ExamplePat -> Pattern
- resugarPair :: ExamplePat -> [ExamplePat]
- resugarList :: ExamplePat -> [ExamplePat]
- resugarString :: ExamplePat -> String
- assumeExampleChar :: ExamplePat -> Char
- desugarClause :: Members '[Fresh, Embed IO] r => [TypedVar] -> Int -> [APattern] -> Sem r Gdt
- desugarTuplePats :: [APattern] -> APattern
- desugarMatch :: Members '[Fresh, Embed IO] r => TypedVar -> APattern -> Sem r [Guard]
- data Gdt where
- type Guard = (TypedVar, GuardConstraint)
- data GuardConstraint where
- GMatch :: DataCon -> [TypedVar] -> GuardConstraint
- GWasOriginally :: TypedVar -> GuardConstraint
- newtype Literal = Literal (TypedVar, LitCond)
- data LitCond where
- data Ant where
- ua :: Members '[Fresh, Reader TyDefCtx] r => [NormRefType] -> Gdt -> Sem r ([NormRefType], Ant)
- addLitMulti :: Members '[Fresh, Reader TyDefCtx] r => [NormRefType] -> Literal -> Sem r [NormRefType]
- addLiteral :: Members '[Fresh, Reader TyDefCtx] r => NormRefType -> Literal -> MaybeT (Sem r) NormRefType
- data InhabPat where
- mkIPMatch :: DataCon -> [InhabPat] -> InhabPat
- findInhabitants :: Members '[Fresh, Reader TyDefCtx] r => [NormRefType] -> [TypedVar] -> Sem r (Possibilities [InhabPat])
- findAllForNref :: Members '[Fresh, Reader TyDefCtx] r => NormRefType -> [TypedVar] -> Sem r (Possibilities [InhabPat])
- findVarInhabitants :: Members '[Fresh, Reader TyDefCtx] r => TypedVar -> NormRefType -> Sem r (Possibilities InhabPat)
- findRedundant :: Members '[Fresh, Reader TyDefCtx] r => Ant -> [TypedVar] -> Sem r [Int]
- data ExamplePat where
- ExamplePat :: DataCon -> [ExamplePat] -> ExamplePat
- findPosExamples :: Members '[Fresh, Reader TyDefCtx] r => [NormRefType] -> [TypedVar] -> Sem r [[ExamplePat]]
- findAllPosForNref :: Members '[Fresh, Reader TyDefCtx] r => Int -> NormRefType -> [TypedVar] -> Sem r (Possibilities [ExamplePat])
- findVarPosExamples :: Members '[Fresh, Reader TyDefCtx] r => Int -> TypedVar -> NormRefType -> Sem r (Possibilities ExamplePat)
- getPosFrom :: Type -> TyDefCtx -> [DataCon] -> [DataCon]
- mkExampleMatch :: DataCon -> [ExamplePat] -> ExamplePat
Documentation
checkClauses :: Members '[Fresh, Reader TyDefCtx, Output (Message ann), Embed IO] r => Name ATerm -> [Type] -> NonEmpty [APattern] -> Sem r () Source #
This exhaustiveness checking algorithm is based on the paper "Lower Your Guards: A Compositional Pattern-Match Coverage Checker": https://www.microsoft.com/en-us/research/uploads/prod/2020/03/lyg.pdf
Some simplifications were made to adapt the algorithm to suit Disco. The most notable change is that here we always generate (at most) 3 concrete examples of uncovered patterns, instead of finding the most general complete description of every uncovered input.
prettyPrintExample :: ExamplePat -> Sem r (Doc ann) Source #
resugarPair :: ExamplePat -> [ExamplePat] Source #
resugarList :: ExamplePat -> [ExamplePat] Source #
resugarString :: ExamplePat -> String Source #
assumeExampleChar :: ExamplePat -> Char Source #
desugarClause :: Members '[Fresh, Embed IO] r => [TypedVar] -> Int -> [APattern] -> Sem r Gdt Source #
desugarTuplePats :: [APattern] -> APattern Source #
desugarMatch :: Members '[Fresh, Embed IO] r => TypedVar -> APattern -> Sem r [Guard] Source #
Convert a Disco APattern into a list of Guards which cover that pattern
These patterns are currently not handled: , APNeg --still need to handle rational case , APFrac --required for rationals? algebraic (probably will be eventually replaced anyway): , APAdd , APMul , APSub These (or some updated version of them) may be handled eventually, once updated arithmetic patterns are merged.
We treat unhandled patterns as if they are exhaustively matched against (aka, they are seen as wildcards by the checker). This necessarily results in some false negatives, but no false positives.
type Guard = (TypedVar, GuardConstraint) Source #
data GuardConstraint where Source #
Constructors
GMatch :: DataCon -> [TypedVar] -> GuardConstraint | |
GWasOriginally :: TypedVar -> GuardConstraint |
Instances
Show GuardConstraint Source # | |
Defined in Disco.Exhaustiveness Methods showsPrec :: Int -> GuardConstraint -> ShowS # show :: GuardConstraint -> String # showList :: [GuardConstraint] -> ShowS # | |
Eq GuardConstraint Source # | |
Defined in Disco.Exhaustiveness Methods (==) :: GuardConstraint -> GuardConstraint -> Bool # (/=) :: GuardConstraint -> GuardConstraint -> Bool # |
Constructors
LitMatch :: DataCon -> [TypedVar] -> LitCond | |
LitNot :: DataCon -> LitCond | |
LitWasOriginally :: TypedVar -> LitCond |
ua :: Members '[Fresh, Reader TyDefCtx] r => [NormRefType] -> Gdt -> Sem r ([NormRefType], Ant) Source #
addLitMulti :: Members '[Fresh, Reader TyDefCtx] r => [NormRefType] -> Literal -> Sem r [NormRefType] Source #
addLiteral :: Members '[Fresh, Reader TyDefCtx] r => NormRefType -> Literal -> MaybeT (Sem r) NormRefType Source #
findInhabitants :: Members '[Fresh, Reader TyDefCtx] r => [NormRefType] -> [TypedVar] -> Sem r (Possibilities [InhabPat]) Source #
findAllForNref :: Members '[Fresh, Reader TyDefCtx] r => NormRefType -> [TypedVar] -> Sem r (Possibilities [InhabPat]) Source #
findVarInhabitants :: Members '[Fresh, Reader TyDefCtx] r => TypedVar -> NormRefType -> Sem r (Possibilities InhabPat) Source #
data ExamplePat where Source #
Constructors
ExamplePat :: DataCon -> [ExamplePat] -> ExamplePat |
Instances
Show ExamplePat Source # | |
Defined in Disco.Exhaustiveness Methods showsPrec :: Int -> ExamplePat -> ShowS # show :: ExamplePat -> String # showList :: [ExamplePat] -> ShowS # |
findPosExamples :: Members '[Fresh, Reader TyDefCtx] r => [NormRefType] -> [TypedVar] -> Sem r [[ExamplePat]] Source #
Less general version of the above inhabitant finding function returns a maximum of 3 possible args lists that haven't been matched against, as to not overwhelm new users of the language. This is essentially a DFS, and it has a bad habit of trying to build infinite lists whenever it can, so we give it a max depth of 32 If we reach 32 levels of nested dataconstructors in this language, it is pretty safe to assume we were chasing after an infinite structure
findAllPosForNref :: Members '[Fresh, Reader TyDefCtx] r => Int -> NormRefType -> [TypedVar] -> Sem r (Possibilities [ExamplePat]) Source #
findVarPosExamples :: Members '[Fresh, Reader TyDefCtx] r => Int -> TypedVar -> NormRefType -> Sem r (Possibilities ExamplePat) Source #
mkExampleMatch :: DataCon -> [ExamplePat] -> ExamplePat Source #