2021-04-09 23:41:16 +02:00
|
|
|
{-# LANGUAGE DataKinds #-}
|
|
|
|
{-# LANGUAGE FlexibleContexts #-}
|
|
|
|
{-# LANGUAGE NoImplicitPrelude #-}
|
|
|
|
{-# LANGUAGE OverloadedStrings #-}
|
|
|
|
{-# LANGUAGE ScopedTypeVariables #-}
|
|
|
|
{-# LANGUAGE TemplateHaskell #-}
|
|
|
|
{-# LANGUAGE TypeApplications #-}
|
|
|
|
{-# LANGUAGE TypeFamilies #-}
|
|
|
|
{-# LANGUAGE TypeOperators #-}
|
|
|
|
|
|
|
|
module Week02.Burn
|
|
|
|
( burn
|
|
|
|
, grab
|
2021-04-10 00:08:26 +02:00
|
|
|
, BurnSchema
|
2021-04-09 23:41:16 +02:00
|
|
|
, endpoints
|
|
|
|
, schemas
|
|
|
|
, registeredKnownCurrencies
|
|
|
|
, printJson
|
|
|
|
, printSchemas
|
|
|
|
, ensureKnownCurrencies
|
|
|
|
, stage
|
|
|
|
) where
|
|
|
|
|
|
|
|
import Control.Monad hiding (fmap)
|
|
|
|
import Data.Map as Map
|
|
|
|
import Data.Text (Text)
|
|
|
|
import Data.Void (Void)
|
|
|
|
import Plutus.Contract hiding (when)
|
|
|
|
import PlutusTx (Data (..))
|
|
|
|
import qualified PlutusTx
|
|
|
|
import PlutusTx.Prelude hiding (Semigroup(..), unless)
|
|
|
|
import Ledger hiding (singleton)
|
|
|
|
import Ledger.Constraints as Constraints
|
|
|
|
import qualified Ledger.Scripts as Scripts
|
|
|
|
import Ledger.Ada as Ada
|
|
|
|
import Playground.Contract (printJson, printSchemas, ensureKnownCurrencies, stage)
|
|
|
|
import Playground.TH (mkKnownCurrencies, mkSchemaDefinitions)
|
|
|
|
import Playground.Types (KnownCurrency (..))
|
|
|
|
import Prelude (Semigroup (..))
|
|
|
|
import Text.Printf (printf)
|
|
|
|
|
2021-04-10 00:33:33 +02:00
|
|
|
{-# INLINABLE mkBurnValidator #-}
|
|
|
|
mkBurnValidator :: Data -> Data -> Data -> ()
|
|
|
|
mkBurnValidator _ _ _ = traceError "NO WAY!"
|
2021-04-09 23:41:16 +02:00
|
|
|
|
2021-04-10 00:33:33 +02:00
|
|
|
burnValidator :: Validator
|
|
|
|
burnValidator = mkValidatorScript $$(PlutusTx.compile [|| mkBurnValidator ||])
|
2021-04-09 23:41:16 +02:00
|
|
|
|
2021-04-10 00:33:33 +02:00
|
|
|
burnHash :: Ledger.ValidatorHash
|
|
|
|
burnHash = Scripts.validatorHash burnValidator
|
2021-04-09 23:41:16 +02:00
|
|
|
|
2021-04-10 00:33:33 +02:00
|
|
|
burnAddress :: Ledger.Address
|
|
|
|
burnAddress = ScriptAddress burnHash
|
2021-04-09 23:41:16 +02:00
|
|
|
|
2021-04-10 00:08:26 +02:00
|
|
|
type BurnSchema =
|
2021-04-09 23:41:16 +02:00
|
|
|
BlockchainActions
|
|
|
|
.\/ Endpoint "burn" Integer
|
|
|
|
.\/ Endpoint "grab" ()
|
|
|
|
|
|
|
|
burn :: (HasBlockchainActions s, AsContractError e) => Integer -> Contract w s e ()
|
|
|
|
burn amount = do
|
2021-04-10 00:33:33 +02:00
|
|
|
let tx = mustPayToOtherScript burnHash (Datum $ Constr 0 []) $ Ada.lovelaceValueOf amount
|
2021-04-09 23:41:16 +02:00
|
|
|
ledgerTx <- submitTx tx
|
|
|
|
void $ awaitTxConfirmed $ txId ledgerTx
|
|
|
|
logInfo @String $ printf "burnt %d lovelace" amount
|
|
|
|
|
|
|
|
grab :: forall w s e. (HasBlockchainActions s, AsContractError e) => Contract w s e ()
|
|
|
|
grab = do
|
2021-04-10 00:33:33 +02:00
|
|
|
utxos <- utxoAt $ ScriptAddress burnHash
|
2021-04-09 23:41:16 +02:00
|
|
|
let orefs = fst <$> Map.toList utxos
|
|
|
|
lookups = Constraints.unspentOutputs utxos <>
|
2021-04-10 00:33:33 +02:00
|
|
|
Constraints.otherScript burnValidator
|
2021-04-09 23:41:16 +02:00
|
|
|
tx :: TxConstraints Void Void
|
|
|
|
tx = mconcat [mustSpendScriptOutput oref $ Redeemer $ I 17 | oref <- orefs]
|
|
|
|
ledgerTx <- submitTxConstraintsWith @Void lookups tx
|
|
|
|
void $ awaitTxConfirmed $ txId ledgerTx
|
|
|
|
logInfo @String $ "collected gifts"
|
|
|
|
|
2021-04-10 00:08:26 +02:00
|
|
|
endpoints :: Contract () BurnSchema Text ()
|
2021-04-09 23:41:16 +02:00
|
|
|
endpoints = (give' `select` grab') >> endpoints
|
|
|
|
where
|
|
|
|
give' = endpoint @"burn" >>= burn
|
|
|
|
grab' = endpoint @"grab" >> grab
|
|
|
|
|
2021-04-10 00:08:26 +02:00
|
|
|
mkSchemaDefinitions ''BurnSchema
|
2021-04-09 23:41:16 +02:00
|
|
|
|
|
|
|
mkKnownCurrencies []
|