| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Ledger
Synopsis
- examplePlutusScriptAlwaysFails :: WitCtx witctx -> PlutusScript PlutusScriptV1
- examplePlutusScriptAlwaysSucceeds :: WitCtx witctx -> PlutusScript PlutusScriptV1
- data WitCtx witctx where
- data Language
- data ExBudget = ExBudget {}
- newtype ExMemory = ExMemory CostingInteger
- newtype ExCPU = ExCPU CostingInteger
- data SatInt
- spendsOutput :: TxInfo -> TxId -> Integer -> Bool
- ownCurrencySymbol :: ScriptContext -> CurrencySymbol
- valueProduced :: TxInfo -> Value
- valueSpent :: TxInfo -> Value
- valuePaidTo :: TxInfo -> PubKeyHash -> Value
- pubKeyOutputsAt :: PubKeyHash -> TxInfo -> [Value]
- valueLockedBy :: TxInfo -> ValidatorHash -> Value
- scriptOutputsAt :: ValidatorHash -> TxInfo -> [(DatumHash, Value)]
- fromSymbol :: CurrencySymbol -> ValidatorHash
- ownHash :: ScriptContext -> ValidatorHash
- ownHashes :: ScriptContext -> (ValidatorHash, DatumHash)
- pubKeyOutput :: TxOut -> Maybe PubKeyHash
- txSignedBy :: TxInfo -> PubKeyHash -> Bool
- getContinuingOutputs :: ScriptContext -> [TxOut]
- findContinuingOutputs :: ScriptContext -> [Integer]
- findTxInByTxOutRef :: TxOutRef -> TxInfo -> Maybe TxInInfo
- findDatumHash :: Datum -> TxInfo -> Maybe DatumHash
- findDatum :: DatumHash -> TxInfo -> Maybe Datum
- findOwnInput :: ScriptContext -> Maybe TxInInfo
- data TxInInfo = TxInInfo {}
- data ScriptPurpose
- data TxInfo = TxInfo {
- txInfoInputs :: [TxInInfo]
- txInfoOutputs :: [TxOut]
- txInfoFee :: Value
- txInfoMint :: Value
- txInfoDCert :: [DCert]
- txInfoWdrl :: [(StakingCredential, Integer)]
- txInfoValidRange :: POSIXTimeRange
- txInfoSignatories :: [PubKeyHash]
- txInfoData :: [(DatumHash, Datum)]
- txInfoId :: TxId
- data ScriptContext = ScriptContext {}
- pubKeyHashTxOut :: Value -> PubKeyHash -> TxOut
- isPayToScriptOut :: TxOut -> Bool
- isPubKeyOut :: TxOut -> Bool
- txOutDatum :: TxOut -> Maybe DatumHash
- newtype TxId = TxId {}
- data ScriptTag
- data RedeemerPtr = RedeemerPtr ScriptTag Integer
- type Redeemers = Map RedeemerPtr Redeemer
- data TxOutRef = TxOutRef {
- txOutRefId :: TxId
- txOutRefIdx :: Integer
- stakingCredential :: Address -> Maybe StakingCredential
- scriptHashAddress :: ValidatorHash -> Address
- toValidatorHash :: Address -> Maybe ValidatorHash
- toPubKeyHash :: Address -> Maybe PubKeyHash
- data Address = Address {}
- newtype PubKeyHash = PubKeyHash {}
- unitRedeemer :: Redeemer
- unitDatum :: Datum
- runStakeValidatorScript :: MonadError ScriptError m => Context -> StakeValidator -> Redeemer -> m (ExBudget, [Text])
- applyStakeValidatorScript :: Context -> StakeValidator -> Redeemer -> Script
- runMintingPolicyScript :: MonadError ScriptError m => Context -> MintingPolicy -> Redeemer -> m (ExBudget, [Text])
- applyMintingPolicyScript :: Context -> MintingPolicy -> Redeemer -> Script
- runScript :: MonadError ScriptError m => Context -> Validator -> Datum -> Redeemer -> m (ExBudget, [Text])
- applyValidator :: Context -> Validator -> Datum -> Redeemer -> Script
- unStakeValidatorScript :: StakeValidator -> Script
- mkStakeValidatorScript :: CompiledCode (BuiltinData -> BuiltinData -> ()) -> StakeValidator
- unMintingPolicyScript :: MintingPolicy -> Script
- mkMintingPolicyScript :: CompiledCode (BuiltinData -> BuiltinData -> ()) -> MintingPolicy
- unValidatorScript :: Validator -> Script
- mkValidatorScript :: CompiledCode (BuiltinData -> BuiltinData -> BuiltinData -> ()) -> Validator
- evaluateScript :: MonadError ScriptError m => Script -> m (ExBudget, [Text])
- applyArguments :: Script -> [Data] -> Script
- fromCompiledCode :: CompiledCode a -> Script
- scriptSize :: Script -> Integer
- newtype Script = Script {}
- data ScriptError
- newtype Validator = Validator {}
- newtype Datum = Datum {}
- newtype Redeemer = Redeemer {}
- newtype MintingPolicy = MintingPolicy {}
- newtype StakeValidator = StakeValidator {}
- newtype ScriptHash = ScriptHash {}
- newtype ValidatorHash = ValidatorHash BuiltinByteString
- newtype DatumHash = DatumHash BuiltinByteString
- newtype RedeemerHash = RedeemerHash BuiltinByteString
- newtype MintingPolicyHash = MintingPolicyHash BuiltinByteString
- newtype StakeValidatorHash = StakeValidatorHash BuiltinByteString
- newtype Context = Context BuiltinData
- fromMilliSeconds :: DiffMilliSeconds -> POSIXTime
- type POSIXTimeRange = Interval POSIXTime
- newtype POSIXTime = POSIXTime {}
- newtype DiffMilliSeconds = DiffMilliSeconds Integer
- after :: Ord a => a -> Interval a -> Bool
- before :: Ord a => a -> Interval a -> Bool
- isEmpty :: (Enum a, Ord a) => Interval a -> Bool
- contains :: Ord a => Interval a -> Interval a -> Bool
- hull :: Ord a => Interval a -> Interval a -> Interval a
- intersection :: Ord a => Interval a -> Interval a -> Interval a
- overlaps :: (Enum a, Ord a) => Interval a -> Interval a -> Bool
- member :: Ord a => a -> Interval a -> Bool
- never :: Interval a
- always :: Interval a
- to :: a -> Interval a
- from :: a -> Interval a
- singleton :: a -> Interval a
- interval :: a -> a -> Interval a
- upperBound :: a -> UpperBound a
- lowerBound :: a -> LowerBound a
- strictLowerBound :: a -> LowerBound a
- strictUpperBound :: a -> UpperBound a
- data Interval a = Interval {
- ivFrom :: LowerBound a
- ivTo :: UpperBound a
- data Extended a
- type Closure = Bool
- data UpperBound a = UpperBound (Extended a) Closure
- data LowerBound a = LowerBound (Extended a) Closure
- dataHash :: BuiltinData -> BuiltinByteString
- redeemerHash :: Redeemer -> RedeemerHash
- datumHash :: Datum -> DatumHash
- scriptCurrencySymbol :: Versioned MintingPolicy -> CurrencySymbol
- stakeValidatorHash :: Versioned StakeValidator -> StakeValidatorHash
- mintingPolicyHash :: Versioned MintingPolicy -> MintingPolicyHash
- validatorHash :: Versioned Validator -> ValidatorHash
- scriptHash :: Versioned Script -> ScriptHash
- data Versioned script = Versioned {
- unversioned :: script
- version :: Language
- examplePlutusScriptAlwaysSucceedsHash :: WitCtx ctx -> BuiltinByteString
- examplePlutusScriptAlwaysFailsHash :: WitCtx ctx -> BuiltinByteString
- newtype Slot = Slot {}
- type SlotRange = Interval Slot
- width :: SlotRange -> Maybe Integer
- noAdaValue :: Value -> Value
- newtype Signature = Signature {}
- newtype Passphrase = Passphrase {}
- newtype PubKey = PubKey {}
- newtype PrivateKey = PrivateKey {}
- pubKeyHash :: PubKey -> PubKeyHash
- signedBy :: ByteArrayAccess a => Signature -> PubKey -> a -> Bool
- signTx :: TxId -> XPrv -> Passphrase -> Signature
- signTx' :: TxId -> XPrv -> Signature
- sign :: ByteArrayAccess a => a -> XPrv -> Passphrase -> Signature
- sign' :: ByteArrayAccess a => a -> XPrv -> Signature
- generateFromSeed :: ByteString -> Passphrase -> XPrv
- generateFromSeed' :: ByteString -> XPrv
- xPubToPublicKey :: XPub -> PubKey
- toPublicKey :: XPrv -> PubKey
- newtype PaymentPubKey = PaymentPubKey {}
- newtype PaymentPrivateKey = PaymentPrivateKey {}
- type CardanoAddress = AddressInEra BabbageEra
- cardanoAddressCredential :: AddressInEra era -> Credential
- cardanoStakingCredential :: AddressInEra era -> Maybe StakingCredential
- cardanoPubKeyHash :: AddressInEra era -> Maybe PubKeyHash
- toPlutusAddress :: AddressInEra era -> Address
- toPlutusPubKeyHash :: Hash PaymentKey -> PubKeyHash
- newtype PaymentPubKeyHash = PaymentPubKeyHash {}
- xprvToPaymentPubKey :: XPrv -> PaymentPubKey
- newtype StakePubKey = StakePubKey {}
- xprvToPaymentPubKeyHash :: XPrv -> PaymentPubKeyHash
- newtype StakePubKeyHash = StakePubKeyHash {}
- xprvToStakePubKey :: XPrv -> StakePubKey
- xprvToStakePubKeyHash :: XPrv -> StakePubKeyHash
- xprvToStakingCredential :: XPrv -> StakingCredential
- paymentPubKeyHash :: PaymentPubKey -> PaymentPubKeyHash
- pubKeyHashAddress :: PaymentPubKeyHash -> Maybe StakingCredential -> Address
- pubKeyAddress :: PaymentPubKey -> Maybe StakingCredential -> Address
- scriptValidatorHashAddress :: ValidatorHash -> Maybe StakingCredential -> Address
- stakePubKeyHashCredential :: StakePubKeyHash -> StakingCredential
- stakeValidatorHashCredential :: StakeValidatorHash -> StakingCredential
- data ToCardanoError
- = TxBodyError String
- | DeserialisationError
- | InvalidValidityRange
- | ValueNotPureAda
- | OutputHasZeroAda
- | StakingPointersNotSupported
- | SimpleScriptsNotSupportedToCardano
- | MissingInputValidator
- | MissingDatum
- | MissingMintingPolicy
- | ScriptPurposeNotSupported ScriptTag
- | MissingMintingPolicyRedeemer
- | MissingStakeValidator
- | UnsupportedPlutusVersion Language
- | Tag String ToCardanoError
- data SomeCardanoApiTx where
- SomeTx :: IsCardanoEra era => Tx era -> EraInMode era CardanoMode -> SomeCardanoApiTx
- pattern CardanoApiEmulatorEraTx :: Tx BabbageEra -> SomeCardanoApiTx
- type ReferenceScript = ReferenceScript BabbageEra
- data TxOutTx = TxOutTx {
- txOutTxTx :: Tx
- txOutTxOut :: TxOut
- data TxStripped = TxStripped {}
- data Tx = Tx {
- txInputs :: [TxInput]
- txReferenceInputs :: [TxInput]
- txCollateralInputs :: [TxInput]
- txOutputs :: [TxOut]
- txReturnCollateral :: Maybe TxOut
- txTotalCollateral :: Maybe Value
- txMint :: !Value
- txFee :: !Value
- txValidRange :: !SlotRange
- txMintingWitnesses :: MintingWitnessesMap
- txWithdrawals :: [Withdrawal]
- txCertificates :: [Certificate]
- txSignatures :: Map PubKey Signature
- txScripts :: ScriptsMap
- txData :: Map DatumHash Datum
- txMetadata :: Maybe BuiltinByteString
- type MintingWitnessesMap = Map MintingPolicyHash (Redeemer, Maybe (Versioned TxOutRef))
- type ScriptsMap = Map ScriptHash (Versioned Script)
- newtype TxOut = TxOut {}
- data Certificate = Certificate {}
- data Withdrawal = Withdrawal {}
- data TxInput = TxInput {
- txInputRef :: !TxOutRef
- txInputType :: !TxInputType
- data TxInputType
- data TxIn = TxIn {}
- data TxInType
- pubKeyTxIn :: TxOutRef -> TxIn
- scriptTxIn :: TxOutRef -> Versioned Validator -> Redeemer -> Maybe Datum -> TxIn
- inputRef :: Lens' TxInput TxOutRef
- inputType :: Lens' TxInput TxInputType
- inScripts :: TxIn -> Maybe (Versioned Validator, Redeemer, Maybe Datum)
- inRef :: Lens' TxInput TxOutRef
- inType :: Lens' TxInput TxInputType
- pubKeyTxInputs :: Fold [TxInput] TxInput
- scriptTxInputs :: Fold [TxInput] TxInput
- referenceScriptTxInputs :: Fold [TxInput] TxInput
- toSizedTxOut :: TxOut -> Sized (TxOut StandardBabbage)
- inputs :: Lens' Tx [TxInput]
- referenceInputs :: Lens' Tx [TxInput]
- collateralInputs :: Lens' Tx [TxInput]
- outputs :: Lens' Tx [TxOut]
- returnCollateral :: Lens' Tx (Maybe TxOut)
- totalCollateral :: Lens' Tx (Maybe Value)
- validRange :: Lens' Tx SlotRange
- signatures :: Lens' Tx (Map PubKey Signature)
- fee :: Lens' Tx Value
- mint :: Lens' Tx Value
- mintScripts :: Lens' Tx MintingWitnessesMap
- scriptWitnesses :: Lens' Tx ScriptsMap
- datumWitnesses :: Lens' Tx (Map DatumHash Datum)
- metadata :: Lens' Tx (Maybe BuiltinByteString)
- lookupSignature :: PubKey -> Tx -> Maybe Signature
- lookupDatum :: Tx -> DatumHash -> Maybe Datum
- validValuesTx :: Tx -> Bool
- txOutValue :: TxOut -> Value
- outValue :: Lens TxOut TxOut Value (TxOutValue BabbageEra)
- outValue' :: Lens' TxOut (TxOutValue BabbageEra)
- strip :: Tx -> TxStripped
- txOutTxDatum :: TxOutTx -> Maybe Datum
- txOutDatumHash :: TxOut -> Maybe DatumHash
- txOutPubKey :: TxOut -> Maybe PubKeyHash
- txOutAddress :: TxOut -> CardanoAddress
- outAddress :: Lens' TxOut (AddressInEra BabbageEra)
- outDatumHash :: Lens TxOut TxOut (Maybe DatumHash) (TxOutDatum CtxTx BabbageEra)
- txOutReferenceScript :: TxOut -> ReferenceScript
- outReferenceScript :: Lens' TxOut ReferenceScript
- lookupScript :: ScriptsMap -> ScriptHash -> Maybe (Versioned Script)
- lookupValidator :: ScriptsMap -> ValidatorHash -> Maybe (Versioned Validator)
- spentOutputs :: Tx -> [TxOutRef]
- referencedOutputs :: Tx -> [TxOutRef]
- lookupMintingPolicy :: ScriptsMap -> MintingPolicyHash -> Maybe (Versioned MintingPolicy)
- lookupStakeValidator :: ScriptsMap -> StakeValidatorHash -> Maybe (Versioned StakeValidator)
- fillTxInputWitnesses :: Tx -> TxInput -> TxIn
- pubKeyTxInput :: TxOutRef -> TxInput
- addMintingPolicy :: Versioned MintingPolicy -> (Redeemer, Maybe (Versioned TxOutRef)) -> Tx -> Tx
- addScriptTxInput :: TxOutRef -> Versioned Validator -> Redeemer -> Maybe Datum -> Tx -> Tx
- addReferenceTxInput :: TxOutRef -> Versioned TxOutRef -> Redeemer -> Maybe Datum -> Tx -> Tx
- txRedeemers :: Tx -> Map ScriptPurpose Redeemer
- txSpendingRedeemers :: Tx -> Map TxOutRef Redeemer
- txMintingRedeemers :: Tx -> Map MintingPolicyHash Redeemer
- txRewardingRedeemers :: Tx -> Map Credential Redeemer
- txCertifyingRedeemers :: Tx -> Map DCert Redeemer
- data ValidationError
- newtype UtxoIndex = UtxoIndex {}
- type ValidationSuccess = Map RdmrPtr ([Text], ExUnits)
- type ValidationErrorInPhase = (ValidationPhase, ValidationError)
- data ValidationPhase
- _CardanoLedgerValidationError :: AsValidationError r => Prism' r Text
- _TxOutRefNotFound :: AsValidationError r => Prism' r TxOutRef
- _ScriptFailure :: AsValidationError r => Prism' r ScriptError
- data DatumFromQuery
- data DecoratedTxOut
- = PublicKeyDecoratedTxOut { }
- | ScriptDecoratedTxOut {
- _decoratedTxOutValidatorHash :: ValidatorHash
- _decoratedTxOutStakingCredential :: Maybe StakingCredential
- _decoratedTxOutValue :: Value
- _decoratedTxOutScriptDatum :: (DatumHash, DatumFromQuery)
- _decoratedTxOutReferenceScript :: Maybe (Versioned Script)
- _decoratedTxOutValidator :: Maybe (Versioned Validator)
- datumInDatumFromQuery :: Traversal' DatumFromQuery Datum
- decoratedTxOutPubKeyDatum :: Traversal' DecoratedTxOut (Maybe (DatumHash, DatumFromQuery))
- decoratedTxOutPubKeyHash :: Traversal' DecoratedTxOut PubKeyHash
- decoratedTxOutReferenceScript :: Lens' DecoratedTxOut (Maybe (Versioned Script))
- decoratedTxOutScriptDatum :: Traversal' DecoratedTxOut (DatumHash, DatumFromQuery)
- decoratedTxOutStakingCredential :: Lens' DecoratedTxOut (Maybe StakingCredential)
- decoratedTxOutValidator :: Traversal' DecoratedTxOut (Maybe (Versioned Validator))
- decoratedTxOutValidatorHash :: Traversal' DecoratedTxOut ValidatorHash
- decoratedTxOutValue :: Lens' DecoratedTxOut Value
- data CardanoTx
- = EmulatorTx {
- _emulatorTx :: Tx
- | CardanoApiTx { }
- = EmulatorTx {
- _PublicKeyDecoratedTxOut :: Prism' DecoratedTxOut (PubKeyHash, Maybe StakingCredential, Value, Maybe (DatumHash, DatumFromQuery), Maybe (Versioned Script))
- _ScriptDecoratedTxOut :: Prism' DecoratedTxOut (ValidatorHash, Maybe StakingCredential, Value, (DatumHash, DatumFromQuery), Maybe (Versioned Script), Maybe (Versioned Validator))
- mkDecoratedTxOut :: CardanoAddress -> Value -> (DatumHash, DatumFromQuery) -> Maybe (Versioned Script) -> DecoratedTxOut
- mkPubkeyDecoratedTxOut :: CardanoAddress -> Value -> Maybe (DatumHash, DatumFromQuery) -> Maybe (Versioned Script) -> Maybe DecoratedTxOut
- mkScriptDecoratedTxOut :: CardanoAddress -> Value -> (DatumHash, DatumFromQuery) -> Maybe (Versioned Script) -> Maybe (Versioned Validator) -> Maybe DecoratedTxOut
- _decoratedTxOutAddress :: DecoratedTxOut -> Address
- decoratedTxOutAddress :: Getter DecoratedTxOut Address
- decoratedTxOutDatum :: Traversal' DecoratedTxOut (DatumHash, DatumFromQuery)
- toTxOut :: NetworkId -> DecoratedTxOut -> Either ToCardanoError TxOut
- toTxInfoTxOut :: DecoratedTxOut -> TxOut
- cardanoApiTx :: Traversal' CardanoTx SomeCardanoApiTx
- emulatorTx :: Traversal' CardanoTx Tx
- onCardanoTx :: (Tx -> r) -> (SomeCardanoApiTx -> r) -> CardanoTx -> r
- cardanoTxMap :: (Tx -> Tx) -> (SomeCardanoApiTx -> SomeCardanoApiTx) -> CardanoTx -> CardanoTx
- getCardanoTxId :: CardanoTx -> TxId
- getCardanoTxInputs :: CardanoTx -> [TxIn]
- getTxBodyContentInputs :: TxBodyContent ctx era -> [TxIn]
- getCardanoTxCollateralInputs :: CardanoTx -> [TxIn]
- getTxBodyContentCollateralInputs :: TxBodyContent ctx era -> [TxIn]
- getCardanoTxOutRefs :: CardanoTx -> [(TxOut, TxOutRef)]
- getCardanoTxOutputs :: CardanoTx -> [TxOut]
- getCardanoTxProducedOutputs :: CardanoTx -> Map TxOutRef TxOut
- getCardanoTxSpentOutputs :: CardanoTx -> Set TxOutRef
- getCardanoTxReturnCollateral :: CardanoTx -> Maybe TxOut
- getTxBodyContentReturnCollateral :: TxBodyContent ctx BabbageEra -> Maybe TxOut
- getCardanoTxProducedReturnCollateral :: CardanoTx -> Map TxOutRef TxOut
- getCardanoTxTotalCollateral :: CardanoTx -> Maybe Value
- getCardanoTxFee :: CardanoTx -> Value
- getCardanoTxMint :: CardanoTx -> Value
- getTxBodyContentMint :: TxBodyContent ctx era -> Value
- getCardanoTxValidityRange :: CardanoTx -> SlotRange
- getCardanoTxData :: CardanoTx -> Map DatumHash Datum
- txBodyContentIns :: Lens' (TxBodyContent BuildTx BabbageEra) [(TxIn, BuildTxWith BuildTx (Witness WitCtxTxIn BabbageEra))]
- txBodyContentCollateralIns :: Lens' (TxBodyContent BuildTx BabbageEra) [TxIn]
- txBodyContentOuts :: Lens' (TxBodyContent ctx BabbageEra) [TxOut]
- getCardanoTxRedeemers :: CardanoTx -> Map ScriptPurpose Redeemer
- txId :: Tx -> TxId
- updateUtxo :: CardanoTx -> Map TxOutRef TxOut -> Map TxOutRef TxOut
- updateUtxoCollateral :: CardanoTx -> Map TxOutRef TxOut -> Map TxOutRef TxOut
- txOutRefs :: Tx -> [(TxOut, TxOutRef)]
- unspentOutputsTx :: Tx -> Map TxOutRef TxOut
- pubKeyTxOut :: Value -> PaymentPubKey -> Maybe StakingCredential -> Either ToCardanoError TxOut
- addCardanoTxSignature :: PrivateKey -> CardanoTx -> CardanoTx
- addSignature :: PrivateKey -> Passphrase -> Tx -> Tx
- addSignature' :: PrivateKey -> Tx -> Tx
- type Blockchain = [Block]
- type Block = [OnChainTx]
- data OnChainTx
- newtype BlockId = BlockId {}
- eitherTx :: (CardanoTx -> r) -> (CardanoTx -> r) -> OnChainTx -> r
- unOnChain :: OnChainTx -> CardanoTx
- onChainTxIsValid :: OnChainTx -> Bool
- consumableInputs :: OnChainTx -> [TxIn]
- outputsProduced :: OnChainTx -> Map TxOutRef TxOut
- transaction :: Blockchain -> TxId -> Maybe OnChainTx
- out :: Blockchain -> TxOutRef -> Maybe TxOut
- value :: Blockchain -> TxOutRef -> Maybe Value
- datumTxo :: Blockchain -> TxOutRef -> Maybe DatumHash
- pubKeyTxo :: Blockchain -> TxOutRef -> Maybe PubKeyHash
- unspentOutputs :: Blockchain -> Map TxOutRef TxOut
- _Invalid :: Prism' OnChainTx CardanoTx
- _Valid :: Prism' OnChainTx CardanoTx
- initialise :: Blockchain -> UtxoIndex
- insert :: CardanoTx -> UtxoIndex -> UtxoIndex
- insertCollateral :: CardanoTx -> UtxoIndex -> UtxoIndex
- insertBlock :: Block -> UtxoIndex -> UtxoIndex
- lookup :: MonadError ValidationError m => TxOutRef -> UtxoIndex -> m TxOut
- scriptTxIns :: Fold [TxIn] TxIn
- pubKeyTxIns :: Fold [TxIn] TxIn
- adjustTxOut :: PParams (BabbageEra StandardCrypto) -> TxOut -> Either ToCardanoError ([Ada], TxOut)
- minAdaTxOut :: PParams (BabbageEra StandardCrypto) -> TxOut -> Ada
- minAdaTxOutEstimated :: Ada
- maxMinAdaTxOut :: Ada
- minFee :: Tx -> Value
- maxFee :: Ada
- data AssetClass
- data CurrencySymbol
- data TokenName
- data Value
- data Ada
- data DCert
- data NetworkId
- data Credential
- data StakingCredential
Documentation
examplePlutusScriptAlwaysFails :: WitCtx witctx -> PlutusScript PlutusScriptV1 Source #
An example Plutus script that always fails, irrespective of inputs.
For example, if one were to use this for a payment address then it would be impossible for anyone to ever spend from it.
The exact script depends on the context in which it is to be used.
examplePlutusScriptAlwaysSucceeds :: WitCtx witctx -> PlutusScript PlutusScriptV1 Source #
An example Plutus script that always succeeds, irrespective of inputs.
For example, if one were to use this for a payment address then it would allow anyone to spend from it.
The exact script depends on the context in which it is to be used.
data WitCtx witctx where Source #
This GADT provides a value-level representation of all the witness contexts. This enables pattern matching on the context to allow them to be treated in a non-uniform way.
Constructors
| WitCtxTxIn :: WitCtx WitCtxTxIn | |
| WitCtxMint :: WitCtx WitCtxMint | |
| WitCtxStake :: WitCtx WitCtxStake |
Non-Native Script language. This is an Enumerated type. This is expected to be an open type. We will add new Constuctors to this type as additional Non-Native scripting language as are added. We use an enumerated type for two reasons. 1) We can write total functions by case analysis over the constructors 2) We will use DataKinds to make some datatypes indexed by Language For now, the only Non-Native Scriting language is Plutus We might add new languages in the futures.
Note that the the serialization of Language depends on the ordering.
Instances
| Bounded Language | |
| Enum Language | |
Defined in Cardano.Ledger.Alonzo.Language Methods succ :: Language -> Language Source # pred :: Language -> Language Source # toEnum :: Int -> Language Source # fromEnum :: Language -> Int Source # enumFrom :: Language -> [Language] Source # enumFromThen :: Language -> Language -> [Language] Source # enumFromTo :: Language -> Language -> [Language] Source # enumFromThenTo :: Language -> Language -> Language -> [Language] Source # | |
| Eq Language | |
| Ord Language | |
Defined in Cardano.Ledger.Alonzo.Language | |
| Show Language | |
| Ix Language | |
Defined in Cardano.Ledger.Alonzo.Language | |
| Generic Language | |
| NFData Language | |
Defined in Cardano.Ledger.Alonzo.Language | |
| FromCBOR Language | |
| ToCBOR Language | |
| NoThunks Language | |
| ToSchema Language Source # | |
Defined in Ledger.Orphans Methods declareNamedSchema :: Proxy Language -> Declare (Definitions Schema) NamedSchema Source # | |
| type Rep Language | |
Defined in Cardano.Ledger.Alonzo.Language | |
Constructors
| ExBudget | |
Fields | |
Instances
| Eq ExBudget | |
| Show ExBudget | |
| Generic ExBudget | |
| Semigroup ExBudget | |
| Monoid ExBudget | |
| NFData ExBudget | |
Defined in PlutusCore.Evaluation.Machine.ExBudget | |
| ToJSON ExBudget | |
| FromJSON ExBudget | |
| NoThunks ExBudget | |
| Pretty ExBudget | |
| Lift ExBudget | |
| PrettyBy config ExBudget | |
| type Rep ExBudget | |
Defined in PlutusCore.Evaluation.Machine.ExBudget type Rep ExBudget = D1 ('MetaData "ExBudget" "PlutusCore.Evaluation.Machine.ExBudget" "plutus-core-1.0.0.1-AYZ1DL3hDMt58i5HNUtSdG" 'False) (C1 ('MetaCons "ExBudget" 'PrefixI 'True) (S1 ('MetaSel ('Just "exBudgetCPU") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedUnpack) (Rec0 ExCPU) :*: S1 ('MetaSel ('Just "exBudgetMemory") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedUnpack) (Rec0 ExMemory))) | |
Counts size in machine words.
Constructors
| ExMemory CostingInteger |
Instances
Counts CPU units in picoseconds: maximum value for SatInt is 2^63 ps, or appproximately 106 days.
Constructors
| ExCPU CostingInteger |
Instances
| Eq ExCPU | |
| Num ExCPU | |
Defined in PlutusCore.Evaluation.Machine.ExMemory | |
| Ord ExCPU | |
Defined in PlutusCore.Evaluation.Machine.ExMemory | |
| Show ExCPU | |
| Generic ExCPU | |
| Semigroup ExCPU | |
| Monoid ExCPU | |
| NFData ExCPU | |
Defined in PlutusCore.Evaluation.Machine.ExMemory | |
| ToJSON ExCPU | |
| FromJSON ExCPU | |
| NoThunks ExCPU | |
| Pretty ExCPU | |
| Lift ExCPU | |
| PrettyBy config ExCPU | |
| type Rep ExCPU | |
Defined in PlutusCore.Evaluation.Machine.ExMemory type Rep ExCPU = D1 ('MetaData "ExCPU" "PlutusCore.Evaluation.Machine.ExMemory" "plutus-core-1.0.0.1-AYZ1DL3hDMt58i5HNUtSdG" 'True) (C1 ('MetaCons "ExCPU" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 CostingInteger))) | |
Instances
spendsOutput :: TxInfo -> TxId -> Integer -> Bool Source #
Check if the pending transaction spends a specific transaction output (identified by the hash of a transaction and an index into that transactions' outputs)
ownCurrencySymbol :: ScriptContext -> CurrencySymbol Source #
The CurrencySymbol of the current validator script.
valueProduced :: TxInfo -> Value Source #
Get the total value of outputs produced by this transaction.
valueSpent :: TxInfo -> Value Source #
Get the total value of inputs spent by this transaction.
valuePaidTo :: TxInfo -> PubKeyHash -> Value Source #
Get the total value paid to a public key address by a pending transaction.
pubKeyOutputsAt :: PubKeyHash -> TxInfo -> [Value] Source #
Get the values paid to a public key address by a pending transaction.
valueLockedBy :: TxInfo -> ValidatorHash -> Value Source #
Get the total value locked by the given validator in this transaction.
scriptOutputsAt :: ValidatorHash -> TxInfo -> [(DatumHash, Value)] Source #
Get the list of TxOut outputs of the pending transaction at
a given script address.
fromSymbol :: CurrencySymbol -> ValidatorHash Source #
Convert a CurrencySymbol to a ValidatorHash
ownHash :: ScriptContext -> ValidatorHash Source #
Get the hash of the validator script that is currently being validated.
ownHashes :: ScriptContext -> (ValidatorHash, DatumHash) Source #
Get the validator and datum hashes of the output that is curently being validated
pubKeyOutput :: TxOut -> Maybe PubKeyHash Source #
Get the public key hash that locks the transaction output, if any.
txSignedBy :: TxInfo -> PubKeyHash -> Bool Source #
Check if a transaction was signed by the given public key.
getContinuingOutputs :: ScriptContext -> [TxOut] Source #
findContinuingOutputs :: ScriptContext -> [Integer] Source #
Finds all the outputs that pay to the same script address that we are currently spending from, if any.
findDatumHash :: Datum -> TxInfo -> Maybe DatumHash Source #
Find the hash of a datum, if it is part of the pending transaction's hashes
findDatum :: DatumHash -> TxInfo -> Maybe Datum Source #
Find the data corresponding to a data hash, if there is one
findOwnInput :: ScriptContext -> Maybe TxInInfo Source #
Find the input currently being validated.
An input of a pending transaction.
Constructors
| TxInInfo | |
Fields | |
Instances
data ScriptPurpose Source #
Purpose of the script that is currently running
Instances
A pending transaction. This is the view as seen by validator scripts, so some details are stripped out.
Constructors
| TxInfo | |
Fields
| |
Instances
data ScriptContext Source #
Constructors
| ScriptContext | |
Fields | |
Instances
pubKeyHashTxOut :: Value -> PubKeyHash -> TxOut Source #
Create a transaction output locked by a public key.
isPayToScriptOut :: TxOut -> Bool Source #
Whether the output is a pay-to-script output.
isPubKeyOut :: TxOut -> Bool Source #
Whether the output is a pay-to-pubkey output.
A transaction ID, using a SHA256 hash as the transaction id.
Constructors
| TxId | |
Fields | |
Instances
A tag indicating the type of script that we are pointing to.
Instances
| Eq ScriptTag | |
| Ord ScriptTag | |
Defined in Plutus.V1.Ledger.Tx | |
| Show ScriptTag | |
| Generic ScriptTag | |
| NFData ScriptTag | |
Defined in Plutus.V1.Ledger.Tx | |
| ToJSON ScriptTag Source # | |
| FromJSON ScriptTag Source # | |
| ToSchema ScriptTag Source # | |
Defined in Ledger.Orphans Methods declareNamedSchema :: Proxy ScriptTag -> Declare (Definitions Schema) NamedSchema Source # | |
| Serialise ScriptTag Source # | |
| type Rep ScriptTag | |
Defined in Plutus.V1.Ledger.Tx type Rep ScriptTag = D1 ('MetaData "ScriptTag" "Plutus.V1.Ledger.Tx" "plutus-ledger-api-1.0.0.1-EUjexvcAhXiGIaLon6olWb" 'False) ((C1 ('MetaCons "Spend" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Mint" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Cert" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Reward" 'PrefixI 'False) (U1 :: Type -> Type))) | |
data RedeemerPtr Source #
A redeemer pointer is a pair of a script type tag t and an index i, picking out the ith script of type t in the transaction.
Constructors
| RedeemerPtr ScriptTag Integer |
Instances
A reference to a transaction output. This is a pair of a transaction reference, and an index indicating which of the outputs of that transaction we are referring to.
Constructors
| TxOutRef | |
Fields
| |
Instances
stakingCredential :: Address -> Maybe StakingCredential Source #
The staking credential of an address (if any)
scriptHashAddress :: ValidatorHash -> Address Source #
The address that should be used by a transaction output locked by the given validator script hash.
toValidatorHash :: Address -> Maybe ValidatorHash Source #
The validator hash of the address, if any
toPubKeyHash :: Address -> Maybe PubKeyHash Source #
The PubKeyHash of the address, if any
Address with two kinds of credentials, normal and staking.
Constructors
| Address | |
Instances
newtype PubKeyHash Source #
The hash of a public key. This is frequently used to identify the public key, rather than the key itself.
Constructors
| PubKeyHash | |
Fields | |
Instances
unitRedeemer :: Redeemer Source #
() as a redeemer.
runStakeValidatorScript :: MonadError ScriptError m => Context -> StakeValidator -> Redeemer -> m (ExBudget, [Text]) Source #
Evaluate a StakeValidator with its Context and Redeemer, returning the log.
applyStakeValidatorScript :: Context -> StakeValidator -> Redeemer -> Script Source #
Apply StakeValidator to its Context and Redeemer.
runMintingPolicyScript :: MonadError ScriptError m => Context -> MintingPolicy -> Redeemer -> m (ExBudget, [Text]) Source #
Evaluate a MintingPolicy with its Context and Redeemer, returning the log.
applyMintingPolicyScript :: Context -> MintingPolicy -> Redeemer -> Script Source #
Apply MintingPolicy to its Context and Redeemer.
runScript :: MonadError ScriptError m => Context -> Validator -> Datum -> Redeemer -> m (ExBudget, [Text]) Source #
mkStakeValidatorScript :: CompiledCode (BuiltinData -> BuiltinData -> ()) -> StakeValidator Source #
mkMintingPolicyScript :: CompiledCode (BuiltinData -> BuiltinData -> ()) -> MintingPolicy Source #
unValidatorScript :: Validator -> Script Source #
mkValidatorScript :: CompiledCode (BuiltinData -> BuiltinData -> BuiltinData -> ()) -> Validator Source #
evaluateScript :: MonadError ScriptError m => Script -> m (ExBudget, [Text]) Source #
Evaluate a script, returning the trace log.
fromCompiledCode :: CompiledCode a -> Script Source #
Turn a CompiledCode (usually produced by compile) into a Script for use with this package.
scriptSize :: Script -> Integer Source #
The size of a Script. No particular interpretation is given to this, other than that it is
proportional to the serialized size of the script.
A script on the chain. This is an opaque type as far as the chain is concerned.
Constructors
| Script | |
Fields | |
Instances
| Eq Script | Note [Using Flat inside CBOR instance of Script] `plutus-ledger` uses CBOR for data serialisation and `plutus-core` uses Flat. The choice to use Flat was made to have a more efficient (most wins are in uncompressed size) data serialisation format and use less space on-chain. To make `plutus-ledger` work with scripts serialised with Flat, and keep the CBOR format otherwise we have defined a Serialise instance for Script, which is a wrapper over Programs serialised with Flat. The instance will see programs as an opaque ByteString, which is the result of encoding programs using Flat. Because Flat is not self-describing and it gets used in the encoding of Programs, data structures that include scripts (for example, transactions) no-longer benefit for CBOR's ability to self-describe it's format. |
| Ord Script | |
| Show Script | |
| Generic Script | |
| NFData Script | |
Defined in Plutus.V1.Ledger.Scripts | |
| ToJSON Script Source # | |
| FromJSON Script Source # | |
| ToSchema Script Source # | |
Defined in Ledger.Orphans Methods declareNamedSchema :: Proxy Script -> Declare (Definitions Schema) NamedSchema Source # | |
| Serialise Script | |
| type Rep Script | |
Defined in Plutus.V1.Ledger.Scripts type Rep Script = D1 ('MetaData "Script" "Plutus.V1.Ledger.Scripts" "plutus-ledger-api-1.0.0.1-EUjexvcAhXiGIaLon6olWb" 'True) (C1 ('MetaCons "Script" 'PrefixI 'True) (S1 ('MetaSel ('Just "unScript") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Program DeBruijn DefaultUni DefaultFun ())))) | |
data ScriptError Source #
Constructors
| EvaluationError [Text] String | Expected behavior of the engine (e.g. user-provided error) |
| EvaluationException String String | Unexpected behavior of the engine (a bug) |
Instances
Constructors
| Validator | |
Fields | |
Instances
| Eq Validator | |
| Ord Validator | |
Defined in Plutus.V1.Ledger.Scripts | |
| Show Validator | |
| Generic Validator | |
| NFData Validator | |
Defined in Plutus.V1.Ledger.Scripts | |
| ToJSON Validator Source # | |
| FromJSON Validator Source # | |
| ToSchema Validator Source # | |
Defined in Ledger.Orphans Methods declareNamedSchema :: Proxy Validator -> Declare (Definitions Schema) NamedSchema Source # | |
| Pretty Validator | |
| Serialise Validator | |
| type Rep Validator | |
Defined in Plutus.V1.Ledger.Scripts | |
Datum is a wrapper around Data values which are used as data in transaction outputs.
Constructors
| Datum | |
Fields | |
Instances
Redeemer is a wrapper around Data values that are used as redeemers in transaction inputs.
Constructors
| Redeemer | |
Fields | |
Instances
newtype MintingPolicy Source #
MintingPolicy is a wrapper around Scripts which are used as validators for minting constraints.
Constructors
| MintingPolicy | |
Fields | |
Instances
newtype StakeValidator Source #
StakeValidator is a wrapper around Scripts which are used as validators for withdrawals and stake address certificates.
Constructors
| StakeValidator | |
Fields | |
Instances
newtype ScriptHash Source #
Script runtime representation of a Digest SHA256.
Constructors
| ScriptHash | |
Fields | |
Instances
newtype ValidatorHash Source #
Script runtime representation of a Digest SHA256.
Constructors
| ValidatorHash BuiltinByteString |
Instances
Script runtime representation of a Digest SHA256.
Constructors
| DatumHash BuiltinByteString |
Instances
newtype RedeemerHash Source #
Script runtime representation of a Digest SHA256.
Constructors
| RedeemerHash BuiltinByteString |
Instances
newtype MintingPolicyHash Source #
Script runtime representation of a Digest SHA256.
Constructors
| MintingPolicyHash BuiltinByteString |
Instances
newtype StakeValidatorHash Source #
Script runtime representation of a Digest SHA256.
Constructors
| StakeValidatorHash BuiltinByteString |
Instances
Information about the state of the blockchain and about the transaction
that is currently being validated, represented as a value in Data.
Constructors
| Context BuiltinData |
fromMilliSeconds :: DiffMilliSeconds -> POSIXTime Source #
Simple conversion from DiffMilliSeconds to POSIXTime.
POSIX time is measured as the number of milliseconds since 1970-01-01T00:00:00Z
Constructors
| POSIXTime | |
Fields | |
Instances
newtype DiffMilliSeconds Source #
This is a length of time, as measured by a number of milliseconds.
Constructors
| DiffMilliSeconds Integer |
Instances
after :: Ord a => a -> Interval a -> Bool Source #
Check if a value is later than the end of a Interval.
before :: Ord a => a -> Interval a -> Bool Source #
Check if a value is earlier than the beginning of an Interval.
hull :: Ord a => Interval a -> Interval a -> Interval a Source #
'hull a b' is the smallest interval containing a and b.
intersection :: Ord a => Interval a -> Interval a -> Interval a Source #
'intersection a b' is the largest interval that is contained in a and in
b, if it exists.
overlaps :: (Enum a, Ord a) => Interval a -> Interval a -> Bool Source #
Check whether two intervals overlap, that is, whether there is a value that is a member of both intervals.
to :: a -> Interval a Source #
to a is an Interval that includes all values that are
smaller than or equal to a.
from :: a -> Interval a Source #
from a is an Interval that includes all values that are
greater than or equal to a.
interval :: a -> a -> Interval a Source #
interval a b includes all values that are greater than or equal to a
and smaller than or equal to b. Therefore it includes a and b.
upperBound :: a -> UpperBound a Source #
lowerBound :: a -> LowerBound a Source #
strictLowerBound :: a -> LowerBound a Source #
strictUpperBound :: a -> UpperBound a Source #
An interval of as.
The interval may be either closed or open at either end, meaning that the endpoints may or may not be included in the interval.
The interval can also be unbounded on either side.
Constructors
| Interval | |
Fields
| |
Instances
A set extended with a positive and negative infinity.
Instances
data UpperBound a Source #
The upper bound of an interval.
Constructors
| UpperBound (Extended a) Closure |
Instances
data LowerBound a Source #
The lower bound of an interval.
Constructors
| LowerBound (Extended a) Closure |
Instances
dataHash :: BuiltinData -> BuiltinByteString Source #
Hash a BuiltinData
redeemerHash :: Redeemer -> RedeemerHash Source #
Hash a Redeemer builtin data.
scriptCurrencySymbol :: Versioned MintingPolicy -> CurrencySymbol Source #
The CurrencySymbol of a MintingPolicy.
stakeValidatorHash :: Versioned StakeValidator -> StakeValidatorHash Source #
Hash a Versioned StakeValidator script.
mintingPolicyHash :: Versioned MintingPolicy -> MintingPolicyHash Source #
Hash a Versioned MintingPolicy script.
scriptHash :: Versioned Script -> ScriptHash Source #
Hash a Versioned Script
data Versioned script Source #
A script of some kind with its Plutus language version
Constructors
| Versioned | |
Fields
| |
Instances
The slot number. This is a good proxy for time, since on the Cardano blockchain slots pass at a constant rate.
Instances
width :: SlotRange -> Maybe Integer Source #
Number of Slots covered by the interval, if finite. width (from x) == Nothing.
noAdaValue :: Value -> Value Source #
Value without any Ada.
A message with a cryptographic signature.
Constructors
| Signature | |
Fields | |
Instances
newtype Passphrase Source #
Passphrase newtype to mark intent
Constructors
| Passphrase | |
Fields | |
Instances
| Show Passphrase Source # | |
Defined in Ledger.Crypto | |
| IsString Passphrase Source # | |
Defined in Ledger.Crypto Methods fromString :: String -> Passphrase Source # | |
Constructors
| PubKey | |
Fields | |
Instances
newtype PrivateKey Source #
A cryptographic private key.
Constructors
| PrivateKey | |
Fields | |
Instances
pubKeyHash :: PubKey -> PubKeyHash Source #
Compute the hash of a public key.
signedBy :: ByteArrayAccess a => Signature -> PubKey -> a -> Bool Source #
Check whether the given Signature was signed by the private key corresponding to the given public key.
signTx :: TxId -> XPrv -> Passphrase -> Signature Source #
Sign the hash of a transaction using a private key and passphrase.
signTx' :: TxId -> XPrv -> Signature Source #
Sign the hash of a transaction using a private key that has no passphrase.
sign :: ByteArrayAccess a => a -> XPrv -> Passphrase -> Signature Source #
Sign a message using a private key and passphrase.
sign' :: ByteArrayAccess a => a -> XPrv -> Signature Source #
Sign a message using a private key with no passphrase.
generateFromSeed :: ByteString -> Passphrase -> XPrv Source #
Generate a private key from a seed phrase and passphrase
generateFromSeed' :: ByteString -> XPrv Source #
Generate a private key from a seed phrase without a passphrase.
xPubToPublicKey :: XPub -> PubKey Source #
toPublicKey :: XPrv -> PubKey Source #
newtype PaymentPubKey Source #
Constructors
| PaymentPubKey | |
Fields | |
Instances
newtype PaymentPrivateKey Source #
Constructors
| PaymentPrivateKey | |
Fields | |
type CardanoAddress = AddressInEra BabbageEra Source #
cardanoAddressCredential :: AddressInEra era -> Credential Source #
cardanoPubKeyHash :: AddressInEra era -> Maybe PubKeyHash Source #
toPlutusAddress :: AddressInEra era -> Address Source #
newtype PaymentPubKeyHash Source #
Constructors
| PaymentPubKeyHash | |
Fields | |
Instances
newtype StakePubKey Source #
Constructors
| StakePubKey | |
Fields | |
Instances
newtype StakePubKeyHash Source #
Constructors
| StakePubKeyHash | |
Fields | |
Instances
xprvToStakePubKey :: XPrv -> StakePubKey Source #
pubKeyHashAddress :: PaymentPubKeyHash -> Maybe StakingCredential -> Address Source #
The address that should be targeted by a transaction output locked by the given public payment key (with its staking credentials).
pubKeyAddress :: PaymentPubKey -> Maybe StakingCredential -> Address Source #
The address that should be targeted by a transaction output locked by the given public key. (with its staking credentials).
scriptValidatorHashAddress :: ValidatorHash -> Maybe StakingCredential -> Address Source #
The address that should be used by a transaction output locked by the given validator script (with its staking credentials).
stakePubKeyHashCredential :: StakePubKeyHash -> StakingCredential Source #
Construct a StakingCredential from a public key hash.
stakeValidatorHashCredential :: StakeValidatorHash -> StakingCredential Source #
Construct a StakingCredential from a validator script hash.
data ToCardanoError Source #
Constructors
Instances
data SomeCardanoApiTx where Source #
Cardano tx from any era.
Constructors
| SomeTx :: IsCardanoEra era => Tx era -> EraInMode era CardanoMode -> SomeCardanoApiTx |
Bundled Patterns
| pattern CardanoApiEmulatorEraTx :: Tx BabbageEra -> SomeCardanoApiTx |
Instances
A TxOut along with the Tx it comes from, which may have additional information e.g.
the full data script that goes with the TxOut.
Constructors
| TxOutTx | |
Fields
| |
Instances
| Eq TxOutTx Source # | |
| Show TxOutTx Source # | |
| Generic TxOutTx Source # | |
| ToJSON TxOutTx Source # | |
| FromJSON TxOutTx Source # | |
| Serialise TxOutTx Source # | |
| type Rep TxOutTx Source # | |
Defined in Ledger.Tx.Internal type Rep TxOutTx = D1 ('MetaData "TxOutTx" "Ledger.Tx.Internal" "plutus-ledger-1.1.0.0-JskZbcPMCdRJVHaAZ0to82" 'False) (C1 ('MetaCons "TxOutTx" 'PrefixI 'True) (S1 ('MetaSel ('Just "txOutTxTx") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Tx) :*: S1 ('MetaSel ('Just "txOutTxOut") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 TxOut))) | |
data TxStripped Source #
A babbage era transaction without witnesses for its inputs.
Constructors
| TxStripped | |
Fields
| |
Instances
A Babbage-era transaction, including witnesses for its inputs.
Constructors
| Tx | |
Fields
| |
Instances
type MintingWitnessesMap = Map MintingPolicyHash (Redeemer, Maybe (Versioned TxOutRef)) Source #
type ScriptsMap = Map ScriptHash (Versioned Script) Source #
Validator, redeemer, and data scripts of a transaction input that spends a "pay to script" output. inScripts :: Tx -> TxInput -> Maybe (LedgerPlutusVersion, Validator, Redeemer, Datum) inScripts tx i@TxInput{txInputType=TxConsumeScriptAddress pv _ _ _} = case txInType $ fillTxInputWitnesses tx i of Just (ConsumeScriptAddress v r d) -> Just (pv, v, r, d) _ -> Nothing inScripts _ _ = Nothing
Constructors
| TxOut | |
Fields | |
Instances
| Eq TxOut Source # | |
| Show TxOut Source # | |
| Generic TxOut Source # | |
| NFData TxOut Source # | |
Defined in Ledger.Tx.Internal | |
| ToJSON TxOut Source # | |
| FromJSON TxOut Source # | |
| FromCBOR TxOut Source # | |
| ToCBOR TxOut Source # | |
| ToSchema TxOut Source # | |
Defined in Ledger.Tx.Internal Methods declareNamedSchema :: Proxy TxOut -> Declare (Definitions Schema) NamedSchema Source # | |
| Pretty TxOut Source # | |
| Serialise TxOut Source # | |
| type Rep TxOut Source # | |
Defined in Ledger.Tx.Internal type Rep TxOut = D1 ('MetaData "TxOut" "Ledger.Tx.Internal" "plutus-ledger-1.1.0.0-JskZbcPMCdRJVHaAZ0to82" 'True) (C1 ('MetaCons "TxOut" 'PrefixI 'True) (S1 ('MetaSel ('Just "getTxOut") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (TxOut CtxTx BabbageEra)))) | |
data Certificate Source #
Constructors
| Certificate | |
Fields
| |
Instances
data Withdrawal Source #
Stake withdrawal, if applicable the script should be included in txScripts.
Constructors
| Withdrawal | |
Fields
| |
Instances
A transaction input, consisting of a transaction output reference and an input type. Differs with TxIn by: TxIn *maybe* contains *full* data witnesses, TxInput always contains redeemer witness, but datum/validator hashes.
Constructors
| TxInput | |
Fields
| |
Instances
| Eq TxInput Source # | |
| Ord TxInput Source # | |
Defined in Ledger.Tx.Internal | |
| Show TxInput Source # | |
| Generic TxInput Source # | |
| NFData TxInput Source # | |
Defined in Ledger.Tx.Internal | |
| ToJSON TxInput Source # | |
| FromJSON TxInput Source # | |
| ToSchema TxInput Source # | |
Defined in Ledger.Tx.Internal Methods declareNamedSchema :: Proxy TxInput -> Declare (Definitions Schema) NamedSchema Source # | |
| Pretty TxInput Source # | |
| Serialise TxInput Source # | |
| type Rep TxInput Source # | |
Defined in Ledger.Tx.Internal type Rep TxInput = D1 ('MetaData "TxInput" "Ledger.Tx.Internal" "plutus-ledger-1.1.0.0-JskZbcPMCdRJVHaAZ0to82" 'False) (C1 ('MetaCons "TxInput" 'PrefixI 'True) (S1 ('MetaSel ('Just "txInputRef") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 TxOutRef) :*: S1 ('MetaSel ('Just "txInputType") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 TxInputType))) | |
data TxInputType Source #
The type of a transaction input with hashes.
Constructors
| TxScriptAddress !Redeemer !(Either ValidatorHash (Versioned TxOutRef)) !(Maybe DatumHash) | A transaction input that consumes (with a validator hash) or references (with a txOutRef) a script address with the given the redeemer and datum hash. |
| TxConsumePublicKeyAddress | A transaction input that consumes a public key address. |
| TxConsumeSimpleScriptAddress | Consume a simple script |
Instances
A transaction input, consisting of a transaction output reference and an input type.
Instances
| Eq TxIn Source # | |
| Ord TxIn Source # | |
| Show TxIn Source # | |
| Generic TxIn Source # | |
| NFData TxIn Source # | |
Defined in Ledger.Tx.Internal | |
| ToJSON TxIn Source # | |
| FromJSON TxIn Source # | |
| ToSchema TxIn Source # | |
Defined in Ledger.Tx.Internal Methods declareNamedSchema :: Proxy TxIn -> Declare (Definitions Schema) NamedSchema Source # | |
| Pretty TxIn Source # | |
| Serialise TxIn Source # | |
| type Rep TxIn Source # | |
Defined in Ledger.Tx.Internal type Rep TxIn = D1 ('MetaData "TxIn" "Ledger.Tx.Internal" "plutus-ledger-1.1.0.0-JskZbcPMCdRJVHaAZ0to82" 'False) (C1 ('MetaCons "TxIn" 'PrefixI 'True) (S1 ('MetaSel ('Just "txInRef") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 TxOutRef) :*: S1 ('MetaSel ('Just "txInType") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe TxInType)))) | |
The type of a transaction input.
Constructors
| ScriptAddress !(Either (Versioned Validator) (Versioned TxOutRef)) !Redeemer !(Maybe Datum) | A transaction input that consumes (with a validator) or references (with a txOutRef) a script address with the given the redeemer and datum. Datum is optional if the input refers to a script output which contains an inline datum |
| ConsumePublicKeyAddress | A transaction input that consumes a public key address. |
| ConsumeSimpleScriptAddress | Consume a simple script |
Instances
pubKeyTxIn :: TxOutRef -> TxIn Source #
A transaction input that spends a "pay to public key" output, given the witness.
scriptTxIn :: TxOutRef -> Versioned Validator -> Redeemer -> Maybe Datum -> TxIn Source #
A transaction input that spends a "pay to script" output, given witnesses. Datum is optional if the input refers to a script output which contains an inline datum
inScripts :: TxIn -> Maybe (Versioned Validator, Redeemer, Maybe Datum) Source #
Validator, redeemer, and data scripts of a transaction input that spends a "pay to script" output.
scriptTxInputs :: Fold [TxInput] TxInput Source #
Filter to get only the scripts that consume or reference a script address
referenceScriptTxInputs :: Fold [TxInput] TxInput Source #
Filter to get only the scripts that reference a script address
toSizedTxOut :: TxOut -> Sized (TxOut StandardBabbage) Source #
collateralInputs :: Lens' Tx [TxInput] Source #
The collateral inputs of a transaction for paying fees when validating the transaction fails.
validValuesTx :: Tx -> Bool Source #
Check that all values in a transaction are non-negative.
txOutValue :: TxOut -> Value Source #
strip :: Tx -> TxStripped Source #
txOutDatumHash :: TxOut -> Maybe DatumHash Source #
Get a hash from the stored TxOutDatum (either dirctly or by hashing the inlined datum)
txOutPubKey :: TxOut -> Maybe PubKeyHash Source #
txOutAddress :: TxOut -> CardanoAddress Source #
lookupScript :: ScriptsMap -> ScriptHash -> Maybe (Versioned Script) Source #
lookupValidator :: ScriptsMap -> ValidatorHash -> Maybe (Versioned Validator) Source #
spentOutputs :: Tx -> [TxOutRef] Source #
The transaction output references consumed by a transaction.
referencedOutputs :: Tx -> [TxOutRef] Source #
The transaction output references referenced by a transaction.
lookupStakeValidator :: ScriptsMap -> StakeValidatorHash -> Maybe (Versioned StakeValidator) Source #
fillTxInputWitnesses :: Tx -> TxInput -> TxIn Source #
Translate TxInput to old Plutus.V1.Ledger.Api TxIn taking script and datum witnesses from Tx.
pubKeyTxInput :: TxOutRef -> TxInput Source #
addMintingPolicy :: Versioned MintingPolicy -> (Redeemer, Maybe (Versioned TxOutRef)) -> Tx -> Tx Source #
Add minting policy together with the redeemer into txMintingWitnesses and txScripts accordingly. Doesn't alter txMint.
addScriptTxInput :: TxOutRef -> Versioned Validator -> Redeemer -> Maybe Datum -> Tx -> Tx Source #
Add validator together with the redeemer and datum into txInputs, txData and txScripts accordingly. Datum is optional if the input refers to a script output which contains an inline datum
addReferenceTxInput :: TxOutRef -> Versioned TxOutRef -> Redeemer -> Maybe Datum -> Tx -> Tx Source #
Add script reference together with the redeemer and datum into txInputs and txData accordingly. Datum is optional if the input refers to a script output which contains an inline datum
txRedeemers :: Tx -> Map ScriptPurpose Redeemer Source #
data ValidationError Source #
A reason why a transaction is invalid.
Constructors
| TxOutRefNotFound TxOutRef | The transaction output consumed by a transaction input could not be found (either because it was already spent, or because there was no transaction with the given hash on the blockchain). |
| ScriptFailure ScriptError | For pay-to-script outputs: evaluation of the validator script failed. |
| CardanoLedgerValidationError Text | An error from Cardano.Ledger validation |
Instances
The UTxOs of a blockchain indexed by their references.
Instances
| Eq UtxoIndex Source # | |
| Show UtxoIndex Source # | |
| Generic UtxoIndex Source # | |
| Semigroup UtxoIndex Source # | |
| Monoid UtxoIndex Source # | |
| NFData UtxoIndex Source # | |
Defined in Ledger.Index.Internal | |
| ToJSON UtxoIndex Source # | |
| FromJSON UtxoIndex Source # | |
| ToSchema UtxoIndex Source # | |
Defined in Ledger.Index.Internal Methods declareNamedSchema :: Proxy UtxoIndex -> Declare (Definitions Schema) NamedSchema Source # | |
| Serialise UtxoIndex Source # | |
| type Rep UtxoIndex Source # | |
Defined in Ledger.Index.Internal | |
data ValidationPhase Source #
Instances
_TxOutRefNotFound :: AsValidationError r => Prism' r TxOutRef Source #
_ScriptFailure :: AsValidationError r => Prism' r ScriptError Source #
data DatumFromQuery Source #
A datum in a transaction output that comes from a chain index query.
Constructors
| DatumUnknown | |
| DatumInline Datum | |
| DatumInBody Datum |
Instances
data DecoratedTxOut Source #
Offchain view of a transaction output.
Constructors
| PublicKeyDecoratedTxOut | |
Fields
| |
| ScriptDecoratedTxOut | |
Fields
| |
Instances
Constructors
| EmulatorTx | |
Fields
| |
| CardanoApiTx | |
Fields | |
Instances
| Eq CardanoTx Source # | |
| Show CardanoTx Source # | |
| Generic CardanoTx Source # | |
| ToJSON CardanoTx Source # | |
| FromJSON CardanoTx Source # | |
| ToSchema CardanoTx Source # | |
Defined in Ledger.Tx Methods declareNamedSchema :: Proxy CardanoTx -> Declare (Definitions Schema) NamedSchema Source # | |
| Pretty CardanoTx Source # | |
| Serialise CardanoTx Source # | |
| type Rep CardanoTx Source # | |
Defined in Ledger.Tx type Rep CardanoTx = D1 ('MetaData "CardanoTx" "Ledger.Tx" "plutus-ledger-1.1.0.0-JskZbcPMCdRJVHaAZ0to82" 'False) (C1 ('MetaCons "EmulatorTx" 'PrefixI 'True) (S1 ('MetaSel ('Just "_emulatorTx") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Tx)) :+: C1 ('MetaCons "CardanoApiTx" 'PrefixI 'True) (S1 ('MetaSel ('Just "_cardanoApiTx") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SomeCardanoApiTx))) | |
_PublicKeyDecoratedTxOut :: Prism' DecoratedTxOut (PubKeyHash, Maybe StakingCredential, Value, Maybe (DatumHash, DatumFromQuery), Maybe (Versioned Script)) Source #
_ScriptDecoratedTxOut :: Prism' DecoratedTxOut (ValidatorHash, Maybe StakingCredential, Value, (DatumHash, DatumFromQuery), Maybe (Versioned Script), Maybe (Versioned Validator)) Source #
mkDecoratedTxOut :: CardanoAddress -> Value -> (DatumHash, DatumFromQuery) -> Maybe (Versioned Script) -> DecoratedTxOut Source #
mkPubkeyDecoratedTxOut :: CardanoAddress -> Value -> Maybe (DatumHash, DatumFromQuery) -> Maybe (Versioned Script) -> Maybe DecoratedTxOut Source #
mkScriptDecoratedTxOut :: CardanoAddress -> Value -> (DatumHash, DatumFromQuery) -> Maybe (Versioned Script) -> Maybe (Versioned Validator) -> Maybe DecoratedTxOut Source #
toTxOut :: NetworkId -> DecoratedTxOut -> Either ToCardanoError TxOut Source #
toTxInfoTxOut :: DecoratedTxOut -> TxOut Source #
Converts a transaction output from the chain index to the plutus-ledger-api transaction output.
Note that DecoratedTxOut supports features such inline datums and
reference scripts which are not supported by V1 TxOut. Converting from
DecoratedTxOut to TxOut and back is therefore lossy.
onCardanoTx :: (Tx -> r) -> (SomeCardanoApiTx -> r) -> CardanoTx -> r Source #
cardanoTxMap :: (Tx -> Tx) -> (SomeCardanoApiTx -> SomeCardanoApiTx) -> CardanoTx -> CardanoTx Source #
getCardanoTxId :: CardanoTx -> TxId Source #
getCardanoTxInputs :: CardanoTx -> [TxIn] Source #
getTxBodyContentInputs :: TxBodyContent ctx era -> [TxIn] Source #
getCardanoTxCollateralInputs :: CardanoTx -> [TxIn] Source #
getTxBodyContentCollateralInputs :: TxBodyContent ctx era -> [TxIn] Source #
getCardanoTxOutputs :: CardanoTx -> [TxOut] Source #
getCardanoTxFee :: CardanoTx -> Value Source #
getCardanoTxMint :: CardanoTx -> Value Source #
getTxBodyContentMint :: TxBodyContent ctx era -> Value Source #
txBodyContentIns :: Lens' (TxBodyContent BuildTx BabbageEra) [(TxIn, BuildTxWith BuildTx (Witness WitCtxTxIn BabbageEra))] Source #
txBodyContentOuts :: Lens' (TxBodyContent ctx BabbageEra) [TxOut] Source #
updateUtxo :: CardanoTx -> Map TxOutRef TxOut -> Map TxOutRef TxOut Source #
Update a map of unspent transaction outputs and signatures based on the inputs and outputs of a transaction.
updateUtxoCollateral :: CardanoTx -> Map TxOutRef TxOut -> Map TxOutRef TxOut Source #
Update a map of unspent transaction outputs and signatures based on the collateral inputs of a transaction (for when it is invalid).
txOutRefs :: Tx -> [(TxOut, TxOutRef)] Source #
A list of a transaction's outputs paired with a TxOutRefs referring to them.
pubKeyTxOut :: Value -> PaymentPubKey -> Maybe StakingCredential -> Either ToCardanoError TxOut Source #
Create a transaction output locked by a public payment key and optionnaly a public stake key.
addCardanoTxSignature :: PrivateKey -> CardanoTx -> CardanoTx Source #
addSignature :: PrivateKey -> Passphrase -> Tx -> Tx Source #
Sign the transaction with a PrivateKey and passphrase (ByteString) and add the signature to the
transaction's list of signatures.
addSignature' :: PrivateKey -> Tx -> Tx Source #
Sign the transaction with a PrivateKey that has no passphrase and add the signature to the
transaction's list of signatures
type Blockchain = [Block] Source #
A blockchain, which is just a list of blocks, starting with the newest.
type Block = [OnChainTx] Source #
A block on the blockchain. This is just a list of transactions following on from the chain so far.
A transaction on the blockchain. Invalid transactions are still put on the chain to be able to collect fees.
Instances
| Eq OnChainTx Source # | |
| Show OnChainTx Source # | |
| Generic OnChainTx Source # | |
| ToJSON OnChainTx Source # | |
| FromJSON OnChainTx Source # | |
| Pretty OnChainTx Source # | |
| Serialise OnChainTx Source # | |
| type Rep OnChainTx Source # | |
Defined in Ledger.Blockchain type Rep OnChainTx = D1 ('MetaData "OnChainTx" "Ledger.Blockchain" "plutus-ledger-1.1.0.0-JskZbcPMCdRJVHaAZ0to82" 'False) (C1 ('MetaCons "Invalid" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 CardanoTx)) :+: C1 ('MetaCons "Valid" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 CardanoTx))) | |
Block identifier (usually a hash)
Constructors
| BlockId | |
Fields | |
Instances
| Eq BlockId Source # | |
| Ord BlockId Source # | |
Defined in Ledger.Blockchain | |
| Show BlockId Source # | |
| Generic BlockId Source # | |
| ToJSON BlockId Source # | |
| FromJSON BlockId Source # | |
| ToSchema BlockId Source # | |
Defined in Ledger.Blockchain Methods declareNamedSchema :: Proxy BlockId -> Declare (Definitions Schema) NamedSchema Source # | |
| Pretty BlockId Source # | |
| type Rep BlockId Source # | |
Defined in Ledger.Blockchain type Rep BlockId = D1 ('MetaData "BlockId" "Ledger.Blockchain" "plutus-ledger-1.1.0.0-JskZbcPMCdRJVHaAZ0to82" 'True) (C1 ('MetaCons "BlockId" 'PrefixI 'True) (S1 ('MetaSel ('Just "getBlockId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ByteString))) | |
onChainTxIsValid :: OnChainTx -> Bool Source #
outputsProduced :: OnChainTx -> Map TxOutRef TxOut Source #
Outputs added to the UTXO set by the OnChainTx
transaction :: Blockchain -> TxId -> Maybe OnChainTx Source #
Lookup a transaction in a Blockchain by its id.
out :: Blockchain -> TxOutRef -> Maybe TxOut Source #
Determine the unspent output that an input refers to
value :: Blockchain -> TxOutRef -> Maybe Value Source #
Determine the unspent value that a transaction output refers to.
datumTxo :: Blockchain -> TxOutRef -> Maybe DatumHash Source #
Determine the data script that a transaction output refers to.
pubKeyTxo :: Blockchain -> TxOutRef -> Maybe PubKeyHash Source #
Determine the public key that locks a transaction output, if there is one.
unspentOutputs :: Blockchain -> Map TxOutRef TxOut Source #
The unspent transaction outputs of the ledger as a whole.
initialise :: Blockchain -> UtxoIndex Source #
Create an index of all UTxOs on the chain.
insert :: CardanoTx -> UtxoIndex -> UtxoIndex Source #
Update the index for the addition of a transaction.
insertCollateral :: CardanoTx -> UtxoIndex -> UtxoIndex Source #
Update the index for the addition of only the collateral inputs of a failed transaction.
insertBlock :: Block -> UtxoIndex -> UtxoIndex Source #
Update the index for the addition of a block.
lookup :: MonadError ValidationError m => TxOutRef -> UtxoIndex -> m TxOut Source #
Find an unspent transaction output by the TxOutRef that spends it.
adjustTxOut :: PParams (BabbageEra StandardCrypto) -> TxOut -> Either ToCardanoError ([Ada], TxOut) Source #
Adjust a single transaction output so it contains at least the minimum amount of Ada and return the adjustment (if any) and the updated TxOut.
minAdaTxOut :: PParams (BabbageEra StandardCrypto) -> TxOut -> Ada Source #
Exact computation of the mimimum Ada required for a given TxOut. TODO: Should be moved to cardano-api-extended once created
minAdaTxOutEstimated :: Ada Source #
Provide a reasonable estimate of the mimimum of Ada required for a TxOut.
An exact estimate of the the mimimum of Ada in a TxOut is determined by two things:
- the PParams, more precisely its coinPerUTxOWord parameter.
- the size of the TxOut.
In many situations though, we need to determine a plausible value for the minimum of Ada needed for a TxOut
without knowing much of the TxOut.
This function provides a value big enough to balance UTxOs without
a large inlined data (larger than a hash) nor a complex val with a lot of minted values.
It's superior to the lowest minimum needed for an UTxO, as the lowest value require no datum.
An estimate of the minimum required Ada for each tx output.
maxMinAdaTxOut :: Ada Source #
TODO Should be calculated based on the maximum script size permitted on the Cardano blockchain.
data AssetClass Source #
An asset class, identified by currency symbol and token name.
Instances
data CurrencySymbol Source #
Instances
ByteString of a name of a token, shown as UTF-8 string when possible
Instances
A cryptocurrency value. This is a map from CurrencySymbols to a
quantity of that currency.
Operations on currencies are usually implemented pointwise. That is,
we apply the operation to the quantities for each currency in turn. So
when we add two Values the resulting Value has, for each currency,
the sum of the quantities of that particular currency in the argument
Value. The effect of this is that the currencies in the Value are "independent",
and are operated on separately.
Whenever we need to get the quantity of a currency in a Value where there
is no explicit quantity of that currency in the Value, then the quantity is
taken to be zero.
See note [Currencies] for more details.
Instances
ADA, the special currency on the Cardano blockchain. The unit of Ada is Lovelace, and
1M Lovelace is one Ada.
See note [Currencies] in TH.
Instances
A representation of the ledger DCert. Some information is digested, and not included
Instances
Instances
| Eq NetworkId | |
| Data NetworkId Source # | |
Defined in Ledger.Orphans Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> NetworkId -> c NetworkId Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c NetworkId Source # toConstr :: NetworkId -> Constr Source # dataTypeOf :: NetworkId -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c NetworkId) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c NetworkId) Source # gmapT :: (forall b. Data b => b -> b) -> NetworkId -> NetworkId Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> NetworkId -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> NetworkId -> r Source # gmapQ :: (forall d. Data d => d -> u) -> NetworkId -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> NetworkId -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> NetworkId -> m NetworkId Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> NetworkId -> m NetworkId Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> NetworkId -> m NetworkId Source # | |
| Show NetworkId | |
| Generic NetworkId Source # | |
| type Rep NetworkId Source # | |
Defined in Ledger.Orphans type Rep NetworkId = D1 ('MetaData "NetworkId" "Cardano.Api.NetworkId" "cardano-api-1.35.4-1Qeb0LwBSO04Jx7qro0yT5" 'False) (C1 ('MetaCons "Mainnet" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Testnet" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedUnpack) (Rec0 NetworkMagic))) | |
data Credential Source #
Credential required to unlock a transaction output
Instances
data StakingCredential Source #
Staking credential used to assign rewards