plutus-use-cases-1.2.0.0: Collection of smart contracts to develop the plutus/wallet interface
Safe HaskellNone
LanguageHaskell2010

Plutus.Contracts.Tutorial.EscrowStrict

Description

A general-purpose escrow contract in Plutus

Synopsis

Documentation

The escrow contract implements the exchange of value between multiple parties. It is defined by a list of targets (public keys and script addresses, each associated with a value). It works similar to the crowdfunding contract in that the contributions can be made independently, and the funds can be unlocked only by a transaction that pays the correct amount to each target. A refund is possible if the outputs locked by the contract have not been spent by the deadline. (Compared to the crowdfunding contract, the refund policy is simpler because here because there is no "collection period" during which the outputs may be spent after the deadline has passed. This is because we're assuming that the participants in the escrow contract will make their deposits as quickly as possible after agreeing on a deal)

The contract supports two modes of operation, manual and automatic. In manual mode, all actions are driven by endpoints that exposed via payEp redeemEp and refundEp. In automatic mode, the pay, redeem and refundactions start immediately. This mode is useful when the escrow is called from within another contract, for example during setup (collection of the initial deposits).

data Escrow Source #

Instances

Instances details
ValidatorTypes Escrow Source # 
Instance details

Defined in Plutus.Contracts.Tutorial.EscrowStrict

Associated Types

type RedeemerType Escrow

type DatumType Escrow

type DatumType Escrow Source # 
Instance details

Defined in Plutus.Contracts.Tutorial.EscrowStrict

type DatumType Escrow = PaymentPubKeyHash
type RedeemerType Escrow Source # 
Instance details

Defined in Plutus.Contracts.Tutorial.EscrowStrict

type RedeemerType Escrow = Action

data EscrowError Source #

Instances

Instances details
Show EscrowError Source # 
Instance details

Defined in Plutus.Contracts.Tutorial.EscrowStrict

Generic EscrowError Source # 
Instance details

Defined in Plutus.Contracts.Tutorial.EscrowStrict

Associated Types

type Rep EscrowError :: Type -> Type Source #

FromJSON EscrowError Source # 
Instance details

Defined in Plutus.Contracts.Tutorial.EscrowStrict

Methods

parseJSON :: Value -> Parser EscrowError

parseJSONList :: Value -> Parser [EscrowError]

ToJSON EscrowError Source # 
Instance details

Defined in Plutus.Contracts.Tutorial.EscrowStrict

Methods

toJSON :: EscrowError -> Value

toEncoding :: EscrowError -> Encoding

toJSONList :: [EscrowError] -> Value

toEncodingList :: [EscrowError] -> Encoding

AsContractError EscrowError Source # 
Instance details

Defined in Plutus.Contracts.Tutorial.EscrowStrict

Methods

_ContractError :: Prism' EscrowError ContractError

_WalletContractError :: Prism' EscrowError WalletAPIError

_ChainIndexContractError :: Prism' EscrowError (Text, ChainIndexResponse)

_ConstraintResolutionContractError :: Prism' EscrowError MkTxError

_ToCardanoConvertContractError :: Prism' EscrowError ToCardanoError

_ResumableContractError :: Prism' EscrowError MatchingError

_CCheckpointContractError :: Prism' EscrowError CheckpointError

_EndpointDecodeContractError :: Prism' EscrowError (EndpointDescription, EndpointValue Value, Text)

_OtherContractError :: Prism' EscrowError Text

AsEscrowError EscrowError Source # 
Instance details

Defined in Plutus.Contracts.Tutorial.EscrowStrict

type Rep EscrowError Source # 
Instance details

Defined in Plutus.Contracts.Tutorial.EscrowStrict

type Rep EscrowError = D1 ('MetaData "EscrowError" "Plutus.Contracts.Tutorial.EscrowStrict" "plutus-use-cases-1.2.0.0-BuYOLXrynPcLosE012cowc" 'False) (C1 ('MetaCons "RedeemFailed" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 RedeemFailReason)) :+: (C1 ('MetaCons "RefundFailed" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "EContractError" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ContractError))))

class AsEscrowError r where Source #

Minimal complete definition

_EscrowError

Methods

_EscrowError :: Prism' r EscrowError Source #

_RedeemFailed :: Prism' r RedeemFailReason Source #

_RefundFailed :: Prism' r () Source #

_EContractError :: Prism' r ContractError Source #

data EscrowParams d Source #

Definition of an escrow contract, consisting of a deadline and a list of targets

Constructors

EscrowParams 

Fields

  • escrowTargets :: [EscrowTarget d]

    Where the money should go. For each target, the contract checks that the output mkTxOutput of the target is present in the spending transaction.

Instances

Instances details
Functor EscrowParams Source # 
Instance details

Defined in Plutus.Contracts.Tutorial.EscrowStrict

Methods

fmap :: (a -> b) -> EscrowParams a -> EscrowParams b Source #

(<$) :: a -> EscrowParams b -> EscrowParams a Source #

(Typeable DefaultUni d, Lift DefaultUni [EscrowTarget d]) => Lift DefaultUni (EscrowParams d) Source # 
Instance details

Defined in Plutus.Contracts.Tutorial.EscrowStrict

Methods

lift :: EscrowParams d -> RTCompile DefaultUni fun (Term TyName Name DefaultUni fun ())

Typeable DefaultUni EscrowParams Source # 
Instance details

Defined in Plutus.Contracts.Tutorial.EscrowStrict

Methods

typeRep :: Proxy EscrowParams -> RTCompile DefaultUni fun (Type TyName DefaultUni ())

data EscrowTarget d Source #

Defines where the money should go. Usually we have `d = Datum` (when defining EscrowTarget values in off-chain code). Sometimes we have `d = DatumHash` (when checking the hashes in on-chain code)

Constructors

PaymentPubKeyTarget PaymentPubKeyHash Value 
ScriptTarget ValidatorHash d Value 

Instances

Instances details
Functor EscrowTarget Source # 
Instance details

Defined in Plutus.Contracts.Tutorial.EscrowStrict

Methods

fmap :: (a -> b) -> EscrowTarget a -> EscrowTarget b Source #

(<$) :: a -> EscrowTarget b -> EscrowTarget a Source #

(Typeable DefaultUni d, Lift DefaultUni d) => Lift DefaultUni (EscrowTarget d) Source # 
Instance details

Defined in Plutus.Contracts.Tutorial.EscrowStrict

Methods

lift :: EscrowTarget d -> RTCompile DefaultUni fun (Term TyName Name DefaultUni fun ())

Typeable DefaultUni EscrowTarget Source # 
Instance details

Defined in Plutus.Contracts.Tutorial.EscrowStrict

Methods

typeRep :: Proxy EscrowTarget -> RTCompile DefaultUni fun (Type TyName DefaultUni ())

payToScriptTarget :: ValidatorHash -> Datum -> Value -> EscrowTarget Datum Source #

An EscrowTarget that pays the value to a script address, with the given data script.

payToPaymentPubKeyTarget :: PaymentPubKeyHash -> Value -> EscrowTarget d Source #

An EscrowTarget that pays the value to a public key address.

targetTotal :: EscrowParams d -> Value Source #

The total Value that must be paid into the escrow contract before it can be unlocked

typedValidator :: EscrowParams Datum -> TypedValidator Escrow Source #

Actions

pay Source #

Arguments

:: forall w s e. AsContractError e 
=> TypedValidator Escrow

The instance

-> EscrowParams Datum

The escrow contract

-> Value

How much money to pay in

-> Contract w s e TxId 

Pay some money into the escrow contract.

payEp :: forall w s e. (HasEndpoint "pay-escrow" Value s, AsEscrowError e) => EscrowParams Datum -> Promise w s e TxId Source #

pay with an endpoint that gets the owner's public key and the contribution.

redeem :: forall w s e. AsEscrowError e => TypedValidator Escrow -> EscrowParams Datum -> Contract w s e RedeemSuccess Source #

Redeem all outputs at the contract address using a transaction that has all the outputs defined in the contract's list of targets.

redeemEp :: forall w s e. (HasEndpoint "redeem-escrow" () s, AsEscrowError e) => EscrowParams Datum -> Promise w s e RedeemSuccess Source #

redeem with an endpoint.

refund :: forall w s. TypedValidator Escrow -> EscrowParams Datum -> Contract w s EscrowError RefundSuccess Source #

Claim a refund of the contribution.

refundEp :: forall w s. HasEndpoint "refund-escrow" () s => EscrowParams Datum -> Promise w s EscrowError RefundSuccess Source #

refund with an endpoint.

data RedeemFailReason Source #

Instances

Instances details
Eq RedeemFailReason Source # 
Instance details

Defined in Plutus.Contracts.Tutorial.EscrowStrict

Show RedeemFailReason Source # 
Instance details

Defined in Plutus.Contracts.Tutorial.EscrowStrict

Generic RedeemFailReason Source # 
Instance details

Defined in Plutus.Contracts.Tutorial.EscrowStrict

Associated Types

type Rep RedeemFailReason :: Type -> Type Source #

FromJSON RedeemFailReason Source # 
Instance details

Defined in Plutus.Contracts.Tutorial.EscrowStrict

Methods

parseJSON :: Value -> Parser RedeemFailReason

parseJSONList :: Value -> Parser [RedeemFailReason]

ToJSON RedeemFailReason Source # 
Instance details

Defined in Plutus.Contracts.Tutorial.EscrowStrict

type Rep RedeemFailReason Source # 
Instance details

Defined in Plutus.Contracts.Tutorial.EscrowStrict

type Rep RedeemFailReason = D1 ('MetaData "RedeemFailReason" "Plutus.Contracts.Tutorial.EscrowStrict" "plutus-use-cases-1.2.0.0-BuYOLXrynPcLosE012cowc" 'False) (C1 ('MetaCons "DeadlinePassed" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "NotEnoughFundsAtAddress" 'PrefixI 'False) (U1 :: Type -> Type))

type EscrowSchema = (Endpoint "pay-escrow" Value .\/ Endpoint "redeem-escrow" ()) .\/ Endpoint "refund-escrow" () Source #

Exposed for test endpoints

data Action Source #

Constructors

Redeem 
Refund 

Instances

Instances details
ToData Action Source # 
Instance details

Defined in Plutus.Contracts.Tutorial.EscrowStrict

Methods

toBuiltinData :: Action -> BuiltinData

FromData Action Source # 
Instance details

Defined in Plutus.Contracts.Tutorial.EscrowStrict

Methods

fromBuiltinData :: BuiltinData -> Maybe Action

UnsafeFromData Action Source # 
Instance details

Defined in Plutus.Contracts.Tutorial.EscrowStrict

Methods

unsafeFromBuiltinData :: BuiltinData -> Action

Lift DefaultUni Action Source # 
Instance details

Defined in Plutus.Contracts.Tutorial.EscrowStrict

Methods

lift :: Action -> RTCompile DefaultUni fun (Term TyName Name DefaultUni fun ())

Typeable DefaultUni Action Source # 
Instance details

Defined in Plutus.Contracts.Tutorial.EscrowStrict

Methods

typeRep :: Proxy Action -> RTCompile DefaultUni fun (Type TyName DefaultUni ())