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

Constrained.Core

Documentation

data Var a Source #

Constructors

Var 

Fields

Instances

Instances details
Show (Var a) Source # 
Instance details

Defined in Constrained.Core

Methods

showsPrec ∷ Int → Var a → ShowS

showVar a → String

showList ∷ [Var a] → ShowS

Typeable a ⇒ Rename (Var a) Source # 
Instance details

Defined in Constrained.Core

Methods

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

Eq (Var a) Source # 
Instance details

Defined in Constrained.Core

Methods

(==)Var a → Var a → Bool

(/=)Var a → Var a → Bool

Ord (Var a) Source # 
Instance details

Defined in Constrained.Core

Methods

compareVar a → Var a → Ordering

(<)Var a → Var a → Bool

(<=)Var a → Var a → Bool

(>)Var a → Var a → Bool

(>=)Var a → Var a → Bool

maxVar a → Var a → Var a

minVar a → Var a → Var a

Pretty (Var a) Source # 
Instance details

Defined in Constrained.Syntax

Methods

prettyVar a → Doc ann Source #

prettyList ∷ [Var a] → Doc ann Source #

eqVar ∷ ∀ a a'. (Typeable a, Typeable a') ⇒ Var a → Var a' → Maybe (a :~: a') Source #

class Rename a where Source #

Methods

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

Instances

Instances details
Rename Pred Source # 
Instance details

Defined in Constrained.Syntax

Methods

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

Rename Name Source # 
Instance details

Defined in Constrained.Syntax

Methods

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

Rename () Source # 
Instance details

Defined in Constrained.Core

Methods

rename ∷ Typeable x ⇒ Var x → Var x → () → () Source #

Rename (Binder a) Source # 
Instance details

Defined in Constrained.Syntax

Methods

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

Rename (Term a) Source # 
Instance details

Defined in Constrained.Syntax

Methods

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

Typeable a ⇒ Rename (Var a) Source # 
Instance details

Defined in Constrained.Core

Methods

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

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

Defined in Constrained.Core

Methods

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

(Functor t, Rename a) ⇒ Rename (t a) Source # 
Instance details

Defined in Constrained.Core

Methods

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

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

Defined in Constrained.Core

Methods

rename ∷ Typeable x ⇒ Var x → Var x → (a, b) → (a, b) Source #

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

Defined in Constrained.Syntax

Methods

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

(∀ a. Rename (f a)) ⇒ Rename (List f as) Source # 
Instance details

Defined in Constrained.Core

Methods

rename ∷ Typeable x ⇒ Var x → Var x → List f as → List f as Source #

freshVarVar a → Set Int → Var a Source #

freshen ∷ (Typeable a, Rename t) ⇒ Var a → t → Set Int → (Var a, t) Source #

data Value a where Source #

Constructors

Value ∷ Show a ⇒ !a → Value a 

Instances

Instances details
Show (Value a) Source # 
Instance details

Defined in Constrained.Core

Methods

showsPrec ∷ Int → Value a → ShowS

showValue a → String

showList ∷ [Value a] → ShowS

Eq a ⇒ Eq (Value a) Source # 
Instance details

Defined in Constrained.Core

Methods

(==)Value a → Value a → Bool

(/=)Value a → Value a → Bool

Ord a ⇒ Ord (Value a) Source # 
Instance details

Defined in Constrained.Core

Methods

compareValue a → Value a → Ordering

(<)Value a → Value a → Bool

(<=)Value a → Value a → Bool

(>)Value a → Value a → Bool

(>=)Value a → Value a → Bool

maxValue a → Value a → Value a

minValue a → Value a → Value a

unValueValue a → a 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 Evidence c where Source #

Constructors

Evidence ∷ c ⇒ Evidence c 

Instances

Instances details
Typeable c ⇒ Show (Evidence c) 
Instance details

Defined in Constrained.Base

Methods

showsPrec ∷ Int → Evidence c → ShowS

showEvidence c → String

showList ∷ [Evidence c] → ShowS

unionWithMaybe ∷ (a → a → a) → Maybe a → Maybe a → Maybe a Source #

Orphan instances

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