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

Constrained.API

Synopsis

Documentation

class LogicRequires s t dom rng ⇒ Logic s t dom rng | s → 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

Methods

info ∷ t s dom rng → String Source #

propagateContext s t dom rng hole → Specification rng → Specification hole Source #

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

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

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

Instances

Instances details
OrdLike a ⇒ Logic "<." NumOrdW '[a, a] Bool Source # 
Instance details

Defined in Constrained.TheKnot

Methods

infoNumOrdW "<." '[a, a] Bool → String Source #

propagateContext "<." NumOrdW '[a, a] Bool hole → Specification Bool → Specification hole Source #

rewriteRulesNumOrdW "<." '[a, a] Bool → List Term '[a, a] → Evidence (AppRequires "<." NumOrdW '[a, a] Bool) → Maybe (Term Bool) Source #

mapTypeSpec ∷ ('[a, a] ~ '[a0], Bool ~ b, HasSpec a0, HasSpec b) ⇒ NumOrdW "<." '[a0] b → TypeSpec a0 → Specification b Source #

saturateNumOrdW "<." '[a, a] Bool → List Term '[a, a] → [Pred] Source #

OrdLike a ⇒ Logic "<=." NumOrdW '[a, a] Bool Source # 
Instance details

Defined in Constrained.TheKnot

Methods

infoNumOrdW "<=." '[a, a] Bool → String Source #

propagateContext "<=." NumOrdW '[a, a] Bool hole → Specification Bool → Specification hole Source #

rewriteRulesNumOrdW "<=." '[a, a] Bool → List Term '[a, a] → Evidence (AppRequires "<=." NumOrdW '[a, a] Bool) → Maybe (Term Bool) Source #

mapTypeSpec ∷ ('[a, a] ~ '[a0], Bool ~ b, HasSpec a0, HasSpec b) ⇒ NumOrdW "<=." '[a0] b → TypeSpec a0 → Specification b Source #

saturateNumOrdW "<=." '[a, a] Bool → List Term '[a, a] → [Pred] Source #

(HasSpec Bool, Eq a, Typeable a) ⇒ Logic "==." BaseW '[a, a] Bool Source # 
Instance details

Defined in Constrained.TheKnot

Methods

infoBaseW "==." '[a, a] Bool → String Source #

propagateContext "==." BaseW '[a, a] Bool hole → Specification Bool → Specification hole Source #

rewriteRulesBaseW "==." '[a, a] Bool → List Term '[a, a] → Evidence (AppRequires "==." BaseW '[a, a] Bool) → Maybe (Term Bool) Source #

mapTypeSpec ∷ ('[a, a] ~ '[a0], Bool ~ b, HasSpec a0, HasSpec b) ⇒ BaseW "==." '[a0] b → TypeSpec a0 → Specification b Source #

saturateBaseW "==." '[a, a] Bool → List Term '[a, a] → [Pred] Source #

OrdLike a ⇒ Logic ">." NumOrdW '[a, a] Bool Source # 
Instance details

Defined in Constrained.TheKnot

Methods

infoNumOrdW ">." '[a, a] Bool → String Source #

propagateContext ">." NumOrdW '[a, a] Bool hole → Specification Bool → Specification hole Source #

rewriteRulesNumOrdW ">." '[a, a] Bool → List Term '[a, a] → Evidence (AppRequires ">." NumOrdW '[a, a] Bool) → Maybe (Term Bool) Source #

mapTypeSpec ∷ ('[a, a] ~ '[a0], Bool ~ b, HasSpec a0, HasSpec b) ⇒ NumOrdW ">." '[a0] b → TypeSpec a0 → Specification b Source #

saturateNumOrdW ">." '[a, a] Bool → List Term '[a, a] → [Pred] Source #

OrdLike a ⇒ Logic ">=." NumOrdW '[a, a] Bool Source # 
Instance details

Defined in Constrained.TheKnot

Methods

infoNumOrdW ">=." '[a, a] Bool → String Source #

propagateContext ">=." NumOrdW '[a, a] Bool hole → Specification Bool → Specification hole Source #

rewriteRulesNumOrdW ">=." '[a, a] Bool → List Term '[a, a] → Evidence (AppRequires ">=." NumOrdW '[a, a] Bool) → Maybe (Term Bool) Source #

mapTypeSpec ∷ ('[a, a] ~ '[a0], Bool ~ b, HasSpec a0, HasSpec b) ⇒ NumOrdW ">=." '[a0] b → TypeSpec a0 → Specification b Source #

saturateNumOrdW ">=." '[a, a] Bool → List Term '[a, a] → [Pred] Source #

NumLike a ⇒ Logic "addFn" IntW '[a, a] a 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

infoIntW "addFn" '[a, a] a → String Source #

propagateContext "addFn" IntW '[a, a] a hole → Specification a → Specification hole Source #

rewriteRulesIntW "addFn" '[a, a] a → List Term '[a, a] → Evidence (AppRequires "addFn" IntW '[a, a] a) → Maybe (Term a) Source #

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

saturateIntW "addFn" '[a, a] Bool → List Term '[a, a] → [Pred] Source #

(All (Typeable ∷ Type → Constraint) '[a, r], HasSpec r) ⇒ Logic "composeFn" FunW '[a] r Source # 
Instance details

Defined in Constrained.Spec.ListFoldy

Methods

infoFunW "composeFn" '[a] r → String Source #

propagateContext "composeFn" FunW '[a] r hole → Specification r → Specification hole Source #

rewriteRulesFunW "composeFn" '[a] r → List Term '[a] → Evidence (AppRequires "composeFn" FunW '[a] r) → Maybe (Term r) Source #

mapTypeSpec ∷ ('[a] ~ '[a0], r ~ b, HasSpec a0, HasSpec b) ⇒ FunW "composeFn" '[a0] b → TypeSpec a0 → Specification b Source #

saturateFunW "composeFn" '[a] Bool → List Term '[a] → [Pred] Source #

(HasSpec a, Ord a) ⇒ Logic "disjoint_" SetW '[Set a, Set a] Bool Source # 
Instance details

Defined in Constrained.Spec.Set

Methods

infoSetW "disjoint_" '[Set a, Set a] Bool → String Source #

propagateContext "disjoint_" SetW '[Set a, Set a] Bool hole → Specification Bool → Specification hole Source #

rewriteRulesSetW "disjoint_" '[Set a, Set a] Bool → List Term '[Set a, Set a] → Evidence (AppRequires "disjoint_" SetW '[Set a, Set a] Bool) → Maybe (Term Bool) Source #

mapTypeSpec ∷ ('[Set a, Set a] ~ '[a0], Bool ~ b, HasSpec a0, HasSpec b) ⇒ SetW "disjoint_" '[a0] b → TypeSpec a0 → Specification b Source #

saturateSetW "disjoint_" '[Set a, Set a] Bool → List Term '[Set a, Set a] → [Pred] Source #

HasSpec a ⇒ Logic "elem_" BaseW '[a, [a]] Bool Source # 
Instance details

Defined in Constrained.Spec.ListFoldy

Methods

infoBaseW "elem_" '[a, [a]] Bool → String Source #

propagateContext "elem_" BaseW '[a, [a]] Bool hole → Specification Bool → Specification hole Source #

rewriteRulesBaseW "elem_" '[a, [a]] Bool → List Term '[a, [a]] → Evidence (AppRequires "elem_" BaseW '[a, [a]] Bool) → Maybe (Term Bool) Source #

mapTypeSpec ∷ ('[a, [a]] ~ '[a0], Bool ~ b, HasSpec a0, HasSpec b) ⇒ BaseW "elem_" '[a0] b → TypeSpec a0 → Specification b Source #

saturateBaseW "elem_" '[a, [a]] Bool → List Term '[a, [a]] → [Pred] Source #

(∀ (sym ∷ Symbol) (t ∷ Symbol → [Type] → Type → Type). Logic sym t '[a, b] r, All (Typeable ∷ Type → Constraint) '[a, b, r]) ⇒ Logic "flip_" FunW '[b, a] r Source # 
Instance details

Defined in Constrained.Spec.ListFoldy

Methods

infoFunW "flip_" '[b, a] r → String Source #

propagateContext "flip_" FunW '[b, a] r hole → Specification r → Specification hole Source #

rewriteRulesFunW "flip_" '[b, a] r → List Term '[b, a] → Evidence (AppRequires "flip_" FunW '[b, a] r) → Maybe (Term r) Source #

mapTypeSpec ∷ ('[b, a] ~ '[a0], r ~ b0, HasSpec a0, HasSpec b0) ⇒ FunW "flip_" '[a0] b0 → TypeSpec a0 → Specification b0 Source #

saturateFunW "flip_" '[b, a] Bool → List Term '[b, a] → [Pred] Source #

(Typeable a, Foldy b) ⇒ Logic "foldMap_" ListW '[[a]] b Source # 
Instance details

Defined in Constrained.Spec.ListFoldy

Methods

infoListW "foldMap_" '[[a]] b → String Source #

propagateContext "foldMap_" ListW '[[a]] b hole → Specification b → Specification hole Source #

rewriteRulesListW "foldMap_" '[[a]] b → List Term '[[a]] → Evidence (AppRequires "foldMap_" ListW '[[a]] b) → Maybe (Term b) Source #

mapTypeSpec ∷ ('[[a]] ~ '[a0], b ~ b0, HasSpec a0, HasSpec b0) ⇒ ListW "foldMap_" '[a0] b0 → TypeSpec a0 → Specification b0 Source #

saturateListW "foldMap_" '[[a]] Bool → List Term '[[a]] → [Pred] Source #

(GenericRequires a, dom ~ SimpleRep a) ⇒ Logic "fromGenericFn" BaseW '[dom] a Source # 
Instance details

Defined in Constrained.Base

Methods

infoBaseW "fromGenericFn" '[dom] a → String Source #

propagateContext "fromGenericFn" BaseW '[dom] a hole → Specification a → Specification hole Source #

rewriteRulesBaseW "fromGenericFn" '[dom] a → List Term '[dom] → Evidence (AppRequires "fromGenericFn" BaseW '[dom] a) → Maybe (Term a) Source #

mapTypeSpec ∷ ('[dom] ~ '[a0], a ~ b, HasSpec a0, HasSpec b) ⇒ BaseW "fromGenericFn" '[a0] b → TypeSpec a0 → Specification b Source #

saturateBaseW "fromGenericFn" '[dom] Bool → List Term '[dom] → [Pred] Source #

HasSpec a ⇒ Logic "id_" FunW '[a] a Source # 
Instance details

Defined in Constrained.Spec.ListFoldy

Methods

infoFunW "id_" '[a] a → String Source #

propagateContext "id_" FunW '[a] a hole → Specification a → Specification hole Source #

rewriteRulesFunW "id_" '[a] a → List Term '[a] → Evidence (AppRequires "id_" FunW '[a] a) → Maybe (Term a) Source #

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

saturateFunW "id_" '[a] Bool → List Term '[a] → [Pred] Source #

(HasSpec a, Ord a) ⇒ Logic "member_" SetW '[a, Set a] Bool Source # 
Instance details

Defined in Constrained.Spec.Set

Methods

infoSetW "member_" '[a, Set a] Bool → String Source #

propagateContext "member_" SetW '[a, Set a] Bool hole → Specification Bool → Specification hole Source #

rewriteRulesSetW "member_" '[a, Set a] Bool → List Term '[a, Set a] → Evidence (AppRequires "member_" SetW '[a, Set a] Bool) → Maybe (Term Bool) Source #

mapTypeSpec ∷ ('[a, Set a] ~ '[a0], Bool ~ b, HasSpec a0, HasSpec b) ⇒ SetW "member_" '[a0] b → TypeSpec a0 → Specification b Source #

saturateSetW "member_" '[a, Set a] Bool → List Term '[a, Set a] → [Pred] Source #

NumLike a ⇒ Logic "negateFn" IntW '[a] a Source # 
Instance details

Defined in Constrained.NumSpec

Methods

infoIntW "negateFn" '[a] a → String Source #

propagateContext "negateFn" IntW '[a] a hole → Specification a → Specification hole Source #

rewriteRulesIntW "negateFn" '[a] a → List Term '[a] → Evidence (AppRequires "negateFn" IntW '[a] a) → Maybe (Term a) Source #

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

saturateIntW "negateFn" '[a] Bool → List Term '[a] → [Pred] Source #

(HasSpec Bool, TypeSpec Bool ~ SumSpec () ()) ⇒ Logic "not_" BoolW '[Bool] Bool Source # 
Instance details

Defined in Constrained.TheKnot

Methods

infoBoolW "not_" '[Bool] Bool → String Source #

propagateContext "not_" BoolW '[Bool] Bool hole → Specification Bool → Specification hole Source #

rewriteRulesBoolW "not_" '[Bool] Bool → List Term '[Bool] → Evidence (AppRequires "not_" BoolW '[Bool] Bool) → Maybe (Term Bool) Source #

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

saturateBoolW "not_" '[Bool] Bool → List Term '[Bool] → [Pred] Source #

HasSpec Bool ⇒ Logic "or_" BoolW '[Bool, Bool] Bool Source # 
Instance details

Defined in Constrained.TheKnot

Methods

infoBoolW "or_" '[Bool, Bool] Bool → String Source #

propagateContext "or_" BoolW '[Bool, Bool] Bool hole → Specification Bool → Specification hole Source #

rewriteRulesBoolW "or_" '[Bool, Bool] Bool → List Term '[Bool, Bool] → Evidence (AppRequires "or_" BoolW '[Bool, Bool] Bool) → Maybe (Term Bool) Source #

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

saturateBoolW "or_" '[Bool, Bool] Bool → List Term '[Bool, Bool] → [Pred] Source #

(HasSpec a, HasSpec b) ⇒ Logic "prodFst_" BaseW '[Prod a b] a Source # 
Instance details

Defined in Constrained.TheKnot

Methods

infoBaseW "prodFst_" '[Prod a b] a → String Source #

propagateContext "prodFst_" BaseW '[Prod a b] a hole → Specification a → Specification hole Source #

rewriteRulesBaseW "prodFst_" '[Prod a b] a → List Term '[Prod a b] → Evidence (AppRequires "prodFst_" BaseW '[Prod a b] a) → Maybe (Term a) Source #

mapTypeSpec ∷ ('[Prod a b] ~ '[a0], a ~ b0, HasSpec a0, HasSpec b0) ⇒ BaseW "prodFst_" '[a0] b0 → TypeSpec a0 → Specification b0 Source #

saturateBaseW "prodFst_" '[Prod a b] Bool → List Term '[Prod a b] → [Pred] Source #

(HasSpec a, HasSpec b) ⇒ Logic "prodSnd_" BaseW '[Prod a b] b Source # 
Instance details

Defined in Constrained.TheKnot

Methods

infoBaseW "prodSnd_" '[Prod a b] b → String Source #

propagateContext "prodSnd_" BaseW '[Prod a b] b hole → Specification b → Specification hole Source #

rewriteRulesBaseW "prodSnd_" '[Prod a b] b → List Term '[Prod a b] → Evidence (AppRequires "prodSnd_" BaseW '[Prod a b] b) → Maybe (Term b) Source #

mapTypeSpec ∷ ('[Prod a b] ~ '[a0], b ~ b0, HasSpec a0, HasSpec b0) ⇒ BaseW "prodSnd_" '[a0] b0 → TypeSpec a0 → Specification b0 Source #

saturateBaseW "prodSnd_" '[Prod a b] Bool → List Term '[Prod a b] → [Pred] Source #

HasSpec a ⇒ Logic "rootLabel_" TreeW '[Tree a] a Source # 
Instance details

Defined in Constrained.Spec.Tree

Methods

infoTreeW "rootLabel_" '[Tree a] a → String Source #

propagateContext "rootLabel_" TreeW '[Tree a] a hole → Specification a → Specification hole Source #

rewriteRulesTreeW "rootLabel_" '[Tree a] a → List Term '[Tree a] → Evidence (AppRequires "rootLabel_" TreeW '[Tree a] a) → Maybe (Term a) Source #

mapTypeSpec ∷ ('[Tree a] ~ '[a0], a ~ b, HasSpec a0, HasSpec b) ⇒ TreeW "rootLabel_" '[a0] b → TypeSpec a0 → Specification b Source #

saturateTreeW "rootLabel_" '[Tree a] Bool → List Term '[Tree a] → [Pred] Source #

(Sized t, HasSpec t) ⇒ Logic "sizeOf_" SizeW '[t] Integer Source # 
Instance details

Defined in Constrained.Spec.Size

Methods

infoSizeW "sizeOf_" '[t] Integer → String Source #

propagateContext "sizeOf_" SizeW '[t] Integer hole → Specification Integer → Specification hole Source #

rewriteRulesSizeW "sizeOf_" '[t] Integer → List Term '[t] → Evidence (AppRequires "sizeOf_" SizeW '[t] Integer) → Maybe (Term Integer) Source #

mapTypeSpec ∷ ('[t] ~ '[a], Integer ~ b, HasSpec a, HasSpec b) ⇒ SizeW "sizeOf_" '[a] b → TypeSpec a → Specification b Source #

saturateSizeW "sizeOf_" '[t] Bool → List Term '[t] → [Pred] Source #

(HasSpec a, Ord a) ⇒ Logic "subset_" SetW '[Set a, Set a] Bool Source # 
Instance details

Defined in Constrained.Spec.Set

Methods

infoSetW "subset_" '[Set a, Set a] Bool → String Source #

propagateContext "subset_" SetW '[Set a, Set a] Bool hole → Specification Bool → Specification hole Source #

rewriteRulesSetW "subset_" '[Set a, Set a] Bool → List Term '[Set a, Set a] → Evidence (AppRequires "subset_" SetW '[Set a, Set a] Bool) → Maybe (Term Bool) Source #

mapTypeSpec ∷ ('[Set a, Set a] ~ '[a0], Bool ~ b, HasSpec a0, HasSpec b) ⇒ SetW "subset_" '[a0] b → TypeSpec a0 → Specification b Source #

saturateSetW "subset_" '[Set a, Set a] Bool → List Term '[Set a, Set a] → [Pred] Source #

(GenericRequires a, simplerepA ~ SimpleRep a) ⇒ Logic "toGenericFn" BaseW '[a] simplerepA Source # 
Instance details

Defined in Constrained.Base

Methods

infoBaseW "toGenericFn" '[a] simplerepA → String Source #

propagateContext "toGenericFn" BaseW '[a] simplerepA hole → Specification simplerepA → Specification hole Source #

rewriteRulesBaseW "toGenericFn" '[a] simplerepA → List Term '[a] → Evidence (AppRequires "toGenericFn" BaseW '[a] simplerepA) → Maybe (Term simplerepA) Source #

mapTypeSpec ∷ ('[a] ~ '[a0], simplerepA ~ b, HasSpec a0, HasSpec b) ⇒ BaseW "toGenericFn" '[a0] b → TypeSpec a0 → Specification b Source #

saturateBaseW "toGenericFn" '[a] Bool → List Term '[a] → [Pred] Source #

(Sized [a], HasSpec a) ⇒ Logic "append_" ListW '[[a], [a]] [a] Source # 
Instance details

Defined in Constrained.Spec.ListFoldy

Methods

infoListW "append_" '[[a], [a]] [a] → String Source #

propagateContext "append_" ListW '[[a], [a]] [a] hole → Specification [a] → Specification hole Source #

rewriteRulesListW "append_" '[[a], [a]] [a] → List Term '[[a], [a]] → Evidence (AppRequires "append_" ListW '[[a], [a]] [a]) → Maybe (Term [a]) Source #

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

saturateListW "append_" '[[a], [a]] Bool → List Term '[[a], [a]] → [Pred] Source #

(HasSpec k, HasSpec v, Ord k, IsNormalType v, IsNormalType k) ⇒ Logic "dom_" MapW '[Map k v] (Set k) Source # 
Instance details

Defined in Constrained.Spec.Map

Methods

infoMapW "dom_" '[Map k v] (Set k) → String Source #

propagateContext "dom_" MapW '[Map k v] (Set k) hole → Specification (Set k) → Specification hole Source #

rewriteRulesMapW "dom_" '[Map k v] (Set k) → List Term '[Map k v] → Evidence (AppRequires "dom_" MapW '[Map k v] (Set k)) → Maybe (Term (Set k)) Source #

mapTypeSpec ∷ ('[Map k v] ~ '[a], Set k ~ b, HasSpec a, HasSpec b) ⇒ MapW "dom_" '[a] b → TypeSpec a → Specification b Source #

saturateMapW "dom_" '[Map k v] Bool → List Term '[Map k v] → [Pred] Source #

(HasSpec a, Ord a) ⇒ Logic "fromList_" SetW '[[a]] (Set a) Source # 
Instance details

Defined in Constrained.Spec.Set

Methods

infoSetW "fromList_" '[[a]] (Set a) → String Source #

propagateContext "fromList_" SetW '[[a]] (Set a) hole → Specification (Set a) → Specification hole Source #

rewriteRulesSetW "fromList_" '[[a]] (Set a) → List Term '[[a]] → Evidence (AppRequires "fromList_" SetW '[[a]] (Set a)) → Maybe (Term (Set a)) Source #

mapTypeSpec ∷ ('[[a]] ~ '[a0], Set a ~ b, HasSpec a0, HasSpec b) ⇒ SetW "fromList_" '[a0] b → TypeSpec a0 → Specification b Source #

saturateSetW "fromList_" '[[a]] Bool → List Term '[[a]] → [Pred] Source #

(HasSpec k, HasSpec v, IsNormalType v, IsNormalType k) ⇒ Logic "lookup_" MapW '[k, Map k v] (Maybe v) Source # 
Instance details

Defined in Constrained.Spec.Map

Methods

infoMapW "lookup_" '[k, Map k v] (Maybe v) → String Source #

propagateContext "lookup_" MapW '[k, Map k v] (Maybe v) hole → Specification (Maybe v) → Specification hole Source #

rewriteRulesMapW "lookup_" '[k, Map k v] (Maybe v) → List Term '[k, Map k v] → Evidence (AppRequires "lookup_" MapW '[k, Map k v] (Maybe v)) → Maybe (Term (Maybe v)) Source #

mapTypeSpec ∷ ('[k, Map k v] ~ '[a], Maybe v ~ b, HasSpec a, HasSpec b) ⇒ MapW "lookup_" '[a] b → TypeSpec a → Specification b Source #

saturateMapW "lookup_" '[k, Map k v] Bool → List Term '[k, Map k v] → [Pred] Source #

(HasSpec k, HasSpec v, Ord k, IsNormalType v, IsNormalType k) ⇒ Logic "rng_" MapW '[Map k v] [v] Source # 
Instance details

Defined in Constrained.Spec.Map

Methods

infoMapW "rng_" '[Map k v] [v] → String Source #

propagateContext "rng_" MapW '[Map k v] [v] hole → Specification [v] → Specification hole Source #

rewriteRulesMapW "rng_" '[Map k v] [v] → List Term '[Map k v] → Evidence (AppRequires "rng_" MapW '[Map k v] [v]) → Maybe (Term [v]) Source #

mapTypeSpec ∷ ('[Map k v] ~ '[a], [v] ~ b, HasSpec a, HasSpec b) ⇒ MapW "rng_" '[a] b → TypeSpec a → Specification b Source #

saturateMapW "rng_" '[Map k v] Bool → List Term '[Map k v] → [Pred] Source #

HasSpec a ⇒ Logic "singeltonList_" ListW '[a] [a] Source # 
Instance details

Defined in Constrained.Spec.ListFoldy

Methods

infoListW "singeltonList_" '[a] [a] → String Source #

propagateContext "singeltonList_" ListW '[a] [a] hole → Specification [a] → Specification hole Source #

rewriteRulesListW "singeltonList_" '[a] [a] → List Term '[a] → Evidence (AppRequires "singeltonList_" ListW '[a] [a]) → Maybe (Term [a]) Source #

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

saturateListW "singeltonList_" '[a] Bool → List Term '[a] → [Pred] Source #

(HasSpec a, Ord a) ⇒ Logic "singleton_" SetW '[a] (Set a) Source # 
Instance details

Defined in Constrained.Spec.Set

Methods

infoSetW "singleton_" '[a] (Set a) → String Source #

propagateContext "singleton_" SetW '[a] (Set a) hole → Specification (Set a) → Specification hole Source #

rewriteRulesSetW "singleton_" '[a] (Set a) → List Term '[a] → Evidence (AppRequires "singleton_" SetW '[a] (Set a)) → Maybe (Term (Set a)) Source #

mapTypeSpec ∷ ('[a] ~ '[a0], Set a ~ b, HasSpec a0, HasSpec b) ⇒ SetW "singleton_" '[a0] b → TypeSpec a0 → Specification b Source #

saturateSetW "singleton_" '[a] Bool → List Term '[a] → [Pred] Source #

(HasSpec a, Ord a) ⇒ Logic "union_" SetW '[Set a, Set a] (Set a) Source # 
Instance details

Defined in Constrained.Spec.Set

Methods

infoSetW "union_" '[Set a, Set a] (Set a) → String Source #

propagateContext "union_" SetW '[Set a, Set a] (Set a) hole → Specification (Set a) → Specification hole Source #

rewriteRulesSetW "union_" '[Set a, Set a] (Set a) → List Term '[Set a, Set a] → Evidence (AppRequires "union_" SetW '[Set a, Set a] (Set a)) → Maybe (Term (Set a)) Source #

mapTypeSpec ∷ ('[Set a, Set a] ~ '[a0], Set a ~ b, HasSpec a0, HasSpec b) ⇒ SetW "union_" '[a0] b → TypeSpec a0 → Specification b Source #

saturateSetW "union_" '[Set a, Set a] Bool → List Term '[Set a, Set a] → [Pred] Source #

(HasSpec a, HasSpec b, KnownNat (CountCases b)) ⇒ Logic "leftFn" BaseW '[a] (Sum a b) Source # 
Instance details

Defined in Constrained.Spec.SumProd

Methods

infoBaseW "leftFn" '[a] (Sum a b) → String Source #

propagateContext "leftFn" BaseW '[a] (Sum a b) hole → Specification (Sum a b) → Specification hole Source #

rewriteRulesBaseW "leftFn" '[a] (Sum a b) → List Term '[a] → Evidence (AppRequires "leftFn" BaseW '[a] (Sum a b)) → Maybe (Term (Sum a b)) Source #

mapTypeSpec ∷ ('[a] ~ '[a0], Sum a b ~ b0, HasSpec a0, HasSpec b0) ⇒ BaseW "leftFn" '[a0] b0 → TypeSpec a0 → Specification b0 Source #

saturateBaseW "leftFn" '[a] Bool → List Term '[a] → [Pred] Source #

(HasSpec a, HasSpec b) ⇒ Logic "prod_" BaseW '[a, b] (Prod a b) Source # 
Instance details

Defined in Constrained.TheKnot

Methods

infoBaseW "prod_" '[a, b] (Prod a b) → String Source #

propagateContext "prod_" BaseW '[a, b] (Prod a b) hole → Specification (Prod a b) → Specification hole Source #

rewriteRulesBaseW "prod_" '[a, b] (Prod a b) → List Term '[a, b] → Evidence (AppRequires "prod_" BaseW '[a, b] (Prod a b)) → Maybe (Term (Prod a b)) Source #

mapTypeSpec ∷ ('[a, b] ~ '[a0], Prod a b ~ b0, HasSpec a0, HasSpec b0) ⇒ BaseW "prod_" '[a0] b0 → TypeSpec a0 → Specification b0 Source #

saturateBaseW "prod_" '[a, b] Bool → List Term '[a, b] → [Pred] Source #

(HasSpec a, HasSpec b, KnownNat (CountCases b)) ⇒ Logic "rightFn" BaseW '[b] (Sum a b) Source # 
Instance details

Defined in Constrained.Spec.SumProd

Methods

infoBaseW "rightFn" '[b] (Sum a b) → String Source #

propagateContext "rightFn" BaseW '[b] (Sum a b) hole → Specification (Sum a b) → Specification hole Source #

rewriteRulesBaseW "rightFn" '[b] (Sum a b) → List Term '[b] → Evidence (AppRequires "rightFn" BaseW '[b] (Sum a b)) → Maybe (Term (Sum a b)) Source #

mapTypeSpec ∷ ('[b] ~ '[a0], Sum a b ~ b0, HasSpec a0, HasSpec b0) ⇒ BaseW "rightFn" '[a0] b0 → TypeSpec a0 → Specification b0 Source #

saturateBaseW "rightFn" '[b] Bool → List Term '[b] → [Pred] Source #

class Syntax t ⇒ Semantics (t ∷ Symbol → [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 ∷ ∀ s d r. t s d r → FunTy d r Source #

Instances

Instances details
Semantics BaseW Source # 
Instance details

Defined in Constrained.Base

Methods

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

Semantics IntW Source # 
Instance details

Defined in Constrained.NumSpec

Methods

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

Semantics NumOrdW Source # 
Instance details

Defined in Constrained.NumSpec

Methods

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

Semantics FunW Source # 
Instance details

Defined in Constrained.Spec.ListFoldy

Methods

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

Semantics ListW Source # 
Instance details

Defined in Constrained.Spec.ListFoldy

Methods

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

Semantics MapW Source # 
Instance details

Defined in Constrained.Spec.Map

Methods

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

Semantics SetW Source # 
Instance details

Defined in Constrained.Spec.Set

Methods

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

Semantics SizeW Source # 
Instance details

Defined in Constrained.Spec.Size

Methods

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

Semantics TreeW Source # 
Instance details

Defined in Constrained.Spec.Tree

Methods

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

Semantics BoolW Source # 
Instance details

Defined in Constrained.TheKnot

Methods

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

class Syntax (t ∷ FSType) where Source #

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

Minimal complete definition

Nothing

Methods

isInFix ∷ ∀ s dom rng. t s dom rng → Bool Source #

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

Instances

Instances details
Syntax BaseW Source # 
Instance details

Defined in Constrained.Base

Methods

isInFix ∷ ∀ (s ∷ Symbol) (dom ∷ [Type]) rng. BaseW s dom rng → Bool Source #

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

Syntax IntW Source # 
Instance details

Defined in Constrained.NumSpec

Methods

isInFix ∷ ∀ (s ∷ Symbol) (dom ∷ [Type]) rng. IntW s dom rng → Bool Source #

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

Syntax NumOrdW Source # 
Instance details

Defined in Constrained.NumSpec

Methods

isInFix ∷ ∀ (s ∷ Symbol) (dom ∷ [Type]) rng. NumOrdW s dom rng → Bool Source #

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

Syntax FunW Source # 
Instance details

Defined in Constrained.Spec.ListFoldy

Methods

isInFix ∷ ∀ (s ∷ Symbol) (dom ∷ [Type]) rng. FunW s dom rng → Bool Source #

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

Syntax ListW Source # 
Instance details

Defined in Constrained.Spec.ListFoldy

Methods

isInFix ∷ ∀ (s ∷ Symbol) (dom ∷ [Type]) rng. ListW s dom rng → Bool Source #

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

Syntax MapW Source # 
Instance details

Defined in Constrained.Spec.Map

Methods

isInFix ∷ ∀ (s ∷ Symbol) (dom ∷ [Type]) rng. MapW s dom rng → Bool Source #

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

Syntax SetW Source # 
Instance details

Defined in Constrained.Spec.Set

Methods

isInFix ∷ ∀ (s ∷ Symbol) (dom ∷ [Type]) rng. SetW s dom rng → Bool Source #

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

Syntax SizeW Source # 
Instance details

Defined in Constrained.Spec.Size

Methods

isInFix ∷ ∀ (s ∷ Symbol) (dom ∷ [Type]) rng. SizeW s dom rng → Bool Source #

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

Syntax TreeW Source # 
Instance details

Defined in Constrained.Spec.Tree

Methods

isInFix ∷ ∀ (s ∷ Symbol) (dom ∷ [Type]) rng. TreeW s dom rng → Bool Source #

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

Syntax BoolW Source # 
Instance details

Defined in Constrained.TheKnot

Methods

isInFix ∷ ∀ (s ∷ Symbol) (dom ∷ [Type]) rng. BoolW s dom rng → Bool Source #

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

class (HasSpec a, NumLike a, Logic "addFn" IntW '[a, a] a) ⇒ Foldy a where Source #

Minimal complete definition

genList, genSizedList, noNegativeValues

Methods

genListMonadGenError m ⇒ Specification a → Specification a → GenT m [a] Source #

theAddFnIntW "addFn" '[a, a] a Source #

theZero ∷ a Source #

genSizedListMonadGenError m ⇒ Specification Integer → Specification a → Specification a → GenT m [a] Source #

noNegativeValues ∷ Bool Source #

Instances

Instances details
Foldy Int16 Source # 
Instance details

Defined in Constrained.Spec.ListFoldy

Methods

genList ∷ ∀ (m ∷ Type → Type). MonadGenError m ⇒ Specification Int16 → Specification Int16 → GenT m [Int16] Source #

theAddFnIntW "addFn" '[Int16, Int16] Int16 Source #

theZero ∷ Int16 Source #

genSizedList ∷ ∀ (m ∷ Type → Type). MonadGenError m ⇒ Specification Integer → Specification Int16 → Specification Int16 → GenT m [Int16] Source #

noNegativeValues ∷ Bool Source #

Foldy Int32 Source # 
Instance details

Defined in Constrained.Spec.ListFoldy

Methods

genList ∷ ∀ (m ∷ Type → Type). MonadGenError m ⇒ Specification Int32 → Specification Int32 → GenT m [Int32] Source #

theAddFnIntW "addFn" '[Int32, Int32] Int32 Source #

theZero ∷ Int32 Source #

genSizedList ∷ ∀ (m ∷ Type → Type). MonadGenError m ⇒ Specification Integer → Specification Int32 → Specification Int32 → GenT m [Int32] Source #

noNegativeValues ∷ Bool Source #

Foldy Int64 Source # 
Instance details

Defined in Constrained.Spec.ListFoldy

Methods

genList ∷ ∀ (m ∷ Type → Type). MonadGenError m ⇒ Specification Int64 → Specification Int64 → GenT m [Int64] Source #

theAddFnIntW "addFn" '[Int64, Int64] Int64 Source #

theZero ∷ Int64 Source #

genSizedList ∷ ∀ (m ∷ Type → Type). MonadGenError m ⇒ Specification Integer → Specification Int64 → Specification Int64 → GenT m [Int64] Source #

noNegativeValues ∷ Bool Source #

Foldy Int8 Source # 
Instance details

Defined in Constrained.Spec.ListFoldy

Methods

genList ∷ ∀ (m ∷ Type → Type). MonadGenError m ⇒ Specification Int8 → Specification Int8 → GenT m [Int8] Source #

theAddFnIntW "addFn" '[Int8, Int8] Int8 Source #

theZero ∷ Int8 Source #

genSizedList ∷ ∀ (m ∷ Type → Type). MonadGenError m ⇒ Specification Integer → Specification Int8 → Specification Int8 → GenT m [Int8] Source #

noNegativeValues ∷ Bool Source #

Foldy Word16 Source # 
Instance details

Defined in Constrained.Spec.ListFoldy

Methods

genList ∷ ∀ (m ∷ Type → Type). MonadGenError m ⇒ Specification Word16 → Specification Word16 → GenT m [Word16] Source #

theAddFnIntW "addFn" '[Word16, Word16] Word16 Source #

theZero ∷ Word16 Source #

genSizedList ∷ ∀ (m ∷ Type → Type). MonadGenError m ⇒ Specification Integer → Specification Word16 → Specification Word16 → GenT m [Word16] Source #

noNegativeValues ∷ Bool Source #

Foldy Word32 Source # 
Instance details

Defined in Constrained.Spec.ListFoldy

Methods

genList ∷ ∀ (m ∷ Type → Type). MonadGenError m ⇒ Specification Word32 → Specification Word32 → GenT m [Word32] Source #

theAddFnIntW "addFn" '[Word32, Word32] Word32 Source #

theZero ∷ Word32 Source #

genSizedList ∷ ∀ (m ∷ Type → Type). MonadGenError m ⇒ Specification Integer → Specification Word32 → Specification Word32 → GenT m [Word32] Source #

noNegativeValues ∷ Bool Source #

Foldy Word64 Source # 
Instance details

Defined in Constrained.Spec.ListFoldy

Methods

genList ∷ ∀ (m ∷ Type → Type). MonadGenError m ⇒ Specification Word64 → Specification Word64 → GenT m [Word64] Source #

theAddFnIntW "addFn" '[Word64, Word64] Word64 Source #

theZero ∷ Word64 Source #

genSizedList ∷ ∀ (m ∷ Type → Type). MonadGenError m ⇒ Specification Integer → Specification Word64 → Specification Word64 → GenT m [Word64] Source #

noNegativeValues ∷ Bool Source #

Foldy Word8 Source # 
Instance details

Defined in Constrained.Spec.ListFoldy

Methods

genList ∷ ∀ (m ∷ Type → Type). MonadGenError m ⇒ Specification Word8 → Specification Word8 → GenT m [Word8] Source #

theAddFnIntW "addFn" '[Word8, Word8] Word8 Source #

theZero ∷ Word8 Source #

genSizedList ∷ ∀ (m ∷ Type → Type). MonadGenError m ⇒ Specification Integer → Specification Word8 → Specification Word8 → GenT m [Word8] Source #

noNegativeValues ∷ Bool Source #

Foldy Integer Source # 
Instance details

Defined in Constrained.Spec.ListFoldy

Methods

genList ∷ ∀ (m ∷ Type → Type). MonadGenError m ⇒ Specification Integer → Specification Integer → GenT m [Integer] Source #

theAddFnIntW "addFn" '[Integer, Integer] Integer Source #

theZero ∷ Integer Source #

genSizedList ∷ ∀ (m ∷ Type → Type). MonadGenError m ⇒ Specification Integer → Specification Integer → Specification Integer → GenT m [Integer] Source #

noNegativeValues ∷ Bool Source #

Foldy Natural Source # 
Instance details

Defined in Constrained.Spec.ListFoldy

Methods

genList ∷ ∀ (m ∷ Type → Type). MonadGenError m ⇒ Specification Natural → Specification Natural → GenT m [Natural] Source #

theAddFnIntW "addFn" '[Natural, Natural] Natural Source #

theZero ∷ Natural Source #

genSizedList ∷ ∀ (m ∷ Type → Type). MonadGenError m ⇒ Specification Integer → Specification Natural → Specification Natural → GenT m [Natural] Source #

noNegativeValues ∷ Bool Source #

Foldy Int Source # 
Instance details

Defined in Constrained.Spec.ListFoldy

Methods

genList ∷ ∀ (m ∷ Type → Type). MonadGenError m ⇒ Specification Int → Specification Int → GenT m [Int] Source #

theAddFnIntW "addFn" '[Int, Int] Int Source #

theZero ∷ Int Source #

genSizedList ∷ ∀ (m ∷ Type → Type). MonadGenError m ⇒ Specification Integer → Specification Int → Specification Int → GenT m [Int] Source #

noNegativeValues ∷ Bool Source #

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

Constructors

InjLeftW ∷ ∀ a b. BaseW "leftFn" '[a] (Sum a b) 
InjRightW ∷ ∀ a b. BaseW "rightFn" '[b] (Sum a b) 
ProdW ∷ ∀ a b. BaseW "prod_" '[a, b] (Prod a b) 
ProdFstW ∷ ∀ a b. BaseW "prodFst_" '[Prod a b] a 
ProdSndW ∷ ∀ a b. BaseW "prodSnd_" '[Prod a b] b 
EqualW ∷ ∀ a. Eq a ⇒ BaseW "==." '[a, a] Bool 
ToGenericWGenericRequires a ⇒ BaseW "toGenericFn" '[a] (SimpleRep a) 
FromGenericWGenericRequires a ⇒ BaseW "fromGenericFn" '[SimpleRep a] a 
ElemW ∷ ∀ a. Eq a ⇒ BaseW "elem_" '[a, [a]] Bool 

Instances

Instances details
Semantics BaseW Source # 
Instance details

Defined in Constrained.Base

Methods

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

Syntax BaseW Source # 
Instance details

Defined in Constrained.Base

Methods

isInFix ∷ ∀ (s ∷ Symbol) (dom ∷ [Type]) rng. BaseW s dom rng → Bool Source #

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

(HasSpec Bool, Eq a, Typeable a) ⇒ Logic "==." BaseW '[a, a] Bool Source # 
Instance details

Defined in Constrained.TheKnot

Methods

infoBaseW "==." '[a, a] Bool → String Source #

propagateContext "==." BaseW '[a, a] Bool hole → Specification Bool → Specification hole Source #

rewriteRulesBaseW "==." '[a, a] Bool → List Term '[a, a] → Evidence (AppRequires "==." BaseW '[a, a] Bool) → Maybe (Term Bool) Source #

mapTypeSpec ∷ ('[a, a] ~ '[a0], Bool ~ b, HasSpec a0, HasSpec b) ⇒ BaseW "==." '[a0] b → TypeSpec a0 → Specification b Source #

saturateBaseW "==." '[a, a] Bool → List Term '[a, a] → [Pred] Source #

HasSpec a ⇒ Logic "elem_" BaseW '[a, [a]] Bool Source # 
Instance details

Defined in Constrained.Spec.ListFoldy

Methods

infoBaseW "elem_" '[a, [a]] Bool → String Source #

propagateContext "elem_" BaseW '[a, [a]] Bool hole → Specification Bool → Specification hole Source #

rewriteRulesBaseW "elem_" '[a, [a]] Bool → List Term '[a, [a]] → Evidence (AppRequires "elem_" BaseW '[a, [a]] Bool) → Maybe (Term Bool) Source #

mapTypeSpec ∷ ('[a, [a]] ~ '[a0], Bool ~ b, HasSpec a0, HasSpec b) ⇒ BaseW "elem_" '[a0] b → TypeSpec a0 → Specification b Source #

saturateBaseW "elem_" '[a, [a]] Bool → List Term '[a, [a]] → [Pred] Source #

(GenericRequires a, dom ~ SimpleRep a) ⇒ Logic "fromGenericFn" BaseW '[dom] a Source # 
Instance details

Defined in Constrained.Base

Methods

infoBaseW "fromGenericFn" '[dom] a → String Source #

propagateContext "fromGenericFn" BaseW '[dom] a hole → Specification a → Specification hole Source #

rewriteRulesBaseW "fromGenericFn" '[dom] a → List Term '[dom] → Evidence (AppRequires "fromGenericFn" BaseW '[dom] a) → Maybe (Term a) Source #

mapTypeSpec ∷ ('[dom] ~ '[a0], a ~ b, HasSpec a0, HasSpec b) ⇒ BaseW "fromGenericFn" '[a0] b → TypeSpec a0 → Specification b Source #

saturateBaseW "fromGenericFn" '[dom] Bool → List Term '[dom] → [Pred] Source #

(HasSpec a, HasSpec b) ⇒ Logic "prodFst_" BaseW '[Prod a b] a Source # 
Instance details

Defined in Constrained.TheKnot

Methods

infoBaseW "prodFst_" '[Prod a b] a → String Source #

propagateContext "prodFst_" BaseW '[Prod a b] a hole → Specification a → Specification hole Source #

rewriteRulesBaseW "prodFst_" '[Prod a b] a → List Term '[Prod a b] → Evidence (AppRequires "prodFst_" BaseW '[Prod a b] a) → Maybe (Term a) Source #

mapTypeSpec ∷ ('[Prod a b] ~ '[a0], a ~ b0, HasSpec a0, HasSpec b0) ⇒ BaseW "prodFst_" '[a0] b0 → TypeSpec a0 → Specification b0 Source #

saturateBaseW "prodFst_" '[Prod a b] Bool → List Term '[Prod a b] → [Pred] Source #

(HasSpec a, HasSpec b) ⇒ Logic "prodSnd_" BaseW '[Prod a b] b Source # 
Instance details

Defined in Constrained.TheKnot

Methods

infoBaseW "prodSnd_" '[Prod a b] b → String Source #

propagateContext "prodSnd_" BaseW '[Prod a b] b hole → Specification b → Specification hole Source #

rewriteRulesBaseW "prodSnd_" '[Prod a b] b → List Term '[Prod a b] → Evidence (AppRequires "prodSnd_" BaseW '[Prod a b] b) → Maybe (Term b) Source #

mapTypeSpec ∷ ('[Prod a b] ~ '[a0], b ~ b0, HasSpec a0, HasSpec b0) ⇒ BaseW "prodSnd_" '[a0] b0 → TypeSpec a0 → Specification b0 Source #

saturateBaseW "prodSnd_" '[Prod a b] Bool → List Term '[Prod a b] → [Pred] Source #

(GenericRequires a, simplerepA ~ SimpleRep a) ⇒ Logic "toGenericFn" BaseW '[a] simplerepA Source # 
Instance details

Defined in Constrained.Base

Methods

infoBaseW "toGenericFn" '[a] simplerepA → String Source #

propagateContext "toGenericFn" BaseW '[a] simplerepA hole → Specification simplerepA → Specification hole Source #

rewriteRulesBaseW "toGenericFn" '[a] simplerepA → List Term '[a] → Evidence (AppRequires "toGenericFn" BaseW '[a] simplerepA) → Maybe (Term simplerepA) Source #

mapTypeSpec ∷ ('[a] ~ '[a0], simplerepA ~ b, HasSpec a0, HasSpec b) ⇒ BaseW "toGenericFn" '[a0] b → TypeSpec a0 → Specification b Source #

saturateBaseW "toGenericFn" '[a] Bool → List Term '[a] → [Pred] Source #

(HasSpec a, HasSpec b, KnownNat (CountCases b)) ⇒ Logic "leftFn" BaseW '[a] (Sum a b) Source # 
Instance details

Defined in Constrained.Spec.SumProd

Methods

infoBaseW "leftFn" '[a] (Sum a b) → String Source #

propagateContext "leftFn" BaseW '[a] (Sum a b) hole → Specification (Sum a b) → Specification hole Source #

rewriteRulesBaseW "leftFn" '[a] (Sum a b) → List Term '[a] → Evidence (AppRequires "leftFn" BaseW '[a] (Sum a b)) → Maybe (Term (Sum a b)) Source #

mapTypeSpec ∷ ('[a] ~ '[a0], Sum a b ~ b0, HasSpec a0, HasSpec b0) ⇒ BaseW "leftFn" '[a0] b0 → TypeSpec a0 → Specification b0 Source #

saturateBaseW "leftFn" '[a] Bool → List Term '[a] → [Pred] Source #

(HasSpec a, HasSpec b) ⇒ Logic "prod_" BaseW '[a, b] (Prod a b) Source # 
Instance details

Defined in Constrained.TheKnot

Methods

infoBaseW "prod_" '[a, b] (Prod a b) → String Source #

propagateContext "prod_" BaseW '[a, b] (Prod a b) hole → Specification (Prod a b) → Specification hole Source #

rewriteRulesBaseW "prod_" '[a, b] (Prod a b) → List Term '[a, b] → Evidence (AppRequires "prod_" BaseW '[a, b] (Prod a b)) → Maybe (Term (Prod a b)) Source #

mapTypeSpec ∷ ('[a, b] ~ '[a0], Prod a b ~ b0, HasSpec a0, HasSpec b0) ⇒ BaseW "prod_" '[a0] b0 → TypeSpec a0 → Specification b0 Source #

saturateBaseW "prod_" '[a, b] Bool → List Term '[a, b] → [Pred] Source #

(HasSpec a, HasSpec b, KnownNat (CountCases b)) ⇒ Logic "rightFn" BaseW '[b] (Sum a b) Source # 
Instance details

Defined in Constrained.Spec.SumProd

Methods

infoBaseW "rightFn" '[b] (Sum a b) → String Source #

propagateContext "rightFn" BaseW '[b] (Sum a b) hole → Specification (Sum a b) → Specification hole Source #

rewriteRulesBaseW "rightFn" '[b] (Sum a b) → List Term '[b] → Evidence (AppRequires "rightFn" BaseW '[b] (Sum a b)) → Maybe (Term (Sum a b)) Source #

mapTypeSpec ∷ ('[b] ~ '[a0], Sum a b ~ b0, HasSpec a0, HasSpec b0) ⇒ BaseW "rightFn" '[a0] b0 → TypeSpec a0 → Specification b0 Source #

saturateBaseW "rightFn" '[b] Bool → List Term '[b] → [Pred] Source #

Show (BaseW s d r) Source # 
Instance details

Defined in Constrained.Base

Methods

showsPrec ∷ Int → BaseW s d r → ShowS

showBaseW s d r → String

showList ∷ [BaseW s d r] → ShowS

Eq (BaseW s dom rng) Source # 
Instance details

Defined in Constrained.Base

Methods

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

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

data BoolW (sym ∷ Symbol) (dom ∷ [Type]) (rng ∷ Type) where Source #

Operations on Bool

Constructors

NotWBoolW "not_" '[Bool] Bool 
OrWBoolW "or_" '[Bool, Bool] Bool 

Instances

Instances details
Semantics BoolW Source # 
Instance details

Defined in Constrained.TheKnot

Methods

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

Syntax BoolW Source # 
Instance details

Defined in Constrained.TheKnot

Methods

isInFix ∷ ∀ (s ∷ Symbol) (dom ∷ [Type]) rng. BoolW s dom rng → Bool Source #

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

(HasSpec Bool, TypeSpec Bool ~ SumSpec () ()) ⇒ Logic "not_" BoolW '[Bool] Bool Source # 
Instance details

Defined in Constrained.TheKnot

Methods

infoBoolW "not_" '[Bool] Bool → String Source #

propagateContext "not_" BoolW '[Bool] Bool hole → Specification Bool → Specification hole Source #

rewriteRulesBoolW "not_" '[Bool] Bool → List Term '[Bool] → Evidence (AppRequires "not_" BoolW '[Bool] Bool) → Maybe (Term Bool) Source #

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

saturateBoolW "not_" '[Bool] Bool → List Term '[Bool] → [Pred] Source #

HasSpec Bool ⇒ Logic "or_" BoolW '[Bool, Bool] Bool Source # 
Instance details

Defined in Constrained.TheKnot

Methods

infoBoolW "or_" '[Bool, Bool] Bool → String Source #

propagateContext "or_" BoolW '[Bool, Bool] Bool hole → Specification Bool → Specification hole Source #

rewriteRulesBoolW "or_" '[Bool, Bool] Bool → List Term '[Bool, Bool] → Evidence (AppRequires "or_" BoolW '[Bool, Bool] Bool) → Maybe (Term Bool) Source #

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

saturateBoolW "or_" '[Bool, Bool] Bool → List Term '[Bool, Bool] → [Pred] Source #

Show (BoolW s dom rng) Source # 
Instance details

Defined in Constrained.TheKnot

Methods

showsPrec ∷ Int → BoolW s dom rng → ShowS

showBoolW s dom rng → String

showList ∷ [BoolW s dom rng] → ShowS

Eq (BoolW s dom rng) Source # 
Instance details

Defined in Constrained.TheKnot

Methods

(==)BoolW s dom rng → BoolW s dom rng → Bool

(/=)BoolW s dom rng → BoolW s dom rng → Bool

data NumOrdW (sym ∷ Symbol) (dom ∷ [Type]) (rng ∷ Type) where Source #

Constructors

LessOrEqualWOrdLike a ⇒ NumOrdW "<=." '[a, a] Bool 
LessWOrdLike a ⇒ NumOrdW "<." '[a, a] Bool 
GreaterOrEqualWOrdLike a ⇒ NumOrdW ">=." '[a, a] Bool 
GreaterWOrdLike a ⇒ NumOrdW ">." '[a, a] Bool 

Instances

Instances details
Semantics NumOrdW Source # 
Instance details

Defined in Constrained.NumSpec

Methods

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

Syntax NumOrdW Source # 
Instance details

Defined in Constrained.NumSpec

Methods

isInFix ∷ ∀ (s ∷ Symbol) (dom ∷ [Type]) rng. NumOrdW s dom rng → Bool Source #

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

OrdLike a ⇒ Logic "<." NumOrdW '[a, a] Bool Source # 
Instance details

Defined in Constrained.TheKnot

Methods

infoNumOrdW "<." '[a, a] Bool → String Source #

propagateContext "<." NumOrdW '[a, a] Bool hole → Specification Bool → Specification hole Source #

rewriteRulesNumOrdW "<." '[a, a] Bool → List Term '[a, a] → Evidence (AppRequires "<." NumOrdW '[a, a] Bool) → Maybe (Term Bool) Source #

mapTypeSpec ∷ ('[a, a] ~ '[a0], Bool ~ b, HasSpec a0, HasSpec b) ⇒ NumOrdW "<." '[a0] b → TypeSpec a0 → Specification b Source #

saturateNumOrdW "<." '[a, a] Bool → List Term '[a, a] → [Pred] Source #

OrdLike a ⇒ Logic "<=." NumOrdW '[a, a] Bool Source # 
Instance details

Defined in Constrained.TheKnot

Methods

infoNumOrdW "<=." '[a, a] Bool → String Source #

propagateContext "<=." NumOrdW '[a, a] Bool hole → Specification Bool → Specification hole Source #

rewriteRulesNumOrdW "<=." '[a, a] Bool → List Term '[a, a] → Evidence (AppRequires "<=." NumOrdW '[a, a] Bool) → Maybe (Term Bool) Source #

mapTypeSpec ∷ ('[a, a] ~ '[a0], Bool ~ b, HasSpec a0, HasSpec b) ⇒ NumOrdW "<=." '[a0] b → TypeSpec a0 → Specification b Source #

saturateNumOrdW "<=." '[a, a] Bool → List Term '[a, a] → [Pred] Source #

OrdLike a ⇒ Logic ">." NumOrdW '[a, a] Bool Source # 
Instance details

Defined in Constrained.TheKnot

Methods

infoNumOrdW ">." '[a, a] Bool → String Source #

propagateContext ">." NumOrdW '[a, a] Bool hole → Specification Bool → Specification hole Source #

rewriteRulesNumOrdW ">." '[a, a] Bool → List Term '[a, a] → Evidence (AppRequires ">." NumOrdW '[a, a] Bool) → Maybe (Term Bool) Source #

mapTypeSpec ∷ ('[a, a] ~ '[a0], Bool ~ b, HasSpec a0, HasSpec b) ⇒ NumOrdW ">." '[a0] b → TypeSpec a0 → Specification b Source #

saturateNumOrdW ">." '[a, a] Bool → List Term '[a, a] → [Pred] Source #

OrdLike a ⇒ Logic ">=." NumOrdW '[a, a] Bool Source # 
Instance details

Defined in Constrained.TheKnot

Methods

infoNumOrdW ">=." '[a, a] Bool → String Source #

propagateContext ">=." NumOrdW '[a, a] Bool hole → Specification Bool → Specification hole Source #

rewriteRulesNumOrdW ">=." '[a, a] Bool → List Term '[a, a] → Evidence (AppRequires ">=." NumOrdW '[a, a] Bool) → Maybe (Term Bool) Source #

mapTypeSpec ∷ ('[a, a] ~ '[a0], Bool ~ b, HasSpec a0, HasSpec b) ⇒ NumOrdW ">=." '[a0] b → TypeSpec a0 → Specification b Source #

saturateNumOrdW ">=." '[a, a] Bool → List Term '[a, a] → [Pred] Source #

Show (NumOrdW s ds r) Source # 
Instance details

Defined in Constrained.NumSpec

Methods

showsPrec ∷ Int → NumOrdW s ds r → ShowS

showNumOrdW s ds r → String

showList ∷ [NumOrdW s ds r] → ShowS

Eq (NumOrdW s ds r) Source # 
Instance details

Defined in Constrained.NumSpec

Methods

(==)NumOrdW s ds r → NumOrdW s ds r → Bool

(/=)NumOrdW s ds r → NumOrdW s ds r → Bool

data IntW (s ∷ Symbol) (as ∷ [Type]) b where Source #

Constructors

AddWNumLike a ⇒ IntW "addFn" '[a, a] a 
NegateWNumLike a ⇒ IntW "negateFn" '[a] a 

Instances

Instances details
Semantics IntW Source # 
Instance details

Defined in Constrained.NumSpec

Methods

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

Syntax IntW Source # 
Instance details

Defined in Constrained.NumSpec

Methods

isInFix ∷ ∀ (s ∷ Symbol) (dom ∷ [Type]) rng. IntW s dom rng → Bool Source #

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

NumLike a ⇒ Logic "addFn" IntW '[a, a] a 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

infoIntW "addFn" '[a, a] a → String Source #

propagateContext "addFn" IntW '[a, a] a hole → Specification a → Specification hole Source #

rewriteRulesIntW "addFn" '[a, a] a → List Term '[a, a] → Evidence (AppRequires "addFn" IntW '[a, a] a) → Maybe (Term a) Source #

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

saturateIntW "addFn" '[a, a] Bool → List Term '[a, a] → [Pred] Source #

NumLike a ⇒ Logic "negateFn" IntW '[a] a Source # 
Instance details

Defined in Constrained.NumSpec

Methods

infoIntW "negateFn" '[a] a → String Source #

propagateContext "negateFn" IntW '[a] a hole → Specification a → Specification hole Source #

rewriteRulesIntW "negateFn" '[a] a → List Term '[a] → Evidence (AppRequires "negateFn" IntW '[a] a) → Maybe (Term a) Source #

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

saturateIntW "negateFn" '[a] Bool → List Term '[a] → [Pred] Source #

Show (IntW s d r) Source # 
Instance details

Defined in Constrained.NumSpec

Methods

showsPrec ∷ Int → IntW s d r → ShowS

showIntW s d r → String

showList ∷ [IntW s d r] → ShowS

Eq (IntW s dom rng) Source # 
Instance details

Defined in Constrained.NumSpec

Methods

(==)IntW s dom rng → IntW s dom rng → Bool

(/=)IntW s dom rng → IntW s dom rng → Bool

data SizeW (s ∷ Symbol) (dom ∷ [Type]) rng ∷ Type where Source #

Constructors

SizeOfW ∷ ∀ n. Sized n ⇒ SizeW "sizeOf_" '[n] Integer 

Instances

Instances details
Semantics SizeW Source # 
Instance details

Defined in Constrained.Spec.Size

Methods

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

Syntax SizeW Source # 
Instance details

Defined in Constrained.Spec.Size

Methods

isInFix ∷ ∀ (s ∷ Symbol) (dom ∷ [Type]) rng. SizeW s dom rng → Bool Source #

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

(Sized t, HasSpec t) ⇒ Logic "sizeOf_" SizeW '[t] Integer Source # 
Instance details

Defined in Constrained.Spec.Size

Methods

infoSizeW "sizeOf_" '[t] Integer → String Source #

propagateContext "sizeOf_" SizeW '[t] Integer hole → Specification Integer → Specification hole Source #

rewriteRulesSizeW "sizeOf_" '[t] Integer → List Term '[t] → Evidence (AppRequires "sizeOf_" SizeW '[t] Integer) → Maybe (Term Integer) Source #

mapTypeSpec ∷ ('[t] ~ '[a], Integer ~ b, HasSpec a, HasSpec b) ⇒ SizeW "sizeOf_" '[a] b → TypeSpec a → Specification b Source #

saturateSizeW "sizeOf_" '[t] Bool → List Term '[t] → [Pred] Source #

Show (SizeW s d r) Source # 
Instance details

Defined in Constrained.Spec.Size

Methods

showsPrec ∷ Int → SizeW s d r → ShowS

showSizeW s d r → String

showList ∷ [SizeW s d r] → ShowS

Eq (SizeW s ds r) Source # 
Instance details

Defined in Constrained.Spec.Size

Methods

(==)SizeW s ds r → SizeW s ds r → Bool

(/=)SizeW s ds r → SizeW s ds r → Bool

data FunW (sym ∷ Symbol) (dom ∷ [Type]) (rng ∷ Type) where Source #

Constructors

IdW ∷ ∀ a. FunW "id_" '[a] a 
ComposeW ∷ ∀ b s1 s2 t1 t2 a r. (Logic s1 t1 '[b] r, Logic s2 t2 '[a] b, HasSpec b) ⇒ t1 s1 '[b] r → t2 s2 '[a] b → FunW "composeFn" '[a] r 
FlipW ∷ ∀ sym t a b r. Logic sym t '[a, b] r ⇒ t sym '[a, b] r → FunW "flip_" '[b, a] r 

Instances

Instances details
Semantics FunW Source # 
Instance details

Defined in Constrained.Spec.ListFoldy

Methods

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

Syntax FunW Source # 
Instance details

Defined in Constrained.Spec.ListFoldy

Methods

isInFix ∷ ∀ (s ∷ Symbol) (dom ∷ [Type]) rng. FunW s dom rng → Bool Source #

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

(All (Typeable ∷ Type → Constraint) '[a, r], HasSpec r) ⇒ Logic "composeFn" FunW '[a] r Source # 
Instance details

Defined in Constrained.Spec.ListFoldy

Methods

infoFunW "composeFn" '[a] r → String Source #

propagateContext "composeFn" FunW '[a] r hole → Specification r → Specification hole Source #

rewriteRulesFunW "composeFn" '[a] r → List Term '[a] → Evidence (AppRequires "composeFn" FunW '[a] r) → Maybe (Term r) Source #

mapTypeSpec ∷ ('[a] ~ '[a0], r ~ b, HasSpec a0, HasSpec b) ⇒ FunW "composeFn" '[a0] b → TypeSpec a0 → Specification b Source #

saturateFunW "composeFn" '[a] Bool → List Term '[a] → [Pred] Source #

(∀ (sym ∷ Symbol) (t ∷ Symbol → [Type] → Type → Type). Logic sym t '[a, b] r, All (Typeable ∷ Type → Constraint) '[a, b, r]) ⇒ Logic "flip_" FunW '[b, a] r Source # 
Instance details

Defined in Constrained.Spec.ListFoldy

Methods

infoFunW "flip_" '[b, a] r → String Source #

propagateContext "flip_" FunW '[b, a] r hole → Specification r → Specification hole Source #

rewriteRulesFunW "flip_" '[b, a] r → List Term '[b, a] → Evidence (AppRequires "flip_" FunW '[b, a] r) → Maybe (Term r) Source #

mapTypeSpec ∷ ('[b, a] ~ '[a0], r ~ b0, HasSpec a0, HasSpec b0) ⇒ FunW "flip_" '[a0] b0 → TypeSpec a0 → Specification b0 Source #

saturateFunW "flip_" '[b, a] Bool → List Term '[b, a] → [Pred] Source #

HasSpec a ⇒ Logic "id_" FunW '[a] a Source # 
Instance details

Defined in Constrained.Spec.ListFoldy

Methods

infoFunW "id_" '[a] a → String Source #

propagateContext "id_" FunW '[a] a hole → Specification a → Specification hole Source #

rewriteRulesFunW "id_" '[a] a → List Term '[a] → Evidence (AppRequires "id_" FunW '[a] a) → Maybe (Term a) Source #

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

saturateFunW "id_" '[a] Bool → List Term '[a] → [Pred] Source #

KnownSymbol s ⇒ Show (FunW s dom rng) Source # 
Instance details

Defined in Constrained.Spec.ListFoldy

Methods

showsPrec ∷ Int → FunW s dom rng → ShowS

showFunW s dom rng → String

showList ∷ [FunW s dom rng] → ShowS

Eq (FunW s dom rng) Source # 
Instance details

Defined in Constrained.Spec.ListFoldy

Methods

(==)FunW s dom rng → FunW s dom rng → Bool

(/=)FunW s dom rng → FunW s dom rng → Bool

data ListW (s ∷ Symbol) (args ∷ [Type]) (res ∷ Type) where Source #

Constructors

FoldMapW ∷ ∀ a b. (Foldy b, HasSpec a) ⇒ Fun '[a] b → ListW "foldMap_" '[[a]] b 
SingletonListWListW "singeltonList_" '[a] [a] 
AppendW ∷ (Typeable a, Show a) ⇒ ListW "append_" '[[a], [a]] [a] 

Instances

Instances details
Semantics ListW Source # 
Instance details

Defined in Constrained.Spec.ListFoldy

Methods

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

Syntax ListW Source # 
Instance details

Defined in Constrained.Spec.ListFoldy

Methods

isInFix ∷ ∀ (s ∷ Symbol) (dom ∷ [Type]) rng. ListW s dom rng → Bool Source #

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

(Typeable a, Foldy b) ⇒ Logic "foldMap_" ListW '[[a]] b Source # 
Instance details

Defined in Constrained.Spec.ListFoldy

Methods

infoListW "foldMap_" '[[a]] b → String Source #

propagateContext "foldMap_" ListW '[[a]] b hole → Specification b → Specification hole Source #

rewriteRulesListW "foldMap_" '[[a]] b → List Term '[[a]] → Evidence (AppRequires "foldMap_" ListW '[[a]] b) → Maybe (Term b) Source #

mapTypeSpec ∷ ('[[a]] ~ '[a0], b ~ b0, HasSpec a0, HasSpec b0) ⇒ ListW "foldMap_" '[a0] b0 → TypeSpec a0 → Specification b0 Source #

saturateListW "foldMap_" '[[a]] Bool → List Term '[[a]] → [Pred] Source #

(Sized [a], HasSpec a) ⇒ Logic "append_" ListW '[[a], [a]] [a] Source # 
Instance details

Defined in Constrained.Spec.ListFoldy

Methods

infoListW "append_" '[[a], [a]] [a] → String Source #

propagateContext "append_" ListW '[[a], [a]] [a] hole → Specification [a] → Specification hole Source #

rewriteRulesListW "append_" '[[a], [a]] [a] → List Term '[[a], [a]] → Evidence (AppRequires "append_" ListW '[[a], [a]] [a]) → Maybe (Term [a]) Source #

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

saturateListW "append_" '[[a], [a]] Bool → List Term '[[a], [a]] → [Pred] Source #

HasSpec a ⇒ Logic "singeltonList_" ListW '[a] [a] Source # 
Instance details

Defined in Constrained.Spec.ListFoldy

Methods

infoListW "singeltonList_" '[a] [a] → String Source #

propagateContext "singeltonList_" ListW '[a] [a] hole → Specification [a] → Specification hole Source #

rewriteRulesListW "singeltonList_" '[a] [a] → List Term '[a] → Evidence (AppRequires "singeltonList_" ListW '[a] [a]) → Maybe (Term [a]) Source #

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

saturateListW "singeltonList_" '[a] Bool → List Term '[a] → [Pred] Source #

Show (ListW s d r) Source # 
Instance details

Defined in Constrained.Spec.ListFoldy

Methods

showsPrec ∷ Int → ListW s d r → ShowS

showListW s d r → String

showList ∷ [ListW s d r] → ShowS

Eq (ListW s d r) Source # 
Instance details

Defined in Constrained.Spec.ListFoldy

Methods

(==)ListW s d r → ListW s d r → Bool

(/=)ListW s d r → ListW s d r → Bool

data MapW (sym ∷ Symbol) (dom ∷ [Type]) (rng ∷ Type) where Source #

Constructors

DomW ∷ ∀ k v. Ord k ⇒ MapW "dom_" '[Map k v] (Set k) 
RngW ∷ ∀ k v. Ord k ⇒ MapW "rng_" '[Map k v] [v] 
LookupW ∷ ∀ k v. Ord k ⇒ MapW "lookup_" '[k, Map k v] (Maybe v) 

Instances

Instances details
Semantics MapW Source # 
Instance details

Defined in Constrained.Spec.Map

Methods

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

Syntax MapW Source # 
Instance details

Defined in Constrained.Spec.Map

Methods

isInFix ∷ ∀ (s ∷ Symbol) (dom ∷ [Type]) rng. MapW s dom rng → Bool Source #

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

(HasSpec k, HasSpec v, Ord k, IsNormalType v, IsNormalType k) ⇒ Logic "dom_" MapW '[Map k v] (Set k) Source # 
Instance details

Defined in Constrained.Spec.Map

Methods

infoMapW "dom_" '[Map k v] (Set k) → String Source #

propagateContext "dom_" MapW '[Map k v] (Set k) hole → Specification (Set k) → Specification hole Source #

rewriteRulesMapW "dom_" '[Map k v] (Set k) → List Term '[Map k v] → Evidence (AppRequires "dom_" MapW '[Map k v] (Set k)) → Maybe (Term (Set k)) Source #

mapTypeSpec ∷ ('[Map k v] ~ '[a], Set k ~ b, HasSpec a, HasSpec b) ⇒ MapW "dom_" '[a] b → TypeSpec a → Specification b Source #

saturateMapW "dom_" '[Map k v] Bool → List Term '[Map k v] → [Pred] Source #

(HasSpec k, HasSpec v, IsNormalType v, IsNormalType k) ⇒ Logic "lookup_" MapW '[k, Map k v] (Maybe v) Source # 
Instance details

Defined in Constrained.Spec.Map

Methods

infoMapW "lookup_" '[k, Map k v] (Maybe v) → String Source #

propagateContext "lookup_" MapW '[k, Map k v] (Maybe v) hole → Specification (Maybe v) → Specification hole Source #

rewriteRulesMapW "lookup_" '[k, Map k v] (Maybe v) → List Term '[k, Map k v] → Evidence (AppRequires "lookup_" MapW '[k, Map k v] (Maybe v)) → Maybe (Term (Maybe v)) Source #

mapTypeSpec ∷ ('[k, Map k v] ~ '[a], Maybe v ~ b, HasSpec a, HasSpec b) ⇒ MapW "lookup_" '[a] b → TypeSpec a → Specification b Source #

saturateMapW "lookup_" '[k, Map k v] Bool → List Term '[k, Map k v] → [Pred] Source #

(HasSpec k, HasSpec v, Ord k, IsNormalType v, IsNormalType k) ⇒ Logic "rng_" MapW '[Map k v] [v] Source # 
Instance details

Defined in Constrained.Spec.Map

Methods

infoMapW "rng_" '[Map k v] [v] → String Source #

propagateContext "rng_" MapW '[Map k v] [v] hole → Specification [v] → Specification hole Source #

rewriteRulesMapW "rng_" '[Map k v] [v] → List Term '[Map k v] → Evidence (AppRequires "rng_" MapW '[Map k v] [v]) → Maybe (Term [v]) Source #

mapTypeSpec ∷ ('[Map k v] ~ '[a], [v] ~ b, HasSpec a, HasSpec b) ⇒ MapW "rng_" '[a] b → TypeSpec a → Specification b Source #

saturateMapW "rng_" '[Map k v] Bool → List Term '[Map k v] → [Pred] Source #

Show (MapW s d r) Source # 
Instance details

Defined in Constrained.Spec.Map

Methods

showsPrec ∷ Int → MapW s d r → ShowS

showMapW s d r → String

showList ∷ [MapW s d r] → ShowS

Eq (MapW s dom rng) Source # 
Instance details

Defined in Constrained.Spec.Map

Methods

(==)MapW s dom rng → MapW s dom rng → Bool

(/=)MapW s dom rng → MapW s dom rng → Bool

data NumSpec n Source #

Constructors

NumSpecInterval (Maybe n) (Maybe n) 

Instances

Instances details
(Arbitrary a, Ord a) ⇒ Arbitrary (NumSpec a) Source # 
Instance details

Defined in Constrained.NumSpec

Methods

arbitraryGen (NumSpec a) Source #

shrinkNumSpec a → [NumSpec a] Source #

Ord n ⇒ Monoid (NumSpec n) Source # 
Instance details

Defined in Constrained.NumSpec

Methods

memptyNumSpec n

mappendNumSpec n → NumSpec n → NumSpec n

mconcat ∷ [NumSpec n] → NumSpec n

Ord n ⇒ Semigroup (NumSpec n) Source # 
Instance details

Defined in Constrained.NumSpec

Methods

(<>)NumSpec n → NumSpec n → NumSpec n #

sconcatNonEmpty (NumSpec n) → NumSpec n

stimes ∷ Integral b ⇒ b → NumSpec n → NumSpec n

Num (NumSpec Integer) Source # 
Instance details

Defined in Constrained.NumSpec

Methods

(+)NumSpec Integer → NumSpec Integer → NumSpec Integer

(-)NumSpec Integer → NumSpec Integer → NumSpec Integer

(*)NumSpec Integer → NumSpec Integer → NumSpec Integer

negateNumSpec Integer → NumSpec Integer

absNumSpec Integer → NumSpec Integer

signumNumSpec Integer → NumSpec Integer

fromInteger ∷ Integer → NumSpec Integer

Show n ⇒ Show (NumSpec n) Source # 
Instance details

Defined in Constrained.NumSpec

Methods

showsPrec ∷ Int → NumSpec n → ShowS

showNumSpec n → String

showList ∷ [NumSpec n] → ShowS

Ord n ⇒ Eq (NumSpec n) Source # 
Instance details

Defined in Constrained.NumSpec

Methods

(==)NumSpec n → NumSpec n → Bool

(/=)NumSpec n → NumSpec n → Bool

class MaybeBounded a where Source #

Minimal complete definition

Nothing

Methods

lowerBound ∷ Maybe a Source #

default lowerBound ∷ Bounded a ⇒ Maybe a Source #

upperBound ∷ Maybe a Source #

default upperBound ∷ Bounded a ⇒ Maybe a Source #

Instances

Instances details
MaybeBounded Int16 Source # 
Instance details

Defined in Constrained.NumSpec

Methods

lowerBound ∷ Maybe Int16 Source #

upperBound ∷ Maybe Int16 Source #

MaybeBounded Int32 Source # 
Instance details

Defined in Constrained.NumSpec

Methods

lowerBound ∷ Maybe Int32 Source #

upperBound ∷ Maybe Int32 Source #

MaybeBounded Int64 Source # 
Instance details

Defined in Constrained.NumSpec

Methods

lowerBound ∷ Maybe Int64 Source #

upperBound ∷ Maybe Int64 Source #

MaybeBounded Int8 Source # 
Instance details

Defined in Constrained.NumSpec

Methods

lowerBound ∷ Maybe Int8 Source #

upperBound ∷ Maybe Int8 Source #

MaybeBounded Word16 Source # 
Instance details

Defined in Constrained.NumSpec

Methods

lowerBound ∷ Maybe Word16 Source #

upperBound ∷ Maybe Word16 Source #

MaybeBounded Word32 Source # 
Instance details

Defined in Constrained.NumSpec

Methods

lowerBound ∷ Maybe Word32 Source #

upperBound ∷ Maybe Word32 Source #

MaybeBounded Word64 Source # 
Instance details

Defined in Constrained.NumSpec

Methods

lowerBound ∷ Maybe Word64 Source #

upperBound ∷ Maybe Word64 Source #

MaybeBounded Word8 Source # 
Instance details

Defined in Constrained.NumSpec

Methods

lowerBound ∷ Maybe Word8 Source #

upperBound ∷ Maybe Word8 Source #

MaybeBounded Integer Source # 
Instance details

Defined in Constrained.NumSpec

Methods

lowerBound ∷ Maybe Integer Source #

upperBound ∷ Maybe Integer Source #

MaybeBounded Natural Source # 
Instance details

Defined in Constrained.NumSpec

Methods

lowerBound ∷ Maybe Natural Source #

upperBound ∷ Maybe Natural Source #

MaybeBounded Float Source # 
Instance details

Defined in Constrained.NumSpec

Methods

lowerBound ∷ Maybe Float Source #

upperBound ∷ Maybe Float Source #

MaybeBounded Int Source # 
Instance details

Defined in Constrained.NumSpec

Methods

lowerBound ∷ Maybe Int Source #

upperBound ∷ Maybe Int Source #

MaybeBounded (Ratio Integer) Source # 
Instance details

Defined in Constrained.NumSpec

Methods

lowerBound ∷ Maybe (Ratio Integer) Source #

upperBound ∷ Maybe (Ratio Integer) Source #

data NonEmpty a #

Constructors

a :| [a] 

Instances

Instances details
MonadFix NonEmpty 
Instance details

Defined in Control.Monad.Fix

Methods

mfix ∷ (a → NonEmpty a) → NonEmpty a

Foldable NonEmpty 
Instance details

Defined in Data.Foldable

Methods

fold ∷ Monoid m ⇒ NonEmpty m → m

foldMap ∷ Monoid m ⇒ (a → m) → NonEmpty a → m

foldMap' ∷ Monoid m ⇒ (a → m) → NonEmpty a → m

foldr ∷ (a → b → b) → b → NonEmpty a → b

foldr' ∷ (a → b → b) → b → NonEmpty a → b

foldl ∷ (b → a → b) → b → NonEmpty a → b

foldl' ∷ (b → a → b) → b → NonEmpty a → b

foldr1 ∷ (a → a → a) → NonEmpty a → a

foldl1 ∷ (a → a → a) → NonEmpty a → a

toListNonEmpty a → [a]

nullNonEmpty a → Bool

lengthNonEmpty a → Int

elem ∷ Eq a ⇒ a → NonEmpty a → Bool

maximum ∷ Ord a ⇒ NonEmpty a → a

minimum ∷ Ord a ⇒ NonEmpty a → a

sum ∷ Num a ⇒ NonEmpty a → a

product ∷ Num a ⇒ NonEmpty a → a

Eq1 NonEmpty 
Instance details

Defined in Data.Functor.Classes

Methods

liftEq ∷ (a → b → Bool) → NonEmpty a → NonEmpty b → Bool

Ord1 NonEmpty 
Instance details

Defined in Data.Functor.Classes

Methods

liftCompare ∷ (a → b → Ordering) → NonEmpty a → NonEmpty b → Ordering

Read1 NonEmpty 
Instance details

Defined in Data.Functor.Classes

Methods

liftReadsPrec ∷ (Int → ReadS a) → ReadS [a] → Int → ReadS (NonEmpty a)

liftReadList ∷ (Int → ReadS a) → ReadS [a] → ReadS [NonEmpty a]

liftReadPrec ∷ ReadPrec a → ReadPrec [a] → ReadPrec (NonEmpty a)

liftReadListPrec ∷ ReadPrec a → ReadPrec [a] → ReadPrec [NonEmpty a]

Show1 NonEmpty 
Instance details

Defined in Data.Functor.Classes

Methods

liftShowsPrec ∷ (Int → a → ShowS) → ([a] → ShowS) → Int → NonEmpty a → ShowS

liftShowList ∷ (Int → a → ShowS) → ([a] → ShowS) → [NonEmpty a] → ShowS

Traversable NonEmpty 
Instance details

Defined in Data.Traversable

Methods

traverse ∷ Applicative f ⇒ (a → f b) → NonEmpty a → f (NonEmpty b)

sequenceA ∷ Applicative f ⇒ NonEmpty (f a) → f (NonEmpty a)

mapM ∷ Monad m ⇒ (a → m b) → NonEmpty a → m (NonEmpty b)

sequence ∷ Monad m ⇒ NonEmpty (m a) → m (NonEmpty a)

Applicative NonEmpty 
Instance details

Defined in GHC.Base

Methods

pure ∷ a → NonEmpty a

(<*>)NonEmpty (a → b) → NonEmpty a → NonEmpty b

liftA2 ∷ (a → b → c) → NonEmpty a → NonEmpty b → NonEmpty c

(*>)NonEmpty a → NonEmpty b → NonEmpty b

(<*)NonEmpty a → NonEmpty b → NonEmpty a

Functor NonEmpty 
Instance details

Defined in GHC.Base

Methods

fmap ∷ (a → b) → NonEmpty a → NonEmpty b

(<$) ∷ a → NonEmpty b → NonEmpty a

Monad NonEmpty 
Instance details

Defined in GHC.Base

Methods

(>>=)NonEmpty a → (a → NonEmpty b) → NonEmpty b

(>>)NonEmpty a → NonEmpty b → NonEmpty b

return ∷ a → NonEmpty a

Generic1 NonEmpty 
Instance details

Defined in GHC.Generics

Associated Types

type Rep1 NonEmpty ∷ k → Type

Methods

from1 ∷ ∀ (a ∷ k). NonEmpty a → Rep1 NonEmpty a

to1 ∷ ∀ (a ∷ k). Rep1 NonEmpty a → NonEmpty a

Lift a ⇒ Lift (NonEmpty a ∷ Type) 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

lift ∷ Quote m ⇒ NonEmpty a → m Exp

liftTyped ∷ ∀ (m ∷ Type → Type). Quote m ⇒ NonEmpty a → Code m (NonEmpty a)

Arbitrary a ⇒ Arbitrary (NonEmpty a) Source # 
Instance details

Defined in Constrained.Core

Semigroup (NonEmpty a) 
Instance details

Defined in GHC.Base

Methods

(<>)NonEmpty a → NonEmpty a → NonEmpty a #

sconcatNonEmpty (NonEmpty a) → NonEmpty a

stimes ∷ Integral b ⇒ b → NonEmpty a → NonEmpty a

IsList (NonEmpty a) 
Instance details

Defined in GHC.Exts

Associated Types

type Item (NonEmpty a)

Methods

fromList ∷ [Item (NonEmpty a)] → NonEmpty a

fromListN ∷ Int → [Item (NonEmpty a)] → NonEmpty a

toListNonEmpty a → [Item (NonEmpty a)]

Generic (NonEmpty a) 
Instance details

Defined in GHC.Generics

Associated Types

type Rep (NonEmpty a) ∷ Type → Type

Methods

fromNonEmpty a → Rep (NonEmpty a) x

to ∷ Rep (NonEmpty a) x → NonEmpty a

Read a ⇒ Read (NonEmpty a) 
Instance details

Defined in GHC.Read

Methods

readsPrec ∷ Int → ReadS (NonEmpty a)

readList ∷ ReadS [NonEmpty a]

readPrec ∷ ReadPrec (NonEmpty a)

readListPrec ∷ ReadPrec [NonEmpty a]

Show a ⇒ Show (NonEmpty a) 
Instance details

Defined in GHC.Show

Methods

showsPrec ∷ Int → NonEmpty a → ShowS

showNonEmpty a → String

showList ∷ [NonEmpty a] → ShowS

Eq a ⇒ Eq (NonEmpty a) 
Instance details

Defined in GHC.Base

Methods

(==)NonEmpty a → NonEmpty a → Bool

(/=)NonEmpty a → NonEmpty a → Bool

Ord a ⇒ Ord (NonEmpty a) 
Instance details

Defined in GHC.Base

Methods

compareNonEmpty a → NonEmpty a → Ordering

(<)NonEmpty a → NonEmpty a → Bool

(<=)NonEmpty a → NonEmpty a → Bool

(>)NonEmpty a → NonEmpty a → Bool

(>=)NonEmpty a → NonEmpty a → Bool

maxNonEmpty a → NonEmpty a → NonEmpty a

minNonEmpty a → NonEmpty a → NonEmpty a

Pretty a ⇒ Pretty (NonEmpty a) 
Instance details

Defined in Prettyprinter.Internal

Methods

prettyNonEmpty a → Doc ann Source #

prettyList ∷ [NonEmpty a] → Doc ann Source #

type Rep1 NonEmpty 
Instance details

Defined in GHC.Generics

type Rep1 NonEmpty = D1 ('MetaData "NonEmpty" "GHC.Base" "base" 'False) (C1 ('MetaCons ":|" ('InfixI 'LeftAssociative 9) 'False) (S1 ('MetaSel ('Nothing ∷ Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) Par1 :*: S1 ('MetaSel ('Nothing ∷ Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec1 [])))
type Item (NonEmpty a) 
Instance details

Defined in GHC.Exts

type Item (NonEmpty a) = a
type Rep (NonEmpty a) 
Instance details

Defined in GHC.Generics

type Rep (NonEmpty a) = D1 ('MetaData "NonEmpty" "GHC.Base" "base" 'False) (C1 ('MetaCons ":|" ('InfixI 'LeftAssociative 9) 'False) (S1 ('MetaSel ('Nothing ∷ Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Nothing ∷ Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [a])))

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

data Term a where Source #

Constructors

App ∷ ∀ sym t dom rng. AppRequires sym t dom rng ⇒ t sym dom rng → List Term dom → Term rng 
LitLiteral 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 #

data Fun dom rng where Source #

Constructors

Fun ∷ ∀ s t dom rng. Logic s t dom rng ⇒ t s 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

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 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 #

type Literal a = (Typeable a, Eq a, Show a) Source #

Properties needed by objects to appear in the system, if they have no semantic or logical requirements. Mostly used for Lit terms, which are self evaluating But such things also occurr in Contexts.

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.Spec.Num

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.Spec.Num

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.Spec.Num

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.Spec.Num

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.Spec.Num

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.Spec.Num

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.Spec.Num

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.Spec.Num

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.Spec.Num

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.Spec.Num

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.Spec.Num

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.Spec.Num

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.Spec.ListFoldy

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 #

class Typeable (SimpleRep a) ⇒ HasSimpleRep a where Source #

Minimal complete definition

Nothing

Associated Types

type SimpleRep a Source #

type SimpleRep a = SOP (TheSop a)

type TheSop a ∷ [Type] Source #

type TheSop a = SOPOf (Rep a)

Methods

toSimpleRep ∷ a → SimpleRep a Source #

default toSimpleRep ∷ (Generic a, SimpleGeneric (Rep a), SimpleRep a ~ SimplifyRep (Rep a)) ⇒ a → SimpleRep a Source #

fromSimpleRepSimpleRep a → a Source #

default fromSimpleRep ∷ (Generic a, SimpleGeneric (Rep a), SimpleRep a ~ SimplifyRep (Rep a)) ⇒ SimpleRep a → a Source #

Instances

Instances details
HasSimpleRep Foo Source # 
Instance details

Defined in Constrained.Examples.Basic

Associated Types

type SimpleRep Foo Source #

type TheSop Foo ∷ [Type] Source #

HasSimpleRep Three Source # 
Instance details

Defined in Constrained.Examples.Basic

Associated Types

type SimpleRep Three Source #

type TheSop Three ∷ [Type] Source #

HasSimpleRep FooBarBaz Source # 
Instance details

Defined in Constrained.Examples.CheatSheet

Associated Types

type SimpleRep FooBarBaz Source #

type TheSop FooBarBaz ∷ [Type] Source #

HasSimpleRep () Source # 
Instance details

Defined in Constrained.Base

Associated Types

type SimpleRep () Source #

type TheSop () ∷ [Type] Source #

Methods

toSimpleRep ∷ () → SimpleRep () Source #

fromSimpleRepSimpleRep () → () Source #

HasSimpleRep Bool Source # 
Instance details

Defined in Constrained.TheKnot

Associated Types

type SimpleRep Bool Source #

type TheSop Bool ∷ [Type] Source #

Methods

toSimpleRep ∷ Bool → SimpleRep Bool Source #

fromSimpleRepSimpleRep Bool → Bool Source #

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

Defined in Constrained.Examples.Set

Associated Types

type SimpleRep (NotASet a) Source #

type TheSop (NotASet a) ∷ [Type] Source #

Typeable a ⇒ HasSimpleRep (Maybe a) Source # 
Instance details

Defined in Constrained.Spec.SumProd

Associated Types

type SimpleRep (Maybe a) Source #

type TheSop (Maybe a) ∷ [Type] Source #

Methods

toSimpleRep ∷ Maybe a → SimpleRep (Maybe a) Source #

fromSimpleRepSimpleRep (Maybe a) → Maybe a Source #

(Typeable a, Typeable b) ⇒ HasSimpleRep (Either a b) Source # 
Instance details

Defined in Constrained.Spec.SumProd

Associated Types

type SimpleRep (Either a b) Source #

type TheSop (Either a b) ∷ [Type] Source #

Methods

toSimpleRep ∷ Either a b → SimpleRep (Either a b) Source #

fromSimpleRepSimpleRep (Either a b) → Either a b Source #

(Typeable a, Typeable b) ⇒ HasSimpleRep (a, b) Source # 
Instance details

Defined in Constrained.Spec.SumProd

Associated Types

type SimpleRep (a, b) Source #

type TheSop (a, b) ∷ [Type] Source #

Methods

toSimpleRep ∷ (a, b) → SimpleRep (a, b) Source #

fromSimpleRepSimpleRep (a, b) → (a, b) Source #

(Typeable a, Typeable b, Typeable c) ⇒ HasSimpleRep (a, b, c) Source # 
Instance details

Defined in Constrained.Spec.SumProd

Associated Types

type SimpleRep (a, b, c) Source #

type TheSop (a, b, c) ∷ [Type] Source #

Methods

toSimpleRep ∷ (a, b, c) → SimpleRep (a, b, c) Source #

fromSimpleRepSimpleRep (a, b, c) → (a, b, c) Source #

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

Defined in Constrained.Spec.SumProd

Associated Types

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

type TheSop (a, b, c, d) ∷ [Type] Source #

Methods

toSimpleRep ∷ (a, b, c, d) → SimpleRep (a, b, c, d) Source #

fromSimpleRepSimpleRep (a, b, c, d) → (a, b, c, d) Source #

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

Defined in Constrained.Spec.SumProd

Associated Types

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

type TheSop (a, b, c, d, e) ∷ [Type] Source #

Methods

toSimpleRep ∷ (a, b, c, d, e) → SimpleRep (a, b, c, d, e) Source #

fromSimpleRepSimpleRep (a, b, c, d, e) → (a, b, c, d, e) Source #

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

Defined in Constrained.Spec.SumProd

Associated Types

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

type TheSop (a, b, c, d, e, g) ∷ [Type] Source #

Methods

toSimpleRep ∷ (a, b, c, d, e, g) → SimpleRep (a, b, c, d, e, g) Source #

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

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

Defined in Constrained.Spec.SumProd

Associated Types

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

type TheSop (a, b, c, d, e, g, h) ∷ [Type] Source #

Methods

toSimpleRep ∷ (a, b, c, d, e, g, h) → SimpleRep (a, b, c, d, e, g, h) Source #

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

class (Ord a, HasSpec a) ⇒ OrdLike a where Source #

Minimal complete definition

Nothing

Instances

Instances details
(Ord a, HasSpec a, MaybeBounded a, Num a, TypeSpec a ~ NumSpec a) ⇒ OrdLike a Source #

This instance should be general enough for every type of Number that has a NumSpec as its TypeSpec

Instance details

Defined in Constrained.NumSpec

conformsToSpecE ∷ ∀ a. HasSpec a ⇒ a → Specification a → NonEmpty String → Maybe (NonEmpty String) Source #

conformsToSpec with explanation. Nothing if (conformsToSpec a spec), but (Just explanations) if not(conformsToSpec a spec).

conformsToSpecHasSpec a ⇒ a → Specification a → Bool Source #

satisfies ∷ ∀ a. HasSpec a ⇒ Term a → Specification a → Pred Source #

genFromSpecT ∷ ∀ a m. (HasCallStack, HasSpec a, MonadGenError m) ⇒ Specification a → GenT m a Source #

Generate a value that satisfies the spec. This function can fail if the spec is inconsistent, there is a dependency error, or if the underlying generators are not flexible enough.

genFromSpec ∷ ∀ a. (HasCallStack, HasSpec a) ⇒ Specification a → Gen a Source #

A version of genFromSpecT that simply errors if the generator fails

debugSpec ∷ ∀ a. HasSpec a ⇒ Specification a → IO () Source #

A version of genFromSpecT that runs in the IO monad. Good for debugging.

genFromSpecWithSeed ∷ ∀ a. (HasCallStack, HasSpec a) ⇒ Int → Int → Specification a → a Source #

A version of genFromSpecT that takes a seed and a size and gives you a result

cardinality ∷ ∀ a. (Number Integer, HasSpec a) ⇒ Specification a → Specification Integer Source #

Put some (admittedly loose bounds) on the number of solutions that genFromTypeSpec might return. For lots of types, there is no way to be very accurate. Here we lift the HasSpec methods cardinalTrueSpec and cardinalTypeSpec from (TypeSpec Integer) to (Specification Integer)

ifElse ∷ (IsPred p, IsPred q) ⇒ Term Bool → p → q → Pred Source #

If the `Specification Bool` doesn't constrain the boolean you will get a TrueSpec out.

whenTrue ∷ ∀ p. IsPred p ⇒ Term Bool → p → Pred Source #

simplifyTerm ∷ ∀ a. Term a → Term a Source #

Simplify a Term, if the Term is an App, apply the rewrite rules chosen by the (Logic sym t bs a) instance attached to the function witness f

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

assertExplainIsPred p ⇒ NonEmpty String → p → Pred Source #

assertIsPred p ⇒ p → Pred Source #

forAll ∷ (Forallable t a, HasSpec t, HasSpec a, IsPred p) ⇒ Term t → (Term a → p) → Pred Source #

exists ∷ ∀ a p. (HasSpec a, IsPred p) ⇒ ((∀ b. Term b → b) → GE a) → (Term a → p) → Pred Source #

unsafeExists ∷ ∀ a p. (HasSpec a, IsPred p) ⇒ (Term a → p) → Pred Source #

letBind ∷ (HasSpec a, IsPred p) ⇒ Term a → (Term a → p) → Pred Source #

reify ∷ (HasSpec a, HasSpec b, IsPred p) ⇒ Term a → (a → b) → (Term b → p) → Pred Source #

assertReified ∷ (HasSpec Bool, HasSpec a) ⇒ Term a → (a → Bool) → Pred Source #

requires (HasSpec Bool)

explanationNonEmpty String → PredPred Source #

Wrap an Explain around a Pred, unless there is a simpler form.

monitor ∷ ((∀ a. Term a → a) → PropertyProperty) → Pred Source #

Add QuickCheck monitoring (e.g. collect or counterexample) to a predicate. To use the monitoring in a property call monitorSpec on the Specification containing the monitoring and a value generated from the specification.

reifies ∷ (HasSpec a, HasSpec b) ⇒ Term b → Term a → (a → b) → Pred Source #

dependsOn ∷ (HasSpec a, HasSpec b) ⇒ Term a → Term b → Pred Source #

litHasSpec a ⇒ a → Term a Source #

genHint ∷ ∀ t. HasGenHint t ⇒ Hint t → Term t → Pred Source #

(<.) ∷ ∀ a. OrdLike a ⇒ Term a → Term a → Term Bool infixr 4 Source #

(<=.) ∷ ∀ a. OrdLike a ⇒ Term a → Term a → Term Bool infixr 4 Source #

(>=.) ∷ ∀ a. OrdLike a ⇒ Term a → Term a → Term Bool infixr 4 Source #

(>.) ∷ ∀ a. OrdLike a ⇒ Term a → Term a → Term Bool infixr 4 Source #

(==.)HasSpec a ⇒ Term a → Term a → Term Bool infix 4 Source #

(/=.)HasSpec a ⇒ Term a → Term a → Term Bool infix 4 Source #

not_Term Bool → Term Bool Source #

or_Term Bool → Term Bool → Term Bool Source #

(||.)Term Bool → Term Bool → Term Bool infixr 2 Source #

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

fromGeneric_ ∷ ∀ a. (GenericRequires a, AppRequires "fromGenericFn" BaseW '[SimpleRep a] a) ⇒ Term (SimpleRep a) → Term a Source #

(+.)NumLike a ⇒ Term a → Term a → Term a infix 4 Source #

(-.)Numeric n ⇒ Term n → Term n → Term n infix 4 Source #

negate_NumLike a ⇒ Term a → Term a Source #

addFn ∷ ∀ a. NumLike a ⇒ Term a → Term a → Term a Source #

negateFn ∷ ∀ a. NumLike a ⇒ Term a → Term a Source #

type Numeric a = (HasSpec a, Ord a, Num a, TypeSpec a ~ NumSpec a, MaybeBounded a) Source #

pair_ ∷ (HasSpec a, HasSpec b, IsNormalType a, IsNormalType b) ⇒ Term a → Term b → Term (a, b) Source #

fst_ ∷ (HasSpec x, HasSpec y) ⇒ Term (x, y) → Term x Source #

snd_ ∷ (HasSpec x, HasSpec y) ⇒ Term (x, y) → Term y Source #

prodSnd_ ∷ (HasSpec a, HasSpec b) ⇒ Term (Prod a b) → Term b Source #

prodFst_ ∷ (HasSpec a, HasSpec b) ⇒ Term (Prod a b) → Term a Source #

prod_ ∷ (HasSpec a, HasSpec b) ⇒ Term a → Term b → Term (Prod a b) Source #

type IsNormalType a = (Cases a ~ '[a], Args a ~ '[a], IsProd a, CountCases a ~ 1) Source #

leftFn ∷ (HasSpec a, HasSpec b, KnownNat (CountCases b)) ⇒ Term a → Term (Sum a b) Source #

rightFn ∷ (HasSpec a, HasSpec b, KnownNat (CountCases b)) ⇒ Term b → Term (Sum a b) Source #

left_ ∷ (HasSpec a, HasSpec b, IsNormalType a, IsNormalType b) ⇒ Term a → Term (Either a b) Source #

right_ ∷ (HasSpec a, HasSpec b, IsNormalType a, IsNormalType b) ⇒ Term b → Term (Either a b) Source #

cJust_ ∷ (HasSpec a, IsNormalType a) ⇒ Term a → Term (Maybe a) Source #

cNothing_ ∷ (HasSpec a, IsNormalType a) ⇒ Term (Maybe a) Source #

caseOn ∷ ∀ a. (HasSpec a, HasSpec (SimpleRep a), HasSimpleRep a, TypeSpec a ~ TypeSpec (SimpleRep a), SimpleRep a ~ SumOver (Cases (SimpleRep a)), TypeList (Cases (SimpleRep a))) ⇒ Term a → FunTy (MapList (Weighted Binder) (Cases (SimpleRep a))) Pred Source #

branch ∷ ∀ p a. (HasSpec a, All HasSpec (Args a), IsPred p, IsProd a) ⇒ FunTy (MapList Term (Args a)) p → Weighted Binder a Source #

branchW ∷ ∀ p a. (HasSpec a, All HasSpec (Args a), IsPred p, IsProd a) ⇒ Int → FunTy (MapList Term (Args a)) p → Weighted Binder a Source #

forAll' ∷ ∀ t a p. (Forallable t a, Cases (SimpleRep a) ~ '[SimpleRep a], TypeSpec a ~ TypeSpec (SimpleRep a), HasSpec t, HasSpec (SimpleRep a), HasSimpleRep a, All HasSpec (Args (SimpleRep a)), IsPred p, IsProd (SimpleRep a), HasSpec a) ⇒ Term t → FunTy (MapList Term (Args (SimpleRep a))) p → Pred Source #

Like forAll but pattern matches on the `Term a`

constrained' ∷ ∀ a p. (Cases (SimpleRep a) ~ '[SimpleRep a], TypeSpec a ~ TypeSpec (SimpleRep a), HasSpec (SimpleRep a), HasSimpleRep a, All HasSpec (Args (SimpleRep a)), IsProd (SimpleRep a), HasSpec a, IsPred p) ⇒ FunTy (MapList Term (Args (SimpleRep a))) p → Specification a Source #

Like constrained but pattern matches on the bound `Term a`

reify' ∷ ∀ a b p. (Cases (SimpleRep b) ~ '[SimpleRep b], TypeSpec b ~ TypeSpec (SimpleRep b), HasSpec (SimpleRep b), HasSimpleRep b, All HasSpec (Args (SimpleRep b)), IsProd (SimpleRep b), HasSpec a, HasSpec b, IsPred p) ⇒ Term a → (a → b) → FunTy (MapList Term (Args (SimpleRep b))) p → Pred Source #

Like reify but pattern matches on the bound `Term b`

con ∷ ∀ c a r. (SimpleRep a ~ SOP (TheSop a), TypeSpec a ~ TypeSpec (SOP (TheSop a)), TypeList (ConstrOf c (TheSop a)), HasSpec a, HasSimpleRep a, r ~ FunTy (MapList Term (ConstrOf c (TheSop a))) (Term a), ResultType r ~ Term a, SOPTerm c (TheSop a), ConstrTerm (ConstrOf c (TheSop a))) ⇒ r Source #

onCon ∷ ∀ c a p. (IsConstrOf c (ProdOver (ConstrOf c (TheSop a))) (TheSop a), TypeSpec a ~ TypeSpec (SimpleRep a), HasSimpleRep a, HasSpec a, HasSpec (SimpleRep a), SumOver (Cases (SOP (TheSop a))) ~ SimpleRep a, All HasSpec (Cases (SOP (TheSop a))), HasSpec (ProdOver (ConstrOf c (TheSop a))), IsPred p, Args (ProdOver (ConstrOf c (TheSop a))) ~ ConstrOf c (TheSop a), All HasSpec (ConstrOf c (TheSop a)), IsProd (ProdOver (ConstrOf c (TheSop a)))) ⇒ Term a → FunTy (MapList Term (ConstrOf c (TheSop a))) p → Pred Source #

isCon ∷ ∀ c a. (IsConstrOf c (ProdOver (ConstrOf c (TheSop a))) (TheSop a), TypeSpec a ~ TypeSpec (SimpleRep a), HasSimpleRep a, HasSpec a, HasSpec (SimpleRep a), SumOver (Cases (SOP (TheSop a))) ~ SimpleRep a, All HasSpec (Cases (SOP (TheSop a))), HasSpec (ProdOver (ConstrOf c (TheSop a)))) ⇒ Term a → Pred Source #

sel ∷ ∀ n a c as. (SimpleRep a ~ ProdOver as, TheSop a ~ '[c ::: as], TypeSpec a ~ TypeSpec (ProdOver as), Select n as, HasSpec a, HasSpec (ProdOver as), HasSimpleRep a) ⇒ Term a → Term (At n as) Source #

match ∷ ∀ p a. (HasSpec a, IsProductType a, IsPred p) ⇒ Term a → FunTy (MapList Term (ProductAsList a)) p → Pred Source #

onJust ∷ ∀ a p. (HasSpec a, IsNormalType a, IsPred p) ⇒ Term (Maybe a) → (Term a → p) → Pred Source #

isJust ∷ ∀ a. (HasSpec a, IsNormalType a) ⇒ Term (Maybe a) → Pred Source #

chooseSpecHasSpec a ⇒ (Int, Specification a) → (Int, Specification a) → Specification a Source #

ChooseSpec is one of the ways we can Or two Specs together This works for any kind of type that has a HasSpec instance. If your type is a Sum type. One can use CaseOn which is much easier.

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

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

id_ ∷ ∀ a. HasSpec a ⇒ Term a → Term a Source #

flip_ ∷ ∀ (t ∷ FSType) (sym ∷ Symbol) a b r. (HasSpec b, HasSpec a, HasSpec r, ∀ sym1 t1. Logic sym1 t1 '[a, b] r) ⇒ t sym '[a, b] r → Term b → Term a → Term r Source #

compose_ ∷ ∀ b s1 s2 t1 t2 a r. (AppRequires s1 t1 '[b] r, AppRequires s2 t2 '[a] b) ⇒ t1 s1 '[b] r → t2 s2 '[a] b → Term a → Term r Source #

foldMap_ ∷ ∀ a b. (Sized [a], Foldy b, HasSpec a) ⇒ (Term a → Term b) → Term [a] → Term b Source #

sum_Foldy a ⇒ Term [a] → Term a Source #

elem_ ∷ (Sized [a], HasSpec a) ⇒ Term a → Term [a] → Term Bool infix 4 Source #

singletonList_ ∷ (Sized [a], HasSpec a) ⇒ Term a → Term [a] Source #

append_ ∷ (Sized [a], HasSpec a) ⇒ Term [a] → Term [a] → Term [a] Source #

(++.)HasSpec a ⇒ Term [a] → Term [a] → Term [a] infixr 5 Source #

sizeOfSized t ⇒ t → Integer Source #

sizeOf_ ∷ (HasSpec t, Sized t) ⇒ Term t → Term Integer Source #

null_ ∷ (HasSpec a, Sized a) ⇒ Term a → Term Bool Source #

rangeSize ∷ Integer → Integer → SizeSpec Source #

length_HasSpec a ⇒ Term [a] → Term Integer Source #

genFromSizeSpecMonadGenError m ⇒ Specification Integer → GenT m Integer Source #

Because Sizes should always be >= 0, We provide this alternate generator that can be used to replace (genFromSpecT @Integer), to ensure this important property

between ∷ (HasSpec a, TypeSpec a ~ NumSpec a) ⇒ a → a → Specification a Source #

maxSpecSpecification Integer → Specification Integer Source #

The widest interval whose largest element is admitted by the original spec

data SetW (s ∷ Symbol) (d ∷ [Type]) (r ∷ Type) where Source #

Constructors

SingletonW ∷ Ord a ⇒ SetW "singleton_" '[a] (Set a) 
UnionW ∷ (Literal a, Ord a) ⇒ SetW "union_" '[Set a, Set a] (Set a) 
SubsetW ∷ (Literal a, Ord a) ⇒ SetW "subset_" '[Set a, Set a] Bool 
MemberW ∷ (Literal a, Ord a) ⇒ SetW "member_" '[a, Set a] Bool 
DisjointW ∷ (Literal a, Ord a) ⇒ SetW "disjoint_" '[Set a, Set a] Bool 
FromListW ∷ ∀ a. (HasSpec a, Ord a) ⇒ SetW "fromList_" '[[a]] (Set a) 

Instances

Instances details
Semantics SetW Source # 
Instance details

Defined in Constrained.Spec.Set

Methods

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

Syntax SetW Source # 
Instance details

Defined in Constrained.Spec.Set

Methods

isInFix ∷ ∀ (s ∷ Symbol) (dom ∷ [Type]) rng. SetW s dom rng → Bool Source #

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

(HasSpec a, Ord a) ⇒ Logic "disjoint_" SetW '[Set a, Set a] Bool Source # 
Instance details

Defined in Constrained.Spec.Set

Methods

infoSetW "disjoint_" '[Set a, Set a] Bool → String Source #

propagateContext "disjoint_" SetW '[Set a, Set a] Bool hole → Specification Bool → Specification hole Source #

rewriteRulesSetW "disjoint_" '[Set a, Set a] Bool → List Term '[Set a, Set a] → Evidence (AppRequires "disjoint_" SetW '[Set a, Set a] Bool) → Maybe (Term Bool) Source #

mapTypeSpec ∷ ('[Set a, Set a] ~ '[a0], Bool ~ b, HasSpec a0, HasSpec b) ⇒ SetW "disjoint_" '[a0] b → TypeSpec a0 → Specification b Source #

saturateSetW "disjoint_" '[Set a, Set a] Bool → List Term '[Set a, Set a] → [Pred] Source #

(HasSpec a, Ord a) ⇒ Logic "member_" SetW '[a, Set a] Bool Source # 
Instance details

Defined in Constrained.Spec.Set

Methods

infoSetW "member_" '[a, Set a] Bool → String Source #

propagateContext "member_" SetW '[a, Set a] Bool hole → Specification Bool → Specification hole Source #

rewriteRulesSetW "member_" '[a, Set a] Bool → List Term '[a, Set a] → Evidence (AppRequires "member_" SetW '[a, Set a] Bool) → Maybe (Term Bool) Source #

mapTypeSpec ∷ ('[a, Set a] ~ '[a0], Bool ~ b, HasSpec a0, HasSpec b) ⇒ SetW "member_" '[a0] b → TypeSpec a0 → Specification b Source #

saturateSetW "member_" '[a, Set a] Bool → List Term '[a, Set a] → [Pred] Source #

(HasSpec a, Ord a) ⇒ Logic "subset_" SetW '[Set a, Set a] Bool Source # 
Instance details

Defined in Constrained.Spec.Set

Methods

infoSetW "subset_" '[Set a, Set a] Bool → String Source #

propagateContext "subset_" SetW '[Set a, Set a] Bool hole → Specification Bool → Specification hole Source #

rewriteRulesSetW "subset_" '[Set a, Set a] Bool → List Term '[Set a, Set a] → Evidence (AppRequires "subset_" SetW '[Set a, Set a] Bool) → Maybe (Term Bool) Source #

mapTypeSpec ∷ ('[Set a, Set a] ~ '[a0], Bool ~ b, HasSpec a0, HasSpec b) ⇒ SetW "subset_" '[a0] b → TypeSpec a0 → Specification b Source #

saturateSetW "subset_" '[Set a, Set a] Bool → List Term '[Set a, Set a] → [Pred] Source #

(HasSpec a, Ord a) ⇒ Logic "fromList_" SetW '[[a]] (Set a) Source # 
Instance details

Defined in Constrained.Spec.Set

Methods

infoSetW "fromList_" '[[a]] (Set a) → String Source #

propagateContext "fromList_" SetW '[[a]] (Set a) hole → Specification (Set a) → Specification hole Source #

rewriteRulesSetW "fromList_" '[[a]] (Set a) → List Term '[[a]] → Evidence (AppRequires "fromList_" SetW '[[a]] (Set a)) → Maybe (Term (Set a)) Source #

mapTypeSpec ∷ ('[[a]] ~ '[a0], Set a ~ b, HasSpec a0, HasSpec b) ⇒ SetW "fromList_" '[a0] b → TypeSpec a0 → Specification b Source #

saturateSetW "fromList_" '[[a]] Bool → List Term '[[a]] → [Pred] Source #

(HasSpec a, Ord a) ⇒ Logic "singleton_" SetW '[a] (Set a) Source # 
Instance details

Defined in Constrained.Spec.Set

Methods

infoSetW "singleton_" '[a] (Set a) → String Source #

propagateContext "singleton_" SetW '[a] (Set a) hole → Specification (Set a) → Specification hole Source #

rewriteRulesSetW "singleton_" '[a] (Set a) → List Term '[a] → Evidence (AppRequires "singleton_" SetW '[a] (Set a)) → Maybe (Term (Set a)) Source #

mapTypeSpec ∷ ('[a] ~ '[a0], Set a ~ b, HasSpec a0, HasSpec b) ⇒ SetW "singleton_" '[a0] b → TypeSpec a0 → Specification b Source #

saturateSetW "singleton_" '[a] Bool → List Term '[a] → [Pred] Source #

(HasSpec a, Ord a) ⇒ Logic "union_" SetW '[Set a, Set a] (Set a) Source # 
Instance details

Defined in Constrained.Spec.Set

Methods

infoSetW "union_" '[Set a, Set a] (Set a) → String Source #

propagateContext "union_" SetW '[Set a, Set a] (Set a) hole → Specification (Set a) → Specification hole Source #

rewriteRulesSetW "union_" '[Set a, Set a] (Set a) → List Term '[Set a, Set a] → Evidence (AppRequires "union_" SetW '[Set a, Set a] (Set a)) → Maybe (Term (Set a)) Source #

mapTypeSpec ∷ ('[Set a, Set a] ~ '[a0], Set a ~ b, HasSpec a0, HasSpec b) ⇒ SetW "union_" '[a0] b → TypeSpec a0 → Specification b Source #

saturateSetW "union_" '[Set a, Set a] Bool → List Term '[Set a, Set a] → [Pred] Source #

Show (SetW s ds r) Source # 
Instance details

Defined in Constrained.Spec.Set

Methods

showsPrec ∷ Int → SetW s ds r → ShowS

showSetW s ds r → String

showList ∷ [SetW s ds r] → ShowS

Eq (SetW s dom rng) Source # 
Instance details

Defined in Constrained.Spec.Set

Methods

(==)SetW s dom rng → SetW s dom rng → Bool

(/=)SetW s dom rng → SetW s dom rng → Bool

data SetSpec a Source #

Constructors

SetSpec (Set a) (Specification a) (Specification Integer) 

Instances

Instances details
(Ord a, Arbitrary (Specification a), Arbitrary a) ⇒ Arbitrary (SetSpec a) Source # 
Instance details

Defined in Constrained.Spec.Set

Methods

arbitraryGen (SetSpec a) Source #

shrinkSetSpec a → [SetSpec a] Source #

(Ord a, HasSpec a) ⇒ Monoid (SetSpec a) Source # 
Instance details

Defined in Constrained.Spec.Set

Methods

memptySetSpec a

mappendSetSpec a → SetSpec a → SetSpec a

mconcat ∷ [SetSpec a] → SetSpec a

(Ord a, HasSpec a) ⇒ Semigroup (SetSpec a) Source # 
Instance details

Defined in Constrained.Spec.Set

Methods

(<>)SetSpec a → SetSpec a → SetSpec a #

sconcatNonEmpty (SetSpec a) → SetSpec a

stimes ∷ Integral b ⇒ b → SetSpec a → SetSpec a

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

Defined in Constrained.Spec.Set

Methods

showsPrec ∷ Int → SetSpec a → ShowS

showSetSpec a → String

showList ∷ [SetSpec a] → ShowS

singleton_ ∷ (Ord a, HasSpec a) ⇒ Term a → Term (Set a) Source #

member_ ∷ (Ord a, HasSpec a) ⇒ Term a → Term (Set a) → Term Bool Source #

union_ ∷ (Ord a, HasSpec a) ⇒ Term (Set a) → Term (Set a) → Term (Set a) Source #

subset_ ∷ (Ord a, HasSpec a) ⇒ Term (Set a) → Term (Set a) → Term Bool Source #

disjoint_ ∷ (Ord a, HasSpec a) ⇒ Term (Set a) → Term (Set a) → Term Bool Source #

fromList_ ∷ ∀ a. (Ord a, HasSpec a) ⇒ Term [a] → Term (Set a) Source #

pattern Equal ∷ ∀ b. () ⇒ ∀ a. (b ~ Bool, Eq a, HasSpec a) ⇒ Term a → Term a → Term b Source #

pattern Elem ∷ ∀ b. () ⇒ ∀ a. (b ~ Bool, Eq a, HasSpec a) ⇒ Term a → Term [a] → Term b Source #

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

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

pattern InjLeft ∷ ∀ c. () ⇒ ∀ a b. (c ~ Sum a b, AppRequires "leftFn" BaseW '[a] c) ⇒ Term a → Term c Source #

pattern InjRight ∷ ∀ c. () ⇒ ∀ a b. (c ~ Sum a b, AppRequires "rightFn" BaseW '[b] c) ⇒ Term b → Term c Source #

pattern ProdFst ∷ ∀ c. () ⇒ ∀ a b. (c ~ a, Typeable (Prod a b), HasSpec a, AppRequires "prodFst_" BaseW '[Prod a b] a) ⇒ Term (Prod a b) → Term c Source #

pattern ProdSnd ∷ ∀ c. () ⇒ ∀ a b. (c ~ b, Typeable (Prod a b), HasSpec b, AppRequires "prodSnd_" BaseW '[Prod a b] b) ⇒ Term (Prod a b) → Term c Source #

pattern Product ∷ ∀ c. () ⇒ ∀ a b. (c ~ Prod a b, AppRequires "prod_" BaseW '[a, b] c) ⇒ Term a → Term b → Term c Source #

printPlanHasSpec a ⇒ Specification a → IO () Source #

class (Num a, HasSpec a) ⇒ NumLike a Source #

Instances

Instances details
Numeric a ⇒ NumLike a Source # 
Instance details

Defined in Constrained.NumSpec

Methods

subtractSpec ∷ a → TypeSpec a → Specification a Source #

negateSpecTypeSpec a → Specification a Source #

safeSubtract ∷ a → a → Maybe a Source #

data PairSpec a b Source #

Constructors

Cartesian (Specification a) (Specification b) 

Instances

Instances details
(Arbitrary (Specification a), Arbitrary (Specification b)) ⇒ Arbitrary (PairSpec a b) Source # 
Instance details

Defined in Constrained.TheKnot

Methods

arbitraryGen (PairSpec a b) Source #

shrinkPairSpec a b → [PairSpec a b] Source #

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

Defined in Constrained.TheKnot

Methods

showsPrec ∷ Int → PairSpec a b → ShowS

showPairSpec a b → String

showList ∷ [PairSpec a b] → ShowS

data MapSpec k v Source #

Constructors

MapSpec 

Fields

Instances

Instances details
(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 #

(Arbitrary k, Arbitrary v, Arbitrary (TypeSpec k), Arbitrary (TypeSpec v), Ord k, HasSpec k, Foldy v) ⇒ Arbitrary (MapSpec k v) Source # 
Instance details

Defined in Constrained.Spec.Map

Methods

arbitraryGen (MapSpec k v) Source #

shrinkMapSpec k v → [MapSpec k v] Source #

Generic (MapSpec k v) Source # 
Instance details

Defined in Constrained.Spec.Map

Associated Types

type Rep (MapSpec k v) ∷ Type → Type

Methods

fromMapSpec k v → Rep (MapSpec k v) x

to ∷ Rep (MapSpec k v) x → MapSpec k v

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

Defined in Constrained.Spec.Map

Methods

showsPrec ∷ Int → MapSpec k v → ShowS

showMapSpec k v → String

showList ∷ [MapSpec k v] → ShowS

type Rep (MapSpec k v) Source # 
Instance details

Defined in Constrained.Spec.Map

type Rep (MapSpec k v) = D1 ('MetaData "MapSpec" "Constrained.Spec.Map" "constrained-generators-0.2.0.0-inplace" 'False) (C1 ('MetaCons "MapSpec" 'PrefixI 'True) ((S1 ('MetaSel ('Just "mapSpecHint") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Integer)) :*: (S1 ('MetaSel ('Just "mapSpecMustKeys") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Set k)) :*: S1 ('MetaSel ('Just "mapSpecMustValues") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [v]))) :*: (S1 ('MetaSel ('Just "mapSpecSize") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Specification Integer)) :*: (S1 ('MetaSel ('Just "mapSpecElem") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Specification (k, v))) :*: S1 ('MetaSel ('Just "mapSpecFold") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (FoldSpec v))))))

dom_ ∷ (HasSpec (Map k v), HasSpec v, HasSpec k, Ord k, IsNormalType k, IsNormalType v) ⇒ Term (Map k v) → Term (Set k) Source #

rng_ ∷ (HasSpec k, HasSpec v, Ord k, IsNormalType k, IsNormalType v) ⇒ Term (Map k v) → Term [v] Source #

lookup_ ∷ (HasSpec k, HasSpec v, Ord k, IsNormalType k, IsNormalType v) ⇒ Term k → Term (Map k v) → Term (Maybe v) Source #

fstSpec ∷ ∀ k v. (HasSpec k, HasSpec v) ⇒ Specification (k, v) → Specification k Source #

sndSpec ∷ ∀ k v. (HasSpec k, HasSpec v) ⇒ Specification (k, v) → Specification v Source #

var ∷ QuasiQuoter Source #

data Prod a b Source #

Constructors

Prod 

Fields

Instances

Instances details
(HasSpec a, HasSpec b) ⇒ Logic "prodFst_" BaseW '[Prod a b] a Source # 
Instance details

Defined in Constrained.TheKnot

Methods

infoBaseW "prodFst_" '[Prod a b] a → String Source #

propagateContext "prodFst_" BaseW '[Prod a b] a hole → Specification a → Specification hole Source #

rewriteRulesBaseW "prodFst_" '[Prod a b] a → List Term '[Prod a b] → Evidence (AppRequires "prodFst_" BaseW '[Prod a b] a) → Maybe (Term a) Source #

mapTypeSpec ∷ ('[Prod a b] ~ '[a0], a ~ b0, HasSpec a0, HasSpec b0) ⇒ BaseW "prodFst_" '[a0] b0 → TypeSpec a0 → Specification b0 Source #

saturateBaseW "prodFst_" '[Prod a b] Bool → List Term '[Prod a b] → [Pred] Source #

(HasSpec a, HasSpec b) ⇒ Logic "prodSnd_" BaseW '[Prod a b] b Source # 
Instance details

Defined in Constrained.TheKnot

Methods

infoBaseW "prodSnd_" '[Prod a b] b → String Source #

propagateContext "prodSnd_" BaseW '[Prod a b] b hole → Specification b → Specification hole Source #

rewriteRulesBaseW "prodSnd_" '[Prod a b] b → List Term '[Prod a b] → Evidence (AppRequires "prodSnd_" BaseW '[Prod a b] b) → Maybe (Term b) Source #

mapTypeSpec ∷ ('[Prod a b] ~ '[a0], b ~ b0, HasSpec a0, HasSpec b0) ⇒ BaseW "prodSnd_" '[a0] b0 → TypeSpec a0 → Specification b0 Source #

saturateBaseW "prodSnd_" '[Prod a b] Bool → List Term '[Prod a b] → [Pred] Source #

(HasSpec a, HasSpec b) ⇒ Logic "prod_" BaseW '[a, b] (Prod a b) Source # 
Instance details

Defined in Constrained.TheKnot

Methods

infoBaseW "prod_" '[a, b] (Prod a b) → String Source #

propagateContext "prod_" BaseW '[a, b] (Prod a b) hole → Specification (Prod a b) → Specification hole Source #

rewriteRulesBaseW "prod_" '[a, b] (Prod a b) → List Term '[a, b] → Evidence (AppRequires "prod_" BaseW '[a, b] (Prod a b)) → Maybe (Term (Prod a b)) Source #

mapTypeSpec ∷ ('[a, b] ~ '[a0], Prod a b ~ b0, HasSpec a0, HasSpec b0) ⇒ BaseW "prod_" '[a0] b0 → TypeSpec a0 → Specification b0 Source #

saturateBaseW "prod_" '[a, b] Bool → List Term '[a, b] → [Pred] Source #

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

Defined in Constrained.Generic

Methods

showsPrec ∷ Int → Prod a b → ShowS

showProd a b → String

showList ∷ [Prod a b] → ShowS

(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 #

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

Defined in Constrained.Generic

Methods

(==)Prod a b → Prod a b → Bool

(/=)Prod a b → Prod a b → Bool

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

Defined in Constrained.Generic

Methods

compareProd a b → Prod a b → Ordering

(<)Prod a b → Prod a b → Bool

(<=)Prod a b → Prod a b → Bool

(>)Prod a b → Prod a b → Bool

(>=)Prod a b → Prod a b → Bool

maxProd a b → Prod a b → Prod a b

minProd a b → Prod a b → Prod a b

type Prerequisites (Prod a b) Source # 
Instance details

Defined in Constrained.TheKnot

type Prerequisites (Prod a b) = (HasSpec a, HasSpec b)
type TypeSpec (Prod a b) Source # 
Instance details

Defined in Constrained.TheKnot

type TypeSpec (Prod a b) = PairSpec a b