plutus-pioneer-program/code/week02/src/Week02/Burn.hs

77 lines
2.8 KiB
Haskell
Raw Normal View History

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 #-}
2021-04-12 22:59:51 +02:00
module Week02.Burn where
2021-04-09 23:41:16 +02:00
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-12 22:59:51 +02:00
{-# INLINABLE mkValidator #-}
mkValidator :: Data -> Data -> Data -> ()
mkValidator _ _ _ = traceError "NO WAY!"
2021-04-09 23:41:16 +02:00
2021-04-12 22:59:51 +02:00
validator :: Validator
validator = mkValidatorScript $$(PlutusTx.compile [|| mkValidator ||])
2021-04-09 23:41:16 +02:00
2021-04-12 22:59:51 +02:00
valHash :: Ledger.ValidatorHash
valHash = Scripts.validatorHash validator
2021-04-09 23:41:16 +02:00
2021-04-12 22:59:51 +02:00
scrAddress :: Ledger.Address
scrAddress = ScriptAddress valHash
2021-04-09 23:41:16 +02:00
2021-04-12 22:59:51 +02:00
type GiftSchema =
2021-04-09 23:41:16 +02:00
BlockchainActions
2021-04-12 22:59:51 +02:00
.\/ Endpoint "give" Integer
2021-04-09 23:41:16 +02:00
.\/ Endpoint "grab" ()
2021-04-12 22:59:51 +02:00
give :: (HasBlockchainActions s, AsContractError e) => Integer -> Contract w s e ()
give amount = do
let tx = mustPayToOtherScript valHash (Datum $ Constr 0 []) $ Ada.lovelaceValueOf amount
2021-04-09 23:41:16 +02:00
ledgerTx <- submitTx tx
void $ awaitTxConfirmed $ txId ledgerTx
2021-04-12 22:59:51 +02:00
logInfo @String $ printf "made a gift of %d lovelace" amount
2021-04-09 23:41:16 +02:00
grab :: forall w s e. (HasBlockchainActions s, AsContractError e) => Contract w s e ()
grab = do
2021-04-12 22:59:51 +02:00
utxos <- utxoAt scrAddress
2021-04-09 23:41:16 +02:00
let orefs = fst <$> Map.toList utxos
lookups = Constraints.unspentOutputs utxos <>
2021-04-12 22:59:51 +02:00
Constraints.otherScript validator
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-12 22:59:51 +02:00
endpoints :: Contract () GiftSchema Text ()
2021-04-09 23:41:16 +02:00
endpoints = (give' `select` grab') >> endpoints
where
2021-04-12 22:59:51 +02:00
give' = endpoint @"give" >>= give
2021-04-09 23:41:16 +02:00
grab' = endpoint @"grab" >> grab
2021-04-12 22:59:51 +02:00
mkSchemaDefinitions ''GiftSchema
2021-04-09 23:41:16 +02:00
mkKnownCurrencies []