Javier Casas

A random walk through computer science

Plutus Smart Contracts II: Pay $10 in ADA

Enrique asked a quite simple question on the Cardano Developers Telegram channel: Can we make a Cardano smart contract in dollars?

Well, technically we can't, at least directly. Cardano runs on Ada, not dollars. And doesn't include paying by bank or credit cards. Further exploration on his question actually delivered something more feasible: Can we make a Cardano smart contract to pay $10 in ADA for some product or service?

Let's explore this.

A fistful of ADA

This is a very valid use case. In a world dominated by the Dollar, the Euro, the Yen and the Yuan, pretending these currencies don't exist is very shortsighted. So, how do I pay a smart contract $10? Well, first of all, there are exchanges. You know, you can convert USD to ADA, and pay the ADA. But, how much ADA? Technically, what the exchange rate dictates. So, the first approach, the manual one, is:

  • You check the current exchange rate, and find how much ADA per USD.
  • You pay the corresponding amount of ADA for $10.
  • Someone on the other end checks what you paid, and checks the exchange rate. Does the maths, and confirms you paid the agreed amount.

This solution is perfectly viable. But it involves too many manual steps. We didn't sign to the blockchain to do everything manually, didn't we?

For a few ADA more

It is annoying that we have a third party outside the control of Cardano: the exchange. Whatever we do is dictated by someone going to the exchange and checking the rate. Let's see if we can fix this.

How do we deal with external factors outside the control of Cardano? With oracles. In the Cardano world, an oracle is a piece of data, signed by someone we trust, that we can use to measure these external factors and use them in a smart contract. Let's explore more the details of it:

  • A piece of data: any data can be part of an oracle, but usually you want to put in the oracle something that you can't get from the blockchain. Examples: exchange rate of USD/ADA at a certain time, interest rate at a certain point, affirmation that a stakeholder followed his part of a contract.
  • Signed by someone we trust: Technically, you can claim the exchange rate to be any rate you want, or that the interest rate is zero, or minus 100, or infinite, or you can claim that you successfully bought all the shares in a company. You can claim (lie) anything you want, but the world may not believe you. So, for the world to believe you, you have to provide a signature of the data from someone trustworthy. And, this trusty someone will probably want to keep his trustworthiness by only signing true stuff.

So, going back again to the question: how do we pay 10inADA?BypayingsomeADAamount,andprovidingproof(anoracle)thatthisADAisactually10 in ADA? By paying some ADA amount, and providing proof (an oracle) that this ADA is actually10.

For our pay $10 contract, we need an oracle that characterises the exchange rate. There are two ways: we can provide the total amount of ADA to be paid, or we can provide the total amount of USD to be paid, and the exchange rate. And the total amount of ADA, the total amount of USD and the exchange rate have to be provided by someone we trust, not by some wacko we give some pennies to say anything.

The buyer, the seller and the exchange

Let's go with the total amount of ADA to be paid approach. It simplifies the logic a little bit, and is complex enough to start understanding what goes on. So, our steps now will be:

  • You go to an exchange, and get an oracle signed by the exchange stating that $10 is 121ADA as today with current time. You may have to pay for this service, or maybe the exchange provides it for free as part of having an account with them.
  • You pay ADA121 to the smart contract, and provide the $10-is-ADA121 oracle with your payment.
  • The other part collects the smart contract. For that to happen, the smart contract will have to check that the oracle is indeed signed by the exchange, that the amount you paid - ADA121 - indeed is the amount the oracle claims you have to pay, and finally that the timestamp of payment is not significantly different from the timestamp of the oracle.

Why do we need the smart contract to check that many details? Let's see:

  • The oracle is signed by the exchange: so you can't try to cheat out by providing a crazy exchange rate. The exchange rate has to be provided by a real exchange, and the only way to prove it is by having the exchange sign it.
  • You paid what the oracle says: well, this is obvious, isn't it? But, it may span further questions: what if we overpay? Do we get some ADA back? What if we underpay? Can we add the ADA left later?
  • The timestamp of the payment is not significantly different from the timestamp of the oracle: exchange rates fluctuate all the time. If you expect the ADA exchange rate to go down, you may want to get an oracle now with the expensive exchange rate, wait a bit for it to fall, and then pay with cheap ADA. No online exchange or shop would admit such cheat, and we have to check it on the smart contract.

The smart contract

Let's work on the smart contract to deliver this functionality. The main idea is that the payer will adjunt a DataScript with the oracle, whereas, in many cases, the oracle comes in the RedeemerScript.

Let's start with the datatypes to be used in the smart contract. We need a datatype for the content of the oracle. It will be:

data Usd10Payment = Usd10Payment {
    u10AdaToPay :: Value,
    u10ValidRange :: SlotRange
  }

PlutusTx.makeLift ''Usd10Payment

As you can see, there is nothing oracle-ish about it. The real deal comes in the Validator:

usd10Validator :: PubKey -> PubKey -> ValidatorScript
usd10Validator ex seller = ValidatorScript $ validator `applyScript` (Ledger.lifted ex) `applyScript` (Ledger.lifted seller)
  where
    validator = ($$(Ledger.compileScript [||
      \ (exchangePk :: PubKey)
        (sellerPk :: PubKey)
        (ds :: OracleValue Usd10Payment)  -- Oracle goes here
        (a :: Action)
        (tx :: PendingTx) ->

But, before describing the Validator, we need to know about Action:

data Action
  = AcceptPayment

PlutusTx.makeLift ''Action

Action is a simple ADT for describing what kinds of things we can do with the funds in the smart contract. For now, the Seller can AcceptPayment. Later we will see to add more actions.

Let's jump now to the Validator. The validator is configurable, accepting as parameters the public keys of the exchange and the seller. It is made of several parts. First, some boilerplate and common function declaration:

usd10Validator :: PubKey -> PubKey -> ValidatorScript
usd10Validator ex seller = ValidatorScript $ validator `applyScript` (Ledger.lifted ex) `applyScript` (Ledger.lifted seller)
  where
    validator = ($$(Ledger.compileScript [||
      \ (exchangePk :: PubKey)
        (sellerPk :: PubKey)
        (ds :: OracleValue Usd10Payment)  -- Oracle goes here
        (a :: Action)
        (tx :: PendingTx) ->
      let
          (&&) :: Bool -> Bool -> Bool
          (&&) = $$(P.and)

          failWith :: String -> a
          failWith s = $$(P.traceH) s ($$(P.error) ())

          isValidExchangePk :: PubKey -> Bool
          isValidExchangePk pk = $$(eqPubKey) pk exchangePk

With this, we can use the && operator and the failWith function in the rest of the contract. We have decided to have a single valid exchange for now, although a better contract may demand having several, and the oracle to be signed by any of them.

And now, we can start unpacking fields and doing general validation:

        PendingTx pendingTxIns pendingTxOuts _ _ pendingTxIn pendingTxValidRange = tx

        verifyOracle :: OracleValue a -> (Slot, a)
        verifyOracle (OracleValue pk h t) | isValidExchangePk pk = (h, t)
        verifyOracle _ = failWith "Invalid oracle"

        (_, Usd10Payment {
          u10AdaToPay=ada,
          u10ValidRange=validRange
        }) = verifyOracle ds

After exploring several approaches for constructing and validating smart contracts, I have found that having functions that expect and validate, or otherwise failWith, generates the most understandable contracts. In production I would probably erase most of the error messages, but for testing is very helpful. In this case, the first check that we do is ensure that the oracle is signed by a valid exchange public key, otherwise reject the transaction with an "Invalid oracle" error. If we succeed, we unpack the fields to be used later.

Now we can do the Action-specific validation:

    case a of
      AcceptPayment ->
        let
            -- Check that the oracle is valid for the transaction
            slotIsRight = $$(Slot.contains) validRange pendingTxValidRange

            -- Check that is the seller the one claiming the transaction
            destinationIsSeller = case pendingTxOuts of
              [PendingTxOut {pendingTxOutData=PubKeyTxOut pk}] | $$(eqPubKey) pk sellerPk -> True
              [PendingTxOut {pendingTxOutData=PubKeyTxOut _}] -> failWith "Different destination"
              _ -> failWith "More than one destination"

            -- Check that the amount being paid is the same as the oracle states
            amountIsRight = case pendingTxOuts of
              [PendingTxOut {pendingTxOutValue=val}] | $$(Value.eq) val ada -> True
              [PendingTxOut {pendingTxOutData=_}] -> failWith "Different amount of ADA"
              _ -> failWith "More than one destination"
        in
        if slotIsRight && destinationIsSeller && amountIsRight
        then ()
        else $$(P.error) ()

For AcceptPayment to be valid:

  • The payment has to be redeemed in the slot range where the oracle states the exchange rate is valid.
  • There should be a single transaction output, and that output has to be the public key of the seller.
  • The ADA to be paid should be exactly the same as the oracle states.

If all of this is correct, then the transaction is valid. On any failure, we get an error.

With the smart contract in place, we can make our lives easier with some smart contract helpers:

contractAddress :: PubKey -> PubKey -> Address
contractAddress expk sepk = Ledger.scriptAddress (usd10Validator expk sepk)

buyUSD10 :: (WalletAPI m, WalletDiagnostics m) => PubKey -> PubKey -> OracleValue Usd10Payment -> m ()
buyUSD10 expk sepk o = payToScript_ defaultSlotRange (contractAddress expk sepk) vl ds
  where
    vl = u10AdaToPay $ ovValue o
    ds = DataScript (lifted o)

acceptPayments :: (WalletAPI m, WalletDiagnostics m) => PubKey -> PubKey -> m ()
acceptPayments expk sepk = do
                  s <- slot
                  collectFromScript (mkInterval s) (usd10Validator expk sepk) (RedeemerScript $ lifted AcceptPayment)
  where
    mkInterval :: Slot -> Interval Slot
    mkInterval (Slot s) = Interval (Just (Slot s)) (Just (Slot $ s + 3))

The contract address is always helpful, specially for listening and paying to that address. buyUSD10 just prepares the transaction with the oracle and proceeds to pay the right amount. Finally, acceptPayment just collects with the AcceptPayment action.

Next steps

We stated some limitations previously:

  • Underpaying/overpaying: Shall we wait for extra funds? Accept more transactions? Accept transactions with change?
  • Refunds for invalid transactions: What if the seller doesn't redeem the funds in time? What if we provide an invalid oracle? We have no way to close the transaction in that case. Shall these funds be locked forever in the smart contract?
  • How do we collect individual transactions from the smart contract? Collecting transactions on which the oracles don't agree may be impossible, as there may not exist an slot that satisfies all the transactions. So trying to collect all of them at the same time will fail. We need to do better.

As you can see, this smart contract doesn't cover these bits, and it should. On the next article, we will improve the pay-USD10-in-ADA smart contract to address these limitations. Until then, go play with the code at https://github.com/javcasas/smart-contract-samples/tree/master/pay-usd10-smart-contract-1!

  • Are you looking for a way to build your dApp on Cardano?
  • Do you need someone to kickstart your next product using Plutus?
  • Contact Javier Casas
Back to index
Copyright © 2018-2023 Javier Casas - All rights reserved.