Mary era NFTs, Alonzo era NFTs, which are better?

I just published a new NFT project on the Cardano blockchain, we are minting all our NFTs using the following Plutus script:

{-# INLINABLE mkNFTPolicy #-}
mkNFTPolicy :: TokenName -> TxOutRef -> BuiltinData -> ScriptContext -> Bool
mkNFTPolicy tn utxo _ ctx = traceIfFalse "UTxO not consumed"   hasUTxO           &&
                            traceIfFalse "wrong amount minted" checkMintedAmount
  where
    info :: TxInfo
    info = scriptContextTxInfo ctx

    hasUTxO :: Bool
    hasUTxO = any (\i -> txInInfoOutRef i == utxo) $ txInfoInputs info

    checkMintedAmount :: Bool
    checkMintedAmount = case flattenValue (txInfoMint info) of
        [(_, tn', amt)] -> tn' == tn && amt == 1
        _               -> False

The reason we did it like this is that we believe this is the right way of minting NFTs on Cardano, using the time lock policies from the Mary era allows the minter of the NFT to duplicate the token (same policy id + asset name) and he could even “replace” or “destroy the metadata” by issuing a new minting transaction of that asset as the current consensus is to just take the metadata of the latest minting transaction related to that asset.

Now the problem with the Alonzo era NFT is that you have a unique policy id for each NFT (in our case 10000 policy IDs) and this is making it almost impossible to integrate with the current ecosystem of NFT already in place in the Cardano community as they all expect one or just a few policies.

I am curious as to what the developers of the community think about this issue and how are they solving it?

For me is not really acceptable to use an open policy (at least for my project), I believe this partially defeats the purpose of using the blockchain to create digital assets, the whole operation should be trustless, I should not be required to trust the minter not to duplicate or totally destroy the asset I just bought.

But since the whole NFT scene has developed around this “one policy” idea most of the infrastructure out there won’t or can’t integrate with projects with a large number of policies.

I would like to know how other projects are handling this issue?

3 Likes

Here are two approaches for minting multiple Alonzo NFTs under the same policy:

  1. The minting transaction can mint all of the NFTs under the policy in one transaction. Obviously, this won’t let you later mint more under that policy.
  2. Associate the minting validator with a public key hash (not a UTxO), but use a UTxO as the redeemer and derive the asset name from a hash of that UTxO. The policy ID will never change, but (unless there is a hash collision) each minted NFT will be unique. You lose the opportunity to choose the asset name, but the NFT name and ticker can be set in metadata.
4 Likes

You are correct there have not been many verifiable NFT minted using smart contracts as yet. That said most of the CLI minted tokens used the “before” policy to ensure no more tokens could be minted after a certain block/slot.

The simplest way to ensure uniqueness would be to use a UUID algorithm for the asset name (v4 perhaps?) thus preventing hash conflicts across batched or on-demand minting even when using the same policy id for all tokens.

3 Likes

I am aware that the policies use the “before” attribute and expire eventually, but still during the time the policy is open the owner of the policy could re-issue a minting transaction which will duplicate the NFT and modify its metadata if he wishes so.

Ensuring a unique name of the NFT off-chain is also trivial. What I am trying to achieve is to atomically create unique immutable NFTs, enforced by the blockchain, thus removing the need for trust in the minter.

Minting all NFTs in one transaction will only work for a small amount of NFTs, however, if you have a huge collection is not possible.

The second approach you suggest I think is genius, however, the only problem I would see with that is that having a hash as an asset name would make it really hard to find on the wallet, as wallets display the tokens by asset name, especially if they have a huge number of NFT that are using this method, it could become impossible to find the one you want (without using an external resource).

I was thinking maybe a hybrid approach would work great, half the asset name for a prefix and half for the UTXO for example:

Horrocube0238479d0f148a0435dc4

There is a 32 character limit on the asset name so we have to use a small hash, we could just take a section of the UTXO id itself, however, I am having trouble understanding how secure this is, this would mean that to duplicate the NFT the owner of the policy would have to create a UTXO whose last 8 bytes on the ID matches the one used in the mint he is trying to duplicate.

Or to make it even more difficult, reduce the size of the prefix and use more of the UTXO itself:

Hocu0238479d0f148a0435dc4b547a

But still, would this be enough to make it impossible? (In a practical sense).

3 Likes

From a practical standpoint, the probability of a hash collision will be very low for the approaches you outline. I think that a bigger problem is some of the websites for viewing and exploring NFTs would have trouble with binary data in token names, even though they should be using the 721 metadata.

Two additional approaches avoid this problem:

  1. Include a counter in the validator, so that it increments a serial number when minting the next token. Then the token names would have the number appended, like Horrocub123. The validator would have to consume an eUTxO with an NFT for the counter that has datum attached that holds the sequence number of the last NFT minting. The minting transaction for a new NFT would increment that counter in an eUTxO that countains the counter NFT and its new datum. The validator would have to be written carefully, so it provably won’t ever re-use a serial number. (I can explain in more detail or sketch out the logic.)
  2. Include in datums the history of all token names minted under the policy, so that the validator would prevent the reminting under the same name and so that tokens could have whatever names you want (i.e., no hashes or sequence numbers). Each subsequent minting would be more expensive than the previous one, and the validator and off-chain code would have to do a lot of bookkeeping.
2 Likes

Let me see if I understood correctly approach number 3:

Set up an eUTXO with a counter as the datum, have the validator check that said UTXO has been spent and that a new eUTXO with the identifier NFT is being created with the counter increased, add a previous counter to the token name as an append operation. am I correct? this could be a great solution, with 4 byte counter we could have 4294967296 unique asset names under one policy and it would only take 8 spaces from the total 32 available (representing the counter as hex string).

Approach number 4:

Is there a limit on the size of the datum of an eUTXO? for a 10.000 collection and let’s say a 15 char asset name the datum will end up being over 150KB, this would be the safest, but probably more costly approach.

You’re correct about approach 3. It is important that the eUTxO include an NFT that you’ve minted just for the purpose of being attached to the eUTxO with the counter datum and that the validator only accepts datum with where that NFT is present. (Otherwise, there would be security vulnerabilities and/or it would be difficult to prove that the minted tokens are true NFTs.) If you decide to use an approach like this, I’d be happy to review the validator and comment on its security.

For approach 4, you’d eventually need to split the historical data across datum in many UTxOs. This could be expensive and complex, but I suppose that it might be justifiable for some use cases.

1 Like

Thanks a lot, @bwbush, lets see if I can get it right, this is what I have layout so far:

{-# INLINABLE mkNFTPolicy #-}
mkNFTPolicy :: PubKeyHash -> AssetClass -> BuiltinData -> ScriptContext -> Bool
mkNFTPolicy pkh identityNft _ ctx  = 
    let currentDatumValue      = _
        tokenName              = "Horrocube" ++ show currentDatumValue
        isNexDatumValueCorrect = (newDatumValue == (currentDatumValue + 1))
    in  traceIfFalse "Identity NFT not found"         isIdentityNftSpended &&
        traceIfFalse "The new datum value is invalid" isNexDatumValueCorrect &&
        traceIfFalse "Wrong amount minted"            checkMintedAmount
        traceIfFalse "Missing signature"              isTransactionSignedByOwner
    where
      info :: TxInfo
      info = scriptContextTxInfo ctx

      isIdentityNftSpended :: Bool
      isIdentityNftSpended = assetClassValueOf valueSpentByScript identityNft == 1

      checkMintedAmount :: Bool
      checkMintedAmount = case flattenValue (txInfoMint info) of
          [(_, tn', amt)] -> tn' == tokenName && amt == 1
          _               -> False

      valueSpentByScript :: Value
      valueSpentByScript = Validation.valueSpent info

      isTransactionSignedByOwner :: Bool
      isTransactionSignedByOwner = txSignedBy info pkh

      stateDatum :: TxOut -> (DatumHash -> Maybe Datum) -> Maybe StateDatum
      stateDatum o f = do
          dh      <- txOutDatum o
          Datum d <- f dh
          PlutusTx.fromData d

      newDatumValue :: Integer
      newDatumValue = case stateDatum ownOutput (`findDatum` info) of
          Nothing -> traceError "Output datum not found"
          Just datum  -> currentIndex datum

So in the script, I am validating that:

a) The right NFT is being spent (Identity NFT for the eUTXO which will hold the counter)
b) The new datum is prev datum + 1
c) There is exactly one token with asset name “Horrocube” + appended counter being minted (The prefix maybe will be better to have it as another parameter of the validator).
d) The transaction is being signed by the proper key.

The script parameters are the Public Key allowed to mint and the AssetClass of the identity NFT for the eUTXO that will hold the counter.

However, I am not sure how to get the datum of the eUTXO from which the identity NFT is being spent and the datum on of the new eUTXO where the identity NFT is being locked.

1 Like

The validator that you posted looks great. I think you’ll need two validator scripts: a spending validator to increment the counter and the minting validator that you posted.

The spending validator would use findOwnInputs to read the old datum and getContinuingOutputs to read the new datum. (The spending script would check that the increment occurs, so that check wouldn’t actually be needed for in the minting script.)

The minting validator could use txInInfoResolved and txOutValue on each txInfoInputs to locate the input with the identity token holding the datum, and then findDatum and fromData on that to extract the sequence number.

1 Like

Thanks for the pointers @bwbush, I will post it once I have it working.

You mean by spending validator, to have the eUTOX that contains the identity NFT to also enforce the increment of the counter, correct?, out of curiosity, why this can not be done in the minting validator script?

I am really excited about this idea of having the counter included because now I can also enforce that no more tokens than promised (I.E 10.000) will ever be created, adding more guarantees to the process!

2 Likes

Yes. This approach requires spending the eUTxO with the identity token; because that eUTxO holds a datum, the spending must be validated by a script. However, a minting script cannot validate spending—minting validators don’t take a datum as input—, so a spending script is needed. In the end, you’ll have the identity token sitting at the address of the spending script, and each minting transaction will spend it and send it back to the spending script address.

It will be cool to see this running on testnet. Thanks for your great questions!

2 Likes

Hi @bwbush, I just finish the spending script and I have a few questions:

{-|
Module      : Horrocubes.Counter.
Description : Plutus script that keeps track of an internal counter.
License     : Apache-2.0
Maintainer  : angel.castillo@horrocubes.io
Stability   : experimental

This script keeps a counter and increases it everytime the eUTXO is spent.
-}

-- LANGUAGE EXTENSIONS --------------------------------------------------------

{-# LANGUAGE DataKinds                  #-}
{-# LANGUAGE DeriveAnyClass             #-}
{-# LANGUAGE DeriveGeneric              #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE FlexibleContexts           #-}
{-# LANGUAGE MultiParamTypeClasses      #-}
{-# LANGUAGE NoImplicitPrelude          #-}
{-# LANGUAGE OverloadedStrings          #-}
{-# LANGUAGE ScopedTypeVariables        #-}
{-# LANGUAGE TemplateHaskell            #-}
{-# LANGUAGE TypeApplications           #-}
{-# LANGUAGE TypeFamilies               #-}
{-# LANGUAGE TypeOperators              #-}
{-# LANGUAGE DerivingStrategies         #-}
{-# LANGUAGE LambdaCase                 #-}
{-# LANGUAGE NamedFieldPuns             #-}
{-# LANGUAGE ViewPatterns               #-}

-- MODULE DEFINITION ----------------------------------------------------------

module Horrocubes.Counter
(
  counterScript,
  counterScriptShortBs,
  CounterParameter(..)
) where

-- IMPORTS --------------------------------------------------------------------

import           Cardano.Api.Shelley      (PlutusScript (..), PlutusScriptV1)
import           Codec.Serialise
import qualified Data.ByteString.Lazy     as LBS
import qualified Data.ByteString.Short    as SBS
import           Ledger                   hiding (singleton)
import qualified Ledger.Typed.Scripts     as Scripts
import           Ledger.Value             as Value
import qualified PlutusTx
import           PlutusTx.Prelude         as P hiding (Semigroup (..), unless)
import           Data.Aeson               (FromJSON, ToJSON)
import           GHC.Generics             (Generic)
import qualified Ledger.Contexts          as Validation
import           Text.Show

-- DATA TYPES -----------------------------------------------------------------

-- | The parameters for the counter contract.
data CounterParameter = CounterParameter {
        ownerPkh    :: !PubKeyHash, -- ^ The transaction that spends this output must be signed by the private key
        identityNft :: !AssetClass  -- ^ The NFT that identifies the correct eUTXO.
    } deriving (Show, Generic, FromJSON, ToJSON)

PlutusTx.makeLift ''CounterParameter

-- | This Datum represents the state of the counter.
data CounterDatum = CounterDatum {
        counter :: !Integer     -- ^ The current counter value.
    }
    deriving Show

PlutusTx.unstableMakeIsData ''CounterDatum

-- | The Counter script type. Sets the Redeemer and Datum types for this script.
data Counter 
instance Scripts.ValidatorTypes Counter where
    type instance DatumType Counter = CounterDatum
    type instance RedeemerType Counter = ()
    
-- DEFINITIONS ----------------------------------------------------------------

-- | Maybe gets the datum from the transatcion output.
{-# INLINABLE counterDatum #-}
counterDatum :: TxOut -> (DatumHash -> Maybe Datum) -> Maybe CounterDatum
counterDatum o f = do
    dh      <- txOutDatum o
    Datum d <- f dh
    PlutusTx.fromBuiltinData d

-- | Checks that the identity NFT is locked again in the contract.
{-# INLINABLE isIdentityNftRelocked #-}
isIdentityNftRelocked:: CounterParameter -> Value -> Bool
isIdentityNftRelocked params valueLockedByScript = assetClassValueOf valueLockedByScript (identityNft params) == 1

-- | Creates the validator script for the outputs on this contract.
{-# INLINABLE mkCounterValidator #-}
mkCounterValidator :: CounterParameter -> CounterDatum -> () -> ScriptContext -> Bool
mkCounterValidator parameters oldDatum _ ctx = 
    let oldCounterValue        = counter oldDatum
        isRightNexCounterValue = (newDatumValue == (oldCounterValue + 1))
        isIdentityLocked       = isIdentityNftRelocked parameters valueLockedByScript
    in traceIfFalse "Wrong counter value"           isRightNexCounterValue && 
       traceIfFalse "Wrong balance"                 isIdentityLocked && 
       traceIfFalse "Missing signature"             isTransactionSignedByOwner 
    where
        info :: TxInfo
        info = scriptContextTxInfo ctx

        ownOutput :: TxOut
        ownOutput = case getContinuingOutputs ctx of
            [o] -> o
            _   -> traceError "Expected exactly one output"

        newDatumValue :: Integer
        newDatumValue = case counterDatum ownOutput (`findDatum` info) of
            Nothing -> traceError "Counter output datum not found"
            Just datum  -> counter datum

        valueLockedByScript :: Value
        valueLockedByScript = Validation.valueLockedBy info (Validation.ownHash ctx)

        isTransactionSignedByOwner :: Bool
        isTransactionSignedByOwner = txSignedBy info (ownerPkh parameters)

-- | The script instance of the counter. It contains the mkCounterValidator function
--   compiled to a Plutus core validator script.
counterInstance :: CounterParameter -> Scripts.TypedValidator Counter
counterInstance counter = Scripts.mkTypedValidator @Counter
    ($$(PlutusTx.compile [|| mkCounterValidator ||]) `PlutusTx.applyCode` PlutusTx.liftCode counter) $$(PlutusTx.compile [|| wrap ||])
    where
        wrap = Scripts.wrapValidator @CounterDatum @()

-- | Gets the counter validator script that matches the given parameters.
counterValidator :: CounterParameter -> Validator
counterValidator params = Scripts.validatorScript . counterInstance $ params

-- | Generates the plutus script.
counterPlutusScript :: CounterParameter -> Script
counterPlutusScript params = unValidatorScript $ counterValidator params

-- | Serializes the contract in CBOR format.
counterScriptShortBs :: CounterParameter -> SBS.ShortByteString
counterScriptShortBs params = SBS.toShort . LBS.toStrict $ serialise $ counterPlutusScript params

-- | Gets a serizlized plutus script from the given parameters.
counterScript :: PubKeyHash -> AssetClass -> PlutusScript PlutusScriptV1
counterScript pkh ac = PlutusScriptSerialised $ counterScriptShortBs $ CounterParameter { ownerPkh = pkh,  identityNft = ac }
type or paste code here

I already created an instance of the script on the testnet with the appropriate identity NFT inside, you can check the script at the following address:

addr_test1wqesjavxsh7g2q8lf92ptyt7rnrhh07ghnyjq65ra50uwwqsssy2q

cardano-cli query utxo --address addr_test1wqesjavxsh7g2q8lf92ptyt7rnrhh07ghnyjq65ra50uwwqsssy2q --testnet-magic 1097911063
                           TxHash                                 TxIx        Amount
--------------------------------------------------------------------------------------
b2997baf426caa94762e4baeed051ac13bad7994f2f3a43f8c43299d2ba8f050     1        2000000 lovelace + 1 a1c6cefca22b4527acdf17a1d44674b6d7cf17c3e7e35cbd1a57d8b5.Horrocube09997 + TxOutDatumHash ScriptDataInAlonzoEra "03170a2e7597b7b7e3d84c05391d139a62b157e78786d8c082f29dcf4c111314"

The parameters of the script are:

PubKeyHash: 52cdb93f3e798d9c73866450e6e2bfb4a3da911f702ea055e3042dab
AssetClass: a1c6cefca22b4527acdf17a1d44674b6d7cf17c3e7e35cbd1a57d8b5.Horrocube09997

And it was initialized with the datum value 0 (I know this is wrong, as my datum is not an integral type but of CounterDatum type instead).

This is how I am constructing the transaction:

cardano-cli transaction build-raw --alonzo-era --fee 500000  --tx-in b2997baf426caa94762e4baeed051ac13bad7994f2f3a43f8c43299d2ba8f050#0 --tx-in b2997baf426caa94762e4baeed051ac13bad7994f2f3a43f8c43299d2ba8f050#1 --tx-in-script-file ./counter/out2.plutus --tx-in-execution-units "(491845099,1197950)" --tx-in-datum-value 0 --tx-in-redeemer-value 0 --tx-in-collateral b2997baf426caa94762e4baeed051ac13bad7994f2f3a43f8c43299d2ba8f050#0 --tx-out "addr_test1wqesjavxsh7g2q8lf92ptyt7rnrhh07ghnyjq65ra50uwwqsssy2q+2000000+1 a1c6cefca22b4527acdf17a1d44674b6d7cf17c3e7e35cbd1a57d8b5.Horrocube09997" --tx-out-datum-hash ee155ace9c40292074cb6aff8c9ccdd273c81648ff1149ef36bcea6ebb8a3e25 --protocol-params-file protocol.json --out-file tx-script2.build

And after I sign and try to send the transaction I get an error (of course).

I noticed this part in particular:

Datums: [ ( 03170a2e7597b7b7e3d84c05391d139a62b157e78786d8c082f29dcf4c111314\n          , 0 )]

There is only reference to the input datum, but not to the new datum and now that I think about it carefully I am not giving it the new value of the datum, only the hash (which for now is also wrong as it is the datum hash of the integral type 1 and not CounterDatum):

--tx-out-datum-hash ee155ace9c40292074cb6aff8c9ccdd273c81648ff1149ef36bcea6ebb8a3e25

Sorry for the long preamble, now on to the actual questions:

1.- How do you specify the actual value of the new datum using the CLI? It seems it will only let me specify the datum hash of the output, however, if this is the case, how can the script get the actual value of the new datum? hash can not be reversed.

2.- How can we specify non-integral types to the CLI (this one I can probably find on my own).

I apologize for the lengthy post, but I wanted to share as much detail as possible to both share my progress and set the right context for the questions.

Thanks

When you create the eUTxO, you only specify the hash of the datum. When you spend the eUTxO, you supply the datum. So you just need to compute the datum and supply its hash when you create the eUTxO, but remember the datum off-chain so that you can supply it when you spend the eUTxO.

Just use rational numbers (numerator and denominator) or use an integer but with number of decimal places also specfied.

Hi @bwbush thanks for the quick reply:

1.- But the script needs both values, the old datum, and the new datum, If I only provide the value for the old datum, how will the script know the new value from the hash? (The script checks that the new value is equal to the old value +1) It will need to have both values to be able to compare.

The only way to enforce a controlled state transition in the datum within the validator is to have both the new and old values available while spending the script.

What makes me even more confused is that in our Plutus code that we run on the emulator for the other contracts, we actually pass the value for the new datum and not the old datum when we build the transaction:

-- | Tries to solve the ouzzle at the given index.
solve ::  forall w s. HasBlockchainActions s => SolveParams -> Contract w s Text ()
solve solveParams = do
    let cube = CubeParameter { 
        cubeId          = spCubeId solveParams,
        stateMachineNft = spStateMachineNft solveParams
    }
    pkh <- pubKeyHash <$> Contract.ownPubKey
    utxos <- utxoAt $ cubeAddress cube
    addressUtxos <- utxoAt $ pubKeyHashAddress pkh

    let constriants = Constraints.unspentOutputs utxos  <>
                      Constraints.unspentOutputs addressUtxos <>
                      Constraints.otherScript (Scripts.validatorScript (cubeInstance cube))  <>
                      Constraints.scriptInstanceLookups (cubeInstance cube) <> 
                      Constraints.ownPubKeyHash pkh

    m <- findCubeOutput cube
    case m of
        Nothing -> logInfo @String "Cube output not found for solve parameters "
        Just (_, _, dat) -> do
            let datum = dat { currentPuzzleIndex = spPuzzleIndex solveParams + 1 }
                redeemmer = CubeRedeemer (spPuzzleIndex solveParams) (spAnswer solveParams)
                totalValue  = Prelude.foldMap (Tx.txOutValue . Tx.txOutTxOut) utxos
                orefs       = fst <$> Map.toList utxos
                payToSelf   = assetClassValue (cubeId cube) 1 -- We must pay to outselves the cube so we can prove ownership of the cube.
                payToScript = (buildValue cube datum (spPuzzleIndex solveParams) totalValue)
                tx = mconcat [Constraints.mustSpendScriptOutput oref (Redeemer (PlutusTx.toData redeemmer)) | oref <- orefs] <>
                              Constraints.mustPayToTheScript datum payToScript <> 
                              Constraints.mustPayToPubKey pkh payToSelf
            ledgerTx <- submitTxConstraintsWith @Cube constriants tx
            void $ awaitTxConfirmed $ txId ledgerTx

2.- Sorry I expressed myself incorrectly (not a native speaker), I didn’t mean integral types, I guess the right word would be complex type? My datum is a “data” type instead of just an integer, so I am guessing I must somehow express that while calculating the datum hash.

For object type you will want ScriptData schema definition. Assuming you’re using JSON you may find this API documentation useful for how to convert between the off-chain and on-chain format:
https://input-output-hk.github.io/cardano-node/cardano-api/lib/Cardano-Api-ScriptData.html#g:4

1 Like

Thanks, @DinoDude I will check it out, for now, I am using BuiltinData type which should work with the CLI JSON format.

I already figure out how to send the Datum value instead of the hash (someone in this forum had already answered that question) while creating the new eUTXO, I had to update my CLI version to the latest, and now I have these options available:

 [--tx-out ADDRESS VALUE
              [ --tx-out-datum-hash HASH
              | --tx-out-datum-hash-file FILE
              | --tx-out-datum-hash-value JSON VALUE
              | --tx-out-datum-embed-file FILE
              | --tx-out-datum-embed-value JSON VALUE
              ]]

However, I am getting an obscure error when I greater the transaction (not sure if it is because I am passing the value instead of the hash):

The Plutus script evaluation failed: An error has occurred:  User error:
The provided Plutus code called 'error'.
Caused by: [ (builtin unConstrData) (con data #80) ]

It seems it is failing while constructing the builtin data? (this is my datum type), but I am not sure why, this is the format of my json file for the datum:

{"constructor":0,"fields":[{"int":0}]}

And this is how I am building the transaction:

cardano-cli transaction build --alonzo-era --testnet-magic 1097911063  --change-address $(cat counter/payment.addr) --tx-in-collateral 7d65ca46aca44532d94da57ec6b7297efdda2e523626f90bbdc780f3767202f2#0 --tx-in 0be3e055fa3e51b34baa1cc5589397520ee79670dbf2428f7884713ba0066f4f#1 --tx-in-script-file ./counter/out2.plutus --tx-in-datum-file ./datum_0.json --tx-in-redeemer-value [] --tx-out "addr_test1vpfvmwfl8eucm8rnsej9pehzh7628k53raczagz4uvzzm2csx7sfl+1000000" --tx-out-datum-embed-file ./datum_1.json  --protocol-params-file protocol.json --out-file tx-script2.build

Man this is so much easier in the emulator, I hope the PAB is as smooth as well, the CLI is giving me a hard time (probably due to my own ignorance of the nuances)

I finally made it work, this contract in summary:

  • Force the counter on the datum to be incremented by exactly one every time the eUTXO is spent.
  • Verifies that the identity NFT specified in the parameters of the script is always present (you must pay it back to the script everytime you spend the eUTXO).
  • Verifies that the eUTXO was signed with the key that matches the PubKeyHash specified in the parameters of the contract.

There were several things that needed to be specified on the CLI for it to work properly:

1- You must specify the new output datum value instead of the hash

This is because the script actually uses the new datum value to enforce that it is incremented, if you only specified the hash then it can’t find the value in the datums list, this is pretty easy to do, but the ability to do this using the CLI was just recently added in the latest version (So you must update the CLI to the latest).

This is how the datum list looks on the transaction if you use –tx-out-datum-hash

Datums: [( b7afc0e9c25e4fa2933e0ed75b11024f44b271223ddeb5e919c9ed09489e29a1 , <0> ) ]

And this if you use –tx-out-datum-embed-file instead:

Datums: [ ( 58b85f4b6b8f3d8e62f406ee77f09afc99a9e1b959389367969bcce3c485c6ad, <1> )\n          , ( b7afc0e9c25e4fa2933e0ed75b11024f44b271223ddeb5e919c9ed09489e29a1, <0> ) ]

Notice the extra datum key-value pair on the list.

2.- You have to be careful with the encoding of the datums and the redeemer (even if you are not using the redeemer), this one took me a really long time, as I didn’t understand why I was getting some constructor error for a built-in type, I thought there was something wrong with the datums, it turned out to be the redeemer, I was using [] as a dummy value, but in reality, you have to pass a valid value as it will try to construct a value for the redeemer even if you only defined it as unit ().

3.- You have to add –required-signer to sign the new output. That way the eUTXO is signed.

Thanks for all the help and useful information @bwbush & @DinoDude. I apologize for extending this thread out of the initial essential question.

2 Likes

I created another script following one of the other strategies suggested here.

I took half the eUTXO id and encoded it as base58 (The minting script validates this), this yields a worst-case length of 22 characters, leaving 10 characters for a meaningful asset name.

Because I only took 128 bits of the UTXO hash, it seems like this is not very secure?:

You can see the script here:

The asset name would look like this: HCube097043XEdfDgC4VJUq2ut1X7Fb4

I minted one on the testnet:
https://explorer.cardano-testnet.iohkdev.io/en/transaction?id=27b147ae8875fa081b8704d6c0619a38eca2202821bedf5559f490a3bbc99437

Would love to hear your comments @DinoDude & @bwbush regarding the security of this approach. I know 128 bit hashes are not secure, but would brute-forcing a UTXO id in which half its bytes match another UTXO id be harder than brute-forcing a hash, or is roughly equal? I really wanted this approach to work as it is easier to implement and does not suffer from any concurrency problems/bottlenecks, however, it seems like is not good enough.

The probability of a hash collision scales inversely as the square root of the number of possibilities. Here is a brief discussion. Even for billions of NFTs, the probability of two identical ones would be incredibly small if you use 128 bits.

It’s roughly equal.

2 Likes