{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DeriveAnyClass #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DerivingStrategies #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE MonoLocalBinds #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE ViewPatterns #-}
{-# OPTIONS_GHC -fno-ignore-interface-pragmas #-}
{-# OPTIONS_GHC -fno-omit-interface-pragmas #-}
{-# OPTIONS_GHC -fno-specialise #-}
module Plutus.Contracts.MultiSigStateMachine(
Params(..)
, Payment(..)
, State
, mkValidator
, typedValidator
, MultiSigError(..)
, MultiSigSchema
, contract
) where
import Control.Lens (makeClassyPrisms)
import Control.Monad (forever, void)
import Data.Aeson (FromJSON, ToJSON)
import GHC.Generics (Generic)
import Ledger (Address, POSIXTime, PaymentPubKeyHash)
import Ledger.Interval qualified as Interval
import Ledger.Tx.Constraints (TxConstraints)
import Ledger.Tx.Constraints qualified as Constraints
import Ledger.Tx.Constraints.ValidityInterval qualified as ValidityInterval
import Ledger.Typed.Scripts qualified as Scripts
import Plutus.Script.Utils.Ada qualified as Ada
import Plutus.Script.Utils.V2.Contexts qualified as V2
import Plutus.Script.Utils.V2.Typed.Scripts qualified as V2
import Plutus.Script.Utils.Value (Value)
import Plutus.Script.Utils.Value qualified as Value
import Plutus.Contract
import Plutus.Contract.StateMachine (AsSMContractError, State (..), StateMachine (..), Void)
import Plutus.Contract.StateMachine qualified as SM
import PlutusTx qualified
import PlutusTx.Prelude hiding (Applicative (..))
import Prelude qualified as Haskell
data Payment = Payment
{ Payment -> Value
paymentAmount :: Value
, Payment -> Address
paymentRecipient :: Address
, Payment -> POSIXTime
paymentDeadline :: POSIXTime
}
deriving stock (Int -> Payment -> ShowS
[Payment] -> ShowS
Payment -> String
(Int -> Payment -> ShowS)
-> (Payment -> String) -> ([Payment] -> ShowS) -> Show Payment
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Payment] -> ShowS
$cshowList :: [Payment] -> ShowS
show :: Payment -> String
$cshow :: Payment -> String
showsPrec :: Int -> Payment -> ShowS
$cshowsPrec :: Int -> Payment -> ShowS
Haskell.Show, (forall x. Payment -> Rep Payment x)
-> (forall x. Rep Payment x -> Payment) -> Generic Payment
forall x. Rep Payment x -> Payment
forall x. Payment -> Rep Payment x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Payment x -> Payment
$cfrom :: forall x. Payment -> Rep Payment x
Generic)
deriving anyclass ([Payment] -> Encoding
[Payment] -> Value
Payment -> Encoding
Payment -> Value
(Payment -> Value)
-> (Payment -> Encoding)
-> ([Payment] -> Value)
-> ([Payment] -> Encoding)
-> ToJSON Payment
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [Payment] -> Encoding
$ctoEncodingList :: [Payment] -> Encoding
toJSONList :: [Payment] -> Value
$ctoJSONList :: [Payment] -> Value
toEncoding :: Payment -> Encoding
$ctoEncoding :: Payment -> Encoding
toJSON :: Payment -> Value
$ctoJSON :: Payment -> Value
ToJSON, Value -> Parser [Payment]
Value -> Parser Payment
(Value -> Parser Payment)
-> (Value -> Parser [Payment]) -> FromJSON Payment
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [Payment]
$cparseJSONList :: Value -> Parser [Payment]
parseJSON :: Value -> Parser Payment
$cparseJSON :: Value -> Parser Payment
FromJSON)
instance Eq Payment where
{-# INLINABLE (==) #-}
(Payment Value
vl Address
addr POSIXTime
sl) == :: Payment -> Payment -> Bool
== (Payment Value
vl' Address
addr' POSIXTime
sl') = Value
vl Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
== Value
vl' Bool -> Bool -> Bool
&& Address
addr Address -> Address -> Bool
forall a. Eq a => a -> a -> Bool
== Address
addr' Bool -> Bool -> Bool
&& POSIXTime
sl POSIXTime -> POSIXTime -> Bool
forall a. Eq a => a -> a -> Bool
== POSIXTime
sl'
data Params = Params
{ Params -> [PaymentPubKeyHash]
mspSignatories :: [PaymentPubKeyHash]
, Params -> Integer
mspRequiredSigs :: Integer
}
data MSState =
Holding
| CollectingSignatures Payment [PaymentPubKeyHash]
| Finished
deriving stock (Int -> MSState -> ShowS
[MSState] -> ShowS
MSState -> String
(Int -> MSState -> ShowS)
-> (MSState -> String) -> ([MSState] -> ShowS) -> Show MSState
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [MSState] -> ShowS
$cshowList :: [MSState] -> ShowS
show :: MSState -> String
$cshow :: MSState -> String
showsPrec :: Int -> MSState -> ShowS
$cshowsPrec :: Int -> MSState -> ShowS
Haskell.Show, (forall x. MSState -> Rep MSState x)
-> (forall x. Rep MSState x -> MSState) -> Generic MSState
forall x. Rep MSState x -> MSState
forall x. MSState -> Rep MSState x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep MSState x -> MSState
$cfrom :: forall x. MSState -> Rep MSState x
Generic)
deriving anyclass ([MSState] -> Encoding
[MSState] -> Value
MSState -> Encoding
MSState -> Value
(MSState -> Value)
-> (MSState -> Encoding)
-> ([MSState] -> Value)
-> ([MSState] -> Encoding)
-> ToJSON MSState
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [MSState] -> Encoding
$ctoEncodingList :: [MSState] -> Encoding
toJSONList :: [MSState] -> Value
$ctoJSONList :: [MSState] -> Value
toEncoding :: MSState -> Encoding
$ctoEncoding :: MSState -> Encoding
toJSON :: MSState -> Value
$ctoJSON :: MSState -> Value
ToJSON, Value -> Parser [MSState]
Value -> Parser MSState
(Value -> Parser MSState)
-> (Value -> Parser [MSState]) -> FromJSON MSState
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [MSState]
$cparseJSONList :: Value -> Parser [MSState]
parseJSON :: Value -> Parser MSState
$cparseJSON :: Value -> Parser MSState
FromJSON)
instance Eq MSState where
{-# INLINABLE (==) #-}
MSState
Holding == :: MSState -> MSState -> Bool
== MSState
Holding = Bool
True
(CollectingSignatures Payment
pmt [PaymentPubKeyHash]
pks) == (CollectingSignatures Payment
pmt' [PaymentPubKeyHash]
pks') =
Payment
pmt Payment -> Payment -> Bool
forall a. Eq a => a -> a -> Bool
== Payment
pmt' Bool -> Bool -> Bool
&& [PaymentPubKeyHash]
pks [PaymentPubKeyHash] -> [PaymentPubKeyHash] -> Bool
forall a. Eq a => a -> a -> Bool
== [PaymentPubKeyHash]
pks'
MSState
_ == MSState
_ = Bool
False
data Input =
ProposePayment Payment
| AddSignature PaymentPubKeyHash
| Cancel
| Pay
deriving stock (Int -> Input -> ShowS
[Input] -> ShowS
Input -> String
(Int -> Input -> ShowS)
-> (Input -> String) -> ([Input] -> ShowS) -> Show Input
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Input] -> ShowS
$cshowList :: [Input] -> ShowS
show :: Input -> String
$cshow :: Input -> String
showsPrec :: Int -> Input -> ShowS
$cshowsPrec :: Int -> Input -> ShowS
Haskell.Show, (forall x. Input -> Rep Input x)
-> (forall x. Rep Input x -> Input) -> Generic Input
forall x. Rep Input x -> Input
forall x. Input -> Rep Input x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Input x -> Input
$cfrom :: forall x. Input -> Rep Input x
Generic)
deriving anyclass ([Input] -> Encoding
[Input] -> Value
Input -> Encoding
Input -> Value
(Input -> Value)
-> (Input -> Encoding)
-> ([Input] -> Value)
-> ([Input] -> Encoding)
-> ToJSON Input
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [Input] -> Encoding
$ctoEncodingList :: [Input] -> Encoding
toJSONList :: [Input] -> Value
$ctoJSONList :: [Input] -> Value
toEncoding :: Input -> Encoding
$ctoEncoding :: Input -> Encoding
toJSON :: Input -> Value
$ctoJSON :: Input -> Value
ToJSON, Value -> Parser [Input]
Value -> Parser Input
(Value -> Parser Input)
-> (Value -> Parser [Input]) -> FromJSON Input
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [Input]
$cparseJSONList :: Value -> Parser [Input]
parseJSON :: Value -> Parser Input
$cparseJSON :: Value -> Parser Input
FromJSON)
data MultiSigError =
MSContractError ContractError
| MSStateMachineError SM.SMContractError
deriving stock (Int -> MultiSigError -> ShowS
[MultiSigError] -> ShowS
MultiSigError -> String
(Int -> MultiSigError -> ShowS)
-> (MultiSigError -> String)
-> ([MultiSigError] -> ShowS)
-> Show MultiSigError
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [MultiSigError] -> ShowS
$cshowList :: [MultiSigError] -> ShowS
show :: MultiSigError -> String
$cshow :: MultiSigError -> String
showsPrec :: Int -> MultiSigError -> ShowS
$cshowsPrec :: Int -> MultiSigError -> ShowS
Haskell.Show, (forall x. MultiSigError -> Rep MultiSigError x)
-> (forall x. Rep MultiSigError x -> MultiSigError)
-> Generic MultiSigError
forall x. Rep MultiSigError x -> MultiSigError
forall x. MultiSigError -> Rep MultiSigError x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep MultiSigError x -> MultiSigError
$cfrom :: forall x. MultiSigError -> Rep MultiSigError x
Generic)
deriving anyclass ([MultiSigError] -> Encoding
[MultiSigError] -> Value
MultiSigError -> Encoding
MultiSigError -> Value
(MultiSigError -> Value)
-> (MultiSigError -> Encoding)
-> ([MultiSigError] -> Value)
-> ([MultiSigError] -> Encoding)
-> ToJSON MultiSigError
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [MultiSigError] -> Encoding
$ctoEncodingList :: [MultiSigError] -> Encoding
toJSONList :: [MultiSigError] -> Value
$ctoJSONList :: [MultiSigError] -> Value
toEncoding :: MultiSigError -> Encoding
$ctoEncoding :: MultiSigError -> Encoding
toJSON :: MultiSigError -> Value
$ctoJSON :: MultiSigError -> Value
ToJSON, Value -> Parser [MultiSigError]
Value -> Parser MultiSigError
(Value -> Parser MultiSigError)
-> (Value -> Parser [MultiSigError]) -> FromJSON MultiSigError
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [MultiSigError]
$cparseJSONList :: Value -> Parser [MultiSigError]
parseJSON :: Value -> Parser MultiSigError
$cparseJSON :: Value -> Parser MultiSigError
FromJSON)
makeClassyPrisms ''MultiSigError
instance AsContractError MultiSigError where
_ContractError :: p ContractError (f ContractError)
-> p MultiSigError (f MultiSigError)
_ContractError = p ContractError (f ContractError)
-> p MultiSigError (f MultiSigError)
forall r. AsMultiSigError r => Prism' r ContractError
_MSContractError
instance AsSMContractError MultiSigError where
_SMContractError :: p SMContractError (f SMContractError)
-> p MultiSigError (f MultiSigError)
_SMContractError = p SMContractError (f SMContractError)
-> p MultiSigError (f MultiSigError)
forall r. AsMultiSigError r => Prism' r SMContractError
_MSStateMachineError
type MultiSigSchema =
Endpoint "propose-payment" Payment
.\/ Endpoint "add-signature" ()
.\/ Endpoint "cancel-payment" ()
.\/ Endpoint "pay" ()
.\/ Endpoint "lock" Value
{-# INLINABLE isSignatory #-}
isSignatory :: PaymentPubKeyHash -> Params -> Bool
isSignatory :: PaymentPubKeyHash -> Params -> Bool
isSignatory PaymentPubKeyHash
pkh (Params [PaymentPubKeyHash]
sigs Integer
_) = (PaymentPubKeyHash -> Bool) -> [PaymentPubKeyHash] -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any (\PaymentPubKeyHash
pkh' -> PaymentPubKeyHash
pkh PaymentPubKeyHash -> PaymentPubKeyHash -> Bool
forall a. Eq a => a -> a -> Bool
== PaymentPubKeyHash
pkh') [PaymentPubKeyHash]
sigs
{-# INLINABLE containsPk #-}
containsPk :: PaymentPubKeyHash -> [PaymentPubKeyHash] -> Bool
containsPk :: PaymentPubKeyHash -> [PaymentPubKeyHash] -> Bool
containsPk PaymentPubKeyHash
pk = (PaymentPubKeyHash -> Bool) -> [PaymentPubKeyHash] -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any (\PaymentPubKeyHash
pk' -> PaymentPubKeyHash
pk' PaymentPubKeyHash -> PaymentPubKeyHash -> Bool
forall a. Eq a => a -> a -> Bool
== PaymentPubKeyHash
pk)
{-# INLINABLE isValidProposal #-}
isValidProposal :: Value -> Payment -> Bool
isValidProposal :: Value -> Payment -> Bool
isValidProposal Value
vl (Payment Value
amt Address
_ POSIXTime
_) = Value
amt Value -> Value -> Bool
`Value.leq` Value
vl
{-# INLINABLE proposalExpired #-}
proposalExpired :: V2.TxInfo -> Payment -> Bool
proposalExpired :: TxInfo -> Payment -> Bool
proposalExpired V2.TxInfo{POSIXTimeRange
txInfoValidRange :: TxInfo -> POSIXTimeRange
txInfoValidRange :: POSIXTimeRange
V2.txInfoValidRange} Payment{POSIXTime
paymentDeadline :: POSIXTime
paymentDeadline :: Payment -> POSIXTime
paymentDeadline} =
(POSIXTime
paymentDeadline POSIXTime -> POSIXTime -> POSIXTime
forall a. AdditiveGroup a => a -> a -> a
- POSIXTime
1) POSIXTime -> POSIXTimeRange -> Bool
forall a. Ord a => a -> Interval a -> Bool
`Interval.before` POSIXTimeRange
txInfoValidRange
{-# INLINABLE proposalAccepted #-}
proposalAccepted :: Params -> [PaymentPubKeyHash] -> Bool
proposalAccepted :: Params -> [PaymentPubKeyHash] -> Bool
proposalAccepted (Params [PaymentPubKeyHash]
signatories Integer
numReq) [PaymentPubKeyHash]
pks =
let numSigned :: Integer
numSigned = [PaymentPubKeyHash] -> Integer
forall (t :: * -> *) a. Foldable t => t a -> Integer
length ((PaymentPubKeyHash -> Bool)
-> [PaymentPubKeyHash] -> [PaymentPubKeyHash]
forall a. (a -> Bool) -> [a] -> [a]
filter (\PaymentPubKeyHash
pk -> PaymentPubKeyHash -> [PaymentPubKeyHash] -> Bool
containsPk PaymentPubKeyHash
pk [PaymentPubKeyHash]
pks) [PaymentPubKeyHash]
signatories)
in Integer
numSigned Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
>= Integer
numReq
{-# INLINABLE valuePreserved #-}
valuePreserved :: Value -> V2.ScriptContext -> Bool
valuePreserved :: Value -> ScriptContext -> Bool
valuePreserved Value
vl ScriptContext
ctx = Value
vl Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
== TxInfo -> ValidatorHash -> Value
V2.valueLockedBy (ScriptContext -> TxInfo
V2.scriptContextTxInfo ScriptContext
ctx) (ScriptContext -> ValidatorHash
V2.ownHash ScriptContext
ctx)
{-# INLINABLE valuePaid #-}
valuePaid :: Payment -> V2.TxInfo -> Bool
valuePaid :: Payment -> TxInfo -> Bool
valuePaid (Payment Value
vl Address
addr POSIXTime
_) TxInfo
txinfo = Value
vl Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
== TxInfo -> Address -> Value
V2.valuePaidTo TxInfo
txinfo Address
addr
{-# INLINABLE transition #-}
transition :: Params -> State MSState -> Input -> Maybe (TxConstraints Void Void, State MSState)
transition :: Params
-> State MSState
-> Input
-> Maybe (TxConstraints Void Void, State MSState)
transition Params
params State{ stateData :: forall s. State s -> s
stateData =MSState
s, stateValue :: forall s. State s -> Value
stateValue=Value
currentValue} Input
i = case (MSState
s, Input
i) of
(MSState
Holding, ProposePayment Payment
pmt)
| Value -> Payment -> Bool
isValidProposal Value
currentValue Payment
pmt ->
(TxConstraints Void Void, State MSState)
-> Maybe (TxConstraints Void Void, State MSState)
forall a. a -> Maybe a
Just ( TxConstraints Void Void
forall a. Monoid a => a
mempty
, State :: forall s. s -> Value -> State s
State
{ stateData :: MSState
stateData = Payment -> [PaymentPubKeyHash] -> MSState
CollectingSignatures Payment
pmt []
, stateValue :: Value
stateValue = Value
currentValue
}
)
(CollectingSignatures Payment
pmt [PaymentPubKeyHash]
pks, AddSignature PaymentPubKeyHash
pk)
| PaymentPubKeyHash -> Params -> Bool
isSignatory PaymentPubKeyHash
pk Params
params Bool -> Bool -> Bool
&& Bool -> Bool
not (PaymentPubKeyHash -> [PaymentPubKeyHash] -> Bool
containsPk PaymentPubKeyHash
pk [PaymentPubKeyHash]
pks) ->
let constraints :: TxConstraints Void Void
constraints = PaymentPubKeyHash -> TxConstraints Void Void
forall i o. PaymentPubKeyHash -> TxConstraints i o
Constraints.mustBeSignedBy PaymentPubKeyHash
pk in
(TxConstraints Void Void, State MSState)
-> Maybe (TxConstraints Void Void, State MSState)
forall a. a -> Maybe a
Just ( TxConstraints Void Void
constraints
, State :: forall s. s -> Value -> State s
State
{ stateData :: MSState
stateData = Payment -> [PaymentPubKeyHash] -> MSState
CollectingSignatures Payment
pmt (PaymentPubKeyHash
pkPaymentPubKeyHash -> [PaymentPubKeyHash] -> [PaymentPubKeyHash]
forall a. a -> [a] -> [a]
:[PaymentPubKeyHash]
pks)
, stateValue :: Value
stateValue = Value
currentValue
}
)
(CollectingSignatures Payment
payment [PaymentPubKeyHash]
_, Input
Cancel) ->
let constraints :: TxConstraints Void Void
constraints = ValidityInterval POSIXTime -> TxConstraints Void Void
forall i o. ValidityInterval POSIXTime -> TxConstraints i o
Constraints.mustValidateInTimeRange (POSIXTime -> ValidityInterval POSIXTime
forall a. a -> ValidityInterval a
ValidityInterval.from (Payment -> POSIXTime
paymentDeadline Payment
payment)) in
(TxConstraints Void Void, State MSState)
-> Maybe (TxConstraints Void Void, State MSState)
forall a. a -> Maybe a
Just ( TxConstraints Void Void
constraints
, State :: forall s. s -> Value -> State s
State
{ stateData :: MSState
stateData = MSState
Holding
, stateValue :: Value
stateValue = Value
currentValue
}
)
(CollectingSignatures Payment
payment [PaymentPubKeyHash]
pkh, Input
Pay)
| Params -> [PaymentPubKeyHash] -> Bool
proposalAccepted Params
params [PaymentPubKeyHash]
pkh ->
let Payment{Value
paymentAmount :: Value
paymentAmount :: Payment -> Value
paymentAmount, Address
paymentRecipient :: Address
paymentRecipient :: Payment -> Address
paymentRecipient, POSIXTime
paymentDeadline :: POSIXTime
paymentDeadline :: Payment -> POSIXTime
paymentDeadline} = Payment
payment
validityTimeRange :: ValidityInterval POSIXTime
validityTimeRange = POSIXTime -> ValidityInterval POSIXTime
forall a. a -> ValidityInterval a
ValidityInterval.lessThan (POSIXTime -> ValidityInterval POSIXTime)
-> POSIXTime -> ValidityInterval POSIXTime
forall a b. (a -> b) -> a -> b
$ POSIXTime
paymentDeadline POSIXTime -> POSIXTime -> POSIXTime
forall a. AdditiveGroup a => a -> a -> a
- POSIXTime
1
constraints :: TxConstraints Void Void
constraints =
ValidityInterval POSIXTime -> TxConstraints Void Void
forall i o. ValidityInterval POSIXTime -> TxConstraints i o
Constraints.mustValidateInTimeRange ValidityInterval POSIXTime
validityTimeRange
TxConstraints Void Void
-> TxConstraints Void Void -> TxConstraints Void Void
forall a. Semigroup a => a -> a -> a
<> Address -> Value -> TxConstraints Void Void
forall i o. Address -> Value -> TxConstraints i o
Constraints.mustPayToAddress Address
paymentRecipient Value
paymentAmount
newValue :: Value
newValue = Value
currentValue Value -> Value -> Value
forall a. AdditiveGroup a => a -> a -> a
- Value
paymentAmount
in (TxConstraints Void Void, State MSState)
-> Maybe (TxConstraints Void Void, State MSState)
forall a. a -> Maybe a
Just ( TxConstraints Void Void
constraints
, State :: forall s. s -> Value -> State s
State
{ stateData :: MSState
stateData = if Value -> Bool
Value.isZero (Ada -> Value
Ada.toValue (Ada -> Value) -> Ada -> Value
forall a b. (a -> b) -> a -> b
$ Value -> Ada
Ada.fromValue Value
newValue)
then MSState
Finished
else MSState
Holding
, stateValue :: Value
stateValue = Value
newValue
}
)
(MSState, Input)
_ -> Maybe (TxConstraints Void Void, State MSState)
forall a. Maybe a
Nothing
type MultiSigSym = StateMachine MSState Input
{-# INLINABLE machine #-}
machine :: Params -> MultiSigSym
machine :: Params -> MultiSigSym
machine Params
params = Maybe ThreadToken
-> (State MSState
-> Input -> Maybe (TxConstraints Void Void, State MSState))
-> (MSState -> Bool)
-> MultiSigSym
forall s i.
Maybe ThreadToken
-> (State s -> i -> Maybe (TxConstraints Void Void, State s))
-> (s -> Bool)
-> StateMachine s i
SM.mkStateMachine Maybe ThreadToken
forall a. Maybe a
Nothing (Params
-> State MSState
-> Input
-> Maybe (TxConstraints Void Void, State MSState)
transition Params
params) MSState -> Bool
isFinal where
isFinal :: MSState -> Bool
isFinal MSState
Finished = Bool
True
isFinal MSState
_ = Bool
False
{-# INLINABLE mkValidator #-}
mkValidator :: Params -> V2.ValidatorType MultiSigSym
mkValidator :: Params -> ValidatorType MultiSigSym
mkValidator Params
params = MultiSigSym -> MSState -> Input -> ScriptContext -> Bool
forall s i.
ToData s =>
StateMachine s i -> ValidatorType (StateMachine s i)
SM.mkValidator (MultiSigSym -> MSState -> Input -> ScriptContext -> Bool)
-> MultiSigSym -> MSState -> Input -> ScriptContext -> Bool
forall a b. (a -> b) -> a -> b
$ Params -> MultiSigSym
machine Params
params
typedValidator :: Params -> V2.TypedValidator MultiSigSym
typedValidator :: Params -> TypedValidator MultiSigSym
typedValidator = CompiledCode (Params -> ValidatorType MultiSigSym)
-> CompiledCode (ValidatorType MultiSigSym -> UntypedValidator)
-> Params
-> TypedValidator MultiSigSym
forall a param.
Lift DefaultUni param =>
CompiledCode (param -> ValidatorType a)
-> CompiledCode (ValidatorType a -> UntypedValidator)
-> param
-> TypedValidator a
V2.mkTypedValidatorParam @MultiSigSym
$$(PlutusTx.compile [|| mkValidator ||])
$$(PlutusTx.compile [|| wrap ||])
where
wrap :: (MSState -> Input -> ScriptContext -> Bool) -> UntypedValidator
wrap = (MSState -> Input -> ScriptContext -> Bool) -> UntypedValidator
forall sc d r.
(IsScriptContext sc, UnsafeFromData d, UnsafeFromData r) =>
(d -> r -> sc -> Bool) -> UntypedValidator
Scripts.mkUntypedValidator
client :: Params -> SM.StateMachineClient MSState Input
client :: Params -> StateMachineClient MSState Input
client Params
params = StateMachineInstance MSState Input
-> StateMachineClient MSState Input
forall state input.
StateMachineInstance state input -> StateMachineClient state input
SM.mkStateMachineClient (StateMachineInstance MSState Input
-> StateMachineClient MSState Input)
-> StateMachineInstance MSState Input
-> StateMachineClient MSState Input
forall a b. (a -> b) -> a -> b
$ MultiSigSym
-> TypedValidator MultiSigSym -> StateMachineInstance MSState Input
forall s i.
StateMachine s i
-> TypedValidator (StateMachine s i) -> StateMachineInstance s i
SM.StateMachineInstance (Params -> MultiSigSym
machine Params
params) (Params -> TypedValidator MultiSigSym
typedValidator Params
params)
contract ::
( AsContractError e
, AsSMContractError e
)
=> Params
-> Contract () MultiSigSchema e ()
contract :: Params -> Contract () MultiSigSchema e ()
contract Params
params = Contract
()
('R
'[ "add-signature" ':-> (EndpointValue (), ActiveEndpoint),
"cancel-payment" ':-> (EndpointValue (), ActiveEndpoint),
"lock" ':-> (EndpointValue Value, ActiveEndpoint),
"pay" ':-> (EndpointValue (), ActiveEndpoint),
"propose-payment" ':-> (EndpointValue Payment, ActiveEndpoint)])
e
()
-> Contract
()
('R
'[ "add-signature" ':-> (EndpointValue (), ActiveEndpoint),
"cancel-payment" ':-> (EndpointValue (), ActiveEndpoint),
"lock" ':-> (EndpointValue Value, ActiveEndpoint),
"pay" ':-> (EndpointValue (), ActiveEndpoint),
"propose-payment" ':-> (EndpointValue Payment, ActiveEndpoint)])
e
()
forall (f :: * -> *) a b. Applicative f => f a -> f b
forever Contract
()
('R
'[ "add-signature" ':-> (EndpointValue (), ActiveEndpoint),
"cancel-payment" ':-> (EndpointValue (), ActiveEndpoint),
"lock" ':-> (EndpointValue Value, ActiveEndpoint),
"pay" ':-> (EndpointValue (), ActiveEndpoint),
"propose-payment" ':-> (EndpointValue Payment, ActiveEndpoint)])
e
()
endpoints where
theClient :: StateMachineClient MSState Input
theClient = Params -> StateMachineClient MSState Input
client Params
params
endpoints :: Contract
()
('R
'[ "add-signature" ':-> (EndpointValue (), ActiveEndpoint),
"cancel-payment" ':-> (EndpointValue (), ActiveEndpoint),
"lock" ':-> (EndpointValue Value, ActiveEndpoint),
"pay" ':-> (EndpointValue (), ActiveEndpoint),
"propose-payment" ':-> (EndpointValue Payment, ActiveEndpoint)])
e
()
endpoints = [Promise
()
('R
'[ "add-signature" ':-> (EndpointValue (), ActiveEndpoint),
"cancel-payment" ':-> (EndpointValue (), ActiveEndpoint),
"lock" ':-> (EndpointValue Value, ActiveEndpoint),
"pay" ':-> (EndpointValue (), ActiveEndpoint),
"propose-payment" ':-> (EndpointValue Payment, ActiveEndpoint)])
e
()]
-> Contract
()
('R
'[ "add-signature" ':-> (EndpointValue (), ActiveEndpoint),
"cancel-payment" ':-> (EndpointValue (), ActiveEndpoint),
"lock" ':-> (EndpointValue Value, ActiveEndpoint),
"pay" ':-> (EndpointValue (), ActiveEndpoint),
"propose-payment" ':-> (EndpointValue Payment, ActiveEndpoint)])
e
()
forall w (s :: Row *) e a. [Promise w s e a] -> Contract w s e a
selectList [Promise
()
('R
'[ "add-signature" ':-> (EndpointValue (), ActiveEndpoint),
"cancel-payment" ':-> (EndpointValue (), ActiveEndpoint),
"lock" ':-> (EndpointValue Value, ActiveEndpoint),
"pay" ':-> (EndpointValue (), ActiveEndpoint),
"propose-payment" ':-> (EndpointValue Payment, ActiveEndpoint)])
e
()
lock, Promise
()
('R
'[ "add-signature" ':-> (EndpointValue (), ActiveEndpoint),
"cancel-payment" ':-> (EndpointValue (), ActiveEndpoint),
"lock" ':-> (EndpointValue Value, ActiveEndpoint),
"pay" ':-> (EndpointValue (), ActiveEndpoint),
"propose-payment" ':-> (EndpointValue Payment, ActiveEndpoint)])
e
()
propose, Promise
()
('R
'[ "add-signature" ':-> (EndpointValue (), ActiveEndpoint),
"cancel-payment" ':-> (EndpointValue (), ActiveEndpoint),
"lock" ':-> (EndpointValue Value, ActiveEndpoint),
"pay" ':-> (EndpointValue (), ActiveEndpoint),
"propose-payment" ':-> (EndpointValue Payment, ActiveEndpoint)])
e
()
cancel, Promise
()
('R
'[ "add-signature" ':-> (EndpointValue (), ActiveEndpoint),
"cancel-payment" ':-> (EndpointValue (), ActiveEndpoint),
"lock" ':-> (EndpointValue Value, ActiveEndpoint),
"pay" ':-> (EndpointValue (), ActiveEndpoint),
"propose-payment" ':-> (EndpointValue Payment, ActiveEndpoint)])
e
()
addSignature, Promise
()
('R
'[ "add-signature" ':-> (EndpointValue (), ActiveEndpoint),
"cancel-payment" ':-> (EndpointValue (), ActiveEndpoint),
"lock" ':-> (EndpointValue Value, ActiveEndpoint),
"pay" ':-> (EndpointValue (), ActiveEndpoint),
"propose-payment" ':-> (EndpointValue Payment, ActiveEndpoint)])
e
()
pay]
propose :: Promise
()
('R
'[ "add-signature" ':-> (EndpointValue (), ActiveEndpoint),
"cancel-payment" ':-> (EndpointValue (), ActiveEndpoint),
"lock" ':-> (EndpointValue Value, ActiveEndpoint),
"pay" ':-> (EndpointValue (), ActiveEndpoint),
"propose-payment" ':-> (EndpointValue Payment, ActiveEndpoint)])
e
()
propose = forall a w (s :: Row *) e b.
(HasEndpoint "propose-payment" a s, AsContractError e,
FromJSON a) =>
(a -> Contract w s e b) -> Promise w s e b
forall (l :: Symbol) a w (s :: Row *) e b.
(HasEndpoint l a s, AsContractError e, FromJSON a) =>
(a -> Contract w s e b) -> Promise w s e b
endpoint @"propose-payment" ((Payment
-> Contract
()
('R
'[ "add-signature" ':-> (EndpointValue (), ActiveEndpoint),
"cancel-payment" ':-> (EndpointValue (), ActiveEndpoint),
"lock" ':-> (EndpointValue Value, ActiveEndpoint),
"pay" ':-> (EndpointValue (), ActiveEndpoint),
"propose-payment" ':-> (EndpointValue Payment, ActiveEndpoint)])
e
())
-> Promise
()
('R
'[ "add-signature" ':-> (EndpointValue (), ActiveEndpoint),
"cancel-payment" ':-> (EndpointValue (), ActiveEndpoint),
"lock" ':-> (EndpointValue Value, ActiveEndpoint),
"pay" ':-> (EndpointValue (), ActiveEndpoint),
"propose-payment" ':-> (EndpointValue Payment, ActiveEndpoint)])
e
())
-> (Payment
-> Contract
()
('R
'[ "add-signature" ':-> (EndpointValue (), ActiveEndpoint),
"cancel-payment" ':-> (EndpointValue (), ActiveEndpoint),
"lock" ':-> (EndpointValue Value, ActiveEndpoint),
"pay" ':-> (EndpointValue (), ActiveEndpoint),
"propose-payment" ':-> (EndpointValue Payment, ActiveEndpoint)])
e
())
-> Promise
()
('R
'[ "add-signature" ':-> (EndpointValue (), ActiveEndpoint),
"cancel-payment" ':-> (EndpointValue (), ActiveEndpoint),
"lock" ':-> (EndpointValue Value, ActiveEndpoint),
"pay" ':-> (EndpointValue (), ActiveEndpoint),
"propose-payment" ':-> (EndpointValue Payment, ActiveEndpoint)])
e
()
forall a b. (a -> b) -> a -> b
$ Contract
()
('R
'[ "add-signature" ':-> (EndpointValue (), ActiveEndpoint),
"cancel-payment" ':-> (EndpointValue (), ActiveEndpoint),
"lock" ':-> (EndpointValue Value, ActiveEndpoint),
"pay" ':-> (EndpointValue (), ActiveEndpoint),
"propose-payment" ':-> (EndpointValue Payment, ActiveEndpoint)])
e
(TransitionResult MSState Input)
-> Contract
()
('R
'[ "add-signature" ':-> (EndpointValue (), ActiveEndpoint),
"cancel-payment" ':-> (EndpointValue (), ActiveEndpoint),
"lock" ':-> (EndpointValue Value, ActiveEndpoint),
"pay" ':-> (EndpointValue (), ActiveEndpoint),
"propose-payment" ':-> (EndpointValue Payment, ActiveEndpoint)])
e
()
forall (f :: * -> *) a. Functor f => f a -> f ()
void (Contract
()
('R
'[ "add-signature" ':-> (EndpointValue (), ActiveEndpoint),
"cancel-payment" ':-> (EndpointValue (), ActiveEndpoint),
"lock" ':-> (EndpointValue Value, ActiveEndpoint),
"pay" ':-> (EndpointValue (), ActiveEndpoint),
"propose-payment" ':-> (EndpointValue Payment, ActiveEndpoint)])
e
(TransitionResult MSState Input)
-> Contract
()
('R
'[ "add-signature" ':-> (EndpointValue (), ActiveEndpoint),
"cancel-payment" ':-> (EndpointValue (), ActiveEndpoint),
"lock" ':-> (EndpointValue Value, ActiveEndpoint),
"pay" ':-> (EndpointValue (), ActiveEndpoint),
"propose-payment" ':-> (EndpointValue Payment, ActiveEndpoint)])
e
())
-> (Payment
-> Contract
()
('R
'[ "add-signature" ':-> (EndpointValue (), ActiveEndpoint),
"cancel-payment" ':-> (EndpointValue (), ActiveEndpoint),
"lock" ':-> (EndpointValue Value, ActiveEndpoint),
"pay" ':-> (EndpointValue (), ActiveEndpoint),
"propose-payment" ':-> (EndpointValue Payment, ActiveEndpoint)])
e
(TransitionResult MSState Input))
-> Payment
-> Contract
()
('R
'[ "add-signature" ':-> (EndpointValue (), ActiveEndpoint),
"cancel-payment" ':-> (EndpointValue (), ActiveEndpoint),
"lock" ':-> (EndpointValue Value, ActiveEndpoint),
"pay" ':-> (EndpointValue (), ActiveEndpoint),
"propose-payment" ':-> (EndpointValue Payment, ActiveEndpoint)])
e
()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. StateMachineClient MSState Input
-> Input
-> Contract
()
('R
'[ "add-signature" ':-> (EndpointValue (), ActiveEndpoint),
"cancel-payment" ':-> (EndpointValue (), ActiveEndpoint),
"lock" ':-> (EndpointValue Value, ActiveEndpoint),
"pay" ':-> (EndpointValue (), ActiveEndpoint),
"propose-payment" ':-> (EndpointValue Payment, ActiveEndpoint)])
e
(TransitionResult MSState Input)
forall w e state (schema :: Row *) input.
(AsSMContractError e, FromData state, ToData state,
ToData input) =>
StateMachineClient state input
-> input -> Contract w schema e (TransitionResult state input)
SM.runStep StateMachineClient MSState Input
theClient (Input
-> Contract
()
('R
'[ "add-signature" ':-> (EndpointValue (), ActiveEndpoint),
"cancel-payment" ':-> (EndpointValue (), ActiveEndpoint),
"lock" ':-> (EndpointValue Value, ActiveEndpoint),
"pay" ':-> (EndpointValue (), ActiveEndpoint),
"propose-payment" ':-> (EndpointValue Payment, ActiveEndpoint)])
e
(TransitionResult MSState Input))
-> (Payment -> Input)
-> Payment
-> Contract
()
('R
'[ "add-signature" ':-> (EndpointValue (), ActiveEndpoint),
"cancel-payment" ':-> (EndpointValue (), ActiveEndpoint),
"lock" ':-> (EndpointValue Value, ActiveEndpoint),
"pay" ':-> (EndpointValue (), ActiveEndpoint),
"propose-payment" ':-> (EndpointValue Payment, ActiveEndpoint)])
e
(TransitionResult MSState Input)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Payment -> Input
ProposePayment
cancel :: Promise
()
('R
'[ "add-signature" ':-> (EndpointValue (), ActiveEndpoint),
"cancel-payment" ':-> (EndpointValue (), ActiveEndpoint),
"lock" ':-> (EndpointValue Value, ActiveEndpoint),
"pay" ':-> (EndpointValue (), ActiveEndpoint),
"propose-payment" ':-> (EndpointValue Payment, ActiveEndpoint)])
e
()
cancel = forall a w (s :: Row *) e b.
(HasEndpoint "cancel-payment" a s, AsContractError e,
FromJSON a) =>
(a -> Contract w s e b) -> Promise w s e b
forall (l :: Symbol) a w (s :: Row *) e b.
(HasEndpoint l a s, AsContractError e, FromJSON a) =>
(a -> Contract w s e b) -> Promise w s e b
endpoint @"cancel-payment" ((()
-> Contract
()
('R
'[ "add-signature" ':-> (EndpointValue (), ActiveEndpoint),
"cancel-payment" ':-> (EndpointValue (), ActiveEndpoint),
"lock" ':-> (EndpointValue Value, ActiveEndpoint),
"pay" ':-> (EndpointValue (), ActiveEndpoint),
"propose-payment" ':-> (EndpointValue Payment, ActiveEndpoint)])
e
())
-> Promise
()
('R
'[ "add-signature" ':-> (EndpointValue (), ActiveEndpoint),
"cancel-payment" ':-> (EndpointValue (), ActiveEndpoint),
"lock" ':-> (EndpointValue Value, ActiveEndpoint),
"pay" ':-> (EndpointValue (), ActiveEndpoint),
"propose-payment" ':-> (EndpointValue Payment, ActiveEndpoint)])
e
())
-> (()
-> Contract
()
('R
'[ "add-signature" ':-> (EndpointValue (), ActiveEndpoint),
"cancel-payment" ':-> (EndpointValue (), ActiveEndpoint),
"lock" ':-> (EndpointValue Value, ActiveEndpoint),
"pay" ':-> (EndpointValue (), ActiveEndpoint),
"propose-payment" ':-> (EndpointValue Payment, ActiveEndpoint)])
e
())
-> Promise
()
('R
'[ "add-signature" ':-> (EndpointValue (), ActiveEndpoint),
"cancel-payment" ':-> (EndpointValue (), ActiveEndpoint),
"lock" ':-> (EndpointValue Value, ActiveEndpoint),
"pay" ':-> (EndpointValue (), ActiveEndpoint),
"propose-payment" ':-> (EndpointValue Payment, ActiveEndpoint)])
e
()
forall a b. (a -> b) -> a -> b
$ \() -> Contract
()
('R
'[ "add-signature" ':-> (EndpointValue (), ActiveEndpoint),
"cancel-payment" ':-> (EndpointValue (), ActiveEndpoint),
"lock" ':-> (EndpointValue Value, ActiveEndpoint),
"pay" ':-> (EndpointValue (), ActiveEndpoint),
"propose-payment" ':-> (EndpointValue Payment, ActiveEndpoint)])
e
(TransitionResult MSState Input)
-> Contract
()
('R
'[ "add-signature" ':-> (EndpointValue (), ActiveEndpoint),
"cancel-payment" ':-> (EndpointValue (), ActiveEndpoint),
"lock" ':-> (EndpointValue Value, ActiveEndpoint),
"pay" ':-> (EndpointValue (), ActiveEndpoint),
"propose-payment" ':-> (EndpointValue Payment, ActiveEndpoint)])
e
()
forall (f :: * -> *) a. Functor f => f a -> f ()
void (Contract
()
('R
'[ "add-signature" ':-> (EndpointValue (), ActiveEndpoint),
"cancel-payment" ':-> (EndpointValue (), ActiveEndpoint),
"lock" ':-> (EndpointValue Value, ActiveEndpoint),
"pay" ':-> (EndpointValue (), ActiveEndpoint),
"propose-payment" ':-> (EndpointValue Payment, ActiveEndpoint)])
e
(TransitionResult MSState Input)
-> Contract
()
('R
'[ "add-signature" ':-> (EndpointValue (), ActiveEndpoint),
"cancel-payment" ':-> (EndpointValue (), ActiveEndpoint),
"lock" ':-> (EndpointValue Value, ActiveEndpoint),
"pay" ':-> (EndpointValue (), ActiveEndpoint),
"propose-payment" ':-> (EndpointValue Payment, ActiveEndpoint)])
e
())
-> Contract
()
('R
'[ "add-signature" ':-> (EndpointValue (), ActiveEndpoint),
"cancel-payment" ':-> (EndpointValue (), ActiveEndpoint),
"lock" ':-> (EndpointValue Value, ActiveEndpoint),
"pay" ':-> (EndpointValue (), ActiveEndpoint),
"propose-payment" ':-> (EndpointValue Payment, ActiveEndpoint)])
e
(TransitionResult MSState Input)
-> Contract
()
('R
'[ "add-signature" ':-> (EndpointValue (), ActiveEndpoint),
"cancel-payment" ':-> (EndpointValue (), ActiveEndpoint),
"lock" ':-> (EndpointValue Value, ActiveEndpoint),
"pay" ':-> (EndpointValue (), ActiveEndpoint),
"propose-payment" ':-> (EndpointValue Payment, ActiveEndpoint)])
e
()
forall a b. (a -> b) -> a -> b
$ StateMachineClient MSState Input
-> Input
-> Contract
()
('R
'[ "add-signature" ':-> (EndpointValue (), ActiveEndpoint),
"cancel-payment" ':-> (EndpointValue (), ActiveEndpoint),
"lock" ':-> (EndpointValue Value, ActiveEndpoint),
"pay" ':-> (EndpointValue (), ActiveEndpoint),
"propose-payment" ':-> (EndpointValue Payment, ActiveEndpoint)])
e
(TransitionResult MSState Input)
forall w e state (schema :: Row *) input.
(AsSMContractError e, FromData state, ToData state,
ToData input) =>
StateMachineClient state input
-> input -> Contract w schema e (TransitionResult state input)
SM.runStep StateMachineClient MSState Input
theClient Input
Cancel
addSignature :: Promise
()
('R
'[ "add-signature" ':-> (EndpointValue (), ActiveEndpoint),
"cancel-payment" ':-> (EndpointValue (), ActiveEndpoint),
"lock" ':-> (EndpointValue Value, ActiveEndpoint),
"pay" ':-> (EndpointValue (), ActiveEndpoint),
"propose-payment" ':-> (EndpointValue Payment, ActiveEndpoint)])
e
()
addSignature = forall a w (s :: Row *) e b.
(HasEndpoint "add-signature" a s, AsContractError e, FromJSON a) =>
(a -> Contract w s e b) -> Promise w s e b
forall (l :: Symbol) a w (s :: Row *) e b.
(HasEndpoint l a s, AsContractError e, FromJSON a) =>
(a -> Contract w s e b) -> Promise w s e b
endpoint @"add-signature" ((()
-> Contract
()
('R
'[ "add-signature" ':-> (EndpointValue (), ActiveEndpoint),
"cancel-payment" ':-> (EndpointValue (), ActiveEndpoint),
"lock" ':-> (EndpointValue Value, ActiveEndpoint),
"pay" ':-> (EndpointValue (), ActiveEndpoint),
"propose-payment" ':-> (EndpointValue Payment, ActiveEndpoint)])
e
())
-> Promise
()
('R
'[ "add-signature" ':-> (EndpointValue (), ActiveEndpoint),
"cancel-payment" ':-> (EndpointValue (), ActiveEndpoint),
"lock" ':-> (EndpointValue Value, ActiveEndpoint),
"pay" ':-> (EndpointValue (), ActiveEndpoint),
"propose-payment" ':-> (EndpointValue Payment, ActiveEndpoint)])
e
())
-> (()
-> Contract
()
('R
'[ "add-signature" ':-> (EndpointValue (), ActiveEndpoint),
"cancel-payment" ':-> (EndpointValue (), ActiveEndpoint),
"lock" ':-> (EndpointValue Value, ActiveEndpoint),
"pay" ':-> (EndpointValue (), ActiveEndpoint),
"propose-payment" ':-> (EndpointValue Payment, ActiveEndpoint)])
e
())
-> Promise
()
('R
'[ "add-signature" ':-> (EndpointValue (), ActiveEndpoint),
"cancel-payment" ':-> (EndpointValue (), ActiveEndpoint),
"lock" ':-> (EndpointValue Value, ActiveEndpoint),
"pay" ':-> (EndpointValue (), ActiveEndpoint),
"propose-payment" ':-> (EndpointValue Payment, ActiveEndpoint)])
e
()
forall a b. (a -> b) -> a -> b
$ \() -> Contract
()
('R
'[ "add-signature" ':-> (EndpointValue (), ActiveEndpoint),
"cancel-payment" ':-> (EndpointValue (), ActiveEndpoint),
"lock" ':-> (EndpointValue Value, ActiveEndpoint),
"pay" ':-> (EndpointValue (), ActiveEndpoint),
"propose-payment" ':-> (EndpointValue Payment, ActiveEndpoint)])
e
PaymentPubKeyHash
forall w (s :: Row *) e.
AsContractError e =>
Contract w s e PaymentPubKeyHash
ownFirstPaymentPubKeyHash Contract
()
('R
'[ "add-signature" ':-> (EndpointValue (), ActiveEndpoint),
"cancel-payment" ':-> (EndpointValue (), ActiveEndpoint),
"lock" ':-> (EndpointValue Value, ActiveEndpoint),
"pay" ':-> (EndpointValue (), ActiveEndpoint),
"propose-payment" ':-> (EndpointValue Payment, ActiveEndpoint)])
e
PaymentPubKeyHash
-> (PaymentPubKeyHash
-> Contract
()
('R
'[ "add-signature" ':-> (EndpointValue (), ActiveEndpoint),
"cancel-payment" ':-> (EndpointValue (), ActiveEndpoint),
"lock" ':-> (EndpointValue Value, ActiveEndpoint),
"pay" ':-> (EndpointValue (), ActiveEndpoint),
"propose-payment" ':-> (EndpointValue Payment, ActiveEndpoint)])
e
())
-> Contract
()
('R
'[ "add-signature" ':-> (EndpointValue (), ActiveEndpoint),
"cancel-payment" ':-> (EndpointValue (), ActiveEndpoint),
"lock" ':-> (EndpointValue Value, ActiveEndpoint),
"pay" ':-> (EndpointValue (), ActiveEndpoint),
"propose-payment" ':-> (EndpointValue Payment, ActiveEndpoint)])
e
()
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Contract
()
('R
'[ "add-signature" ':-> (EndpointValue (), ActiveEndpoint),
"cancel-payment" ':-> (EndpointValue (), ActiveEndpoint),
"lock" ':-> (EndpointValue Value, ActiveEndpoint),
"pay" ':-> (EndpointValue (), ActiveEndpoint),
"propose-payment" ':-> (EndpointValue Payment, ActiveEndpoint)])
e
(TransitionResult MSState Input)
-> Contract
()
('R
'[ "add-signature" ':-> (EndpointValue (), ActiveEndpoint),
"cancel-payment" ':-> (EndpointValue (), ActiveEndpoint),
"lock" ':-> (EndpointValue Value, ActiveEndpoint),
"pay" ':-> (EndpointValue (), ActiveEndpoint),
"propose-payment" ':-> (EndpointValue Payment, ActiveEndpoint)])
e
()
forall (f :: * -> *) a. Functor f => f a -> f ()
void (Contract
()
('R
'[ "add-signature" ':-> (EndpointValue (), ActiveEndpoint),
"cancel-payment" ':-> (EndpointValue (), ActiveEndpoint),
"lock" ':-> (EndpointValue Value, ActiveEndpoint),
"pay" ':-> (EndpointValue (), ActiveEndpoint),
"propose-payment" ':-> (EndpointValue Payment, ActiveEndpoint)])
e
(TransitionResult MSState Input)
-> Contract
()
('R
'[ "add-signature" ':-> (EndpointValue (), ActiveEndpoint),
"cancel-payment" ':-> (EndpointValue (), ActiveEndpoint),
"lock" ':-> (EndpointValue Value, ActiveEndpoint),
"pay" ':-> (EndpointValue (), ActiveEndpoint),
"propose-payment" ':-> (EndpointValue Payment, ActiveEndpoint)])
e
())
-> (PaymentPubKeyHash
-> Contract
()
('R
'[ "add-signature" ':-> (EndpointValue (), ActiveEndpoint),
"cancel-payment" ':-> (EndpointValue (), ActiveEndpoint),
"lock" ':-> (EndpointValue Value, ActiveEndpoint),
"pay" ':-> (EndpointValue (), ActiveEndpoint),
"propose-payment" ':-> (EndpointValue Payment, ActiveEndpoint)])
e
(TransitionResult MSState Input))
-> PaymentPubKeyHash
-> Contract
()
('R
'[ "add-signature" ':-> (EndpointValue (), ActiveEndpoint),
"cancel-payment" ':-> (EndpointValue (), ActiveEndpoint),
"lock" ':-> (EndpointValue Value, ActiveEndpoint),
"pay" ':-> (EndpointValue (), ActiveEndpoint),
"propose-payment" ':-> (EndpointValue Payment, ActiveEndpoint)])
e
()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. StateMachineClient MSState Input
-> Input
-> Contract
()
('R
'[ "add-signature" ':-> (EndpointValue (), ActiveEndpoint),
"cancel-payment" ':-> (EndpointValue (), ActiveEndpoint),
"lock" ':-> (EndpointValue Value, ActiveEndpoint),
"pay" ':-> (EndpointValue (), ActiveEndpoint),
"propose-payment" ':-> (EndpointValue Payment, ActiveEndpoint)])
e
(TransitionResult MSState Input)
forall w e state (schema :: Row *) input.
(AsSMContractError e, FromData state, ToData state,
ToData input) =>
StateMachineClient state input
-> input -> Contract w schema e (TransitionResult state input)
SM.runStep StateMachineClient MSState Input
theClient (Input
-> Contract
()
('R
'[ "add-signature" ':-> (EndpointValue (), ActiveEndpoint),
"cancel-payment" ':-> (EndpointValue (), ActiveEndpoint),
"lock" ':-> (EndpointValue Value, ActiveEndpoint),
"pay" ':-> (EndpointValue (), ActiveEndpoint),
"propose-payment" ':-> (EndpointValue Payment, ActiveEndpoint)])
e
(TransitionResult MSState Input))
-> (PaymentPubKeyHash -> Input)
-> PaymentPubKeyHash
-> Contract
()
('R
'[ "add-signature" ':-> (EndpointValue (), ActiveEndpoint),
"cancel-payment" ':-> (EndpointValue (), ActiveEndpoint),
"lock" ':-> (EndpointValue Value, ActiveEndpoint),
"pay" ':-> (EndpointValue (), ActiveEndpoint),
"propose-payment" ':-> (EndpointValue Payment, ActiveEndpoint)])
e
(TransitionResult MSState Input)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. PaymentPubKeyHash -> Input
AddSignature
lock :: Promise
()
('R
'[ "add-signature" ':-> (EndpointValue (), ActiveEndpoint),
"cancel-payment" ':-> (EndpointValue (), ActiveEndpoint),
"lock" ':-> (EndpointValue Value, ActiveEndpoint),
"pay" ':-> (EndpointValue (), ActiveEndpoint),
"propose-payment" ':-> (EndpointValue Payment, ActiveEndpoint)])
e
()
lock = forall a w (s :: Row *) e b.
(HasEndpoint "lock" a s, AsContractError e, FromJSON a) =>
(a -> Contract w s e b) -> Promise w s e b
forall (l :: Symbol) a w (s :: Row *) e b.
(HasEndpoint l a s, AsContractError e, FromJSON a) =>
(a -> Contract w s e b) -> Promise w s e b
endpoint @"lock" ((Value
-> Contract
()
('R
'[ "add-signature" ':-> (EndpointValue (), ActiveEndpoint),
"cancel-payment" ':-> (EndpointValue (), ActiveEndpoint),
"lock" ':-> (EndpointValue Value, ActiveEndpoint),
"pay" ':-> (EndpointValue (), ActiveEndpoint),
"propose-payment" ':-> (EndpointValue Payment, ActiveEndpoint)])
e
())
-> Promise
()
('R
'[ "add-signature" ':-> (EndpointValue (), ActiveEndpoint),
"cancel-payment" ':-> (EndpointValue (), ActiveEndpoint),
"lock" ':-> (EndpointValue Value, ActiveEndpoint),
"pay" ':-> (EndpointValue (), ActiveEndpoint),
"propose-payment" ':-> (EndpointValue Payment, ActiveEndpoint)])
e
())
-> (Value
-> Contract
()
('R
'[ "add-signature" ':-> (EndpointValue (), ActiveEndpoint),
"cancel-payment" ':-> (EndpointValue (), ActiveEndpoint),
"lock" ':-> (EndpointValue Value, ActiveEndpoint),
"pay" ':-> (EndpointValue (), ActiveEndpoint),
"propose-payment" ':-> (EndpointValue Payment, ActiveEndpoint)])
e
())
-> Promise
()
('R
'[ "add-signature" ':-> (EndpointValue (), ActiveEndpoint),
"cancel-payment" ':-> (EndpointValue (), ActiveEndpoint),
"lock" ':-> (EndpointValue Value, ActiveEndpoint),
"pay" ':-> (EndpointValue (), ActiveEndpoint),
"propose-payment" ':-> (EndpointValue Payment, ActiveEndpoint)])
e
()
forall a b. (a -> b) -> a -> b
$ Contract
()
('R
'[ "add-signature" ':-> (EndpointValue (), ActiveEndpoint),
"cancel-payment" ':-> (EndpointValue (), ActiveEndpoint),
"lock" ':-> (EndpointValue Value, ActiveEndpoint),
"pay" ':-> (EndpointValue (), ActiveEndpoint),
"propose-payment" ':-> (EndpointValue Payment, ActiveEndpoint)])
e
MSState
-> Contract
()
('R
'[ "add-signature" ':-> (EndpointValue (), ActiveEndpoint),
"cancel-payment" ':-> (EndpointValue (), ActiveEndpoint),
"lock" ':-> (EndpointValue Value, ActiveEndpoint),
"pay" ':-> (EndpointValue (), ActiveEndpoint),
"propose-payment" ':-> (EndpointValue Payment, ActiveEndpoint)])
e
()
forall (f :: * -> *) a. Functor f => f a -> f ()
void (Contract
()
('R
'[ "add-signature" ':-> (EndpointValue (), ActiveEndpoint),
"cancel-payment" ':-> (EndpointValue (), ActiveEndpoint),
"lock" ':-> (EndpointValue Value, ActiveEndpoint),
"pay" ':-> (EndpointValue (), ActiveEndpoint),
"propose-payment" ':-> (EndpointValue Payment, ActiveEndpoint)])
e
MSState
-> Contract
()
('R
'[ "add-signature" ':-> (EndpointValue (), ActiveEndpoint),
"cancel-payment" ':-> (EndpointValue (), ActiveEndpoint),
"lock" ':-> (EndpointValue Value, ActiveEndpoint),
"pay" ':-> (EndpointValue (), ActiveEndpoint),
"propose-payment" ':-> (EndpointValue Payment, ActiveEndpoint)])
e
())
-> (Value
-> Contract
()
('R
'[ "add-signature" ':-> (EndpointValue (), ActiveEndpoint),
"cancel-payment" ':-> (EndpointValue (), ActiveEndpoint),
"lock" ':-> (EndpointValue Value, ActiveEndpoint),
"pay" ':-> (EndpointValue (), ActiveEndpoint),
"propose-payment" ':-> (EndpointValue Payment, ActiveEndpoint)])
e
MSState)
-> Value
-> Contract
()
('R
'[ "add-signature" ':-> (EndpointValue (), ActiveEndpoint),
"cancel-payment" ':-> (EndpointValue (), ActiveEndpoint),
"lock" ':-> (EndpointValue Value, ActiveEndpoint),
"pay" ':-> (EndpointValue (), ActiveEndpoint),
"propose-payment" ':-> (EndpointValue Payment, ActiveEndpoint)])
e
()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. StateMachineClient MSState Input
-> MSState
-> Value
-> Contract
()
('R
'[ "add-signature" ':-> (EndpointValue (), ActiveEndpoint),
"cancel-payment" ':-> (EndpointValue (), ActiveEndpoint),
"lock" ':-> (EndpointValue Value, ActiveEndpoint),
"pay" ':-> (EndpointValue (), ActiveEndpoint),
"propose-payment" ':-> (EndpointValue Payment, ActiveEndpoint)])
e
MSState
forall w e state (schema :: Row *) input.
(FromData state, ToData state, ToData input,
AsSMContractError e) =>
StateMachineClient state input
-> state -> Value -> Contract w schema e state
SM.runInitialise StateMachineClient MSState Input
theClient MSState
Holding
pay :: Promise
()
('R
'[ "add-signature" ':-> (EndpointValue (), ActiveEndpoint),
"cancel-payment" ':-> (EndpointValue (), ActiveEndpoint),
"lock" ':-> (EndpointValue Value, ActiveEndpoint),
"pay" ':-> (EndpointValue (), ActiveEndpoint),
"propose-payment" ':-> (EndpointValue Payment, ActiveEndpoint)])
e
()
pay = forall a w (s :: Row *) e b.
(HasEndpoint "pay" a s, AsContractError e, FromJSON a) =>
(a -> Contract w s e b) -> Promise w s e b
forall (l :: Symbol) a w (s :: Row *) e b.
(HasEndpoint l a s, AsContractError e, FromJSON a) =>
(a -> Contract w s e b) -> Promise w s e b
endpoint @"pay" ((()
-> Contract
()
('R
'[ "add-signature" ':-> (EndpointValue (), ActiveEndpoint),
"cancel-payment" ':-> (EndpointValue (), ActiveEndpoint),
"lock" ':-> (EndpointValue Value, ActiveEndpoint),
"pay" ':-> (EndpointValue (), ActiveEndpoint),
"propose-payment" ':-> (EndpointValue Payment, ActiveEndpoint)])
e
())
-> Promise
()
('R
'[ "add-signature" ':-> (EndpointValue (), ActiveEndpoint),
"cancel-payment" ':-> (EndpointValue (), ActiveEndpoint),
"lock" ':-> (EndpointValue Value, ActiveEndpoint),
"pay" ':-> (EndpointValue (), ActiveEndpoint),
"propose-payment" ':-> (EndpointValue Payment, ActiveEndpoint)])
e
())
-> (()
-> Contract
()
('R
'[ "add-signature" ':-> (EndpointValue (), ActiveEndpoint),
"cancel-payment" ':-> (EndpointValue (), ActiveEndpoint),
"lock" ':-> (EndpointValue Value, ActiveEndpoint),
"pay" ':-> (EndpointValue (), ActiveEndpoint),
"propose-payment" ':-> (EndpointValue Payment, ActiveEndpoint)])
e
())
-> Promise
()
('R
'[ "add-signature" ':-> (EndpointValue (), ActiveEndpoint),
"cancel-payment" ':-> (EndpointValue (), ActiveEndpoint),
"lock" ':-> (EndpointValue Value, ActiveEndpoint),
"pay" ':-> (EndpointValue (), ActiveEndpoint),
"propose-payment" ':-> (EndpointValue Payment, ActiveEndpoint)])
e
()
forall a b. (a -> b) -> a -> b
$ \() -> Contract
()
('R
'[ "add-signature" ':-> (EndpointValue (), ActiveEndpoint),
"cancel-payment" ':-> (EndpointValue (), ActiveEndpoint),
"lock" ':-> (EndpointValue Value, ActiveEndpoint),
"pay" ':-> (EndpointValue (), ActiveEndpoint),
"propose-payment" ':-> (EndpointValue Payment, ActiveEndpoint)])
e
(TransitionResult MSState Input)
-> Contract
()
('R
'[ "add-signature" ':-> (EndpointValue (), ActiveEndpoint),
"cancel-payment" ':-> (EndpointValue (), ActiveEndpoint),
"lock" ':-> (EndpointValue Value, ActiveEndpoint),
"pay" ':-> (EndpointValue (), ActiveEndpoint),
"propose-payment" ':-> (EndpointValue Payment, ActiveEndpoint)])
e
()
forall (f :: * -> *) a. Functor f => f a -> f ()
void (Contract
()
('R
'[ "add-signature" ':-> (EndpointValue (), ActiveEndpoint),
"cancel-payment" ':-> (EndpointValue (), ActiveEndpoint),
"lock" ':-> (EndpointValue Value, ActiveEndpoint),
"pay" ':-> (EndpointValue (), ActiveEndpoint),
"propose-payment" ':-> (EndpointValue Payment, ActiveEndpoint)])
e
(TransitionResult MSState Input)
-> Contract
()
('R
'[ "add-signature" ':-> (EndpointValue (), ActiveEndpoint),
"cancel-payment" ':-> (EndpointValue (), ActiveEndpoint),
"lock" ':-> (EndpointValue Value, ActiveEndpoint),
"pay" ':-> (EndpointValue (), ActiveEndpoint),
"propose-payment" ':-> (EndpointValue Payment, ActiveEndpoint)])
e
())
-> Contract
()
('R
'[ "add-signature" ':-> (EndpointValue (), ActiveEndpoint),
"cancel-payment" ':-> (EndpointValue (), ActiveEndpoint),
"lock" ':-> (EndpointValue Value, ActiveEndpoint),
"pay" ':-> (EndpointValue (), ActiveEndpoint),
"propose-payment" ':-> (EndpointValue Payment, ActiveEndpoint)])
e
(TransitionResult MSState Input)
-> Contract
()
('R
'[ "add-signature" ':-> (EndpointValue (), ActiveEndpoint),
"cancel-payment" ':-> (EndpointValue (), ActiveEndpoint),
"lock" ':-> (EndpointValue Value, ActiveEndpoint),
"pay" ':-> (EndpointValue (), ActiveEndpoint),
"propose-payment" ':-> (EndpointValue Payment, ActiveEndpoint)])
e
()
forall a b. (a -> b) -> a -> b
$ StateMachineClient MSState Input
-> Input
-> Contract
()
('R
'[ "add-signature" ':-> (EndpointValue (), ActiveEndpoint),
"cancel-payment" ':-> (EndpointValue (), ActiveEndpoint),
"lock" ':-> (EndpointValue Value, ActiveEndpoint),
"pay" ':-> (EndpointValue (), ActiveEndpoint),
"propose-payment" ':-> (EndpointValue Payment, ActiveEndpoint)])
e
(TransitionResult MSState Input)
forall w e state (schema :: Row *) input.
(AsSMContractError e, FromData state, ToData state,
ToData input) =>
StateMachineClient state input
-> input -> Contract w schema e (TransitionResult state input)
SM.runStep StateMachineClient MSState Input
theClient Input
Pay
PlutusTx.unstableMakeIsData ''Payment
PlutusTx.makeLift ''Payment
PlutusTx.unstableMakeIsData ''MSState
PlutusTx.makeLift ''MSState
PlutusTx.makeLift ''Params
PlutusTx.unstableMakeIsData ''Input
PlutusTx.makeLift ''Input