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

Constrained.Spec.Generics

Synopsis

Documentation

data GenericsFn fn args res Source #

Instances

Instances details
FunctionLike (GenericsFn fn) Source # 
Instance details

Defined in Constrained.Spec.Generics

Methods

sem ∷ ∀ (as ∷ [Type]) b. GenericsFn fn as b → FunTy as b Source #

BaseUniverse fn ⇒ Functions (GenericsFn fn) fn Source # 
Instance details

Defined in Constrained.Spec.Generics

Methods

propagateSpecFun ∷ ∀ (as ∷ [Type]) a b. (TypeList as, Typeable as, HasSpec fn a, All (HasSpec fn) as) ⇒ GenericsFn fn as b → ListCtx Value as (HOLE a) → Specification fn b → Specification fn a Source #

rewriteRules ∷ ∀ (as ∷ [Type]) b. (TypeList as, Typeable as, HasSpec fn b, All (HasSpec fn) as) ⇒ GenericsFn fn as b → List (Term fn) as → Maybe (Term fn b) Source #

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

Show (GenericsFn fn as b) Source # 
Instance details

Defined in Constrained.Base

Methods

showsPrecIntGenericsFn fn as b → ShowS Source #

showGenericsFn fn as b → String Source #

showList ∷ [GenericsFn fn as b] → ShowS Source #

Eq (GenericsFn fn args res) Source # 
Instance details

Defined in Constrained.Base

Methods

(==)GenericsFn fn args res → GenericsFn fn args res → Bool Source #

(/=)GenericsFn fn args res → GenericsFn fn args res → Bool Source #

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

fst_ ∷ ∀ fn a b. (HasSpec fn a, HasSpec fn b) ⇒ Term fn (a, b) → Term fn a Source #

snd_ ∷ ∀ fn a b. (HasSpec fn a, HasSpec fn b) ⇒ Term fn (a, b) → Term fn b Source #

pair_ ∷ ∀ fn a b. (HasSpec fn a, HasSpec fn b) ⇒ Term fn a → Term fn b → Term fn (a, b) Source #

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

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

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

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

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

Like forAll but pattern matches on the `Term fn a`

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

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

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

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

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

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

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

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

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

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

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

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

Orphan instances

HasSpec fn a ⇒ HasSpec fn (Maybe a) Source # 
Instance details

Associated Types

type TypeSpec fn (Maybe a) Source #

type Prerequisites fn (Maybe a) Source #

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

Associated Types

type TypeSpec fn (Either a b) Source #

type Prerequisites fn (Either a b) Source #

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

Associated Types

type TypeSpec fn (a, b) Source #

type Prerequisites fn (a, b) Source #

Methods

emptySpecTypeSpec fn (a, b) Source #

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

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

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

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

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

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

cardinalTrueSpecSpecification fn Integer Source #

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

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

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

Associated Types

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

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

Methods

emptySpecTypeSpec fn (a, b, c) Source #

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

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

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

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

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

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

cardinalTrueSpecSpecification fn Integer Source #

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

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

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

Associated Types

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

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

Methods

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

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

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

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

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

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

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

cardinalTrueSpecSpecification fn Integer Source #

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

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

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

Associated Types

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

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

Methods

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

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

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

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

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

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

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

cardinalTrueSpecSpecification fn Integer Source #

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

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

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

Associated Types

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

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

Methods

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

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

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

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

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

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

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

cardinalTrueSpecSpecification fn Integer Source #

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

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

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

Associated Types

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

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

Methods

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

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

genFromTypeSpec ∷ ∀ (m ∷ TypeType). (HasCallStack, MonadGenError m) ⇒ TypeSpec fn (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 fn (a, b, c, d, e, g, h) → Bool Source #

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

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

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

cardinalTrueSpecSpecification fn Integer Source #

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

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

HasSimpleRep (Maybe a) Source # 
Instance details

Associated Types

type SimpleRep (Maybe a) Source #

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

FunctionLike (GenericsFn fn) Source # 
Instance details

Methods

sem ∷ ∀ (as ∷ [Type]) b. GenericsFn fn as b → FunTy as b Source #

BaseUniverse fn ⇒ Functions (GenericsFn fn) fn Source # 
Instance details

Methods

propagateSpecFun ∷ ∀ (as ∷ [Type]) a b. (TypeList as, Typeable as, HasSpec fn a, All (HasSpec fn) as) ⇒ GenericsFn fn as b → ListCtx Value as (HOLE a) → Specification fn b → Specification fn a Source #

rewriteRules ∷ ∀ (as ∷ [Type]) b. (TypeList as, Typeable as, HasSpec fn b, All (HasSpec fn) as) ⇒ GenericsFn fn as b → List (Term fn) as → Maybe (Term fn b) Source #

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

BaseUniverse fn ⇒ Functions (SumFn fn) fn Source # 
Instance details

Methods

propagateSpecFun ∷ ∀ (as ∷ [Type]) a b. (TypeList as, Typeable as, HasSpec fn a, All (HasSpec fn) as) ⇒ SumFn fn as b → ListCtx Value as (HOLE a) → Specification fn b → Specification fn a Source #

rewriteRules ∷ ∀ (as ∷ [Type]) b. (TypeList as, Typeable as, HasSpec fn b, All (HasSpec fn) as) ⇒ SumFn fn as b → List (Term fn) as → Maybe (Term fn b) Source #

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

(HasSpec fn a, HasSpec fn b, Arbitrary (FoldSpec fn a), Arbitrary (FoldSpec fn b)) ⇒ Arbitrary (FoldSpec fn (a, b)) Source # 
Instance details

Methods

arbitraryGen (FoldSpec fn (a, b)) Source #

shrinkFoldSpec fn (a, b) → [FoldSpec fn (a, b)] Source #

HasSimpleRep (Either a b) Source # 
Instance details

Associated Types

type SimpleRep (Either a b) Source #

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

HasSimpleRep (a, b) Source # 
Instance details

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 #

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

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 #

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

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 #

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

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 #

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

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 #

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

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 #