constrained-generators-0.2.0.0: Framework for generating constrained random data using a subset of first order logic
Safe HaskellSafe-Inferred
LanguageHaskell2010

Constrained.Base

Description

This module contains the most basic parts the implementation. Essentially everything to define Specification, HasSpec, HasSimpleRep, Term, Pred, and the Syntax, Semantics, and Logic class. It also has a few HasSpec, HasSimpleRep, and Logic instances for basic types needed to define the default types and methods of HasSpec. It also supplies Eq, Pretty, and Show instances on the syntax (Term, Pred, Binder etc.) because many functions require these instances. It exports functions that define the user interface to the domain embedded language (constrained, forall, exists etc.). And, by design, nothing more.

Synopsis

Documentation

class Syntax (t ∷ [Type] → Type → Type) where Source #

A First-order typed logic has 4 components 1. Terms (Variables (x), Constants (5), and Applications (F x 5) Applications, apply a function symbol to a list of arguments: (FunctionSymbol term1 .. termN) 2. Predicates (Ordered, Odd, ...) 3. Connectives (And, Or, Not, =>, ...) 4. Quantifiers (Forall, Exists)

The Syntax, Semantics, and Logic classes implement new function symbols in the first order logic. Note that a function symbol is first order data, that uniquely identifies a higher order function. The three classes supply varying levels of functionality, relating to the Syntax, Semantics, and Logical operations of the function symbol.

Syntactic operations are ones that have to do with the structure and appearence of the type.

Minimal complete definition

Nothing

Methods

inFix ∷ ∀ dom rng. t dom rng → Bool Source #

prettyWit ∷ ∀ dom rng ann. (All HasSpec dom, HasSpec rng) ⇒ t dom rng → List Term dom → Int → Maybe (Doc ann) Source #

Instances

Instances details
Syntax BaseW Source # 
Instance details

Defined in Constrained.Base

Methods

inFix ∷ ∀ (dom ∷ [Type]) rng. BaseW dom rng → Bool Source #

prettyWit ∷ ∀ (dom ∷ [Type]) rng ann. (All HasSpec dom, HasSpec rng) ⇒ BaseW dom rng → List Term dom → Int → Maybe (Doc ann) Source #

Syntax IntW Source # 
Instance details

Defined in Constrained.NumSpec

Methods

inFix ∷ ∀ (dom ∷ [Type]) rng. IntW dom rng → Bool Source #

prettyWit ∷ ∀ (dom ∷ [Type]) rng ann. (All HasSpec dom, HasSpec rng) ⇒ IntW dom rng → List Term dom → Int → Maybe (Doc ann) Source #

Syntax NumOrdW Source # 
Instance details

Defined in Constrained.NumSpec

Methods

inFix ∷ ∀ (dom ∷ [Type]) rng. NumOrdW dom rng → Bool Source #

prettyWit ∷ ∀ (dom ∷ [Type]) rng ann. (All HasSpec dom, HasSpec rng) ⇒ NumOrdW dom rng → List Term dom → Int → Maybe (Doc ann) Source #

Syntax MapW Source # 
Instance details

Defined in Constrained.Spec.Map

Methods

inFix ∷ ∀ (dom ∷ [Type]) rng. MapW dom rng → Bool Source #

prettyWit ∷ ∀ (dom ∷ [Type]) rng ann. (All HasSpec dom, HasSpec rng) ⇒ MapW dom rng → List Term dom → Int → Maybe (Doc ann) Source #

Syntax SetW Source # 
Instance details

Defined in Constrained.Spec.Set

Methods

inFix ∷ ∀ (dom ∷ [Type]) rng. SetW dom rng → Bool Source #

prettyWit ∷ ∀ (dom ∷ [Type]) rng ann. (All HasSpec dom, HasSpec rng) ⇒ SetW dom rng → List Term dom → Int → Maybe (Doc ann) Source #

Syntax TreeW Source # 
Instance details

Defined in Constrained.Spec.Tree

Methods

inFix ∷ ∀ (dom ∷ [Type]) rng. TreeW dom rng → Bool Source #

prettyWit ∷ ∀ (dom ∷ [Type]) rng ann. (All HasSpec dom, HasSpec rng) ⇒ TreeW dom rng → List Term dom → Int → Maybe (Doc ann) Source #

Syntax BoolW Source # 
Instance details

Defined in Constrained.TheKnot

Methods

inFix ∷ ∀ (dom ∷ [Type]) rng. BoolW dom rng → Bool Source #

prettyWit ∷ ∀ (dom ∷ [Type]) rng ann. (All HasSpec dom, HasSpec rng) ⇒ BoolW dom rng → List Term dom → Int → Maybe (Doc ann) Source #

Syntax ElemW Source # 
Instance details

Defined in Constrained.TheKnot

Methods

inFix ∷ ∀ (dom ∷ [Type]) rng. ElemW dom rng → Bool Source #

prettyWit ∷ ∀ (dom ∷ [Type]) rng ann. (All HasSpec dom, HasSpec rng) ⇒ ElemW dom rng → List Term dom → Int → Maybe (Doc ann) Source #

Syntax EqW Source # 
Instance details

Defined in Constrained.TheKnot

Methods

inFix ∷ ∀ (dom ∷ [Type]) rng. EqW dom rng → Bool Source #

prettyWit ∷ ∀ (dom ∷ [Type]) rng ann. (All HasSpec dom, HasSpec rng) ⇒ EqW dom rng → List Term dom → Int → Maybe (Doc ann) Source #

Syntax FunW Source # 
Instance details

Defined in Constrained.TheKnot

Methods

inFix ∷ ∀ (dom ∷ [Type]) rng. FunW dom rng → Bool Source #

prettyWit ∷ ∀ (dom ∷ [Type]) rng ann. (All HasSpec dom, HasSpec rng) ⇒ FunW dom rng → List Term dom → Int → Maybe (Doc ann) Source #

Syntax ListW Source # 
Instance details

Defined in Constrained.TheKnot

Methods

inFix ∷ ∀ (dom ∷ [Type]) rng. ListW dom rng → Bool Source #

prettyWit ∷ ∀ (dom ∷ [Type]) rng ann. (All HasSpec dom, HasSpec rng) ⇒ ListW dom rng → List Term dom → Int → Maybe (Doc ann) Source #

Syntax ProdW Source # 
Instance details

Defined in Constrained.TheKnot

Methods

inFix ∷ ∀ (dom ∷ [Type]) rng. ProdW dom rng → Bool Source #

prettyWit ∷ ∀ (dom ∷ [Type]) rng ann. (All HasSpec dom, HasSpec rng) ⇒ ProdW dom rng → List Term dom → Int → Maybe (Doc ann) Source #

Syntax SizeW Source # 
Instance details

Defined in Constrained.TheKnot

Methods

inFix ∷ ∀ (dom ∷ [Type]) rng. SizeW dom rng → Bool Source #

prettyWit ∷ ∀ (dom ∷ [Type]) rng ann. (All HasSpec dom, HasSpec rng) ⇒ SizeW dom rng → List Term dom → Int → Maybe (Doc ann) Source #

Syntax SumW Source # 
Instance details

Defined in Constrained.TheKnot

Methods

inFix ∷ ∀ (dom ∷ [Type]) rng. SumW dom rng → Bool Source #

prettyWit ∷ ∀ (dom ∷ [Type]) rng ann. (All HasSpec dom, HasSpec rng) ⇒ SumW dom rng → List Term dom → Int → Maybe (Doc ann) Source #

class Syntax t ⇒ Semantics (t ∷ [Type] → Type → Type) where Source #

Semantic operations are ones that give the function symbol, meaning as a function. I.e. how to apply the function to a list of arguments and return a value.

Methods

semantics ∷ ∀ d r. t d r → FunTy d r Source #

Instances

Instances details
Semantics BaseW Source # 
Instance details

Defined in Constrained.Base

Methods

semantics ∷ ∀ (d ∷ [Type]) r. BaseW d r → FunTy d r Source #

Semantics IntW Source # 
Instance details

Defined in Constrained.NumSpec

Methods

semantics ∷ ∀ (d ∷ [Type]) r. IntW d r → FunTy d r Source #

Semantics NumOrdW Source # 
Instance details

Defined in Constrained.NumSpec

Methods

semantics ∷ ∀ (d ∷ [Type]) r. NumOrdW d r → FunTy d r Source #

Semantics MapW Source # 
Instance details

Defined in Constrained.Spec.Map

Methods

semantics ∷ ∀ (d ∷ [Type]) r. MapW d r → FunTy d r Source #

Semantics SetW Source # 
Instance details

Defined in Constrained.Spec.Set

Methods

semantics ∷ ∀ (d ∷ [Type]) r. SetW d r → FunTy d r Source #

Semantics TreeW Source # 
Instance details

Defined in Constrained.Spec.Tree

Methods

semantics ∷ ∀ (d ∷ [Type]) r. TreeW d r → FunTy d r Source #

Semantics BoolW Source # 
Instance details

Defined in Constrained.TheKnot

Methods

semantics ∷ ∀ (d ∷ [Type]) r. BoolW d r → FunTy d r Source #

Semantics ElemW Source # 
Instance details

Defined in Constrained.TheKnot

Methods

semantics ∷ ∀ (d ∷ [Type]) r. ElemW d r → FunTy d r Source #

Semantics EqW Source # 
Instance details

Defined in Constrained.TheKnot

Methods

semantics ∷ ∀ (d ∷ [Type]) r. EqW d r → FunTy d r Source #

Semantics FunW Source # 
Instance details

Defined in Constrained.TheKnot

Methods

semantics ∷ ∀ (d ∷ [Type]) r. FunW d r → FunTy d r Source #

Semantics ListW Source # 
Instance details

Defined in Constrained.TheKnot

Methods

semantics ∷ ∀ (d ∷ [Type]) r. ListW d r → FunTy d r Source #

Semantics ProdW Source # 
Instance details

Defined in Constrained.TheKnot

Methods

semantics ∷ ∀ (d ∷ [Type]) r. ProdW d r → FunTy d r Source #

Semantics SizeW Source # 
Instance details

Defined in Constrained.TheKnot

Methods

semantics ∷ ∀ (d ∷ [Type]) r. SizeW d r → FunTy d r Source #

Semantics SumW Source # 
Instance details

Defined in Constrained.TheKnot

Methods

semantics ∷ ∀ (d ∷ [Type]) r. SumW d r → FunTy d r Source #

type LogicRequires t = (Typeable t, Syntax t, Semantics t) Source #

class LogicRequires t ⇒ Logic t where Source #

Logical operations are one that support reasoning about how a function symbol relates to logical properties, that we call Specification's

Minimal complete definition

propagate | propagateTypeSpec, propagateMemberSpec

Methods

propagateTypeSpec ∷ (AppRequires t as b, HasSpec a) ⇒ t as b → ListCtx Value as (HOLE a) → TypeSpec b → [b] → Specification a Source #

propagateMemberSpec ∷ (AppRequires t as b, HasSpec a) ⇒ t as b → ListCtx Value as (HOLE a) → NonEmpty b → Specification a Source #

propagate ∷ (AppRequires t as b, HasSpec a) ⇒ t as b → ListCtx Value as (HOLE a) → Specification b → Specification a Source #

rewriteRules ∷ (TypeList dom, Typeable dom, HasSpec rng, All HasSpec dom) ⇒ t dom rng → List Term dom → Evidence (AppRequires t dom rng) → Maybe (Term rng) Source #

mapTypeSpec ∷ ∀ a b. (HasSpec a, HasSpec b) ⇒ t '[a] b → TypeSpec a → Specification b Source #

saturate ∷ t dom Bool → List Term dom → [Pred] Source #

Instances

Instances details
Logic BaseW Source # 
Instance details

Defined in Constrained.Base

Methods

propagateTypeSpec ∷ ∀ (as ∷ [Type]) b a. (AppRequires BaseW as b, HasSpec a) ⇒ BaseW as b → ListCtx Value as (HOLE a) → TypeSpec b → [b] → Specification a Source #

propagateMemberSpec ∷ ∀ (as ∷ [Type]) b a. (AppRequires BaseW as b, HasSpec a) ⇒ BaseW as b → ListCtx Value as (HOLE a) → NonEmpty b → Specification a Source #

propagate ∷ ∀ (as ∷ [Type]) b a. (AppRequires BaseW as b, HasSpec a) ⇒ BaseW as b → ListCtx Value as (HOLE a) → Specification b → Specification a Source #

rewriteRules ∷ ∀ (dom ∷ [Type]) rng. (TypeList dom, Typeable dom, HasSpec rng, All HasSpec dom) ⇒ BaseW dom rng → List Term dom → Evidence (AppRequires BaseW dom rng) → Maybe (Term rng) Source #

mapTypeSpec ∷ (HasSpec a, HasSpec b) ⇒ BaseW '[a] b → TypeSpec a → Specification b Source #

saturate ∷ ∀ (dom ∷ [Type]). BaseW dom Bool → List Term dom → [Pred] Source #

Logic IntW Source #

Just a note that these instances won't work until we are in a context where there is a HasSpec instance of a, which (NumLike a) demands. This happens in Constrained.Experiment.TheKnot

Instance details

Defined in Constrained.NumSpec

Methods

propagateTypeSpec ∷ ∀ (as ∷ [Type]) b a. (AppRequires IntW as b, HasSpec a) ⇒ IntW as b → ListCtx Value as (HOLE a) → TypeSpec b → [b] → Specification a Source #

propagateMemberSpec ∷ ∀ (as ∷ [Type]) b a. (AppRequires IntW as b, HasSpec a) ⇒ IntW as b → ListCtx Value as (HOLE a) → NonEmpty b → Specification a Source #

propagate ∷ ∀ (as ∷ [Type]) b a. (AppRequires IntW as b, HasSpec a) ⇒ IntW as b → ListCtx Value as (HOLE a) → Specification b → Specification a Source #

rewriteRules ∷ ∀ (dom ∷ [Type]) rng. (TypeList dom, Typeable dom, HasSpec rng, All HasSpec dom) ⇒ IntW dom rng → List Term dom → Evidence (AppRequires IntW dom rng) → Maybe (Term rng) Source #

mapTypeSpec ∷ (HasSpec a, HasSpec b) ⇒ IntW '[a] b → TypeSpec a → Specification b Source #

saturate ∷ ∀ (dom ∷ [Type]). IntW dom Bool → List Term dom → [Pred] Source #

Logic NumOrdW Source # 
Instance details

Defined in Constrained.TheKnot

Methods

propagateTypeSpec ∷ ∀ (as ∷ [Type]) b a. (AppRequires NumOrdW as b, HasSpec a) ⇒ NumOrdW as b → ListCtx Value as (HOLE a) → TypeSpec b → [b] → Specification a Source #

propagateMemberSpec ∷ ∀ (as ∷ [Type]) b a. (AppRequires NumOrdW as b, HasSpec a) ⇒ NumOrdW as b → ListCtx Value as (HOLE a) → NonEmpty b → Specification a Source #

propagate ∷ ∀ (as ∷ [Type]) b a. (AppRequires NumOrdW as b, HasSpec a) ⇒ NumOrdW as b → ListCtx Value as (HOLE a) → Specification b → Specification a Source #

rewriteRules ∷ ∀ (dom ∷ [Type]) rng. (TypeList dom, Typeable dom, HasSpec rng, All HasSpec dom) ⇒ NumOrdW dom rng → List Term dom → Evidence (AppRequires NumOrdW dom rng) → Maybe (Term rng) Source #

mapTypeSpec ∷ (HasSpec a, HasSpec b) ⇒ NumOrdW '[a] b → TypeSpec a → Specification b Source #

saturate ∷ ∀ (dom ∷ [Type]). NumOrdW dom Bool → List Term dom → [Pred] Source #

Logic MapW Source # 
Instance details

Defined in Constrained.Spec.Map

Methods

propagateTypeSpec ∷ ∀ (as ∷ [Type]) b a. (AppRequires MapW as b, HasSpec a) ⇒ MapW as b → ListCtx Value as (HOLE a) → TypeSpec b → [b] → Specification a Source #

propagateMemberSpec ∷ ∀ (as ∷ [Type]) b a. (AppRequires MapW as b, HasSpec a) ⇒ MapW as b → ListCtx Value as (HOLE a) → NonEmpty b → Specification a Source #

propagate ∷ ∀ (as ∷ [Type]) b a. (AppRequires MapW as b, HasSpec a) ⇒ MapW as b → ListCtx Value as (HOLE a) → Specification b → Specification a Source #

rewriteRules ∷ ∀ (dom ∷ [Type]) rng. (TypeList dom, Typeable dom, HasSpec rng, All HasSpec dom) ⇒ MapW dom rng → List Term dom → Evidence (AppRequires MapW dom rng) → Maybe (Term rng) Source #

mapTypeSpec ∷ (HasSpec a, HasSpec b) ⇒ MapW '[a] b → TypeSpec a → Specification b Source #

saturate ∷ ∀ (dom ∷ [Type]). MapW dom Bool → List Term dom → [Pred] Source #

Logic SetW Source # 
Instance details

Defined in Constrained.Spec.Set

Methods

propagateTypeSpec ∷ ∀ (as ∷ [Type]) b a. (AppRequires SetW as b, HasSpec a) ⇒ SetW as b → ListCtx Value as (HOLE a) → TypeSpec b → [b] → Specification a Source #

propagateMemberSpec ∷ ∀ (as ∷ [Type]) b a. (AppRequires SetW as b, HasSpec a) ⇒ SetW as b → ListCtx Value as (HOLE a) → NonEmpty b → Specification a Source #

propagate ∷ ∀ (as ∷ [Type]) b a. (AppRequires SetW as b, HasSpec a) ⇒ SetW as b → ListCtx Value as (HOLE a) → Specification b → Specification a Source #

rewriteRules ∷ ∀ (dom ∷ [Type]) rng. (TypeList dom, Typeable dom, HasSpec rng, All HasSpec dom) ⇒ SetW dom rng → List Term dom → Evidence (AppRequires SetW dom rng) → Maybe (Term rng) Source #

mapTypeSpec ∷ (HasSpec a, HasSpec b) ⇒ SetW '[a] b → TypeSpec a → Specification b Source #

saturate ∷ ∀ (dom ∷ [Type]). SetW dom Bool → List Term dom → [Pred] Source #

Logic TreeW Source # 
Instance details

Defined in Constrained.Spec.Tree

Methods

propagateTypeSpec ∷ ∀ (as ∷ [Type]) b a. (AppRequires TreeW as b, HasSpec a) ⇒ TreeW as b → ListCtx Value as (HOLE a) → TypeSpec b → [b] → Specification a Source #

propagateMemberSpec ∷ ∀ (as ∷ [Type]) b a. (AppRequires TreeW as b, HasSpec a) ⇒ TreeW as b → ListCtx Value as (HOLE a) → NonEmpty b → Specification a Source #

propagate ∷ ∀ (as ∷ [Type]) b a. (AppRequires TreeW as b, HasSpec a) ⇒ TreeW as b → ListCtx Value as (HOLE a) → Specification b → Specification a Source #

rewriteRules ∷ ∀ (dom ∷ [Type]) rng. (TypeList dom, Typeable dom, HasSpec rng, All HasSpec dom) ⇒ TreeW dom rng → List Term dom → Evidence (AppRequires TreeW dom rng) → Maybe (Term rng) Source #

mapTypeSpec ∷ (HasSpec a, HasSpec b) ⇒ TreeW '[a] b → TypeSpec a → Specification b Source #

saturate ∷ ∀ (dom ∷ [Type]). TreeW dom Bool → List Term dom → [Pred] Source #

Logic BoolW Source # 
Instance details

Defined in Constrained.TheKnot

Methods

propagateTypeSpec ∷ ∀ (as ∷ [Type]) b a. (AppRequires BoolW as b, HasSpec a) ⇒ BoolW as b → ListCtx Value as (HOLE a) → TypeSpec b → [b] → Specification a Source #

propagateMemberSpec ∷ ∀ (as ∷ [Type]) b a. (AppRequires BoolW as b, HasSpec a) ⇒ BoolW as b → ListCtx Value as (HOLE a) → NonEmpty b → Specification a Source #

propagate ∷ ∀ (as ∷ [Type]) b a. (AppRequires BoolW as b, HasSpec a) ⇒ BoolW as b → ListCtx Value as (HOLE a) → Specification b → Specification a Source #

rewriteRules ∷ ∀ (dom ∷ [Type]) rng. (TypeList dom, Typeable dom, HasSpec rng, All HasSpec dom) ⇒ BoolW dom rng → List Term dom → Evidence (AppRequires BoolW dom rng) → Maybe (Term rng) Source #

mapTypeSpec ∷ (HasSpec a, HasSpec b) ⇒ BoolW '[a] b → TypeSpec a → Specification b Source #

saturate ∷ ∀ (dom ∷ [Type]). BoolW dom Bool → List Term dom → [Pred] Source #

Logic ElemW Source # 
Instance details

Defined in Constrained.TheKnot

Methods

propagateTypeSpec ∷ ∀ (as ∷ [Type]) b a. (AppRequires ElemW as b, HasSpec a) ⇒ ElemW as b → ListCtx Value as (HOLE a) → TypeSpec b → [b] → Specification a Source #

propagateMemberSpec ∷ ∀ (as ∷ [Type]) b a. (AppRequires ElemW as b, HasSpec a) ⇒ ElemW as b → ListCtx Value as (HOLE a) → NonEmpty b → Specification a Source #

propagate ∷ ∀ (as ∷ [Type]) b a. (AppRequires ElemW as b, HasSpec a) ⇒ ElemW as b → ListCtx Value as (HOLE a) → Specification b → Specification a Source #

rewriteRules ∷ ∀ (dom ∷ [Type]) rng. (TypeList dom, Typeable dom, HasSpec rng, All HasSpec dom) ⇒ ElemW dom rng → List Term dom → Evidence (AppRequires ElemW dom rng) → Maybe (Term rng) Source #

mapTypeSpec ∷ (HasSpec a, HasSpec b) ⇒ ElemW '[a] b → TypeSpec a → Specification b Source #

saturate ∷ ∀ (dom ∷ [Type]). ElemW dom Bool → List Term dom → [Pred] Source #

Logic EqW Source # 
Instance details

Defined in Constrained.TheKnot

Methods

propagateTypeSpec ∷ ∀ (as ∷ [Type]) b a. (AppRequires EqW as b, HasSpec a) ⇒ EqW as b → ListCtx Value as (HOLE a) → TypeSpec b → [b] → Specification a Source #

propagateMemberSpec ∷ ∀ (as ∷ [Type]) b a. (AppRequires EqW as b, HasSpec a) ⇒ EqW as b → ListCtx Value as (HOLE a) → NonEmpty b → Specification a Source #

propagate ∷ ∀ (as ∷ [Type]) b a. (AppRequires EqW as b, HasSpec a) ⇒ EqW as b → ListCtx Value as (HOLE a) → Specification b → Specification a Source #

rewriteRules ∷ ∀ (dom ∷ [Type]) rng. (TypeList dom, Typeable dom, HasSpec rng, All HasSpec dom) ⇒ EqW dom rng → List Term dom → Evidence (AppRequires EqW dom rng) → Maybe (Term rng) Source #

mapTypeSpec ∷ (HasSpec a, HasSpec b) ⇒ EqW '[a] b → TypeSpec a → Specification b Source #

saturate ∷ ∀ (dom ∷ [Type]). EqW dom Bool → List Term dom → [Pred] Source #

Logic FunW Source # 
Instance details

Defined in Constrained.TheKnot

Methods

propagateTypeSpec ∷ ∀ (as ∷ [Type]) b a. (AppRequires FunW as b, HasSpec a) ⇒ FunW as b → ListCtx Value as (HOLE a) → TypeSpec b → [b] → Specification a Source #

propagateMemberSpec ∷ ∀ (as ∷ [Type]) b a. (AppRequires FunW as b, HasSpec a) ⇒ FunW as b → ListCtx Value as (HOLE a) → NonEmpty b → Specification a Source #

propagate ∷ ∀ (as ∷ [Type]) b a. (AppRequires FunW as b, HasSpec a) ⇒ FunW as b → ListCtx Value as (HOLE a) → Specification b → Specification a Source #

rewriteRules ∷ ∀ (dom ∷ [Type]) rng. (TypeList dom, Typeable dom, HasSpec rng, All HasSpec dom) ⇒ FunW dom rng → List Term dom → Evidence (AppRequires FunW dom rng) → Maybe (Term rng) Source #

mapTypeSpec ∷ (HasSpec a, HasSpec b) ⇒ FunW '[a] b → TypeSpec a → Specification b Source #

saturate ∷ ∀ (dom ∷ [Type]). FunW dom Bool → List Term dom → [Pred] Source #

Logic ListW Source # 
Instance details

Defined in Constrained.TheKnot

Methods

propagateTypeSpec ∷ ∀ (as ∷ [Type]) b a. (AppRequires ListW as b, HasSpec a) ⇒ ListW as b → ListCtx Value as (HOLE a) → TypeSpec b → [b] → Specification a Source #

propagateMemberSpec ∷ ∀ (as ∷ [Type]) b a. (AppRequires ListW as b, HasSpec a) ⇒ ListW as b → ListCtx Value as (HOLE a) → NonEmpty b → Specification a Source #

propagate ∷ ∀ (as ∷ [Type]) b a. (AppRequires ListW as b, HasSpec a) ⇒ ListW as b → ListCtx Value as (HOLE a) → Specification b → Specification a Source #

rewriteRules ∷ ∀ (dom ∷ [Type]) rng. (TypeList dom, Typeable dom, HasSpec rng, All HasSpec dom) ⇒ ListW dom rng → List Term dom → Evidence (AppRequires ListW dom rng) → Maybe (Term rng) Source #

mapTypeSpec ∷ (HasSpec a, HasSpec b) ⇒ ListW '[a] b → TypeSpec a → Specification b Source #

saturate ∷ ∀ (dom ∷ [Type]). ListW dom Bool → List Term dom → [Pred] Source #

Logic ProdW Source # 
Instance details

Defined in Constrained.TheKnot

Methods

propagateTypeSpec ∷ ∀ (as ∷ [Type]) b a. (AppRequires ProdW as b, HasSpec a) ⇒ ProdW as b → ListCtx Value as (HOLE a) → TypeSpec b → [b] → Specification a Source #

propagateMemberSpec ∷ ∀ (as ∷ [Type]) b a. (AppRequires ProdW as b, HasSpec a) ⇒ ProdW as b → ListCtx Value as (HOLE a) → NonEmpty b → Specification a Source #

propagate ∷ ∀ (as ∷ [Type]) b a. (AppRequires ProdW as b, HasSpec a) ⇒ ProdW as b → ListCtx Value as (HOLE a) → Specification b → Specification a Source #

rewriteRules ∷ ∀ (dom ∷ [Type]) rng. (TypeList dom, Typeable dom, HasSpec rng, All HasSpec dom) ⇒ ProdW dom rng → List Term dom → Evidence (AppRequires ProdW dom rng) → Maybe (Term rng) Source #

mapTypeSpec ∷ (HasSpec a, HasSpec b) ⇒ ProdW '[a] b → TypeSpec a → Specification b Source #

saturate ∷ ∀ (dom ∷ [Type]). ProdW dom Bool → List Term dom → [Pred] Source #

Logic SizeW Source # 
Instance details

Defined in Constrained.TheKnot

Methods

propagateTypeSpec ∷ ∀ (as ∷ [Type]) b a. (AppRequires SizeW as b, HasSpec a) ⇒ SizeW as b → ListCtx Value as (HOLE a) → TypeSpec b → [b] → Specification a Source #

propagateMemberSpec ∷ ∀ (as ∷ [Type]) b a. (AppRequires SizeW as b, HasSpec a) ⇒ SizeW as b → ListCtx Value as (HOLE a) → NonEmpty b → Specification a Source #

propagate ∷ ∀ (as ∷ [Type]) b a. (AppRequires SizeW as b, HasSpec a) ⇒ SizeW as b → ListCtx Value as (HOLE a) → Specification b → Specification a Source #

rewriteRules ∷ ∀ (dom ∷ [Type]) rng. (TypeList dom, Typeable dom, HasSpec rng, All HasSpec dom) ⇒ SizeW dom rng → List Term dom → Evidence (AppRequires SizeW dom rng) → Maybe (Term rng) Source #

mapTypeSpec ∷ (HasSpec a, HasSpec b) ⇒ SizeW '[a] b → TypeSpec a → Specification b Source #

saturate ∷ ∀ (dom ∷ [Type]). SizeW dom Bool → List Term dom → [Pred] Source #

Logic SumW Source # 
Instance details

Defined in Constrained.TheKnot

Methods

propagateTypeSpec ∷ ∀ (as ∷ [Type]) b a. (AppRequires SumW as b, HasSpec a) ⇒ SumW as b → ListCtx Value as (HOLE a) → TypeSpec b → [b] → Specification a Source #

propagateMemberSpec ∷ ∀ (as ∷ [Type]) b a. (AppRequires SumW as b, HasSpec a) ⇒ SumW as b → ListCtx Value as (HOLE a) → NonEmpty b → Specification a Source #

propagate ∷ ∀ (as ∷ [Type]) b a. (AppRequires SumW as b, HasSpec a) ⇒ SumW as b → ListCtx Value as (HOLE a) → Specification b → Specification a Source #

rewriteRules ∷ ∀ (dom ∷ [Type]) rng. (TypeList dom, Typeable dom, HasSpec rng, All HasSpec dom) ⇒ SumW dom rng → List Term dom → Evidence (AppRequires SumW dom rng) → Maybe (Term rng) Source #

mapTypeSpec ∷ (HasSpec a, HasSpec b) ⇒ SumW '[a] b → TypeSpec a → Specification b Source #

saturate ∷ ∀ (dom ∷ [Type]). SumW dom Bool → List Term dom → [Pred] Source #

propagateSpec ∷ ∀ v a. HasSpec v ⇒ Specification a → Ctx v a → Specification v Source #

data Ctx v a where Source #

Contexts for Terms, basically a term with a _single_ HOLE instead of a variable. This is used to traverse the defining constraints for a variable and turn them into a spec. Each subterm `f vs Ctx vs'` for lists of values vs and vs` gets given to the propagateSpecFun for f as `(f vs HOLE vs')`.

Constructors

CtxHOLEHasSpec v ⇒ Ctx v v

A single hole of type v. Note ctxHOLE is a nullary constructor, where the a type index is the same as the v type index.

CtxApp ∷ (AppRequires fn as b, HasSpec b, TypeList as, Typeable as, All HasSpec as, Logic fn) ⇒ fn as b → ListCtx Value as (Ctx v) → Ctx v b

The application `f vs Ctx vs'`

data HOLE a b where Source #

This is used together with ListCtx to form just the arguments to `f vs Ctx vs'` - replacing Ctx with HOLE, to get a `ListCtx Value as (HOLE a)` which then can be used as an input to propagate.

Constructors

HOLEHOLE a a 

toCtx ∷ ∀ m v a. (Typeable v, Show v, MonadGenError m, HasCallStack) ⇒ Var v → Term a → m (Ctx v a) Source #

toCtxList ∷ ∀ m v as. (Show v, Typeable v, MonadGenError m, HasCallStack) ⇒ Var v → List Term as → m (ListCtx Value as (Ctx v)) Source #

pattern UnaryHOLE a' a → ListCtx f '[a] (HOLE a') Source #

A Convenient pattern for singleton contexts

pattern (:<:) ∷ (Typeable b, Show b) ⇒ HOLE c a → b → ListCtx Value '[a, b] (HOLE c) Source #

Convenient patterns for binary contexts (the arrow :<: points towards the hole)

pattern (:>:) ∷ (Typeable a, Show a) ⇒ a → HOLE c b → ListCtx Value '[a, b] (HOLE c) Source #

Convenient patterns for binary contexts (the arrow :>: points towards the hole)

flipCtx ∷ (Typeable a, Show a, Typeable b, Show b) ⇒ ListCtx Value '[a, b] (HOLE c) → ListCtx Value '[b, a] (HOLE c) Source #

fromListCtxAll HasSpec as ⇒ ListCtx Value as (HOLE a) → Term a → List Term as Source #

From a ListCtx, build a (List Term as), to which the function symbol can be applied.

sameFunSym ∷ ∀ (t1 ∷ [Type] → Type → Type) d1 r1 (t2 ∷ [Type] → Type → Type) d2 r2. (AppRequires t1 d1 r1, AppRequires t2 d2 r2) ⇒ t1 d1 r1 → t2 d2 r2 → Maybe (t1 d1 r1, t1 :~: t2, d1 :~: d2, r1 :~: r2) Source #

getWitness ∷ ∀ t t' d r. (AppRequires t d r, Typeable t') ⇒ t d r → Maybe (t' d r) Source #

Here we only care about the Type t and the Symbol s the dom, and the rng can be anything. Useful for defining patterns.

data Specification a where Source #

A `Specification a` denotes a set of as

Constructors

ExplainSpec ∷ [String] → Specification a → Specification a

Explain a Specification

MemberSpec

Elements of a known set

Fields

  • NonEmpty a

    It must be an element of this OrdSet (List). Try hard not to put duplicates in the List.

  • Specification a
     
ErrorSpecNonEmpty String → Specification a

The empty set

SuspendedSpec

The set described by some predicates over the bound variable.

Fields

  • HasSpec a
     
  • Var a

    This variable ranges over values denoted by the spec

  • Pred

    And the variable is subject to these constraints

  • Specification a
     
TypeSpec

A type-specific spec

Fields

TrueSpecSpecification a

Anything

Instances

Instances details
(HasSpec a, Arbitrary (TypeSpec a)) ⇒ Arbitrary (Specification a) Source # 
Instance details

Defined in Constrained.TheKnot

HasSpec a ⇒ Monoid (Specification a) 
Instance details

Defined in Constrained.Conformance

HasSpec a ⇒ Semigroup (Specification a) 
Instance details

Defined in Constrained.Conformance

Methods

(<>)Specification a → Specification a → Specification a #

sconcatNonEmpty (Specification a) → Specification a

stimes ∷ Integral b ⇒ b → Specification a → Specification a

Number Integer ⇒ Num (Specification Integer)

This is very liberal, since in lots of cases it returns TrueSpec. for example all operations on SuspendedSpec, and certain operations between TypeSpec and MemberSpec. Perhaps we should remove it. Only the addSpec (+) and multSpec (*) methods are used. But, it is kind of cool ... In Fact we can use this to make Num(Specification n) instance for any n. But, only Integer is safe, because in all other types (+) and especially (-) can lead to overflow or underflow failures.

Instance details

Defined in Constrained.NumSpec

Methods

(+)Specification Integer → Specification Integer → Specification Integer

(-)Specification Integer → Specification Integer → Specification Integer

(*)Specification Integer → Specification Integer → Specification Integer

negateSpecification Integer → Specification Integer

absSpecification Integer → Specification Integer

signumSpecification Integer → Specification Integer

fromInteger ∷ Integer → Specification Integer

HasSpec a ⇒ Show (Specification a) Source # 
Instance details

Defined in Constrained.Base

Methods

showsPrec ∷ Int → Specification a → ShowS

showSpecification a → String

showList ∷ [Specification a] → ShowS

HasSpec a ⇒ Pretty (Specification a) Source # 
Instance details

Defined in Constrained.Base

Methods

prettySpecification a → Doc ann Source #

prettyList ∷ [Specification a] → Doc ann Source #

HasSpec a ⇒ Pretty (WithPrec (Specification a)) Source # 
Instance details

Defined in Constrained.Base

class (Typeable a, Eq a, Show a, Show (TypeSpec a), Typeable (TypeSpec a)) ⇒ HasSpec a where Source #

Minimal complete definition

Nothing

Associated Types

type TypeSpec a Source #

The `TypeSpec a` is the type-specific `Specification a`.

type Prerequisites a ∷ Constraint Source #

Prerequisites for the instance that are sometimes necessary when working with e.g. Specifications or functions in the universe.

type Prerequisites a = ()

Methods

emptySpecTypeSpec a Source #

combineSpecTypeSpec a → TypeSpec a → Specification a Source #

genFromTypeSpec ∷ (HasCallStack, MonadGenError m) ⇒ TypeSpec a → GenT m a Source #

Generate a value that satisfies the Specification. The key property for this generator is soundness: ∀ a ∈ genFromTypeSpec spec. a conformsTo spec

default genFromTypeSpec ∷ (HasSimpleRep a, HasSpec (SimpleRep a), TypeSpec a ~ TypeSpec (SimpleRep a)) ⇒ (HasCallStack, MonadGenError m) ⇒ TypeSpec a → GenT m a Source #

conformsTo ∷ HasCallStack ⇒ a → TypeSpec a → Bool Source #

Check conformance to the spec.

default conformsTo ∷ (HasSimpleRep a, HasSpec (SimpleRep a), TypeSpec a ~ TypeSpec (SimpleRep a)) ⇒ HasCallStack ⇒ a → TypeSpec a → Bool Source #

shrinkWithTypeSpecTypeSpec a → a → [a] Source #

Shrink an a with the aide of a Specification

default shrinkWithTypeSpec ∷ (HasSpec (SimpleRep a), TypeSpec a ~ TypeSpec (SimpleRep a), HasSimpleRep a) ⇒ TypeSpec a → a → [a] Source #

toPredsTerm a → TypeSpec a → Pred Source #

Convert a spec to predicates: The key property here is: ∀ a. a conformsTo spec == a conformsTo constrained (t -> toPreds t spec)

default toPreds ∷ (HasSpec (SimpleRep a), TypeSpec a ~ TypeSpec (SimpleRep a), HasSimpleRep a) ⇒ Term a → TypeSpec a → Pred Source #

cardinalTypeSpecTypeSpec a → Specification Integer Source #

Compute an upper and lower bound on the number of solutions genFromTypeSpec might return

cardinalTrueSpecSpecification Integer Source #

A bound on the number of solutions `genFromTypeSpec TrueSpec` can produce. For a type with finite elements, we can get a much more accurate answer than TrueSpec

typeSpecHasErrorTypeSpec a → Maybe (NonEmpty String) Source #

alternateShowTypeSpec a → BinaryShow Source #

monadConformsTo ∷ a → TypeSpec a → Writer [String] Bool Source #

typeSpecOptTypeSpec a → [a] → Specification a Source #

For some types (especially finite ones) there may be much better ways to construct a Specification than the default method of just adding a large bad list to TypSpec. This function allows each HasSpec instance to decide.

guardTypeSpec ∷ [String] → TypeSpec a → Specification a Source #

This can be used to detect self inconsistencies in a (TypeSpec t) Note this is similar to typeSpecHasError, and the default value for typeSpecHasError is written in terms of guardTypeSpec Both typeSpecHasError and guardTypeSpec can be set individually.

prerequisitesEvidence (Prerequisites a) Source #

Materialize the Prerequisites dictionary. It should not be necessary to implement this function manually.

Instances

Instances details
HasSpec Int16 Source # 
Instance details

Defined in Constrained.TheKnot

Associated Types

type TypeSpec Int16 Source #

type Prerequisites Int16 Source #

Methods

emptySpecTypeSpec Int16 Source #

combineSpecTypeSpec Int16 → TypeSpec Int16 → Specification Int16 Source #

genFromTypeSpec ∷ ∀ (m ∷ Type → Type). (HasCallStack, MonadGenError m) ⇒ TypeSpec Int16 → GenT m Int16 Source #

conformsTo ∷ Int16 → TypeSpec Int16 → Bool Source #

shrinkWithTypeSpecTypeSpec Int16 → Int16 → [Int16] Source #

toPredsTerm Int16 → TypeSpec Int16 → Pred Source #

cardinalTypeSpecTypeSpec Int16 → Specification Integer Source #

cardinalTrueSpecSpecification Integer Source #

typeSpecHasErrorTypeSpec Int16 → Maybe (NonEmpty String) Source #

alternateShowTypeSpec Int16 → BinaryShow Source #

monadConformsTo ∷ Int16 → TypeSpec Int16 → Writer [String] Bool Source #

typeSpecOptTypeSpec Int16 → [Int16] → Specification Int16 Source #

guardTypeSpec ∷ [String] → TypeSpec Int16 → Specification Int16 Source #

prerequisitesEvidence (Prerequisites Int16) Source #

HasSpec Int32 Source # 
Instance details

Defined in Constrained.TheKnot

Associated Types

type TypeSpec Int32 Source #

type Prerequisites Int32 Source #

Methods

emptySpecTypeSpec Int32 Source #

combineSpecTypeSpec Int32 → TypeSpec Int32 → Specification Int32 Source #

genFromTypeSpec ∷ ∀ (m ∷ Type → Type). (HasCallStack, MonadGenError m) ⇒ TypeSpec Int32 → GenT m Int32 Source #

conformsTo ∷ Int32 → TypeSpec Int32 → Bool Source #

shrinkWithTypeSpecTypeSpec Int32 → Int32 → [Int32] Source #

toPredsTerm Int32 → TypeSpec Int32 → Pred Source #

cardinalTypeSpecTypeSpec Int32 → Specification Integer Source #

cardinalTrueSpecSpecification Integer Source #

typeSpecHasErrorTypeSpec Int32 → Maybe (NonEmpty String) Source #

alternateShowTypeSpec Int32 → BinaryShow Source #

monadConformsTo ∷ Int32 → TypeSpec Int32 → Writer [String] Bool Source #

typeSpecOptTypeSpec Int32 → [Int32] → Specification Int32 Source #

guardTypeSpec ∷ [String] → TypeSpec Int32 → Specification Int32 Source #

prerequisitesEvidence (Prerequisites Int32) Source #

HasSpec Int64 Source # 
Instance details

Defined in Constrained.TheKnot

Associated Types

type TypeSpec Int64 Source #

type Prerequisites Int64 Source #

Methods

emptySpecTypeSpec Int64 Source #

combineSpecTypeSpec Int64 → TypeSpec Int64 → Specification Int64 Source #

genFromTypeSpec ∷ ∀ (m ∷ Type → Type). (HasCallStack, MonadGenError m) ⇒ TypeSpec Int64 → GenT m Int64 Source #

conformsTo ∷ Int64 → TypeSpec Int64 → Bool Source #

shrinkWithTypeSpecTypeSpec Int64 → Int64 → [Int64] Source #

toPredsTerm Int64 → TypeSpec Int64 → Pred Source #

cardinalTypeSpecTypeSpec Int64 → Specification Integer Source #

cardinalTrueSpecSpecification Integer Source #

typeSpecHasErrorTypeSpec Int64 → Maybe (NonEmpty String) Source #

alternateShowTypeSpec Int64 → BinaryShow Source #

monadConformsTo ∷ Int64 → TypeSpec Int64 → Writer [String] Bool Source #

typeSpecOptTypeSpec Int64 → [Int64] → Specification Int64 Source #

guardTypeSpec ∷ [String] → TypeSpec Int64 → Specification Int64 Source #

prerequisitesEvidence (Prerequisites Int64) Source #

HasSpec Int8 Source # 
Instance details

Defined in Constrained.TheKnot

Associated Types

type TypeSpec Int8 Source #

type Prerequisites Int8 Source #

Methods

emptySpecTypeSpec Int8 Source #

combineSpecTypeSpec Int8 → TypeSpec Int8 → Specification Int8 Source #

genFromTypeSpec ∷ ∀ (m ∷ Type → Type). (HasCallStack, MonadGenError m) ⇒ TypeSpec Int8 → GenT m Int8 Source #

conformsTo ∷ Int8 → TypeSpec Int8 → Bool Source #

shrinkWithTypeSpecTypeSpec Int8 → Int8 → [Int8] Source #

toPredsTerm Int8 → TypeSpec Int8 → Pred Source #

cardinalTypeSpecTypeSpec Int8 → Specification Integer Source #

cardinalTrueSpecSpecification Integer Source #

typeSpecHasErrorTypeSpec Int8 → Maybe (NonEmpty String) Source #

alternateShowTypeSpec Int8 → BinaryShow Source #

monadConformsTo ∷ Int8 → TypeSpec Int8 → Writer [String] Bool Source #

typeSpecOptTypeSpec Int8 → [Int8] → Specification Int8 Source #

guardTypeSpec ∷ [String] → TypeSpec Int8 → Specification Int8 Source #

prerequisitesEvidence (Prerequisites Int8) Source #

HasSpec Word16 Source # 
Instance details

Defined in Constrained.TheKnot

Associated Types

type TypeSpec Word16 Source #

type Prerequisites Word16 Source #

Methods

emptySpecTypeSpec Word16 Source #

combineSpecTypeSpec Word16 → TypeSpec Word16 → Specification Word16 Source #

genFromTypeSpec ∷ ∀ (m ∷ Type → Type). (HasCallStack, MonadGenError m) ⇒ TypeSpec Word16 → GenT m Word16 Source #

conformsTo ∷ Word16 → TypeSpec Word16 → Bool Source #

shrinkWithTypeSpecTypeSpec Word16 → Word16 → [Word16] Source #

toPredsTerm Word16 → TypeSpec Word16 → Pred Source #

cardinalTypeSpecTypeSpec Word16 → Specification Integer Source #

cardinalTrueSpecSpecification Integer Source #

typeSpecHasErrorTypeSpec Word16 → Maybe (NonEmpty String) Source #

alternateShowTypeSpec Word16 → BinaryShow Source #

monadConformsTo ∷ Word16 → TypeSpec Word16 → Writer [String] Bool Source #

typeSpecOptTypeSpec Word16 → [Word16] → Specification Word16 Source #

guardTypeSpec ∷ [String] → TypeSpec Word16 → Specification Word16 Source #

prerequisitesEvidence (Prerequisites Word16) Source #

HasSpec Word32 Source # 
Instance details

Defined in Constrained.TheKnot

Associated Types

type TypeSpec Word32 Source #

type Prerequisites Word32 Source #

Methods

emptySpecTypeSpec Word32 Source #

combineSpecTypeSpec Word32 → TypeSpec Word32 → Specification Word32 Source #

genFromTypeSpec ∷ ∀ (m ∷ Type → Type). (HasCallStack, MonadGenError m) ⇒ TypeSpec Word32 → GenT m Word32 Source #

conformsTo ∷ Word32 → TypeSpec Word32 → Bool Source #

shrinkWithTypeSpecTypeSpec Word32 → Word32 → [Word32] Source #

toPredsTerm Word32 → TypeSpec Word32 → Pred Source #

cardinalTypeSpecTypeSpec Word32 → Specification Integer Source #

cardinalTrueSpecSpecification Integer Source #

typeSpecHasErrorTypeSpec Word32 → Maybe (NonEmpty String) Source #

alternateShowTypeSpec Word32 → BinaryShow Source #

monadConformsTo ∷ Word32 → TypeSpec Word32 → Writer [String] Bool Source #

typeSpecOptTypeSpec Word32 → [Word32] → Specification Word32 Source #

guardTypeSpec ∷ [String] → TypeSpec Word32 → Specification Word32 Source #

prerequisitesEvidence (Prerequisites Word32) Source #

HasSpec Word64 Source # 
Instance details

Defined in Constrained.TheKnot

Associated Types

type TypeSpec Word64 Source #

type Prerequisites Word64 Source #

Methods

emptySpecTypeSpec Word64 Source #

combineSpecTypeSpec Word64 → TypeSpec Word64 → Specification Word64 Source #

genFromTypeSpec ∷ ∀ (m ∷ Type → Type). (HasCallStack, MonadGenError m) ⇒ TypeSpec Word64 → GenT m Word64 Source #

conformsTo ∷ Word64 → TypeSpec Word64 → Bool Source #

shrinkWithTypeSpecTypeSpec Word64 → Word64 → [Word64] Source #

toPredsTerm Word64 → TypeSpec Word64 → Pred Source #

cardinalTypeSpecTypeSpec Word64 → Specification Integer Source #

cardinalTrueSpecSpecification Integer Source #

typeSpecHasErrorTypeSpec Word64 → Maybe (NonEmpty String) Source #

alternateShowTypeSpec Word64 → BinaryShow Source #

monadConformsTo ∷ Word64 → TypeSpec Word64 → Writer [String] Bool Source #

typeSpecOptTypeSpec Word64 → [Word64] → Specification Word64 Source #

guardTypeSpec ∷ [String] → TypeSpec Word64 → Specification Word64 Source #

prerequisitesEvidence (Prerequisites Word64) Source #

HasSpec Word8 Source # 
Instance details

Defined in Constrained.TheKnot

Associated Types

type TypeSpec Word8 Source #

type Prerequisites Word8 Source #

Methods

emptySpecTypeSpec Word8 Source #

combineSpecTypeSpec Word8 → TypeSpec Word8 → Specification Word8 Source #

genFromTypeSpec ∷ ∀ (m ∷ Type → Type). (HasCallStack, MonadGenError m) ⇒ TypeSpec Word8 → GenT m Word8 Source #

conformsTo ∷ Word8 → TypeSpec Word8 → Bool Source #

shrinkWithTypeSpecTypeSpec Word8 → Word8 → [Word8] Source #

toPredsTerm Word8 → TypeSpec Word8 → Pred Source #

cardinalTypeSpecTypeSpec Word8 → Specification Integer Source #

cardinalTrueSpecSpecification Integer Source #

typeSpecHasErrorTypeSpec Word8 → Maybe (NonEmpty String) Source #

alternateShowTypeSpec Word8 → BinaryShow Source #

monadConformsTo ∷ Word8 → TypeSpec Word8 → Writer [String] Bool Source #

typeSpecOptTypeSpec Word8 → [Word8] → Specification Word8 Source #

guardTypeSpec ∷ [String] → TypeSpec Word8 → Specification Word8 Source #

prerequisitesEvidence (Prerequisites Word8) Source #

HasSpec Foo Source # 
Instance details

Defined in Constrained.Examples.Basic

Associated Types

type TypeSpec Foo Source #

type Prerequisites Foo Source #

HasSpec Three Source # 
Instance details

Defined in Constrained.Examples.Basic

Associated Types

type TypeSpec Three Source #

type Prerequisites Three Source #

HasSpec FooBarBaz Source # 
Instance details

Defined in Constrained.Examples.CheatSheet

HasSpec Integer Source # 
Instance details

Defined in Constrained.TheKnot

Associated Types

type TypeSpec Integer Source #

type Prerequisites Integer Source #

Methods

emptySpecTypeSpec Integer Source #

combineSpecTypeSpec Integer → TypeSpec Integer → Specification Integer Source #

genFromTypeSpec ∷ ∀ (m ∷ Type → Type). (HasCallStack, MonadGenError m) ⇒ TypeSpec Integer → GenT m Integer Source #

conformsTo ∷ Integer → TypeSpec Integer → Bool Source #

shrinkWithTypeSpecTypeSpec Integer → Integer → [Integer] Source #

toPredsTerm Integer → TypeSpec Integer → Pred Source #

cardinalTypeSpecTypeSpec Integer → Specification Integer Source #

cardinalTrueSpecSpecification Integer Source #

typeSpecHasErrorTypeSpec Integer → Maybe (NonEmpty String) Source #

alternateShowTypeSpec Integer → BinaryShow Source #

monadConformsTo ∷ Integer → TypeSpec Integer → Writer [String] Bool Source #

typeSpecOptTypeSpec Integer → [Integer] → Specification Integer Source #

guardTypeSpec ∷ [String] → TypeSpec Integer → Specification Integer Source #

prerequisitesEvidence (Prerequisites Integer) Source #

HasSpec Natural Source # 
Instance details

Defined in Constrained.TheKnot

Associated Types

type TypeSpec Natural Source #

type Prerequisites Natural Source #

Methods

emptySpecTypeSpec Natural Source #

combineSpecTypeSpec Natural → TypeSpec Natural → Specification Natural Source #

genFromTypeSpec ∷ ∀ (m ∷ Type → Type). (HasCallStack, MonadGenError m) ⇒ TypeSpec Natural → GenT m Natural Source #

conformsTo ∷ Natural → TypeSpec Natural → Bool Source #

shrinkWithTypeSpecTypeSpec Natural → Natural → [Natural] Source #

toPredsTerm Natural → TypeSpec Natural → Pred Source #

cardinalTypeSpecTypeSpec Natural → Specification Integer Source #

cardinalTrueSpecSpecification Integer Source #

typeSpecHasErrorTypeSpec Natural → Maybe (NonEmpty String) Source #

alternateShowTypeSpec Natural → BinaryShow Source #

monadConformsTo ∷ Natural → TypeSpec Natural → Writer [String] Bool Source #

typeSpecOptTypeSpec Natural → [Natural] → Specification Natural Source #

guardTypeSpec ∷ [String] → TypeSpec Natural → Specification Natural Source #

prerequisitesEvidence (Prerequisites Natural) Source #

HasSpec () Source # 
Instance details

Defined in Constrained.Base

Associated Types

type TypeSpec () Source #

type Prerequisites () Source #

Methods

emptySpecTypeSpec () Source #

combineSpecTypeSpec () → TypeSpec () → Specification () Source #

genFromTypeSpec ∷ ∀ (m ∷ Type → Type). (HasCallStack, MonadGenError m) ⇒ TypeSpec () → GenT m () Source #

conformsTo ∷ () → TypeSpec () → Bool Source #

shrinkWithTypeSpecTypeSpec () → () → [()] Source #

toPredsTerm () → TypeSpec () → Pred Source #

cardinalTypeSpecTypeSpec () → Specification Integer Source #

cardinalTrueSpecSpecification Integer Source #

typeSpecHasErrorTypeSpec () → Maybe (NonEmpty String) Source #

alternateShowTypeSpec () → BinaryShow Source #

monadConformsTo ∷ () → TypeSpec () → Writer [String] Bool Source #

typeSpecOptTypeSpec () → [()] → Specification () Source #

guardTypeSpec ∷ [String] → TypeSpec () → Specification () Source #

prerequisitesEvidence (Prerequisites ()) Source #

HasSpec Bool Source # 
Instance details

Defined in Constrained.TheKnot

Associated Types

type TypeSpec Bool Source #

type Prerequisites Bool Source #

Methods

emptySpecTypeSpec Bool Source #

combineSpecTypeSpec Bool → TypeSpec Bool → Specification Bool Source #

genFromTypeSpec ∷ ∀ (m ∷ Type → Type). (HasCallStack, MonadGenError m) ⇒ TypeSpec Bool → GenT m Bool Source #

conformsTo ∷ Bool → TypeSpec Bool → Bool Source #

shrinkWithTypeSpecTypeSpec Bool → Bool → [Bool] Source #

toPredsTerm Bool → TypeSpec Bool → Pred Source #

cardinalTypeSpecTypeSpec Bool → Specification Integer Source #

cardinalTrueSpecSpecification Integer Source #

typeSpecHasErrorTypeSpec Bool → Maybe (NonEmpty String) Source #

alternateShowTypeSpec Bool → BinaryShow Source #

monadConformsTo ∷ Bool → TypeSpec Bool → Writer [String] Bool Source #

typeSpecOptTypeSpec Bool → [Bool] → Specification Bool Source #

guardTypeSpec ∷ [String] → TypeSpec Bool → Specification Bool Source #

prerequisitesEvidence (Prerequisites Bool) Source #

HasSpec Float Source # 
Instance details

Defined in Constrained.TheKnot

Associated Types

type TypeSpec Float Source #

type Prerequisites Float Source #

Methods

emptySpecTypeSpec Float Source #

combineSpecTypeSpec Float → TypeSpec Float → Specification Float Source #

genFromTypeSpec ∷ ∀ (m ∷ Type → Type). (HasCallStack, MonadGenError m) ⇒ TypeSpec Float → GenT m Float Source #

conformsTo ∷ Float → TypeSpec Float → Bool Source #

shrinkWithTypeSpecTypeSpec Float → Float → [Float] Source #

toPredsTerm Float → TypeSpec Float → Pred Source #

cardinalTypeSpecTypeSpec Float → Specification Integer Source #

cardinalTrueSpecSpecification Integer Source #

typeSpecHasErrorTypeSpec Float → Maybe (NonEmpty String) Source #

alternateShowTypeSpec Float → BinaryShow Source #

monadConformsTo ∷ Float → TypeSpec Float → Writer [String] Bool Source #

typeSpecOptTypeSpec Float → [Float] → Specification Float Source #

guardTypeSpec ∷ [String] → TypeSpec Float → Specification Float Source #

prerequisitesEvidence (Prerequisites Float) Source #

HasSpec Int Source # 
Instance details

Defined in Constrained.TheKnot

Associated Types

type TypeSpec Int Source #

type Prerequisites Int Source #

Methods

emptySpecTypeSpec Int Source #

combineSpecTypeSpec Int → TypeSpec Int → Specification Int Source #

genFromTypeSpec ∷ ∀ (m ∷ Type → Type). (HasCallStack, MonadGenError m) ⇒ TypeSpec Int → GenT m Int Source #

conformsTo ∷ Int → TypeSpec Int → Bool Source #

shrinkWithTypeSpecTypeSpec Int → Int → [Int] Source #

toPredsTerm Int → TypeSpec Int → Pred Source #

cardinalTypeSpecTypeSpec Int → Specification Integer Source #

cardinalTrueSpecSpecification Integer Source #

typeSpecHasErrorTypeSpec Int → Maybe (NonEmpty String) Source #

alternateShowTypeSpec Int → BinaryShow Source #

monadConformsTo ∷ Int → TypeSpec Int → Writer [String] Bool Source #

typeSpecOptTypeSpec Int → [Int] → Specification Int Source #

guardTypeSpec ∷ [String] → TypeSpec Int → Specification Int Source #

prerequisitesEvidence (Prerequisites Int) Source #

HasSpec (Ratio Integer) Source # 
Instance details

Defined in Constrained.TheKnot

Associated Types

type TypeSpec (Ratio Integer) Source #

type Prerequisites (Ratio Integer) Source #

Methods

emptySpecTypeSpec (Ratio Integer) Source #

combineSpecTypeSpec (Ratio Integer) → TypeSpec (Ratio Integer) → Specification (Ratio Integer) Source #

genFromTypeSpec ∷ ∀ (m ∷ Type → Type). (HasCallStack, MonadGenError m) ⇒ TypeSpec (Ratio Integer) → GenT m (Ratio Integer) Source #

conformsTo ∷ Ratio Integer → TypeSpec (Ratio Integer) → Bool Source #

shrinkWithTypeSpecTypeSpec (Ratio Integer) → Ratio Integer → [Ratio Integer] Source #

toPredsTerm (Ratio Integer) → TypeSpec (Ratio Integer) → Pred Source #

cardinalTypeSpecTypeSpec (Ratio Integer) → Specification Integer Source #

cardinalTrueSpecSpecification Integer Source #

typeSpecHasErrorTypeSpec (Ratio Integer) → Maybe (NonEmpty String) Source #

alternateShowTypeSpec (Ratio Integer) → BinaryShow Source #

monadConformsTo ∷ Ratio Integer → TypeSpec (Ratio Integer) → Writer [String] Bool Source #

typeSpecOptTypeSpec (Ratio Integer) → [Ratio Integer] → Specification (Ratio Integer) Source #

guardTypeSpec ∷ [String] → TypeSpec (Ratio Integer) → Specification (Ratio Integer) Source #

prerequisitesEvidence (Prerequisites (Ratio Integer)) Source #

(Ord a, HasSpec a) ⇒ HasSpec (NotASet a) Source # 
Instance details

Defined in Constrained.Examples.Set

Associated Types

type TypeSpec (NotASet a) Source #

type Prerequisites (NotASet a) Source #

HasSpec a ⇒ HasSpec (BinTree a) Source # 
Instance details

Defined in Constrained.Spec.Tree

Associated Types

type TypeSpec (BinTree a) Source #

type Prerequisites (BinTree a) Source #

(Ord a, HasSpec a) ⇒ HasSpec (Set a) Source # 
Instance details

Defined in Constrained.Spec.Set

Associated Types

type TypeSpec (Set a) Source #

type Prerequisites (Set a) Source #

Methods

emptySpecTypeSpec (Set a) Source #

combineSpecTypeSpec (Set a) → TypeSpec (Set a) → Specification (Set a) Source #

genFromTypeSpec ∷ ∀ (m ∷ Type → Type). (HasCallStack, MonadGenError m) ⇒ TypeSpec (Set a) → GenT m (Set a) Source #

conformsTo ∷ Set a → TypeSpec (Set a) → Bool Source #

shrinkWithTypeSpecTypeSpec (Set a) → Set a → [Set a] Source #

toPredsTerm (Set a) → TypeSpec (Set a) → Pred Source #

cardinalTypeSpecTypeSpec (Set a) → Specification Integer Source #

cardinalTrueSpecSpecification Integer Source #

typeSpecHasErrorTypeSpec (Set a) → Maybe (NonEmpty String) Source #

alternateShowTypeSpec (Set a) → BinaryShow Source #

monadConformsTo ∷ Set a → TypeSpec (Set a) → Writer [String] Bool Source #

typeSpecOptTypeSpec (Set a) → [Set a] → Specification (Set a) Source #

guardTypeSpec ∷ [String] → TypeSpec (Set a) → Specification (Set a) Source #

prerequisitesEvidence (Prerequisites (Set a)) Source #

HasSpec a ⇒ HasSpec (Tree a) Source # 
Instance details

Defined in Constrained.Spec.Tree

Associated Types

type TypeSpec (Tree a) Source #

type Prerequisites (Tree a) Source #

Methods

emptySpecTypeSpec (Tree a) Source #

combineSpecTypeSpec (Tree a) → TypeSpec (Tree a) → Specification (Tree a) Source #

genFromTypeSpec ∷ ∀ (m ∷ Type → Type). (HasCallStack, MonadGenError m) ⇒ TypeSpec (Tree a) → GenT m (Tree a) Source #

conformsTo ∷ Tree a → TypeSpec (Tree a) → Bool Source #

shrinkWithTypeSpecTypeSpec (Tree a) → Tree a → [Tree a] Source #

toPredsTerm (Tree a) → TypeSpec (Tree a) → Pred Source #

cardinalTypeSpecTypeSpec (Tree a) → Specification Integer Source #

cardinalTrueSpecSpecification Integer Source #

typeSpecHasErrorTypeSpec (Tree a) → Maybe (NonEmpty String) Source #

alternateShowTypeSpec (Tree a) → BinaryShow Source #

monadConformsTo ∷ Tree a → TypeSpec (Tree a) → Writer [String] Bool Source #

typeSpecOptTypeSpec (Tree a) → [Tree a] → Specification (Tree a) Source #

guardTypeSpec ∷ [String] → TypeSpec (Tree a) → Specification (Tree a) Source #

prerequisitesEvidence (Prerequisites (Tree a)) Source #

(IsNormalType a, HasSpec a) ⇒ HasSpec (Maybe a) Source # 
Instance details

Defined in Constrained.Spec.SumProd

Associated Types

type TypeSpec (Maybe a) Source #

type Prerequisites (Maybe a) Source #

Methods

emptySpecTypeSpec (Maybe a) Source #

combineSpecTypeSpec (Maybe a) → TypeSpec (Maybe a) → Specification (Maybe a) Source #

genFromTypeSpec ∷ ∀ (m ∷ Type → Type). (HasCallStack, MonadGenError m) ⇒ TypeSpec (Maybe a) → GenT m (Maybe a) Source #

conformsTo ∷ Maybe a → TypeSpec (Maybe a) → Bool Source #

shrinkWithTypeSpecTypeSpec (Maybe a) → Maybe a → [Maybe a] Source #

toPredsTerm (Maybe a) → TypeSpec (Maybe a) → Pred Source #

cardinalTypeSpecTypeSpec (Maybe a) → Specification Integer Source #

cardinalTrueSpecSpecification Integer Source #

typeSpecHasErrorTypeSpec (Maybe a) → Maybe (NonEmpty String) Source #

alternateShowTypeSpec (Maybe a) → BinaryShow Source #

monadConformsTo ∷ Maybe a → TypeSpec (Maybe a) → Writer [String] Bool Source #

typeSpecOptTypeSpec (Maybe a) → [Maybe a] → Specification (Maybe a) Source #

guardTypeSpec ∷ [String] → TypeSpec (Maybe a) → Specification (Maybe a) Source #

prerequisitesEvidence (Prerequisites (Maybe a)) Source #

(Sized [a], HasSpec a) ⇒ HasSpec [a] Source # 
Instance details

Defined in Constrained.TheKnot

Associated Types

type TypeSpec [a] Source #

type Prerequisites [a] Source #

Methods

emptySpecTypeSpec [a] Source #

combineSpecTypeSpec [a] → TypeSpec [a] → Specification [a] Source #

genFromTypeSpec ∷ ∀ (m ∷ Type → Type). (HasCallStack, MonadGenError m) ⇒ TypeSpec [a] → GenT m [a] Source #

conformsTo ∷ [a] → TypeSpec [a] → Bool Source #

shrinkWithTypeSpecTypeSpec [a] → [a] → [[a]] Source #

toPredsTerm [a] → TypeSpec [a] → Pred Source #

cardinalTypeSpecTypeSpec [a] → Specification Integer Source #

cardinalTrueSpecSpecification Integer Source #

typeSpecHasErrorTypeSpec [a] → Maybe (NonEmpty String) Source #

alternateShowTypeSpec [a] → BinaryShow Source #

monadConformsTo ∷ [a] → TypeSpec [a] → Writer [String] Bool Source #

typeSpecOptTypeSpec [a] → [[a]] → Specification [a] Source #

guardTypeSpec ∷ [String] → TypeSpec [a] → Specification [a] Source #

prerequisitesEvidence (Prerequisites [a]) Source #

(HasSpec a, IsNormalType a, HasSpec b, IsNormalType b) ⇒ HasSpec (Either a b) Source # 
Instance details

Defined in Constrained.Spec.SumProd

Associated Types

type TypeSpec (Either a b) Source #

type Prerequisites (Either a b) Source #

Methods

emptySpecTypeSpec (Either a b) Source #

combineSpecTypeSpec (Either a b) → TypeSpec (Either a b) → Specification (Either a b) Source #

genFromTypeSpec ∷ ∀ (m ∷ Type → Type). (HasCallStack, MonadGenError m) ⇒ TypeSpec (Either a b) → GenT m (Either a b) Source #

conformsTo ∷ Either a b → TypeSpec (Either a b) → Bool Source #

shrinkWithTypeSpecTypeSpec (Either a b) → Either a b → [Either a b] Source #

toPredsTerm (Either a b) → TypeSpec (Either a b) → Pred Source #

cardinalTypeSpecTypeSpec (Either a b) → Specification Integer Source #

cardinalTrueSpecSpecification Integer Source #

typeSpecHasErrorTypeSpec (Either a b) → Maybe (NonEmpty String) Source #

alternateShowTypeSpec (Either a b) → BinaryShow Source #

monadConformsTo ∷ Either a b → TypeSpec (Either a b) → Writer [String] Bool Source #

typeSpecOptTypeSpec (Either a b) → [Either a b] → Specification (Either a b) Source #

guardTypeSpec ∷ [String] → TypeSpec (Either a b) → Specification (Either a b) Source #

prerequisitesEvidence (Prerequisites (Either a b)) Source #

(HasSpec a, HasSpec b) ⇒ HasSpec (Prod a b) Source # 
Instance details

Defined in Constrained.TheKnot

Associated Types

type TypeSpec (Prod a b) Source #

type Prerequisites (Prod a b) Source #

Methods

emptySpecTypeSpec (Prod a b) Source #

combineSpecTypeSpec (Prod a b) → TypeSpec (Prod a b) → Specification (Prod a b) Source #

genFromTypeSpec ∷ ∀ (m ∷ Type → Type). (HasCallStack, MonadGenError m) ⇒ TypeSpec (Prod a b) → GenT m (Prod a b) Source #

conformsToProd a b → TypeSpec (Prod a b) → Bool Source #

shrinkWithTypeSpecTypeSpec (Prod a b) → Prod a b → [Prod a b] Source #

toPredsTerm (Prod a b) → TypeSpec (Prod a b) → Pred Source #

cardinalTypeSpecTypeSpec (Prod a b) → Specification Integer Source #

cardinalTrueSpecSpecification Integer Source #

typeSpecHasErrorTypeSpec (Prod a b) → Maybe (NonEmpty String) Source #

alternateShowTypeSpec (Prod a b) → BinaryShow Source #

monadConformsToProd a b → TypeSpec (Prod a b) → Writer [String] Bool Source #

typeSpecOptTypeSpec (Prod a b) → [Prod a b] → Specification (Prod a b) Source #

guardTypeSpec ∷ [String] → TypeSpec (Prod a b) → Specification (Prod a b) Source #

prerequisitesEvidence (Prerequisites (Prod a b)) Source #

(HasSpec a, HasSpec b, KnownNat (CountCases b)) ⇒ HasSpec (Sum a b) Source #

The HasSpec Sum instance

Instance details

Defined in Constrained.TheKnot

Associated Types

type TypeSpec (Sum a b) Source #

type Prerequisites (Sum a b) Source #

Methods

emptySpecTypeSpec (Sum a b) Source #

combineSpecTypeSpec (Sum a b) → TypeSpec (Sum a b) → Specification (Sum a b) Source #

genFromTypeSpec ∷ ∀ (m ∷ Type → Type). (HasCallStack, MonadGenError m) ⇒ TypeSpec (Sum a b) → GenT m (Sum a b) Source #

conformsToSum a b → TypeSpec (Sum a b) → Bool Source #

shrinkWithTypeSpecTypeSpec (Sum a b) → Sum a b → [Sum a b] Source #

toPredsTerm (Sum a b) → TypeSpec (Sum a b) → Pred Source #

cardinalTypeSpecTypeSpec (Sum a b) → Specification Integer Source #

cardinalTrueSpecSpecification Integer Source #

typeSpecHasErrorTypeSpec (Sum a b) → Maybe (NonEmpty String) Source #

alternateShowTypeSpec (Sum a b) → BinaryShow Source #

monadConformsToSum a b → TypeSpec (Sum a b) → Writer [String] Bool Source #

typeSpecOptTypeSpec (Sum a b) → [Sum a b] → Specification (Sum a b) Source #

guardTypeSpec ∷ [String] → TypeSpec (Sum a b) → Specification (Sum a b) Source #

prerequisitesEvidence (Prerequisites (Sum a b)) Source #

(Ord k, HasSpec (Prod k v), HasSpec k, HasSpec v, HasSpec [v], IsNormalType k, IsNormalType v) ⇒ HasSpec (Map k v) Source # 
Instance details

Defined in Constrained.Spec.Map

Associated Types

type TypeSpec (Map k v) Source #

type Prerequisites (Map k v) Source #

Methods

emptySpecTypeSpec (Map k v) Source #

combineSpecTypeSpec (Map k v) → TypeSpec (Map k v) → Specification (Map k v) Source #

genFromTypeSpec ∷ ∀ (m ∷ Type → Type). (HasCallStack, MonadGenError m) ⇒ TypeSpec (Map k v) → GenT m (Map k v) Source #

conformsTo ∷ Map k v → TypeSpec (Map k v) → Bool Source #

shrinkWithTypeSpecTypeSpec (Map k v) → Map k v → [Map k v] Source #

toPredsTerm (Map k v) → TypeSpec (Map k v) → Pred Source #

cardinalTypeSpecTypeSpec (Map k v) → Specification Integer Source #

cardinalTrueSpecSpecification Integer Source #

typeSpecHasErrorTypeSpec (Map k v) → Maybe (NonEmpty String) Source #

alternateShowTypeSpec (Map k v) → BinaryShow Source #

monadConformsTo ∷ Map k v → TypeSpec (Map k v) → Writer [String] Bool Source #

typeSpecOptTypeSpec (Map k v) → [Map k v] → Specification (Map k v) Source #

guardTypeSpec ∷ [String] → TypeSpec (Map k v) → Specification (Map k v) Source #

prerequisitesEvidence (Prerequisites (Map k v)) Source #

(HasSpec a, HasSpec b) ⇒ HasSpec (a, b) Source # 
Instance details

Defined in Constrained.Spec.SumProd

Associated Types

type TypeSpec (a, b) Source #

type Prerequisites (a, b) Source #

Methods

emptySpecTypeSpec (a, b) Source #

combineSpecTypeSpec (a, b) → TypeSpec (a, b) → Specification (a, b) Source #

genFromTypeSpec ∷ ∀ (m ∷ Type → Type). (HasCallStack, MonadGenError m) ⇒ TypeSpec (a, b) → GenT m (a, b) Source #

conformsTo ∷ (a, b) → TypeSpec (a, b) → Bool Source #

shrinkWithTypeSpecTypeSpec (a, b) → (a, b) → [(a, b)] Source #

toPredsTerm (a, b) → TypeSpec (a, b) → Pred Source #

cardinalTypeSpecTypeSpec (a, b) → Specification Integer Source #

cardinalTrueSpecSpecification Integer Source #

typeSpecHasErrorTypeSpec (a, b) → Maybe (NonEmpty String) Source #

alternateShowTypeSpec (a, b) → BinaryShow Source #

monadConformsTo ∷ (a, b) → TypeSpec (a, b) → Writer [String] Bool Source #

typeSpecOptTypeSpec (a, b) → [(a, b)] → Specification (a, b) Source #

guardTypeSpec ∷ [String] → TypeSpec (a, b) → Specification (a, b) Source #

prerequisitesEvidence (Prerequisites (a, b)) Source #

(HasSpec a, HasSpec b, HasSpec c) ⇒ HasSpec (a, b, c) Source # 
Instance details

Defined in Constrained.Spec.SumProd

Associated Types

type TypeSpec (a, b, c) Source #

type Prerequisites (a, b, c) Source #

Methods

emptySpecTypeSpec (a, b, c) Source #

combineSpecTypeSpec (a, b, c) → TypeSpec (a, b, c) → Specification (a, b, c) Source #

genFromTypeSpec ∷ ∀ (m ∷ Type → Type). (HasCallStack, MonadGenError m) ⇒ TypeSpec (a, b, c) → GenT m (a, b, c) Source #

conformsTo ∷ (a, b, c) → TypeSpec (a, b, c) → Bool Source #

shrinkWithTypeSpecTypeSpec (a, b, c) → (a, b, c) → [(a, b, c)] Source #

toPredsTerm (a, b, c) → TypeSpec (a, b, c) → Pred Source #

cardinalTypeSpecTypeSpec (a, b, c) → Specification Integer Source #

cardinalTrueSpecSpecification Integer Source #

typeSpecHasErrorTypeSpec (a, b, c) → Maybe (NonEmpty String) Source #

alternateShowTypeSpec (a, b, c) → BinaryShow Source #

monadConformsTo ∷ (a, b, c) → TypeSpec (a, b, c) → Writer [String] Bool Source #

typeSpecOptTypeSpec (a, b, c) → [(a, b, c)] → Specification (a, b, c) Source #

guardTypeSpec ∷ [String] → TypeSpec (a, b, c) → Specification (a, b, c) Source #

prerequisitesEvidence (Prerequisites (a, b, c)) Source #

(HasSpec a, HasSpec b, HasSpec c, HasSpec d) ⇒ HasSpec (a, b, c, d) Source # 
Instance details

Defined in Constrained.Spec.SumProd

Associated Types

type TypeSpec (a, b, c, d) Source #

type Prerequisites (a, b, c, d) Source #

Methods

emptySpecTypeSpec (a, b, c, d) Source #

combineSpecTypeSpec (a, b, c, d) → TypeSpec (a, b, c, d) → Specification (a, b, c, d) Source #

genFromTypeSpec ∷ ∀ (m ∷ Type → Type). (HasCallStack, MonadGenError m) ⇒ TypeSpec (a, b, c, d) → GenT m (a, b, c, d) Source #

conformsTo ∷ (a, b, c, d) → TypeSpec (a, b, c, d) → Bool Source #

shrinkWithTypeSpecTypeSpec (a, b, c, d) → (a, b, c, d) → [(a, b, c, d)] Source #

toPredsTerm (a, b, c, d) → TypeSpec (a, b, c, d) → Pred Source #

cardinalTypeSpecTypeSpec (a, b, c, d) → Specification Integer Source #

cardinalTrueSpecSpecification Integer Source #

typeSpecHasErrorTypeSpec (a, b, c, d) → Maybe (NonEmpty String) Source #

alternateShowTypeSpec (a, b, c, d) → BinaryShow Source #

monadConformsTo ∷ (a, b, c, d) → TypeSpec (a, b, c, d) → Writer [String] Bool Source #

typeSpecOptTypeSpec (a, b, c, d) → [(a, b, c, d)] → Specification (a, b, c, d) Source #

guardTypeSpec ∷ [String] → TypeSpec (a, b, c, d) → Specification (a, b, c, d) Source #

prerequisitesEvidence (Prerequisites (a, b, c, d)) Source #

(HasSpec a, HasSpec b, HasSpec c, HasSpec d, HasSpec e) ⇒ HasSpec (a, b, c, d, e) Source # 
Instance details

Defined in Constrained.Spec.SumProd

Associated Types

type TypeSpec (a, b, c, d, e) Source #

type Prerequisites (a, b, c, d, e) Source #

Methods

emptySpecTypeSpec (a, b, c, d, e) Source #

combineSpecTypeSpec (a, b, c, d, e) → TypeSpec (a, b, c, d, e) → Specification (a, b, c, d, e) Source #

genFromTypeSpec ∷ ∀ (m ∷ Type → Type). (HasCallStack, MonadGenError m) ⇒ TypeSpec (a, b, c, d, e) → GenT m (a, b, c, d, e) Source #

conformsTo ∷ (a, b, c, d, e) → TypeSpec (a, b, c, d, e) → Bool Source #

shrinkWithTypeSpecTypeSpec (a, b, c, d, e) → (a, b, c, d, e) → [(a, b, c, d, e)] Source #

toPredsTerm (a, b, c, d, e) → TypeSpec (a, b, c, d, e) → Pred Source #

cardinalTypeSpecTypeSpec (a, b, c, d, e) → Specification Integer Source #

cardinalTrueSpecSpecification Integer Source #

typeSpecHasErrorTypeSpec (a, b, c, d, e) → Maybe (NonEmpty String) Source #

alternateShowTypeSpec (a, b, c, d, e) → BinaryShow Source #

monadConformsTo ∷ (a, b, c, d, e) → TypeSpec (a, b, c, d, e) → Writer [String] Bool Source #

typeSpecOptTypeSpec (a, b, c, d, e) → [(a, b, c, d, e)] → Specification (a, b, c, d, e) Source #

guardTypeSpec ∷ [String] → TypeSpec (a, b, c, d, e) → Specification (a, b, c, d, e) Source #

prerequisitesEvidence (Prerequisites (a, b, c, d, e)) Source #

(HasSpec a, HasSpec b, HasSpec c, HasSpec d, HasSpec e, HasSpec g) ⇒ HasSpec (a, b, c, d, e, g) Source # 
Instance details

Defined in Constrained.Spec.SumProd

Associated Types

type TypeSpec (a, b, c, d, e, g) Source #

type Prerequisites (a, b, c, d, e, g) Source #

Methods

emptySpecTypeSpec (a, b, c, d, e, g) Source #

combineSpecTypeSpec (a, b, c, d, e, g) → TypeSpec (a, b, c, d, e, g) → Specification (a, b, c, d, e, g) Source #

genFromTypeSpec ∷ ∀ (m ∷ Type → Type). (HasCallStack, MonadGenError m) ⇒ TypeSpec (a, b, c, d, e, g) → GenT m (a, b, c, d, e, g) Source #

conformsTo ∷ (a, b, c, d, e, g) → TypeSpec (a, b, c, d, e, g) → Bool Source #

shrinkWithTypeSpecTypeSpec (a, b, c, d, e, g) → (a, b, c, d, e, g) → [(a, b, c, d, e, g)] Source #

toPredsTerm (a, b, c, d, e, g) → TypeSpec (a, b, c, d, e, g) → Pred Source #

cardinalTypeSpecTypeSpec (a, b, c, d, e, g) → Specification Integer Source #

cardinalTrueSpecSpecification Integer Source #

typeSpecHasErrorTypeSpec (a, b, c, d, e, g) → Maybe (NonEmpty String) Source #

alternateShowTypeSpec (a, b, c, d, e, g) → BinaryShow Source #

monadConformsTo ∷ (a, b, c, d, e, g) → TypeSpec (a, b, c, d, e, g) → Writer [String] Bool Source #

typeSpecOptTypeSpec (a, b, c, d, e, g) → [(a, b, c, d, e, g)] → Specification (a, b, c, d, e, g) Source #

guardTypeSpec ∷ [String] → TypeSpec (a, b, c, d, e, g) → Specification (a, b, c, d, e, g) Source #

prerequisitesEvidence (Prerequisites (a, b, c, d, e, g)) Source #

(HasSpec a, HasSpec b, HasSpec c, HasSpec d, HasSpec e, HasSpec g, HasSpec h) ⇒ HasSpec (a, b, c, d, e, g, h) Source # 
Instance details

Defined in Constrained.Spec.SumProd

Associated Types

type TypeSpec (a, b, c, d, e, g, h) Source #

type Prerequisites (a, b, c, d, e, g, h) Source #

Methods

emptySpecTypeSpec (a, b, c, d, e, g, h) Source #

combineSpecTypeSpec (a, b, c, d, e, g, h) → TypeSpec (a, b, c, d, e, g, h) → Specification (a, b, c, d, e, g, h) Source #

genFromTypeSpec ∷ ∀ (m ∷ Type → Type). (HasCallStack, MonadGenError m) ⇒ TypeSpec (a, b, c, d, e, g, h) → GenT m (a, b, c, d, e, g, h) Source #

conformsTo ∷ (a, b, c, d, e, g, h) → TypeSpec (a, b, c, d, e, g, h) → Bool Source #

shrinkWithTypeSpecTypeSpec (a, b, c, d, e, g, h) → (a, b, c, d, e, g, h) → [(a, b, c, d, e, g, h)] Source #

toPredsTerm (a, b, c, d, e, g, h) → TypeSpec (a, b, c, d, e, g, h) → Pred Source #

cardinalTypeSpecTypeSpec (a, b, c, d, e, g, h) → Specification Integer Source #

cardinalTrueSpecSpecification Integer Source #

typeSpecHasErrorTypeSpec (a, b, c, d, e, g, h) → Maybe (NonEmpty String) Source #

alternateShowTypeSpec (a, b, c, d, e, g, h) → BinaryShow Source #

monadConformsTo ∷ (a, b, c, d, e, g, h) → TypeSpec (a, b, c, d, e, g, h) → Writer [String] Bool Source #

typeSpecOptTypeSpec (a, b, c, d, e, g, h) → [(a, b, c, d, e, g, h)] → Specification (a, b, c, d, e, g, h) Source #

guardTypeSpec ∷ [String] → TypeSpec (a, b, c, d, e, g, h) → Specification (a, b, c, d, e, g, h) Source #

prerequisitesEvidence (Prerequisites (a, b, c, d, e, g, h)) Source #

data BaseW (dom ∷ [Type]) (rng ∷ Type) where Source #

Constructors

ToGenericWGenericRequires a ⇒ BaseW '[a] (SimpleRep a) 
FromGenericWGenericRequires a ⇒ BaseW '[SimpleRep a] a 

Instances

Instances details
Logic BaseW Source # 
Instance details

Defined in Constrained.Base

Methods

propagateTypeSpec ∷ ∀ (as ∷ [Type]) b a. (AppRequires BaseW as b, HasSpec a) ⇒ BaseW as b → ListCtx Value as (HOLE a) → TypeSpec b → [b] → Specification a Source #

propagateMemberSpec ∷ ∀ (as ∷ [Type]) b a. (AppRequires BaseW as b, HasSpec a) ⇒ BaseW as b → ListCtx Value as (HOLE a) → NonEmpty b → Specification a Source #

propagate ∷ ∀ (as ∷ [Type]) b a. (AppRequires BaseW as b, HasSpec a) ⇒ BaseW as b → ListCtx Value as (HOLE a) → Specification b → Specification a Source #

rewriteRules ∷ ∀ (dom ∷ [Type]) rng. (TypeList dom, Typeable dom, HasSpec rng, All HasSpec dom) ⇒ BaseW dom rng → List Term dom → Evidence (AppRequires BaseW dom rng) → Maybe (Term rng) Source #

mapTypeSpec ∷ (HasSpec a, HasSpec b) ⇒ BaseW '[a] b → TypeSpec a → Specification b Source #

saturate ∷ ∀ (dom ∷ [Type]). BaseW dom Bool → List Term dom → [Pred] Source #

Semantics BaseW Source # 
Instance details

Defined in Constrained.Base

Methods

semantics ∷ ∀ (d ∷ [Type]) r. BaseW d r → FunTy d r Source #

Syntax BaseW Source # 
Instance details

Defined in Constrained.Base

Methods

inFix ∷ ∀ (dom ∷ [Type]) rng. BaseW dom rng → Bool Source #

prettyWit ∷ ∀ (dom ∷ [Type]) rng ann. (All HasSpec dom, HasSpec rng) ⇒ BaseW dom rng → List Term dom → Int → Maybe (Doc ann) Source #

Show (BaseW d r) Source # 
Instance details

Defined in Constrained.Base

Methods

showsPrec ∷ Int → BaseW d r → ShowS

showBaseW d r → String

showList ∷ [BaseW d r] → ShowS

Eq (BaseW dom rng) Source # 
Instance details

Defined in Constrained.Base

Methods

(==)BaseW dom rng → BaseW dom rng → Bool

(/=)BaseW dom rng → BaseW dom rng → Bool

toGeneric_ ∷ ∀ a. GenericRequires a ⇒ Term a → Term (SimpleRep a) Source #

data BinaryShow where Source #

Constructors

BinaryShow ∷ ∀ a. String → [Doc a] → BinaryShow 
NonBinaryBinaryShow 

type AppRequires t dom rng = (Logic t, TypeList dom, Eq (t dom rng), Show (t dom rng), Typeable dom, Typeable rng, All HasSpec dom, HasSpec rng) Source #

What constraints does the Term constructor App require? (Logic sym t dom rng) supplies the Logic of propagating contexts (All HasSpec dom) the argument types are part of the system (HasSpec rng) the return type is part of the system.

data Term a where Source #

Constructors

App ∷ ∀ t dom rng. AppRequires t dom rng ⇒ t dom rng → List Term dom → Term rng 
Lit ∷ (Typeable a, Eq a, Show a) ⇒ a → Term a 
VHasSpec a ⇒ Var a → Term a 

Instances

Instances details
(Ord a, HasSpec a, HasSpec (Set a)) ⇒ Monoid (Term (Set a)) 
Instance details

Defined in Constrained.Spec.Set

Methods

memptyTerm (Set a)

mappendTerm (Set a) → Term (Set a) → Term (Set a)

mconcat ∷ [Term (Set a)] → Term (Set a)

(Ord a, HasSpec a, HasSpec (Set a)) ⇒ Semigroup (Term (Set a)) 
Instance details

Defined in Constrained.Spec.Set

Methods

(<>)Term (Set a) → Term (Set a) → Term (Set a) #

sconcatNonEmpty (Term (Set a)) → Term (Set a)

stimes ∷ Integral b ⇒ b → Term (Set a) → Term (Set a)

NumLike a ⇒ Num (Term a) 
Instance details

Defined in Constrained.NumSpec

Methods

(+)Term a → Term a → Term a

(-)Term a → Term a → Term a

(*)Term a → Term a → Term a

negateTerm a → Term a

absTerm a → Term a

signumTerm a → Term a

fromInteger ∷ Integer → Term a

Show a ⇒ Show (Term a) Source # 
Instance details

Defined in Constrained.Base

Methods

showsPrec ∷ Int → Term a → ShowS

showTerm a → String

showList ∷ [Term a] → ShowS

IsPred (Term Bool) Source # 
Instance details

Defined in Constrained.Base

Methods

toPredTerm Bool → Pred Source #

Rename (Term a) Source # 
Instance details

Defined in Constrained.Syntax

Methods

rename ∷ Typeable x ⇒ Var x → Var x → Term a → Term a Source #

HasVariables (Term a) Source # 
Instance details

Defined in Constrained.Syntax

Methods

freeVarsTerm a → FreeVars Source #

freeVarSetTerm a → Set Name Source #

countOfNameTerm a → Int Source #

appearsInNameTerm a → Bool Source #

Eq (Term a) Source # 
Instance details

Defined in Constrained.Base

Methods

(==)Term a → Term a → Bool

(/=)Term a → Term a → Bool

Show a ⇒ Pretty (Term a) Source # 
Instance details

Defined in Constrained.Base

Methods

prettyTerm a → Doc ann Source #

prettyList ∷ [Term a] → Doc ann Source #

Show a ⇒ Pretty (WithPrec (Term a)) Source # 
Instance details

Defined in Constrained.Base

Methods

prettyWithPrec (Term a) → Doc ann Source #

prettyList ∷ [WithPrec (Term a)] → Doc ann Source #

HasVariables (List Term as) Source # 
Instance details

Defined in Constrained.Syntax

Methods

freeVarsList Term as → FreeVars Source #

freeVarSetList Term as → Set Name Source #

countOfNameList Term as → Int Source #

appearsInNameList Term as → Bool Source #

sameTermsAll HasSpec as ⇒ List Term as → List Term as → Bool Source #

appSym ∷ ∀ t as b. AppRequires t as b ⇒ t as b → List Term as → Term b Source #

Recall function symbols are objects that you can use to build applications They carry information about both its semantic and logical properties. Usually the Haskel name ends in '_', for example consider: not_, subset_ ,lookup_, toGeneric_ Infix function symbols names end in ., for example: ==. , <=. E.g appTerm ToGenericW :: Term a -> Term(SimpleRep a) (appTerm ToGenericW (lit True)) builds the Term (toGeneric_ True) Note the witness (ToGenericW ) must have a Logic instance like: instance Logic BaseW '[a] (SimpleRep a) where ... type of ToGenericW ^ arg types^ result type^ The Logic instance does not demand any of these things have any properties at all. It is here, where we actually build the App node, that we demand the properties App terms require. App :: AppRequires s t ds r => t s ds r -> List Term dom -> Term rng

appTerm ∷ ∀ t ds r. AppRequires t ds r ⇒ t ds r → FunTy (MapList Term ds) (Term r) Source #

name ∷ String → Term a → Term a Source #

named ∷ String → Term a → Term a Source #

Give a Term a nameHint, if its a Var, and doesn't already have one, otherwise return the Term unchanged.

data Binder a where Source #

Constructors

(:->)HasSpec a ⇒ Var a → PredBinder a 

Instances

Instances details
Show (Binder a) Source # 
Instance details

Defined in Constrained.Base

Methods

showsPrec ∷ Int → Binder a → ShowS

showBinder a → String

showList ∷ [Binder a] → ShowS

Rename (Binder a) Source # 
Instance details

Defined in Constrained.Syntax

Methods

rename ∷ Typeable x ⇒ Var x → Var x → Binder a → Binder a Source #

HasVariables (Binder a) Source # 
Instance details

Defined in Constrained.Syntax

Methods

freeVarsBinder a → FreeVars Source #

freeVarSetBinder a → Set Name Source #

countOfNameBinder a → Int Source #

appearsInNameBinder a → Bool Source #

Pretty (Binder a) Source # 
Instance details

Defined in Constrained.Base

Methods

prettyBinder a → Doc ann Source #

prettyList ∷ [Binder a] → Doc ann Source #

HasVariables (List (Weighted Binder) as) Source # 
Instance details

Defined in Constrained.Syntax

Methods

freeVarsList (Weighted Binder) as → FreeVars Source #

freeVarSetList (Weighted Binder) as → Set Name Source #

countOfNameList (Weighted Binder) as → Int Source #

appearsInNameList (Weighted Binder) as → Bool Source #

bind ∷ (HasSpec a, IsPred p) ⇒ (Term a → p) → Binder a Source #

data Weighted f a Source #

Constructors

Weighted 

Fields

Instances

Instances details
Foldable f ⇒ Foldable (Weighted f) Source # 
Instance details

Defined in Constrained.Base

Methods

fold ∷ Monoid m ⇒ Weighted f m → m

foldMap ∷ Monoid m ⇒ (a → m) → Weighted f a → m

foldMap' ∷ Monoid m ⇒ (a → m) → Weighted f a → m

foldr ∷ (a → b → b) → b → Weighted f a → b

foldr' ∷ (a → b → b) → b → Weighted f a → b

foldl ∷ (b → a → b) → b → Weighted f a → b

foldl' ∷ (b → a → b) → b → Weighted f a → b

foldr1 ∷ (a → a → a) → Weighted f a → a

foldl1 ∷ (a → a → a) → Weighted f a → a

toListWeighted f a → [a]

nullWeighted f a → Bool

lengthWeighted f a → Int

elem ∷ Eq a ⇒ a → Weighted f a → Bool

maximum ∷ Ord a ⇒ Weighted f a → a

minimum ∷ Ord a ⇒ Weighted f a → a

sum ∷ Num a ⇒ Weighted f a → a

product ∷ Num a ⇒ Weighted f a → a

Traversable f ⇒ Traversable (Weighted f) Source # 
Instance details

Defined in Constrained.Base

Methods

traverse ∷ Applicative f0 ⇒ (a → f0 b) → Weighted f a → f0 (Weighted f b)

sequenceA ∷ Applicative f0 ⇒ Weighted f (f0 a) → f0 (Weighted f a)

mapM ∷ Monad m ⇒ (a → m b) → Weighted f a → m (Weighted f b)

sequence ∷ Monad m ⇒ Weighted f (m a) → m (Weighted f a)

Functor f ⇒ Functor (Weighted f) Source # 
Instance details

Defined in Constrained.Base

Methods

fmap ∷ (a → b) → Weighted f a → Weighted f b

(<$) ∷ a → Weighted f b → Weighted f a

Rename (f a) ⇒ Rename (Weighted f a) Source # 
Instance details

Defined in Constrained.Syntax

Methods

rename ∷ Typeable x ⇒ Var x → Var x → Weighted f a → Weighted f a Source #

HasVariables (f a) ⇒ HasVariables (Weighted f a) Source # 
Instance details

Defined in Constrained.Syntax

Methods

freeVarsWeighted f a → FreeVars Source #

freeVarSetWeighted f a → Set Name Source #

countOfNameWeighted f a → Int Source #

appearsInNameWeighted f a → Bool Source #

HasVariables (List (Weighted Binder) as) Source # 
Instance details

Defined in Constrained.Syntax

Methods

freeVarsList (Weighted Binder) as → FreeVars Source #

freeVarSetList (Weighted Binder) as → Set Name Source #

countOfNameList (Weighted Binder) as → Int Source #

appearsInNameList (Weighted Binder) as → Bool Source #

Pretty (f a) ⇒ Pretty (Weighted f a) Source # 
Instance details

Defined in Constrained.Base

Methods

prettyWeighted f a → Doc ann Source #

prettyList ∷ [Weighted f a] → Doc ann Source #

mapWeighted ∷ (f a → g b) → Weighted f a → Weighted g b Source #

traverseWeighted ∷ Applicative m ⇒ (f a → m (g a)) → Weighted f a → m (Weighted g a) Source #

data Pred where Source #

Constructors

ElemPred ∷ ∀ a. HasSpec a ⇒ Bool → Term a → NonEmpty a → Pred 
Monitor ∷ ((∀ a. Term a → a) → PropertyProperty) → Pred 
And ∷ [Pred] → Pred 
Exists 

Fields

  • ∷ ((∀ b. Term b → b) → GE a)

    Constructive recovery function for checking existential quantification

  • Binder a
     
  • Pred
     
SubstHasSpec a ⇒ Var a → Term a → PredPred 
LetTerm a → Binder a → Pred 
AssertTerm Bool → Pred 
Reifies 

Fields

  • ∷ (HasSpec a, HasSpec b)
     
  • Term b

    This depends on the a term

  • Term a
     
  • → (a → b)

    Recover a useable value from the a term.

  • Pred
     
DependsOn ∷ (HasSpec a, HasSpec b) ⇒ Term a → Term b → Pred 
ForAll ∷ (Forallable t a, HasSpec t, HasSpec a) ⇒ Term t → Binder a → Pred 
Case 

Fields

WhenHasSpec Bool ⇒ Term Bool → PredPred 
GenHintHasGenHint a ⇒ Hint a → Term a → Pred 
TruePredPred 
FalsePredNonEmpty String → Pred 
ExplainNonEmpty String → PredPred 

Instances

Instances details
Monoid Pred Source # 
Instance details

Defined in Constrained.Base

Methods

memptyPred

mappendPredPredPred

mconcat ∷ [Pred] → Pred

Semigroup Pred Source # 
Instance details

Defined in Constrained.Base

Methods

(<>)PredPredPred #

sconcatNonEmpty PredPred

stimes ∷ Integral b ⇒ b → PredPred

Show Pred Source # 
Instance details

Defined in Constrained.Base

Methods

showsPrec ∷ Int → Pred → ShowS

showPred → String

showList ∷ [Pred] → ShowS

IsPred Pred Source # 
Instance details

Defined in Constrained.Base

Methods

toPredPredPred Source #

Rename Pred Source # 
Instance details

Defined in Constrained.Syntax

Methods

rename ∷ Typeable x ⇒ Var x → Var x → PredPred Source #

HasVariables Pred Source # 
Instance details

Defined in Constrained.Syntax

Methods

freeVarsPredFreeVars Source #

freeVarSetPred → Set Name Source #

countOfNamePred → Int Source #

appearsInNamePred → Bool Source #

Pretty Pred Source # 
Instance details

Defined in Constrained.Base

Methods

prettyPredDoc ann Source #

prettyList ∷ [Pred] → Doc ann Source #

class Forallable t e | t → e where Source #

Minimal complete definition

Nothing

Instances

Instances details
(Typeable a, Ord a) ⇒ Forallable (NotASet a) a Source # 
Instance details

Defined in Constrained.Examples.Set

Ord a ⇒ Forallable (Set a) a Source # 
Instance details

Defined in Constrained.Spec.Set

Methods

fromForAllSpecSpecification a → Specification (Set a) Source #

forAllToList ∷ Set a → [a] Source #

Forallable [a] a Source # 
Instance details

Defined in Constrained.TheKnot

Forallable (Tree a) (a, [Tree a]) Source # 
Instance details

Defined in Constrained.Spec.Tree

Methods

fromForAllSpecSpecification (a, [Tree a]) → Specification (Tree a) Source #

forAllToList ∷ Tree a → [(a, [Tree a])] Source #

Forallable (BinTree a) (BinTree a, a, BinTree a) Source # 
Instance details

Defined in Constrained.Spec.Tree

Ord k ⇒ Forallable (Map k v) (k, v) Source # 
Instance details

Defined in Constrained.Spec.Map

Methods

fromForAllSpecSpecification (k, v) → Specification (Map k v) Source #

forAllToList ∷ Map k v → [(k, v)] Source #

class (HasSpec a, Show (Hint a)) ⇒ HasGenHint a where Source #

Hints are things that only affect generation, and not validation. For instance, parameters to control distribution of generated values.

Associated Types

type Hint a Source #

Methods

giveHintHint a → Specification a Source #

Instances

Instances details
HasSpec a ⇒ HasGenHint (BinTree a) Source # 
Instance details

Defined in Constrained.Spec.Tree

Associated Types

type Hint (BinTree a) Source #

HasSpec a ⇒ HasGenHint (Tree a) Source # 
Instance details

Defined in Constrained.Spec.Tree

Associated Types

type Hint (Tree a) Source #

Methods

giveHintHint (Tree a) → Specification (Tree a) Source #

(Sized [a], HasSpec a) ⇒ HasGenHint [a] Source # 
Instance details

Defined in Constrained.TheKnot

Associated Types

type Hint [a] Source #

Methods

giveHintHint [a] → Specification [a] Source #

(Ord k, HasSpec k, HasSpec v, HasSpec [v], IsNormalType k, IsNormalType v) ⇒ HasGenHint (Map k v) Source # 
Instance details

Defined in Constrained.Spec.Map

Associated Types

type Hint (Map k v) Source #

Methods

giveHintHint (Map k v) → Specification (Map k v) Source #

class Show p ⇒ IsPred p where Source #

Methods

toPred ∷ p → Pred Source #

Instances

Instances details
IsPred Pred Source # 
Instance details

Defined in Constrained.Base

Methods

toPredPredPred Source #

IsPred Bool Source # 
Instance details

Defined in Constrained.Base

Methods

toPred ∷ Bool → Pred Source #

IsPred (Term Bool) Source # 
Instance details

Defined in Constrained.Base

Methods

toPredTerm Bool → Pred Source #

IsPred p ⇒ IsPred [p] Source # 
Instance details

Defined in Constrained.Base

Methods

toPred ∷ [p] → Pred Source #

memberSpecList ∷ [a] → NonEmpty String → Specification a Source #

return a MemberSpec or ans ErrorSpec depending on if xs the null list or not

notEqualSpec ∷ ∀ a. HasSpec a ⇒ a → Specification a Source #

notMemberSpec ∷ ∀ a f. (HasSpec a, Foldable f) ⇒ f a → Specification a Source #

constrained ∷ ∀ a p. (IsPred p, HasSpec a) ⇒ (Term a → p) → Specification a Source #

isErrorLike ∷ ∀ a. Specification a → Bool Source #

fromGESpec ∷ HasCallStack ⇒ GE (Specification a) → Specification a Source #

addToErrorSpecNonEmpty String → Specification a → Specification a Source #

Add the explanations, if it's an ErrorSpec, else drop them

data WithPrec a Source #

Constructors

WithPrec Int a 

Instances

Instances details
HasSpec a ⇒ Pretty (WithPrec (Specification a)) Source # 
Instance details

Defined in Constrained.Base

Show a ⇒ Pretty (WithPrec (Term a)) Source # 
Instance details

Defined in Constrained.Base

Methods

prettyWithPrec (Term a) → Doc ann Source #

prettyList ∷ [WithPrec (Term a)] → Doc ann Source #

(HasSpec (k, v), HasSpec k, HasSpec v, HasSpec [v]) ⇒ Pretty (WithPrec (MapSpec k v)) Source # 
Instance details

Defined in Constrained.Spec.Map

Methods

prettyWithPrec (MapSpec k v) → Doc ann Source #

prettyList ∷ [WithPrec (MapSpec k v)] → Doc ann Source #

HasSpec a ⇒ Pretty (WithPrec (FoldSpec a)) Source # 
Instance details

Defined in Constrained.TheKnot

Methods

prettyWithPrec (FoldSpec a) → Doc ann Source #

prettyList ∷ [WithPrec (FoldSpec a)] → Doc ann Source #

HasSpec a ⇒ Pretty (WithPrec (ListSpec a)) Source # 
Instance details

Defined in Constrained.TheKnot

Methods

prettyWithPrec (ListSpec a) → Doc ann Source #

prettyList ∷ [WithPrec (ListSpec a)] → Doc ann Source #

parensIf ∷ Bool → Doc ann → Doc ann Source #

prettyPrecPretty (WithPrec a) ⇒ Int → a → Doc ann Source #

ppList ∷ ∀ f as ann. All HasSpec as ⇒ (∀ a. HasSpec a ⇒ f a → Doc ann) → List f as → [Doc ann] Source #

ppList_ ∷ ∀ f as ann. (∀ a. f a → Doc ann) → List f as → [Doc ann] Source #

prettyType ∷ ∀ t x. Typeable t ⇒ Doc x Source #

vsep' ∷ [Doc ann] → Doc ann Source #

(/>)Doc ann → Doc ann → Doc ann infixl 5 Source #

short ∷ ∀ a x. (Show a, Typeable a) ⇒ [a] → Doc x Source #

showType ∷ ∀ t. Typeable t ⇒ String Source #

data Fun dom rng where Source #

Constructors

Fun ∷ ∀ t dom rng. AppRequires t dom rng ⇒ t dom rng → Fun dom rng 

Instances

Instances details
Show (Fun dom r) Source # 
Instance details

Defined in Constrained.Base

Methods

showsPrec ∷ Int → Fun dom r → ShowS

showFun dom r → String

showList ∷ [Fun dom r] → ShowS

Eq (Fun d r) Source # 
Instance details

Defined in Constrained.Base

Methods

(==)Fun d r → Fun d r → Bool

(/=)Fun d r → Fun d r → Bool

extractf ∷ ∀ t d r. LogicRequires t ⇒ Fun d r → Maybe (t d r) Source #

appFunFun '[x] b → Term x → Term b Source #

sameFunFun d1 r1 → Fun d2 r2 → Bool Source #

pattern FromGeneric ∷ ∀ rng. () ⇒ ∀ a. (rng ~ a, GenericRequires a, HasSpec a, AppRequires BaseW '[SimpleRep a] rng) ⇒ Term (SimpleRep a) → Term rng Source #

pattern ToGeneric ∷ ∀ rng. () ⇒ ∀ a. (rng ~ SimpleRep a, GenericRequires a, HasSpec a, AppRequires BaseW '[a] rng) ⇒ Term a → Term rng Source #

Orphan instances

HasSimpleRep () Source # 
Instance details

Associated Types

type SimpleRep () Source #

type TheSop () ∷ [Type] Source #

Methods

toSimpleRep ∷ () → SimpleRep () Source #

fromSimpleRepSimpleRep () → () Source #

Typeable c ⇒ Show (Evidence c) Source # 
Instance details

Methods

showsPrec ∷ Int → Evidence c → ShowS

showEvidence c → String

showList ∷ [Evidence c] → ShowS