mirror of
https://github.com/FiloSpaTeam/plutus-pioneer-program.git
synced 2024-11-22 14:52:26 +01:00
Update Week 1 and 2 files to Week 3 env.
This commit is contained in:
parent
83d437c32e
commit
50ee6b0394
11 changed files with 31 additions and 29 deletions
|
@ -22,7 +22,8 @@ source-repository-package
|
||||||
plutus-tx
|
plutus-tx
|
||||||
plutus-tx-plugin
|
plutus-tx-plugin
|
||||||
prettyprinter-configurable
|
prettyprinter-configurable
|
||||||
tag: 3746610e53654a1167aeb4c6294c6096d16b0502
|
quickcheck-dynamic
|
||||||
|
tag: 3aa86304e9bfc425667051a8a94db73fcdc38878
|
||||||
|
|
||||||
-- The following sections are copied from the 'plutus' repository cabal.project at the revision
|
-- The following sections are copied from the 'plutus' repository cabal.project at the revision
|
||||||
-- given above.
|
-- given above.
|
||||||
|
|
|
@ -110,7 +110,7 @@ minBid AuctionDatum{..} = case adHighestBid of
|
||||||
Just Bid{..} -> bBid + 1
|
Just Bid{..} -> bBid + 1
|
||||||
|
|
||||||
{-# INLINABLE mkAuctionValidator #-}
|
{-# INLINABLE mkAuctionValidator #-}
|
||||||
mkAuctionValidator :: AuctionDatum -> AuctionAction -> ValidatorCtx -> Bool
|
mkAuctionValidator :: AuctionDatum -> AuctionAction -> ScriptContext -> Bool
|
||||||
mkAuctionValidator ad redeemer ctx =
|
mkAuctionValidator ad redeemer ctx =
|
||||||
traceIfFalse "wrong input value" correctInputValue &&
|
traceIfFalse "wrong input value" correctInputValue &&
|
||||||
case redeemer of
|
case redeemer of
|
||||||
|
@ -131,12 +131,12 @@ mkAuctionValidator ad redeemer ctx =
|
||||||
|
|
||||||
where
|
where
|
||||||
info :: TxInfo
|
info :: TxInfo
|
||||||
info = valCtxTxInfo ctx
|
info = scriptContextTxInfo ctx
|
||||||
|
|
||||||
input :: TxInInfo
|
input :: TxInInfo
|
||||||
input =
|
input =
|
||||||
let
|
let
|
||||||
isScriptInput i = case txInInfoWitness i of
|
isScriptInput i = case (txOutDatumHash . txInInfoResolved) i of
|
||||||
Nothing -> False
|
Nothing -> False
|
||||||
Just _ -> True
|
Just _ -> True
|
||||||
xs = [i | i <- txInfoInputs info, isScriptInput i]
|
xs = [i | i <- txInfoInputs info, isScriptInput i]
|
||||||
|
@ -146,7 +146,7 @@ mkAuctionValidator ad redeemer ctx =
|
||||||
_ -> traceError "expected exactly one script input"
|
_ -> traceError "expected exactly one script input"
|
||||||
|
|
||||||
inVal :: Value
|
inVal :: Value
|
||||||
inVal = txInInfoValue input
|
inVal = txOutValue . txInInfoResolved $ input
|
||||||
|
|
||||||
auction :: Auction
|
auction :: Auction
|
||||||
auction = adAuction ad
|
auction = adAuction ad
|
||||||
|
@ -162,12 +162,12 @@ mkAuctionValidator ad redeemer ctx =
|
||||||
sufficientBid :: Integer -> Bool
|
sufficientBid :: Integer -> Bool
|
||||||
sufficientBid amount = amount >= minBid ad
|
sufficientBid amount = amount >= minBid ad
|
||||||
|
|
||||||
ownOutput :: TxOutInfo
|
ownOutput :: TxOut
|
||||||
outputDatum :: AuctionDatum
|
outputDatum :: AuctionDatum
|
||||||
(ownOutput, outputDatum) = case getContinuingOutputs ctx of
|
(ownOutput, outputDatum) = case getContinuingOutputs ctx of
|
||||||
[o] -> case txOutType o of
|
[o] -> case txOutDatumHash o of
|
||||||
PayToPubKey -> traceError "wrong output type"
|
Nothing -> traceError "wrong output type"
|
||||||
PayToScript h -> case findDatum h info of
|
Just h -> case findDatum h info of
|
||||||
Nothing -> traceError "datum not found"
|
Nothing -> traceError "datum not found"
|
||||||
Just (Datum d) -> case PlutusTx.fromData d of
|
Just (Datum d) -> case PlutusTx.fromData d of
|
||||||
Just ad' -> (o, ad')
|
Just ad' -> (o, ad')
|
||||||
|
@ -189,7 +189,7 @@ mkAuctionValidator ad redeemer ctx =
|
||||||
let
|
let
|
||||||
os = [ o
|
os = [ o
|
||||||
| o <- txInfoOutputs info
|
| o <- txInfoOutputs info
|
||||||
, txOutAddress o == PubKeyAddress bBidder
|
, txOutAddress o == pubKeyHashAddress bBidder
|
||||||
]
|
]
|
||||||
in
|
in
|
||||||
case os of
|
case os of
|
||||||
|
@ -210,7 +210,7 @@ mkAuctionValidator ad redeemer ctx =
|
||||||
, txOutValue o' == v
|
, txOutValue o' == v
|
||||||
]
|
]
|
||||||
in
|
in
|
||||||
txOutAddress o == PubKeyAddress h
|
txOutAddress o == pubKeyHashAddress h
|
||||||
|
|
||||||
auctionInstance :: Scripts.ScriptInstance Auctioning
|
auctionInstance :: Scripts.ScriptInstance Auctioning
|
||||||
auctionInstance = Scripts.validator @Auctioning
|
auctionInstance = Scripts.validator @Auctioning
|
||||||
|
@ -226,7 +226,7 @@ auctionHash :: Ledger.ValidatorHash
|
||||||
auctionHash = Scripts.validatorHash auctionValidator
|
auctionHash = Scripts.validatorHash auctionValidator
|
||||||
|
|
||||||
auctionAddress :: Ledger.Address
|
auctionAddress :: Ledger.Address
|
||||||
auctionAddress = ScriptAddress auctionHash
|
auctionAddress = scriptHashAddress auctionHash
|
||||||
|
|
||||||
data StartParams = StartParams
|
data StartParams = StartParams
|
||||||
{ spDeadline :: !Slot
|
{ spDeadline :: !Slot
|
||||||
|
@ -336,15 +336,15 @@ findAuction :: HasBlockchainActions s
|
||||||
-> TokenName
|
-> TokenName
|
||||||
-> Contract w s Text (TxOutRef, TxOutTx, AuctionDatum)
|
-> Contract w s Text (TxOutRef, TxOutTx, AuctionDatum)
|
||||||
findAuction cs tn = do
|
findAuction cs tn = do
|
||||||
utxos <- utxoAt $ ScriptAddress auctionHash
|
utxos <- utxoAt $ scriptHashAddress auctionHash
|
||||||
let xs = [ (oref, o)
|
let xs = [ (oref, o)
|
||||||
| (oref, o) <- Map.toList utxos
|
| (oref, o) <- Map.toList utxos
|
||||||
, Value.valueOf (txOutValue $ txOutTxOut o) cs tn == 1
|
, Value.valueOf (txOutValue $ txOutTxOut o) cs tn == 1
|
||||||
]
|
]
|
||||||
case xs of
|
case xs of
|
||||||
[(oref, o)] -> case txOutType $ txOutTxOut o of
|
[(oref, o)] -> case txOutDatumHash $ txOutTxOut o of
|
||||||
PayToPubKey -> throwError "unexpected out type"
|
Nothing -> throwError "unexpected out type"
|
||||||
PayToScript h -> case Map.lookup h $ txData $ txOutTxTx o of
|
Just h -> case Map.lookup h $ txData $ txOutTxTx o of
|
||||||
Nothing -> throwError "datum not found"
|
Nothing -> throwError "datum not found"
|
||||||
Just (Datum e) -> case PlutusTx.fromData e of
|
Just (Datum e) -> case PlutusTx.fromData e of
|
||||||
Nothing -> throwError "datum has wrong type"
|
Nothing -> throwError "datum has wrong type"
|
||||||
|
|
|
@ -22,7 +22,8 @@ source-repository-package
|
||||||
plutus-tx
|
plutus-tx
|
||||||
plutus-tx-plugin
|
plutus-tx-plugin
|
||||||
prettyprinter-configurable
|
prettyprinter-configurable
|
||||||
tag: 3746610e53654a1167aeb4c6294c6096d16b0502
|
quickcheck-dynamic
|
||||||
|
tag: 3aa86304e9bfc425667051a8a94db73fcdc38878
|
||||||
|
|
||||||
-- The following sections are copied from the 'plutus' repository cabal.project at the revision
|
-- The following sections are copied from the 'plutus' repository cabal.project at the revision
|
||||||
-- given above.
|
-- given above.
|
||||||
|
|
|
@ -41,7 +41,7 @@ valHash :: Ledger.ValidatorHash
|
||||||
valHash = Scripts.validatorHash validator
|
valHash = Scripts.validatorHash validator
|
||||||
|
|
||||||
scrAddress :: Ledger.Address
|
scrAddress :: Ledger.Address
|
||||||
scrAddress = ScriptAddress valHash
|
scrAddress = scriptHashAddress valHash
|
||||||
|
|
||||||
type GiftSchema =
|
type GiftSchema =
|
||||||
BlockchainActions
|
BlockchainActions
|
||||||
|
|
|
@ -38,7 +38,7 @@ valHash :: Ledger.ValidatorHash
|
||||||
valHash = Scripts.validatorHash validator
|
valHash = Scripts.validatorHash validator
|
||||||
|
|
||||||
scrAddress :: Ledger.Address
|
scrAddress :: Ledger.Address
|
||||||
scrAddress = ScriptAddress valHash
|
scrAddress = scriptHashAddress valHash
|
||||||
|
|
||||||
type GiftSchema =
|
type GiftSchema =
|
||||||
BlockchainActions
|
BlockchainActions
|
||||||
|
|
|
@ -31,7 +31,7 @@ import Text.Printf (printf)
|
||||||
|
|
||||||
{-# INLINABLE mkValidator #-}
|
{-# INLINABLE mkValidator #-}
|
||||||
-- This should validate if and only if the two Booleans in the redeemer are equal!
|
-- This should validate if and only if the two Booleans in the redeemer are equal!
|
||||||
mkValidator :: () -> (Bool, Bool) -> ValidatorCtx -> Bool
|
mkValidator :: () -> (Bool, Bool) -> ScriptContext -> Bool
|
||||||
mkValidator _ _ _ = True -- FIX ME!
|
mkValidator _ _ _ = True -- FIX ME!
|
||||||
|
|
||||||
data Typed
|
data Typed
|
||||||
|
|
|
@ -42,7 +42,7 @@ PlutusTx.unstableMakeIsData ''MyRedeemer
|
||||||
|
|
||||||
{-# INLINABLE mkValidator #-}
|
{-# INLINABLE mkValidator #-}
|
||||||
-- This should validate if and only if the two Booleans in the redeemer are equal!
|
-- This should validate if and only if the two Booleans in the redeemer are equal!
|
||||||
mkValidator :: () -> MyRedeemer -> ValidatorCtx -> Bool
|
mkValidator :: () -> MyRedeemer -> ScriptContext -> Bool
|
||||||
mkValidator _ _ _ = True -- FIX ME!
|
mkValidator _ _ _ = True -- FIX ME!
|
||||||
|
|
||||||
data Typed
|
data Typed
|
||||||
|
|
|
@ -35,7 +35,7 @@ newtype MySillyRedeemer = MySillyRedeemer Integer
|
||||||
PlutusTx.unstableMakeIsData ''MySillyRedeemer
|
PlutusTx.unstableMakeIsData ''MySillyRedeemer
|
||||||
|
|
||||||
{-# INLINABLE mkValidator #-}
|
{-# INLINABLE mkValidator #-}
|
||||||
mkValidator :: () -> MySillyRedeemer -> ValidatorCtx -> Bool
|
mkValidator :: () -> MySillyRedeemer -> ScriptContext -> Bool
|
||||||
mkValidator () (MySillyRedeemer r) _ = traceIfFalse "wrong redeemer" $ r == 42
|
mkValidator () (MySillyRedeemer r) _ = traceIfFalse "wrong redeemer" $ r == 42
|
||||||
|
|
||||||
data Typed
|
data Typed
|
||||||
|
@ -57,7 +57,7 @@ valHash :: Ledger.ValidatorHash
|
||||||
valHash = Scripts.validatorHash validator
|
valHash = Scripts.validatorHash validator
|
||||||
|
|
||||||
scrAddress :: Ledger.Address
|
scrAddress :: Ledger.Address
|
||||||
scrAddress = ScriptAddress valHash
|
scrAddress = scriptHashAddress valHash
|
||||||
|
|
||||||
type GiftSchema =
|
type GiftSchema =
|
||||||
BlockchainActions
|
BlockchainActions
|
||||||
|
|
|
@ -31,7 +31,7 @@ import Text.Printf (printf)
|
||||||
|
|
||||||
{-# INLINABLE mkValidator #-}
|
{-# INLINABLE mkValidator #-}
|
||||||
-- This should validate if and only if the two Booleans in the redeemer are equal!
|
-- This should validate if and only if the two Booleans in the redeemer are equal!
|
||||||
mkValidator :: () -> (Bool, Bool) -> ValidatorCtx -> Bool
|
mkValidator :: () -> (Bool, Bool) -> ScriptContext -> Bool
|
||||||
mkValidator () (b, c) _ = traceIfFalse "wrong redeemer" $ b == c
|
mkValidator () (b, c) _ = traceIfFalse "wrong redeemer" $ b == c
|
||||||
|
|
||||||
data Typed
|
data Typed
|
||||||
|
@ -53,7 +53,7 @@ valHash :: Ledger.ValidatorHash
|
||||||
valHash = Scripts.validatorHash validator
|
valHash = Scripts.validatorHash validator
|
||||||
|
|
||||||
scrAddress :: Ledger.Address
|
scrAddress :: Ledger.Address
|
||||||
scrAddress = ScriptAddress valHash
|
scrAddress = scriptHashAddress valHash
|
||||||
|
|
||||||
type GiftSchema =
|
type GiftSchema =
|
||||||
BlockchainActions
|
BlockchainActions
|
||||||
|
|
|
@ -42,7 +42,7 @@ PlutusTx.unstableMakeIsData ''MyRedeemer
|
||||||
|
|
||||||
{-# INLINABLE mkValidator #-}
|
{-# INLINABLE mkValidator #-}
|
||||||
-- This should validate if and only if the two Booleans in the redeemer are equal!
|
-- This should validate if and only if the two Booleans in the redeemer are equal!
|
||||||
mkValidator :: () -> MyRedeemer -> ValidatorCtx -> Bool
|
mkValidator :: () -> MyRedeemer -> ScriptContext -> Bool
|
||||||
mkValidator () (MyRedeemer b c) _ = traceIfFalse "wrong redeemer" $ b == c
|
mkValidator () (MyRedeemer b c) _ = traceIfFalse "wrong redeemer" $ b == c
|
||||||
|
|
||||||
data Typed
|
data Typed
|
||||||
|
@ -64,7 +64,7 @@ valHash :: Ledger.ValidatorHash
|
||||||
valHash = Scripts.validatorHash validator
|
valHash = Scripts.validatorHash validator
|
||||||
|
|
||||||
scrAddress :: Ledger.Address
|
scrAddress :: Ledger.Address
|
||||||
scrAddress = ScriptAddress valHash
|
scrAddress = scriptHashAddress valHash
|
||||||
|
|
||||||
type GiftSchema =
|
type GiftSchema =
|
||||||
BlockchainActions
|
BlockchainActions
|
||||||
|
|
|
@ -30,7 +30,7 @@ import Prelude (Semigroup (..))
|
||||||
import Text.Printf (printf)
|
import Text.Printf (printf)
|
||||||
|
|
||||||
{-# INLINABLE mkValidator #-}
|
{-# INLINABLE mkValidator #-}
|
||||||
mkValidator :: () -> Integer -> ValidatorCtx -> Bool
|
mkValidator :: () -> Integer -> ScriptContext -> Bool
|
||||||
mkValidator () r _
|
mkValidator () r _
|
||||||
| r == 42 = True
|
| r == 42 = True
|
||||||
| otherwise = False
|
| otherwise = False
|
||||||
|
@ -54,7 +54,7 @@ valHash :: Ledger.ValidatorHash
|
||||||
valHash = Scripts.validatorHash validator
|
valHash = Scripts.validatorHash validator
|
||||||
|
|
||||||
scrAddress :: Ledger.Address
|
scrAddress :: Ledger.Address
|
||||||
scrAddress = ScriptAddress valHash
|
scrAddress = scriptHashAddress valHash
|
||||||
|
|
||||||
type GiftSchema =
|
type GiftSchema =
|
||||||
BlockchainActions
|
BlockchainActions
|
||||||
|
|
Loading…
Reference in a new issue