55{-# LANGUAGE RankNTypes #-}
66{-# LANGUAGE ScopedTypeVariables #-}
77{-# LANGUAGE StandaloneDeriving #-}
8+ {-# LANGUAGE TupleSections #-}
89{-# LANGUAGE TypeApplications #-}
910
1011module Cardano.Api.Experimental.Tx.Internal.BodyContent.New
@@ -24,6 +25,7 @@ module Cardano.Api.Experimental.Tx.Internal.BodyContent.New
2425 , makeUnsignedTx
2526 , extractAllIndexedPlutusScriptWitnesses
2627 , txMintValueToValue
28+ , mkTxCertificates
2729
2830 -- * Getters and Setters
2931 , setTxAuxScripts
@@ -66,6 +68,7 @@ import Cardano.Api.Experimental.Simple.Script
6668import Cardano.Api.Experimental.Tx.Internal.AnyWitness
6769 ( AnyWitness (.. )
6870 )
71+ import Cardano.Api.Experimental.Tx.Internal.Certificate.Compatible (getTxCertWitness )
6972import Cardano.Api.Experimental.Tx.Internal.TxScriptWitnessRequirements
7073 ( TxScriptWitnessRequirements (.. )
7174 , getTxScriptWitnessesRequirements
@@ -365,6 +368,28 @@ newtype TxCertificates era
365368 { unTxCertificates :: OMap (Exp. Certificate era ) (Maybe (StakeCredential , AnyWitness era ))}
366369 deriving (Show , Eq )
367370
371+ -- | Create 'TxCertificates'. Note that 'Certificate era' will be deduplicated. Only Certificates with a
372+ -- stake credential will be in the result.
373+ --
374+ -- Note that, when building a transaction in Conway era, a witness is not required for staking credential
375+ -- registration, but this is only the case during the transitional period of Conway era and only for staking
376+ -- credential registration certificates without a deposit. Future eras will require a witness for
377+ -- registration certificates, because the one without a deposit will be removed.
378+ mkTxCertificates
379+ :: forall era
380+ . Era era
381+ -> [(Exp. Certificate (LedgerEra era ), AnyWitness (LedgerEra era ))]
382+ -> TxCertificates (LedgerEra era )
383+ mkTxCertificates era certs = TxCertificates . OMap. fromList $ map getStakeCred certs
384+ where
385+ getStakeCred
386+ :: (Exp. Certificate (LedgerEra era ), AnyWitness (LedgerEra era ))
387+ -> ( Exp. Certificate (LedgerEra era )
388+ , Maybe (StakeCredential , AnyWitness (LedgerEra era ))
389+ )
390+ getStakeCred (c@ (Exp. Certificate cert), wit) =
391+ (c, (,wit) <$> getTxCertWitness (convert era) (obtainCommonConstraints era cert))
392+
368393-- This is incorrect. Only scripts can witness minting!
369394newtype TxMintValue era
370395 = TxMintValue
0 commit comments