quickcheck-contractmodel-0.1.4.1
Safe HaskellNone
LanguageHaskell2010

Test.QuickCheck.ContractModel.Internal.Symbolics

Synopsis

Documentation

data SymIndexF f Source #

Constructors

SymIndex 

Fields

Instances

Instances details
Semigroup SymCollectionIndex Source # 
Instance details

Defined in Test.QuickCheck.ContractModel.Internal.Symbolics

Semigroup SymCreationIndex Source # 
Instance details

Defined in Test.QuickCheck.ContractModel.Internal.Symbolics

Semigroup SymIndex Source # 
Instance details

Defined in Test.QuickCheck.ContractModel.Internal.Symbolics

Monad m => MonadWriter SymIndex (RunMonad m) 
Instance details

Defined in Test.QuickCheck.ContractModel.Internal

Methods

writer :: (a, SymIndex) -> RunMonad m a

tell :: SymIndex -> RunMonad m ()

listen :: RunMonad m a -> RunMonad m (a, SymIndex)

pass :: RunMonad m (a, SymIndex -> SymIndex) -> RunMonad m a

AllBF Eq f SymIndexF => Eq (SymIndexF f) Source # 
Instance details

Defined in Test.QuickCheck.ContractModel.Internal.Symbolics

AllBF Show f SymIndexF => Show (SymIndexF f) Source # 
Instance details

Defined in Test.QuickCheck.ContractModel.Internal.Symbolics

Generic (SymIndexF f) Source # 
Instance details

Defined in Test.QuickCheck.ContractModel.Internal.Symbolics

Associated Types

type Rep (SymIndexF f) :: Type -> Type Source #

Methods

from :: SymIndexF f -> Rep (SymIndexF f) x Source #

to :: Rep (SymIndexF f) x -> SymIndexF f Source #

(AllBF Monoid f SymIndexF, Semigroup (SymIndexF f)) => Monoid (SymIndexF f) Source # 
Instance details

Defined in Test.QuickCheck.ContractModel.Internal.Symbolics

ConstraintsB SymIndexF Source # 
Instance details

Defined in Test.QuickCheck.ContractModel.Internal.Symbolics

Associated Types

type AllB c SymIndexF

Methods

baddDicts :: forall (c :: k -> Constraint) (f :: k -> Type). AllB c SymIndexF => SymIndexF f -> SymIndexF (Product (Dict c) f)

FunctorB SymIndexF Source # 
Instance details

Defined in Test.QuickCheck.ContractModel.Internal.Symbolics

Methods

bmap :: (forall (a :: k). f a -> g a) -> SymIndexF f -> SymIndexF g

ApplicativeB SymIndexF Source # 
Instance details

Defined in Test.QuickCheck.ContractModel.Internal.Symbolics

Methods

bpure :: (forall (a :: k). f a) -> SymIndexF f

bprod :: forall (f :: k -> Type) (g :: k -> Type). SymIndexF f -> SymIndexF g -> SymIndexF (Product f g)

TraversableB SymIndexF Source # 
Instance details

Defined in Test.QuickCheck.ContractModel.Internal.Symbolics

Methods

btraverse :: Applicative e => (forall (a :: k). f a -> e (g a)) -> SymIndexF f -> e (SymIndexF g)

type Rep (SymIndexF f) Source # 
Instance details

Defined in Test.QuickCheck.ContractModel.Internal.Symbolics

type Rep (SymIndexF f) = D1 ('MetaData "SymIndexF" "Test.QuickCheck.ContractModel.Internal.Symbolics" "quickcheck-contractmodel-0.1.4.1-3bqn4RrQanG11zXTiHDaXF" 'False) (C1 ('MetaCons "SymIndex" 'PrefixI 'True) (S1 ('MetaSel ('Just "_tokens") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (f AssetId)) :*: (S1 ('MetaSel ('Just "_utxos") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (f (TxOut CtxUTxO Era))) :*: S1 ('MetaSel ('Just "_txIns") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (f TxIn)))))
type AllB (c :: Type -> Constraint) SymIndexF Source # 
Instance details

Defined in Test.QuickCheck.ContractModel.Internal.Symbolics

type AllB (c :: Type -> Constraint) SymIndexF = GAll 0 c (GAllRepB SymIndexF)

utxos :: forall f. Lens' (SymIndexF f) (f (TxOut CtxUTxO Era)) Source #

txIns :: forall f. Lens' (SymIndexF f) (f TxIn) Source #

tokens :: forall f. Lens' (SymIndexF f) (f AssetId) Source #

class HasSymbolicRep t where Source #

Methods

symIndexL :: Lens' (SymIndexF f) (f t) Source #

symPrefix :: String Source #

Instances

Instances details
HasSymbolicRep TxIn Source # 
Instance details

Defined in Test.QuickCheck.ContractModel.Internal.Symbolics

Methods

symIndexL :: forall (f :: Type -> Type). Lens' (SymIndexF f) (f TxIn) Source #

symPrefix :: String Source #

HasSymbolicRep AssetId Source # 
Instance details

Defined in Test.QuickCheck.ContractModel.Internal.Symbolics

Methods

symIndexL :: forall (f :: Type -> Type). Lens' (SymIndexF f) (f AssetId) Source #

symPrefix :: String Source #

HasSymbolicRep (TxOut CtxUTxO Era) Source # 
Instance details

Defined in Test.QuickCheck.ContractModel.Internal.Symbolics

Methods

symIndexL :: forall (f :: Type -> Type). Lens' (SymIndexF f) (f (TxOut CtxUTxO Era)) Source #

symPrefix :: String Source #

bmapConst :: FunctorB b => (forall a. f a -> c) -> b f -> Container b c Source #

mappendSymIndexF :: forall f. (AllBF Semigroup f SymIndexF, Show (SymIndexF f)) => (forall a. f a -> Set String) -> SymIndexF f -> SymIndexF f -> SymIndexF f Source #

type SymIndex = SymIndexF (Map String) Source #

For an assumed variable, what's the mapping of String indices to underlying actual values. This is what is returned by a contract model action when it runs.

type SymCreationIndex = SymIndexF (Const (Set String)) Source #

For a given action, what are the String indices used to construct symbolic variables when this action ran. NOTE: this purposefully does not include the variable because we might want to fake the variable with `Var 0` in some cases. See comment somewhere for why this is safe...

type SymCollectionIndex = SymIndexF SymSet Source #

What symbolic variables have been created in a given run of the Spec monad?

newtype SymSet t Source #

Constructors

SymSet 

Fields

Instances

Instances details
Semigroup SymCollectionIndex Source # 
Instance details

Defined in Test.QuickCheck.ContractModel.Internal.Symbolics

Show (Symbolic t) => Show (SymSet t) Source # 
Instance details

Defined in Test.QuickCheck.ContractModel.Internal.Symbolics

Generic (SymSet t) Source # 
Instance details

Defined in Test.QuickCheck.ContractModel.Internal.Symbolics

Associated Types

type Rep (SymSet t) :: Type -> Type Source #

Methods

from :: SymSet t -> Rep (SymSet t) x Source #

to :: Rep (SymSet t) x -> SymSet t Source #

Semigroup (SymSet t) Source # 
Instance details

Defined in Test.QuickCheck.ContractModel.Internal.Symbolics

Methods

(<>) :: SymSet t -> SymSet t -> SymSet t Source #

sconcat :: NonEmpty (SymSet t) -> SymSet t Source #

stimes :: Integral b => b -> SymSet t -> SymSet t Source #

Monoid (SymSet t) Source # 
Instance details

Defined in Test.QuickCheck.ContractModel.Internal.Symbolics

type Rep (SymSet t) Source # 
Instance details

Defined in Test.QuickCheck.ContractModel.Internal.Symbolics

type Rep (SymSet t) = D1 ('MetaData "SymSet" "Test.QuickCheck.ContractModel.Internal.Symbolics" "quickcheck-contractmodel-0.1.4.1-3bqn4RrQanG11zXTiHDaXF" 'True) (C1 ('MetaCons "SymSet" 'PrefixI 'True) (S1 ('MetaSel ('Just "unSymSet") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Set (Symbolic t)))))

data Symbolic t Source #

Constructors

Symbolic 

Fields

Instances

Instances details
TokenLike SymToken Source # 
Instance details

Defined in Test.QuickCheck.ContractModel.Internal.Symbolics

Eq (Symbolic t) Source # 
Instance details

Defined in Test.QuickCheck.ContractModel.Internal.Symbolics

Methods

(==) :: Symbolic t -> Symbolic t -> Bool Source #

(/=) :: Symbolic t -> Symbolic t -> Bool Source #

Ord (Symbolic t) Source # 
Instance details

Defined in Test.QuickCheck.ContractModel.Internal.Symbolics

HasSymbolicRep t => Show (Symbolic t) Source # 
Instance details

Defined in Test.QuickCheck.ContractModel.Internal.Symbolics

HasVariables (Symbolic t) Source # 
Instance details

Defined in Test.QuickCheck.ContractModel.Internal.Symbolics

Methods

getAllVariables :: Symbolic t -> Set (Any Var)

HasSymbolicRep t => HasSymbolics (Symbolic t) Source # 
Instance details

Defined in Test.QuickCheck.ContractModel.Internal.Model

type SymbolicSemantics = forall t. HasSymbolicRep t => Symbolic t -> t Source #

type SymToken = Symbolic AssetId Source #

A symbolic token is a token that is only available at runtime

type SymTxOut = Symbolic (TxOut CtxUTxO Era) Source #

A SymTxOut is a `TxOut CtxUTxO Era` that is only available at runtime

type SymTxIn = Symbolic TxIn Source #

A SymTxIn is a TxIn that is only available at runtime

data SymValue Source #

A symbolic value is a combination of a real value and a value associating symbolic tokens with an amount

Constructors

SymValue 

Fields

Instances

Instances details
Eq SymValue Source # 
Instance details

Defined in Test.QuickCheck.ContractModel.Internal.Symbolics

Show SymValue Source # 
Instance details

Defined in Test.QuickCheck.ContractModel.Internal.Symbolics

Generic SymValue Source # 
Instance details

Defined in Test.QuickCheck.ContractModel.Internal.Symbolics

Associated Types

type Rep SymValue :: Type -> Type Source #

Semigroup SymValue Source # 
Instance details

Defined in Test.QuickCheck.ContractModel.Internal.Symbolics

Monoid SymValue Source # 
Instance details

Defined in Test.QuickCheck.ContractModel.Internal.Symbolics

Pretty SymValue Source # 
Instance details

Defined in Test.QuickCheck.ContractModel.Internal.Symbolics

SymValueLike SymValue Source # 
Instance details

Defined in Test.QuickCheck.ContractModel.Internal.Symbolics

type Rep SymValue Source # 
Instance details

Defined in Test.QuickCheck.ContractModel.Internal.Symbolics

type Rep SymValue = D1 ('MetaData "SymValue" "Test.QuickCheck.ContractModel.Internal.Symbolics" "quickcheck-contractmodel-0.1.4.1-3bqn4RrQanG11zXTiHDaXF" 'False) (C1 ('MetaCons "SymValue" 'PrefixI 'True) (S1 ('MetaSel ('Just "symValMap") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Map SymToken Quantity)) :*: S1 ('MetaSel ('Just "actualValPart") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Value)))

pPrintValue :: Value -> Doc Source #

pPrintAssetId :: AssetId -> Doc Source #

symIsZero :: SymValue -> Bool Source #

Check if a symbolic value is zero

symLeq :: SymValue -> SymValue -> Bool Source #

Check if one symbolic value is less than or equal to another

toValue :: (SymToken -> AssetId) -> SymValue -> Value Source #

Using a semantics function for symbolic tokens, convert a SymValue to a Value

toSymVal :: (AssetId -> Maybe SymToken) -> Value -> SymValue Source #

Invert a sym token mapping to turn a Value into a SymValue, useful for error reporting

class SymValueLike v where Source #

Methods

toSymValue :: v -> SymValue Source #

Instances

Instances details
SymValueLike Value Source # 
Instance details

Defined in Test.QuickCheck.ContractModel.Internal.Symbolics

Methods

toSymValue :: Value -> SymValue Source #

SymValueLike SymValue Source # 
Instance details

Defined in Test.QuickCheck.ContractModel.Internal.Symbolics

class TokenLike t where Source #

Methods

symAssetIdValueOf :: SymValue -> t -> Quantity Source #

Get the value of a specific token in a SymValue

symAssetIdValue :: t -> Quantity -> SymValue Source #

Convert a token and an amount to a SymValue

Instances

Instances details
TokenLike AssetId Source # 
Instance details

Defined in Test.QuickCheck.ContractModel.Internal.Symbolics

Methods

symAssetIdValueOf :: SymValue -> AssetId -> Quantity Source #

symAssetIdValue :: AssetId -> Quantity -> SymValue Source #

TokenLike SymToken Source # 
Instance details

Defined in Test.QuickCheck.ContractModel.Internal.Symbolics