Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- data SatInt
- newtype ExMemory = ExMemory CostingInteger
- data ExBudget = ExBudget {}
- newtype ExCPU = ExCPU CostingInteger
- findContinuingOutputs :: ScriptContext -> [Integer]
- findDatum :: DatumHash -> TxInfo -> Maybe Datum
- findDatumHash :: Datum -> TxInfo -> Maybe DatumHash
- findOwnInput :: ScriptContext -> Maybe TxInInfo
- findTxInByTxOutRef :: TxOutRef -> TxInfo -> Maybe TxInInfo
- fromSymbol :: CurrencySymbol -> ValidatorHash
- getContinuingOutputs :: ScriptContext -> [TxOut]
- ownCurrencySymbol :: ScriptContext -> CurrencySymbol
- ownHash :: ScriptContext -> ValidatorHash
- ownHashes :: ScriptContext -> (ValidatorHash, DatumHash)
- pubKeyOutput :: TxOut -> Maybe PubKeyHash
- pubKeyOutputsAt :: PubKeyHash -> TxInfo -> [Value]
- scriptOutputsAt :: ValidatorHash -> TxInfo -> [(DatumHash, Value)]
- spendsOutput :: TxInfo -> TxId -> Integer -> Bool
- txSignedBy :: TxInfo -> PubKeyHash -> Bool
- valueLockedBy :: TxInfo -> ValidatorHash -> Value
- valuePaidTo :: TxInfo -> PubKeyHash -> Value
- valueProduced :: TxInfo -> Value
- valueSpent :: TxInfo -> Value
- data ScriptContext = ScriptContext {}
- data ScriptPurpose
- = Minting CurrencySymbol
- | Spending TxOutRef
- | Rewarding StakingCredential
- | Certifying DCert
- data TxInInfo = TxInInfo {
- txInInfoOutRef :: TxOutRef
- txInInfoResolved :: TxOut
- 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 TxOutRef = TxOutRef {
- txOutRefId :: TxId
- txOutRefIdx :: Integer
- newtype POSIXTime = POSIXTime {}
- newtype PubKeyHash = PubKeyHash {
- getPubKeyHash :: BuiltinByteString
- newtype DatumHash = DatumHash BuiltinByteString
- newtype Datum = Datum {
- getDatum :: BuiltinData
- type POSIXTimeRange = Interval POSIXTime
- data Interval a = Interval {
- ivFrom :: LowerBound a
- ivTo :: UpperBound a
- newtype ValidatorHash = ValidatorHash BuiltinByteString
- toPubKeyHash :: Address -> Maybe PubKeyHash
- newtype MintingPolicyHash = MintingPolicyHash BuiltinByteString
- inScripts :: TxIn -> Maybe (Validator, Redeemer, Datum)
- isPayToScriptOut :: TxOut -> Bool
- isPubKeyOut :: TxOut -> Bool
- pubKeyHashTxOut :: Value -> PubKeyHash -> TxOut
- pubKeyTxIns :: Fold (Set TxIn) TxIn
- scriptTxIns :: Fold (Set TxIn) TxIn
- data RedeemerPtr = RedeemerPtr ScriptTag Integer
- type Redeemers = Map RedeemerPtr Redeemer
- data ScriptTag
- newtype Validator = Validator {}
- newtype Redeemer = Redeemer {
- getRedeemer :: BuiltinData
- data Address = Address {}
- applyArguments :: Script -> [Data] -> Script
- applyMintingPolicyScript :: Context -> MintingPolicy -> Redeemer -> Script
- applyStakeValidatorScript :: Context -> StakeValidator -> Redeemer -> Script
- applyValidator :: Context -> Validator -> Datum -> Redeemer -> Script
- evaluateScript :: MonadError ScriptError m => Script -> m (ExBudget, [Text])
- fromCompiledCode :: CompiledCode a -> Script
- mkMintingPolicyScript :: CompiledCode (BuiltinData -> BuiltinData -> ()) -> MintingPolicy
- mkStakeValidatorScript :: CompiledCode (BuiltinData -> BuiltinData -> ()) -> StakeValidator
- mkValidatorScript :: CompiledCode (BuiltinData -> BuiltinData -> BuiltinData -> ()) -> Validator
- runMintingPolicyScript :: MonadError ScriptError m => Context -> MintingPolicy -> Redeemer -> m (ExBudget, [Text])
- runScript :: MonadError ScriptError m => Context -> Validator -> Datum -> Redeemer -> m (ExBudget, [Text])
- runStakeValidatorScript :: MonadError ScriptError m => Context -> StakeValidator -> Redeemer -> m (ExBudget, [Text])
- scriptSize :: Script -> Integer
- unMintingPolicyScript :: MintingPolicy -> Script
- unStakeValidatorScript :: StakeValidator -> Script
- unValidatorScript :: Validator -> Script
- unitDatum :: Datum
- unitRedeemer :: Redeemer
- newtype Context = Context BuiltinData
- newtype MintingPolicy = MintingPolicy {}
- newtype RedeemerHash = RedeemerHash BuiltinByteString
- newtype Script = Script {
- unScript :: Program DeBruijn DefaultUni DefaultFun ()
- data ScriptError
- = EvaluationError [Text] String
- | EvaluationException String String
- newtype ScriptHash = ScriptHash {
- getScriptHash :: BuiltinByteString
- newtype StakeValidator = StakeValidator {}
- newtype StakeValidatorHash = StakeValidatorHash BuiltinByteString
- examplePlutusScriptAlwaysFails :: WitCtx witctx -> PlutusScript PlutusScriptV1
- examplePlutusScriptAlwaysSucceeds :: WitCtx witctx -> PlutusScript PlutusScriptV1
- filterValue :: (AssetId -> Bool) -> Value -> Value
- negateValue :: Value -> Value
- selectAsset :: Value -> AssetId -> Quantity
- selectLovelace :: Value -> Lovelace
- valueFromList :: [(AssetId, Quantity)] -> Value
- valueToList :: Value -> [(AssetId, Quantity)]
- data WitCtx witctx where
- WitCtxTxIn :: WitCtx WitCtxTxIn
- WitCtxMint :: WitCtx WitCtxMint
- WitCtxStake :: WitCtx WitCtxStake
- newtype TxId = TxId (Hash StandardCrypto EraIndependentTxBody)
- data TxIn = TxIn TxId TxIx
- newtype TxIx = TxIx Word
- data AssetId
- data AssetName
- newtype Lovelace = Lovelace Integer
- data PolicyId
- data Value
- dataHash :: BuiltinData -> BuiltinByteString
- datumHash :: Datum -> DatumHash
- mintingPolicyHash :: Versioned MintingPolicy -> MintingPolicyHash
- redeemerHash :: Redeemer -> RedeemerHash
- scriptCurrencySymbol :: Versioned MintingPolicy -> CurrencySymbol
- scriptHash :: Versioned Script -> ScriptHash
- stakeValidatorHash :: Versioned StakeValidator -> StakeValidatorHash
- validatorHash :: Versioned Validator -> ValidatorHash
- data Language
- data Versioned script = Versioned {
- unversioned :: script
- version :: Language
- to :: a -> Interval a
- from :: a -> Interval a
- always :: Interval a
- scriptHashAddress :: ValidatorHash -> Address
- stakingCredential :: Address -> Maybe StakingCredential
- toValidatorHash :: Address -> Maybe ValidatorHash
- after :: Ord a => a -> Interval a -> Bool
- before :: Ord a => 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
- interval :: a -> a -> Interval a
- isEmpty :: (Enum a, Ord a) => Interval a -> Bool
- lowerBound :: a -> LowerBound a
- member :: Ord a => a -> Interval a -> Bool
- never :: Interval a
- overlaps :: (Enum a, Ord a) => Interval a -> Interval a -> Bool
- singleton :: a -> Interval a
- strictLowerBound :: a -> LowerBound a
- strictUpperBound :: a -> UpperBound a
- upperBound :: a -> UpperBound a
- type Closure = Bool
- data Extended a
- data LowerBound a = LowerBound (Extended a) Closure
- data UpperBound a = UpperBound (Extended a) Closure
- fromMilliSeconds :: DiffMilliSeconds -> POSIXTime
- newtype DiffMilliSeconds = DiffMilliSeconds Integer
- examplePlutusScriptAlwaysSucceedsHash :: WitCtx ctx -> BuiltinByteString
- examplePlutusScriptAlwaysFailsHash :: WitCtx ctx -> BuiltinByteString
- newtype Slot = Slot {}
- type SlotRange = Interval Slot
- width :: SlotRange -> Maybe Integer
- newtype Signature = Signature {
- getSignature :: BuiltinByteString
- newtype Passphrase = Passphrase {
- unPassphrase :: ByteString
- newtype PubKey = PubKey {
- getPubKey :: LedgerBytes
- newtype PrivateKey = PrivateKey {
- getPrivateKey :: LedgerBytes
- 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 {
- unPaymentPrivateKey :: XPrv
- 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
- mkValidatorCardanoAddress :: NetworkId -> Versioned Validator -> AddressInEra BabbageEra
- data ToCardanoError
- = TxBodyError String
- | DeserialisationError
- | InvalidValidityRange
- | ValueNotPureAda
- | OutputHasZeroAda
- | StakingPointersNotSupported
- | SimpleScriptsNotSupportedToCardano
- | MissingInputValidator
- | MissingDatum
- | MissingMintingPolicy
- | ScriptPurposeNotSupported ScriptTag
- | MissingMintingPolicyRedeemer
- | MissingStakeValidator
- | UnsupportedPlutusVersion Language
- | Tag String ToCardanoError
- data CardanoTx where
- CardanoTx :: IsCardanoEra era => Tx era -> EraInMode era CardanoMode -> CardanoTx
- pattern CardanoEmulatorEraTx :: Tx BabbageEra -> CardanoTx
- adaToCardanoValue :: Ada -> Value
- fromCardanoValue :: Value -> Value
- toCardanoValue :: Value -> Either ToCardanoError Value
- fromCardanoAssetId :: AssetId -> AssetClass
- toCardanoAssetId :: AssetClass -> Either ToCardanoError AssetId
- lovelaceToValue :: Lovelace -> Value
- lovelaceValueOf :: Integer -> Value
- adaValueOf :: Rational -> Value
- isZero :: Value -> Bool
- isAdaOnlyValue :: Value -> Bool
- noAdaValue :: Value -> Value
- adaOnlyValue :: Value -> Value
- assetIdValue :: AssetId -> Integer -> Value
- scale :: Integer -> Value -> Value
- split :: Value -> (Value, Value)
- policyId :: Versioned MintingPolicy -> PolicyId
- combine :: Monoid m => (AssetId -> Quantity -> Quantity -> m) -> Value -> Value -> m
- valueGeq :: Value -> Value -> Bool
- valueLeq :: Value -> Value -> Bool
- type ReferenceScript = ReferenceScript BabbageEra
- type MintingWitnessesMap = Map MintingPolicyHash (Redeemer, Maybe (Versioned TxOutRef))
- type ScriptsMap = Map ScriptHash (Versioned Script)
- newtype TxOut = TxOut {
- getTxOut :: TxOut CtxTx BabbageEra
- data Certificate = Certificate {}
- data Withdrawal = Withdrawal {}
- cardanoTxOutValue :: TxOut ctx era -> Value
- txOutValue :: TxOut -> Value
- outValue :: Lens TxOut TxOut Value (TxOutValue BabbageEra)
- outValue' :: Lens' TxOut (TxOutValue BabbageEra)
- toSizedTxOut :: TxOut -> Sized (TxOut StandardBabbage)
- toCtxUTxOTxOut :: TxOut -> TxOut CtxUTxO BabbageEra
- txOutDatumHash :: TxOut -> Maybe DatumHash
- txOutDatum :: forall d. FromData d => TxOut -> Maybe d
- cardanoTxOutDatumHash :: TxOutDatum CtxUTxO BabbageEra -> Maybe (Hash ScriptData)
- 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)
- lookupMintingPolicy :: ScriptsMap -> MintingPolicyHash -> Maybe (Versioned MintingPolicy)
- lookupStakeValidator :: ScriptsMap -> StakeValidatorHash -> Maybe (Versioned StakeValidator)
- emptyTxBodyContent :: TxBodyContent BuildTx BabbageEra
- data ValidationError
- type UtxoIndex = UTxO BabbageEra
- newtype OnChainTx = OnChainTx {
- getOnChainTx :: Validated (Tx EmulatorEra)
- eitherTx :: (CardanoTx -> r) -> (CardanoTx -> r) -> OnChainTx -> r
- unOnChain :: OnChainTx -> CardanoTx
- data ValidationResult
- type RedeemerReport = Map RdmrPtr ([Text], ExUnits)
- type ValidationSuccess = (RedeemerReport, Validated (Tx EmulatorEra))
- type ValidationErrorInPhase = (ValidationPhase, ValidationError)
- data ValidationPhase
- _TxOutRefNotFound :: Prism' ValidationError TxIn
- _ScriptFailure :: Prism' ValidationError ScriptError
- _CardanoLedgerValidationError :: Prism' ValidationError Text
- _FailPhase1 :: Prism' ValidationResult (CardanoTx, ValidationError)
- _FailPhase2 :: Prism' ValidationResult (OnChainTx, ValidationError, Value)
- _Success :: Prism' ValidationResult (OnChainTx, RedeemerReport)
- cardanoTxFromValidationResult :: ValidationResult -> CardanoTx
- toOnChain :: ValidationResult -> Maybe OnChainTx
- getEvaluationLogs :: ValidationResult -> [Text]
- 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
- _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 -> Maybe (DatumHash, DatumFromQuery) -> Maybe (Versioned Script) -> Maybe 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)
- toDecoratedTxOut :: TxOut -> Maybe DecoratedTxOut
- toTxOut :: NetworkId -> DecoratedTxOut -> Either ToCardanoError TxOut
- toTxInfoTxOut :: DecoratedTxOut -> TxOut
- fromDecoratedIndex :: NetworkId -> Map TxOutRef DecoratedTxOut -> Either ToCardanoError UtxoIndex
- getCardanoTxId :: CardanoTx -> TxId
- getCardanoTxInputs :: CardanoTx -> [TxIn]
- getTxBodyContentInputs :: TxBodyContent ctx era -> [TxIn]
- getCardanoTxCollateralInputs :: CardanoTx -> [TxIn]
- getTxBodyContentCollateralInputs :: TxBodyContent ctx era -> [TxIn]
- getCardanoTxOutRefs :: CardanoTx -> [(TxOut, TxIn)]
- getCardanoTxOutputs :: CardanoTx -> [TxOut]
- getCardanoTxProducedOutputs :: CardanoTx -> Map TxIn TxOut
- getCardanoTxSpentOutputs :: CardanoTx -> Set TxIn
- getCardanoTxReturnCollateral :: CardanoTx -> Maybe TxOut
- getTxBodyContentReturnCollateral :: TxBodyContent ctx BabbageEra -> Maybe TxOut
- getCardanoTxProducedReturnCollateral :: CardanoTx -> Map TxIn TxOut
- getCardanoTxTotalCollateral :: CardanoTx -> Maybe Lovelace
- getCardanoTxFee :: CardanoTx -> Lovelace
- 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 -> Redeemers
- addCardanoTxSignature :: PrivateKey -> CardanoTx -> CardanoTx
- decoratedTxOutPlutusValue :: DecoratedTxOut -> Value
- type Blockchain = [Block]
- type Block = [OnChainTx]
- newtype BlockId = BlockId {
- getBlockId :: ByteString
- onChainTxIsValid :: OnChainTx -> Bool
- consumableInputs :: OnChainTx -> [TxIn]
- outputsProduced :: OnChainTx -> Map TxIn TxOut
- initialise :: Blockchain -> UtxoIndex
- insert :: CardanoTx -> UtxoIndex -> UtxoIndex
- insertCollateral :: CardanoTx -> UtxoIndex -> UtxoIndex
- insertBlock :: Block -> UtxoIndex -> UtxoIndex
- lookup :: TxIn -> UtxoIndex -> Maybe TxOut
- getCollateral :: UtxoIndex -> CardanoTx -> Value
- adjustTxOut :: PParams (BabbageEra StandardCrypto) -> TxOut -> ([Lovelace], TxOut)
- minAdaTxOut :: PParams (BabbageEra StandardCrypto) -> TxOut -> Lovelace
- minAdaTxOutEstimated :: Ada
- minLovelaceTxOutEstimated :: Lovelace
- maxMinAdaTxOut :: Ada
- maxFee :: Ada
- genesisTxIn :: TxIn
- createGenesisTransaction :: Map CardanoAddress Value -> CardanoTx
- data DCert
- data NetworkId
- data Credential
- data StakingCredential
Documentation
Instances
ExMemory CostingInteger |
Instances
Instances
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 | |
FromJSON ExCPU | |
Defined in PlutusCore.Evaluation.Machine.ExMemory parseJSON :: Value -> Parser ExCPU parseJSONList :: Value -> Parser [ExCPU] | |
ToJSON ExCPU | |
Defined in PlutusCore.Evaluation.Machine.ExMemory | |
Pretty ExCPU | |
Defined in PlutusCore.Evaluation.Machine.ExMemory | |
NoThunks ExCPU | |
Lift ExCPU | |
PrettyBy config ExCPU | |
Defined in PlutusCore.Evaluation.Machine.ExMemory prettyBy :: config -> ExCPU -> Doc ann prettyListBy :: config -> [ExCPU] -> Doc ann | |
type Rep ExCPU | |
Defined in PlutusCore.Evaluation.Machine.ExMemory |
findContinuingOutputs :: ScriptContext -> [Integer] #
findOwnInput :: ScriptContext -> Maybe TxInInfo #
fromSymbol :: CurrencySymbol -> ValidatorHash #
getContinuingOutputs :: ScriptContext -> [TxOut] #
ownCurrencySymbol :: ScriptContext -> CurrencySymbol #
ownHash :: ScriptContext -> ValidatorHash #
ownHashes :: ScriptContext -> (ValidatorHash, DatumHash) #
pubKeyOutput :: TxOut -> Maybe PubKeyHash #
pubKeyOutputsAt :: PubKeyHash -> TxInfo -> [Value] #
scriptOutputsAt :: ValidatorHash -> TxInfo -> [(DatumHash, Value)] #
spendsOutput :: TxInfo -> TxId -> Integer -> Bool #
txSignedBy :: TxInfo -> PubKeyHash -> Bool #
valueLockedBy :: TxInfo -> ValidatorHash -> Value #
valuePaidTo :: TxInfo -> PubKeyHash -> Value #
valueProduced :: TxInfo -> Value #
valueSpent :: TxInfo -> Value #
data ScriptContext #
Instances
data ScriptPurpose #
Minting CurrencySymbol | |
Spending TxOutRef | |
Rewarding StakingCredential | |
Certifying DCert |
Instances
TxInInfo | |
|
Instances
TxInfo | |
|
Instances
TxOutRef | |
|
Instances
Instances
newtype PubKeyHash #
PubKeyHash | |
|
Instances
DatumHash BuiltinByteString |
Instances
Instances
Eq Datum | |
Ord Datum | |
Defined in Plutus.V1.Ledger.Scripts | |
Show Datum | |
Generic Datum | |
NFData Datum | |
Defined in Plutus.V1.Ledger.Scripts | |
Serialise Datum | |
Defined in Ledger.Scripts.Orphans encodeList :: [Datum] -> Encoding decodeList :: Decoder s [Datum] | |
FromJSON Datum | |
Defined in Ledger.Scripts.Orphans parseJSON :: Value -> Parser Datum parseJSONList :: Value -> Parser [Datum] | |
ToJSON Datum | |
Defined in Ledger.Scripts.Orphans | |
Eq Datum | |
Defined in Plutus.V1.Ledger.Scripts | |
Pretty Datum | |
Defined in Plutus.V1.Ledger.Scripts | |
FromData Datum | |
Defined in Plutus.V1.Ledger.Scripts fromBuiltinData :: BuiltinData -> Maybe Datum | |
ToData Datum | |
Defined in Plutus.V1.Ledger.Scripts toBuiltinData :: Datum -> BuiltinData | |
UnsafeFromData Datum | |
Defined in Plutus.V1.Ledger.Scripts unsafeFromBuiltinData :: BuiltinData -> Datum | |
Lift DefaultUni Datum | |
Defined in Plutus.V1.Ledger.Scripts | |
Typeable DefaultUni Datum | |
Defined in Plutus.V1.Ledger.Scripts | |
type Rep Datum | |
Defined in Plutus.V1.Ledger.Scripts |
type POSIXTimeRange = Interval POSIXTime #
Interval | |
|
Instances
Functor Interval | |
Defined in Plutus.V1.Ledger.Interval | |
(Typeable DefaultUni a, Lift DefaultUni (LowerBound a), Lift DefaultUni (UpperBound a)) => Lift DefaultUni (Interval a) | |
Defined in Plutus.V1.Ledger.Interval | |
Eq a => Eq (Interval a) | |
Ord a => Ord (Interval a) | |
Defined in Plutus.V1.Ledger.Interval compare :: Interval a -> Interval a -> Ordering Source # (<) :: Interval a -> Interval a -> Bool Source # (<=) :: Interval a -> Interval a -> Bool Source # (>) :: Interval a -> Interval a -> Bool Source # (>=) :: Interval a -> Interval a -> Bool Source # | |
Show a => Show (Interval a) | |
Generic (Interval a) | |
NFData a => NFData (Interval a) | |
Defined in Plutus.V1.Ledger.Interval | |
Serialise a => Serialise (Interval a) | |
Defined in Ledger.Slot encode :: Interval a -> Encoding decode :: Decoder s (Interval a) encodeList :: [Interval a] -> Encoding decodeList :: Decoder s [Interval a] | |
Hashable a => Hashable (Interval a) | |
Defined in Ledger.Slot | |
FromJSON a => FromJSON (Interval a) | |
Defined in Ledger.Slot parseJSON :: Value -> Parser (Interval a) parseJSONList :: Value -> Parser [Interval a] | |
ToJSON a => ToJSON (Interval a) | |
Defined in Ledger.Slot toEncoding :: Interval a -> Encoding toJSONList :: [Interval a] -> Value toEncodingList :: [Interval a] -> Encoding | |
Eq a => Eq (Interval a) | |
Defined in Plutus.V1.Ledger.Interval | |
Ord a => BoundedJoinSemiLattice (Interval a) | |
Defined in Plutus.V1.Ledger.Interval | |
Ord a => BoundedMeetSemiLattice (Interval a) | |
Defined in Plutus.V1.Ledger.Interval | |
Ord a => JoinSemiLattice (Interval a) | |
Defined in Plutus.V1.Ledger.Interval | |
Ord a => MeetSemiLattice (Interval a) | |
Defined in Plutus.V1.Ledger.Interval | |
Pretty a => Pretty (Interval a) | |
Defined in Plutus.V1.Ledger.Interval | |
FromData a => FromData (Interval a) | |
Defined in Plutus.V1.Ledger.Interval fromBuiltinData :: BuiltinData -> Maybe (Interval a) | |
ToData a => ToData (Interval a) | |
Defined in Plutus.V1.Ledger.Interval toBuiltinData :: Interval a -> BuiltinData | |
UnsafeFromData a => UnsafeFromData (Interval a) | |
Defined in Plutus.V1.Ledger.Interval unsafeFromBuiltinData :: BuiltinData -> Interval a | |
Typeable DefaultUni Interval | |
Defined in Plutus.V1.Ledger.Interval | |
type Rep (Interval a) | |
Defined in Plutus.V1.Ledger.Interval type Rep (Interval a) = D1 ('MetaData "Interval" "Plutus.V1.Ledger.Interval" "plutus-ledger-api-1.0.0.1-6EvbyJiK8IAAVEtnIJDu5Z" 'False) (C1 ('MetaCons "Interval" 'PrefixI 'True) (S1 ('MetaSel ('Just "ivFrom") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (LowerBound a)) :*: S1 ('MetaSel ('Just "ivTo") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (UpperBound a)))) |
newtype ValidatorHash #
ValidatorHash BuiltinByteString |
Instances
toPubKeyHash :: Address -> Maybe PubKeyHash #
newtype MintingPolicyHash #
MintingPolicyHash BuiltinByteString |
Instances
isPayToScriptOut :: TxOut -> Bool #
isPubKeyOut :: TxOut -> Bool #
pubKeyHashTxOut :: Value -> PubKeyHash -> TxOut #
pubKeyTxIns :: Fold (Set TxIn) TxIn #
scriptTxIns :: Fold (Set TxIn) TxIn #
data RedeemerPtr #
Instances
type Redeemers = Map RedeemerPtr Redeemer #
Instances
Instances
Eq Validator | |
Ord Validator | |
Defined in Plutus.V1.Ledger.Scripts | |
Show Validator | |
Generic Validator | |
NFData Validator | |
Defined in Plutus.V1.Ledger.Scripts | |
Serialise Validator | |
Defined in Plutus.V1.Ledger.Scripts encode :: Validator -> Encoding encodeList :: [Validator] -> Encoding decodeList :: Decoder s [Validator] | |
FromJSON Validator | |
Defined in Ledger.Scripts.Orphans parseJSON :: Value -> Parser Validator parseJSONList :: Value -> Parser [Validator] | |
ToJSON Validator | |
Defined in Ledger.Scripts.Orphans toEncoding :: Validator -> Encoding toJSONList :: [Validator] -> Value toEncodingList :: [Validator] -> Encoding | |
Pretty Validator | |
Defined in Plutus.V1.Ledger.Scripts | |
type Rep Validator | |
Defined in Plutus.V1.Ledger.Scripts |
Redeemer | |
|
Instances
Instances
applyArguments :: Script -> [Data] -> Script #
applyMintingPolicyScript :: Context -> MintingPolicy -> Redeemer -> Script #
applyStakeValidatorScript :: Context -> StakeValidator -> Redeemer -> Script #
evaluateScript :: MonadError ScriptError m => Script -> m (ExBudget, [Text]) #
fromCompiledCode :: CompiledCode a -> Script #
mkMintingPolicyScript :: CompiledCode (BuiltinData -> BuiltinData -> ()) -> MintingPolicy #
mkStakeValidatorScript :: CompiledCode (BuiltinData -> BuiltinData -> ()) -> StakeValidator #
mkValidatorScript :: CompiledCode (BuiltinData -> BuiltinData -> BuiltinData -> ()) -> Validator #
runMintingPolicyScript :: MonadError ScriptError m => Context -> MintingPolicy -> Redeemer -> m (ExBudget, [Text]) #
runScript :: MonadError ScriptError m => Context -> Validator -> Datum -> Redeemer -> m (ExBudget, [Text]) #
runStakeValidatorScript :: MonadError ScriptError m => Context -> StakeValidator -> Redeemer -> m (ExBudget, [Text]) #
scriptSize :: Script -> Integer #
unValidatorScript :: Validator -> Script #
Context BuiltinData |
Instances
Show Context | |
FromJSON Context | |
Defined in Ledger.Scripts.Orphans parseJSON :: Value -> Parser Context parseJSONList :: Value -> Parser [Context] | |
ToJSON Context | |
Defined in Ledger.Scripts.Orphans toEncoding :: Context -> Encoding toJSONList :: [Context] -> Value toEncodingList :: [Context] -> Encoding | |
Pretty Context | |
Defined in Plutus.V1.Ledger.Scripts |
newtype MintingPolicy #
Instances
newtype RedeemerHash #
RedeemerHash BuiltinByteString |
Instances
Instances
Eq Script | |
Ord Script | |
Defined in Plutus.V1.Ledger.Scripts | |
Show Script | |
Generic Script | |
NFData Script | |
Defined in Plutus.V1.Ledger.Scripts | |
Serialise Script | |
Defined in Plutus.V1.Ledger.Scripts encodeList :: [Script] -> Encoding decodeList :: Decoder s [Script] | |
FromJSON Script | |
Defined in Ledger.Scripts.Orphans parseJSON :: Value -> Parser Script parseJSONList :: Value -> Parser [Script] | |
ToJSON Script | |
Defined in Ledger.Scripts.Orphans toEncoding :: Script -> Encoding toJSONList :: [Script] -> Value toEncodingList :: [Script] -> Encoding | |
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-6EvbyJiK8IAAVEtnIJDu5Z" 'True) (C1 ('MetaCons "Script" 'PrefixI 'True) (S1 ('MetaSel ('Just "unScript") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Program DeBruijn DefaultUni DefaultFun ())))) |
data ScriptError #
Instances
newtype ScriptHash #
ScriptHash | |
|
Instances
newtype StakeValidator #
Instances
newtype StakeValidatorHash #
StakeValidatorHash BuiltinByteString |
Instances
examplePlutusScriptAlwaysFails :: WitCtx witctx -> PlutusScript PlutusScriptV1 #
examplePlutusScriptAlwaysSucceeds :: WitCtx witctx -> PlutusScript PlutusScriptV1 #
negateValue :: Value -> Value #
selectAsset :: Value -> AssetId -> Quantity #
selectLovelace :: Value -> Lovelace #
valueFromList :: [(AssetId, Quantity)] -> Value #
valueToList :: Value -> [(AssetId, Quantity)] #
WitCtxTxIn :: WitCtx WitCtxTxIn | |
WitCtxMint :: WitCtx WitCtxMint | |
WitCtxStake :: WitCtx WitCtxStake |
TxId (Hash StandardCrypto EraIndependentTxBody) |
Instances
Eq TxId | |
Ord TxId | |
Show TxId | |
IsString TxId | |
Defined in Cardano.Api.TxIn fromString :: String -> TxId Source # | |
Generic TxId Source # | |
Serialise TxId | |
Defined in Ledger.Tx.Orphans encodeList :: [TxId] -> Encoding decodeList :: Decoder s [TxId] | |
FromJSON TxId | |
Defined in Cardano.Api.TxIn parseJSON :: Value -> Parser TxId parseJSONList :: Value -> Parser [TxId] | |
FromJSONKey TxId | |
Defined in Cardano.Api.TxIn fromJSONKey :: FromJSONKeyFunction TxId fromJSONKeyList :: FromJSONKeyFunction [TxId] | |
ToJSON TxId | |
Defined in Cardano.Api.TxIn | |
ToJSONKey TxId | |
Defined in Cardano.Api.TxIn toJSONKey :: ToJSONKeyFunction TxId toJSONKeyList :: ToJSONKeyFunction [TxId] | |
Pretty TxId Source # | |
Defined in Ledger.Tx.Orphans | |
HasTypeProxy TxId | |
SerialiseAsRawBytes TxId | |
Defined in Cardano.Api.TxIn serialiseToRawBytes :: TxId -> ByteString deserialiseFromRawBytes :: AsType TxId -> ByteString -> Maybe TxId | |
type Rep TxId Source # | |
Defined in Ledger.Tx.Orphans | |
data AsType TxId | |
Defined in Cardano.Api.TxIn |
Instances
Instances
Enum TxIx | |
Eq TxIx | |
Ord TxIx | |
Show TxIx | |
Generic TxIx Source # | |
Serialise TxIx | |
Defined in Ledger.Tx.Orphans encodeList :: [TxIx] -> Encoding decodeList :: Decoder s [TxIx] | |
FromJSON TxIx | |
Defined in Cardano.Api.TxIn parseJSON :: Value -> Parser TxIx parseJSONList :: Value -> Parser [TxIx] | |
ToJSON TxIx | |
Defined in Cardano.Api.TxIn | |
type Rep TxIx Source # | |
Defined in Ledger.Tx.Orphans |
Instances
Instances
Instances
Instances
Instances
Eq Value | |
Show Value | |
Semigroup Value | |
Monoid Value | |
Serialise Value | |
Defined in Ledger.Value.Orphans encodeList :: [Value] -> Encoding decodeList :: Decoder s [Value] | |
FromJSON Value | |
Defined in Cardano.Api.Value parseJSON :: Value0 -> Parser Value parseJSONList :: Value0 -> Parser [Value] | |
ToJSON Value | |
Defined in Cardano.Api.Value | |
JoinSemiLattice Value | |
Defined in Ledger.Value.CardanoAPI | |
Pretty Value Source # | |
Defined in Ledger.Value.Orphans |
redeemerHash :: Redeemer -> RedeemerHash #
scriptCurrencySymbol :: Versioned MintingPolicy -> CurrencySymbol #
scriptHash :: Versioned Script -> ScriptHash #
Instances
Versioned | |
|
Instances
Functor Versioned | |
Eq script => Eq (Versioned script) | |
Ord script => Ord (Versioned script) | |
Defined in Plutus.Script.Utils.Scripts compare :: Versioned script -> Versioned script -> Ordering Source # (<) :: Versioned script -> Versioned script -> Bool Source # (<=) :: Versioned script -> Versioned script -> Bool Source # (>) :: Versioned script -> Versioned script -> Bool Source # (>=) :: Versioned script -> Versioned script -> Bool Source # max :: Versioned script -> Versioned script -> Versioned script Source # min :: Versioned script -> Versioned script -> Versioned script Source # | |
Show script => Show (Versioned script) | |
Generic (Versioned script) | |
Serialise script => Serialise (Versioned script) | |
Defined in Plutus.Script.Utils.Scripts encode :: Versioned script -> Encoding decode :: Decoder s (Versioned script) encodeList :: [Versioned script] -> Encoding decodeList :: Decoder s [Versioned script] | |
FromJSON script => FromJSON (Versioned script) | |
Defined in Plutus.Script.Utils.Scripts parseJSON :: Value -> Parser (Versioned script) parseJSONList :: Value -> Parser [Versioned script] | |
ToJSON script => ToJSON (Versioned script) | |
Defined in Plutus.Script.Utils.Scripts toJSON :: Versioned script -> Value toEncoding :: Versioned script -> Encoding toJSONList :: [Versioned script] -> Value toEncodingList :: [Versioned script] -> Encoding | |
Pretty script => Pretty (Versioned script) | |
Defined in Plutus.Script.Utils.Scripts | |
type Rep (Versioned script) | |
Defined in Plutus.Script.Utils.Scripts type Rep (Versioned script) = D1 ('MetaData "Versioned" "Plutus.Script.Utils.Scripts" "plutus-script-utils-1.2.0.0-5TpLCy32WGLK5IaOxcwe9j" 'False) (C1 ('MetaCons "Versioned" 'PrefixI 'True) (S1 ('MetaSel ('Just "unversioned") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 script) :*: S1 ('MetaSel ('Just "version") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Language))) |
intersection :: Ord a => Interval a -> Interval a -> Interval a #
lowerBound :: a -> LowerBound a #
strictLowerBound :: a -> LowerBound a #
strictUpperBound :: a -> UpperBound a #
upperBound :: a -> UpperBound a #
Instances
Functor Extended | |
Defined in Plutus.V1.Ledger.Interval | |
(Typeable DefaultUni a, Lift DefaultUni a) => Lift DefaultUni (Extended a) | |
Defined in Plutus.V1.Ledger.Interval | |
Eq a => Eq (Extended a) | |
Ord a => Ord (Extended a) | |
Defined in Plutus.V1.Ledger.Interval compare :: Extended a -> Extended a -> Ordering Source # (<) :: Extended a -> Extended a -> Bool Source # (<=) :: Extended a -> Extended a -> Bool Source # (>) :: Extended a -> Extended a -> Bool Source # (>=) :: Extended a -> Extended a -> Bool Source # | |
Show a => Show (Extended a) | |
Generic (Extended a) | |
NFData a => NFData (Extended a) | |
Defined in Plutus.V1.Ledger.Interval | |
Serialise a => Serialise (Extended a) | |
Defined in Ledger.Slot encode :: Extended a -> Encoding decode :: Decoder s (Extended a) encodeList :: [Extended a] -> Encoding decodeList :: Decoder s [Extended a] | |
Hashable a => Hashable (Extended a) | |
Defined in Ledger.Slot | |
FromJSON a => FromJSON (Extended a) | |
Defined in Ledger.Slot parseJSON :: Value -> Parser (Extended a) parseJSONList :: Value -> Parser [Extended a] | |
ToJSON a => ToJSON (Extended a) | |
Defined in Ledger.Slot toEncoding :: Extended a -> Encoding toJSONList :: [Extended a] -> Value toEncodingList :: [Extended a] -> Encoding | |
Eq a => Eq (Extended a) | |
Defined in Plutus.V1.Ledger.Interval | |
Ord a => Ord (Extended a) | |
Defined in Plutus.V1.Ledger.Interval | |
Pretty a => Pretty (Extended a) | |
Defined in Plutus.V1.Ledger.Interval | |
FromData a => FromData (Extended a) | |
Defined in Plutus.V1.Ledger.Interval fromBuiltinData :: BuiltinData -> Maybe (Extended a) | |
ToData a => ToData (Extended a) | |
Defined in Plutus.V1.Ledger.Interval toBuiltinData :: Extended a -> BuiltinData | |
UnsafeFromData a => UnsafeFromData (Extended a) | |
Defined in Plutus.V1.Ledger.Interval unsafeFromBuiltinData :: BuiltinData -> Extended a | |
Typeable DefaultUni Extended | |
Defined in Plutus.V1.Ledger.Interval | |
type Rep (Extended a) | |
Defined in Plutus.V1.Ledger.Interval type Rep (Extended a) = D1 ('MetaData "Extended" "Plutus.V1.Ledger.Interval" "plutus-ledger-api-1.0.0.1-6EvbyJiK8IAAVEtnIJDu5Z" 'False) (C1 ('MetaCons "NegInf" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Finite" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a)) :+: C1 ('MetaCons "PosInf" 'PrefixI 'False) (U1 :: Type -> Type))) |
data LowerBound a #
Instances
data UpperBound a #
Instances
newtype DiffMilliSeconds #
Instances
examplePlutusScriptAlwaysSucceedsHash :: WitCtx ctx -> BuiltinByteString Source #
examplePlutusScriptAlwaysFailsHash :: WitCtx ctx -> BuiltinByteString Source #
The slot number. This is a good proxy for time, since on the Cardano blockchain slots pass at a constant rate.
Instances
Enum Slot Source # | |
Eq Slot Source # | |
Integral Slot Source # | |
Defined in Ledger.Slot | |
Data Slot Source # | |
Defined in Ledger.Slot gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Slot -> c Slot Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Slot Source # toConstr :: Slot -> Constr Source # dataTypeOf :: Slot -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Slot) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Slot) Source # gmapT :: (forall b. Data b => b -> b) -> Slot -> Slot Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Slot -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Slot -> r Source # gmapQ :: (forall d. Data d => d -> u) -> Slot -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> Slot -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Slot -> m Slot Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Slot -> m Slot Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Slot -> m Slot Source # | |
Num Slot Source # | |
Ord Slot Source # | |
Real Slot Source # | |
Defined in Ledger.Slot toRational :: Slot -> Rational Source # | |
Show Slot Source # | |
Generic Slot Source # | |
Serialise Slot Source # | |
Defined in Ledger.Slot encodeList :: [Slot] -> Encoding decodeList :: Decoder s [Slot] | |
Hashable Slot Source # | |
Defined in Ledger.Slot | |
FromJSON Slot Source # | |
Defined in Ledger.Slot parseJSON :: Value -> Parser Slot parseJSONList :: Value -> Parser [Slot] | |
FromJSONKey Slot Source # | |
Defined in Ledger.Slot fromJSONKey :: FromJSONKeyFunction Slot fromJSONKeyList :: FromJSONKeyFunction [Slot] | |
ToJSON Slot Source # | |
Defined in Ledger.Slot | |
ToJSONKey Slot Source # | |
Defined in Ledger.Slot toJSONKey :: ToJSONKeyFunction Slot toJSONKeyList :: ToJSONKeyFunction [Slot] | |
Enum Slot Source # | |
Eq Slot Source # | |
Defined in Ledger.Slot | |
AdditiveGroup Slot Source # | |
Defined in Ledger.Slot | |
AdditiveMonoid Slot Source # | |
Defined in Ledger.Slot | |
AdditiveSemigroup Slot Source # | |
Defined in Ledger.Slot | |
Ord Slot Source # | |
Pretty Slot Source # | |
Defined in Ledger.Slot | |
FromData Slot Source # | |
Defined in Ledger.Slot fromBuiltinData :: BuiltinData -> Maybe Slot | |
ToData Slot Source # | |
Defined in Ledger.Slot toBuiltinData :: Slot -> BuiltinData | |
UnsafeFromData Slot Source # | |
Defined in Ledger.Slot unsafeFromBuiltinData :: BuiltinData -> Slot | |
Lift DefaultUni Slot Source # | |
Defined in Ledger.Slot | |
Typeable DefaultUni Slot Source # | |
Defined in Ledger.Slot | |
type Rep Slot Source # | |
Defined in Ledger.Slot |
width :: SlotRange -> Maybe Integer Source #
Number of Slot
s covered by the interval, if finite. width (from x) == Nothing
.
A message with a cryptographic signature.
Signature | |
|
Instances
newtype Passphrase Source #
Passphrase newtype to mark intent
Passphrase | |
|
Instances
Show Passphrase Source # | |
Defined in Ledger.Crypto | |
IsString Passphrase Source # | |
Defined in Ledger.Crypto fromString :: String -> Passphrase Source # |
Instances
newtype PrivateKey Source #
A cryptographic private key.
PrivateKey | |
|
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 #
Instances
newtype PaymentPrivateKey Source #
PaymentPrivateKey | |
|
type CardanoAddress = AddressInEra BabbageEra Source #
cardanoAddressCredential :: AddressInEra era -> Credential Source #
cardanoStakingCredential :: AddressInEra era -> Maybe StakingCredential Source #
cardanoPubKeyHash :: AddressInEra era -> Maybe PubKeyHash Source #
toPlutusAddress :: AddressInEra era -> Address Source #
toPlutusPubKeyHash :: Hash PaymentKey -> PubKeyHash Source #
newtype PaymentPubKeyHash Source #
Instances
xprvToPaymentPubKey :: XPrv -> PaymentPubKey Source #
newtype StakePubKey Source #
Instances
xprvToPaymentPubKeyHash :: XPrv -> PaymentPubKeyHash Source #
newtype StakePubKeyHash Source #
Instances
xprvToStakePubKey :: XPrv -> StakePubKey Source #
xprvToStakePubKeyHash :: XPrv -> StakePubKeyHash Source #
xprvToStakingCredential :: XPrv -> StakingCredential 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.
mkValidatorCardanoAddress :: NetworkId -> Versioned Validator -> AddressInEra BabbageEra Source #
Cardano address of a versioned Validator
script.
data ToCardanoError Source #
Instances
Cardano tx from any era.
pattern CardanoEmulatorEraTx :: Tx BabbageEra -> CardanoTx |
Instances
Eq CardanoTx Source # | |
Show CardanoTx Source # | |
Serialise CardanoTx Source # | |
Defined in Ledger.Tx.CardanoAPI.Internal encode :: CardanoTx -> Encoding encodeList :: [CardanoTx] -> Encoding decodeList :: Decoder s [CardanoTx] | |
FromJSON CardanoTx Source # | Converting If the "tx" field is from an unknown era, the JSON parser will print an error at runtime while parsing. |
Defined in Ledger.Tx.CardanoAPI.Internal parseJSON :: Value -> Parser CardanoTx parseJSONList :: Value -> Parser [CardanoTx] | |
ToJSON CardanoTx Source # | |
Defined in Ledger.Tx.CardanoAPI.Internal toEncoding :: CardanoTx -> Encoding toJSONList :: [CardanoTx] -> Value toEncodingList :: [CardanoTx] -> Encoding | |
Pretty CardanoTx Source # | |
adaToCardanoValue :: Ada -> Value Source #
fromCardanoValue :: Value -> Value Source #
toCardanoValue :: Value -> Either ToCardanoError Value Source #
fromCardanoAssetId :: AssetId -> AssetClass Source #
toCardanoAssetId :: AssetClass -> Either ToCardanoError AssetId Source #
lovelaceToValue :: Lovelace -> Value Source #
lovelaceValueOf :: Integer -> Value Source #
adaValueOf :: Rational -> Value Source #
isAdaOnlyValue :: Value -> Bool Source #
noAdaValue :: Value -> Value Source #
adaOnlyValue :: Value -> Value Source #
type ReferenceScript = ReferenceScript BabbageEra Source #
type MintingWitnessesMap = Map MintingPolicyHash (Redeemer, Maybe (Versioned TxOutRef)) Source #
type ScriptsMap = Map ScriptHash (Versioned Script) Source #
Instances
Eq TxOut Source # | |
Show TxOut Source # | |
Generic TxOut Source # | |
Serialise TxOut Source # | |
Defined in Ledger.Tx.Internal encodeList :: [TxOut] -> Encoding decodeList :: Decoder s [TxOut] | |
FromJSON TxOut Source # | |
Defined in Ledger.Tx.Internal parseJSON :: Value -> Parser TxOut parseJSONList :: Value -> Parser [TxOut] | |
ToJSON TxOut Source # | |
Defined in Ledger.Tx.Internal | |
Pretty TxOut Source # | |
Defined in Ledger.Tx.Internal | |
FromCBOR TxOut Source # | |
ToCBOR TxOut Source # | |
Defined in Ledger.Tx.Internal encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy TxOut -> Size encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [TxOut] -> Size | |
type Rep TxOut Source # | |
Defined in Ledger.Tx.Internal |
data Certificate Source #
Certificate | |
|
Instances
data Withdrawal Source #
Stake withdrawal, if applicable the script should be included in txScripts.
Withdrawal | |
|
Instances
cardanoTxOutValue :: TxOut ctx era -> Value Source #
txOutValue :: TxOut -> Value Source #
toSizedTxOut :: TxOut -> Sized (TxOut StandardBabbage) Source #
toCtxUTxOTxOut :: TxOut -> TxOut CtxUTxO BabbageEra Source #
txOutDatumHash :: TxOut -> Maybe DatumHash Source #
Get a hash from the stored TxOutDatum (either directly or by hashing the inlined datum)
txOutDatum :: forall d. FromData d => TxOut -> Maybe d Source #
cardanoTxOutDatumHash :: TxOutDatum CtxUTxO BabbageEra -> Maybe (Hash ScriptData) Source #
txOutPubKey :: TxOut -> Maybe PubKeyHash Source #
txOutAddress :: TxOut -> CardanoAddress Source #
outAddress :: Lens' TxOut (AddressInEra BabbageEra) Source #
outReferenceScript :: Lens' TxOut ReferenceScript Source #
lookupScript :: ScriptsMap -> ScriptHash -> Maybe (Versioned Script) Source #
lookupValidator :: ScriptsMap -> ValidatorHash -> Maybe (Versioned Validator) Source #
lookupStakeValidator :: ScriptsMap -> StakeValidatorHash -> Maybe (Versioned StakeValidator) Source #
emptyTxBodyContent :: TxBodyContent BuildTx BabbageEra Source #
data ValidationError Source #
A reason why a transaction is invalid.
TxOutRefNotFound TxIn | 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 |
MaxCollateralInputsExceeded | Balancing failed, it needed more than the maximum number of collateral inputs |
Instances
A transaction on the blockchain. Invalid transactions are still put on the chain to be able to collect fees.
OnChainTx | |
|
Instances
Eq OnChainTx Source # | |
Show OnChainTx Source # | |
Generic OnChainTx Source # | |
Serialise OnChainTx Source # | |
Defined in Ledger.Index.Internal encode :: OnChainTx -> Encoding encodeList :: [OnChainTx] -> Encoding decodeList :: Decoder s [OnChainTx] | |
type Rep OnChainTx Source # | |
Defined in Ledger.Index.Internal type Rep OnChainTx = D1 ('MetaData "OnChainTx" "Ledger.Index.Internal" "plutus-ledger-1.2.0.0-8dOSOspdVv7Hd909lHBnfn" 'True) (C1 ('MetaCons "OnChainTx" 'PrefixI 'True) (S1 ('MetaSel ('Just "getOnChainTx") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Validated (Tx EmulatorEra))))) |
data ValidationResult Source #
FailPhase1 !CardanoTx !ValidationError | A transaction failed to validate in phase 1. |
FailPhase2 !OnChainTx !ValidationError !Value | A transaction failed to validate in phase 2. The |
Success !OnChainTx !RedeemerReport |
Instances
type RedeemerReport = Map RdmrPtr ([Text], ExUnits) Source #
type ValidationSuccess = (RedeemerReport, Validated (Tx EmulatorEra)) Source #
data ValidationPhase Source #
Instances
Eq ValidationPhase Source # | |
Defined in Ledger.Index.Internal (==) :: ValidationPhase -> ValidationPhase -> Bool Source # (/=) :: ValidationPhase -> ValidationPhase -> Bool Source # | |
Show ValidationPhase Source # | |
Defined in Ledger.Index.Internal | |
Generic ValidationPhase Source # | |
Defined in Ledger.Index.Internal from :: ValidationPhase -> Rep ValidationPhase x Source # to :: Rep ValidationPhase x -> ValidationPhase Source # | |
FromJSON ValidationPhase Source # | |
Defined in Ledger.Index.Internal parseJSON :: Value -> Parser ValidationPhase parseJSONList :: Value -> Parser [ValidationPhase] | |
ToJSON ValidationPhase Source # | |
Defined in Ledger.Index.Internal toJSON :: ValidationPhase -> Value toEncoding :: ValidationPhase -> Encoding toJSONList :: [ValidationPhase] -> Value toEncodingList :: [ValidationPhase] -> Encoding | |
Pretty ValidationPhase Source # | |
Defined in Ledger.Index.Internal pretty :: ValidationPhase -> Doc ann # prettyList :: [ValidationPhase] -> Doc ann # | |
type Rep ValidationPhase Source # | |
_TxOutRefNotFound :: Prism' ValidationError TxIn Source #
_ScriptFailure :: Prism' ValidationError ScriptError Source #
_CardanoLedgerValidationError :: Prism' ValidationError Text Source #
_FailPhase1 :: Prism' ValidationResult (CardanoTx, ValidationError) Source #
_FailPhase2 :: Prism' ValidationResult (OnChainTx, ValidationError, Value) Source #
_Success :: Prism' ValidationResult (OnChainTx, RedeemerReport) Source #
getEvaluationLogs :: ValidationResult -> [Text] Source #
Get logs from evaluating plutus scripts.
data DatumFromQuery Source #
A datum in a transaction output that comes from a chain index query.
Instances
data DecoratedTxOut Source #
Offchain view of a transaction output.
PublicKeyDecoratedTxOut | |
| |
ScriptDecoratedTxOut | |
|
Instances
datumInDatumFromQuery :: Traversal' DatumFromQuery Datum Source #
decoratedTxOutPubKeyDatum :: Traversal' DecoratedTxOut (Maybe (DatumHash, DatumFromQuery)) Source #
decoratedTxOutPubKeyHash :: Traversal' DecoratedTxOut PubKeyHash Source #
decoratedTxOutReferenceScript :: Lens' DecoratedTxOut (Maybe (Versioned Script)) Source #
decoratedTxOutScriptDatum :: Traversal' DecoratedTxOut (DatumHash, DatumFromQuery) Source #
decoratedTxOutValidator :: Traversal' DecoratedTxOut (Maybe (Versioned Validator)) Source #
decoratedTxOutValidatorHash :: Traversal' DecoratedTxOut ValidatorHash Source #
decoratedTxOutValue :: Lens' DecoratedTxOut Value Source #
_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 -> Maybe (DatumHash, DatumFromQuery) -> Maybe (Versioned Script) -> Maybe 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 #
decoratedTxOutAddress :: Getter DecoratedTxOut Address Source #
decoratedTxOutDatum :: Traversal' DecoratedTxOut (DatumHash, DatumFromQuery) 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.
fromDecoratedIndex :: NetworkId -> Map TxOutRef DecoratedTxOut -> Either ToCardanoError UtxoIndex 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 #
getCardanoTxSpentOutputs :: CardanoTx -> Set TxIn Source #
getTxBodyContentReturnCollateral :: TxBodyContent ctx BabbageEra -> Maybe TxOut Source #
getCardanoTxFee :: CardanoTx -> Lovelace Source #
getCardanoTxMint :: CardanoTx -> Value Source #
getTxBodyContentMint :: TxBodyContent ctx era -> Value Source #
txBodyContentIns :: Lens' (TxBodyContent BuildTx BabbageEra) [(TxIn, BuildTxWith BuildTx (Witness WitCtxTxIn BabbageEra))] Source #
txBodyContentCollateralIns :: Lens' (TxBodyContent BuildTx BabbageEra) [TxIn] Source #
txBodyContentOuts :: Lens' (TxBodyContent ctx BabbageEra) [TxOut] Source #
addCardanoTxSignature :: PrivateKey -> CardanoTx -> CardanoTx Source #
decoratedTxOutPlutusValue :: DecoratedTxOut -> Value Source #
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.
Block identifier (usually a hash)
BlockId | |
|
Instances
Eq BlockId Source # | |
Ord BlockId Source # | |
Show BlockId Source # | |
Generic BlockId Source # | |
FromJSON BlockId Source # | |
Defined in Ledger.Blockchain parseJSON :: Value -> Parser BlockId parseJSONList :: Value -> Parser [BlockId] | |
ToJSON BlockId Source # | |
Defined in Ledger.Blockchain toEncoding :: BlockId -> Encoding toJSONList :: [BlockId] -> Value toEncodingList :: [BlockId] -> Encoding | |
Pretty BlockId Source # | |
Defined in Ledger.Blockchain | |
type Rep BlockId Source # | |
Defined in Ledger.Blockchain |
onChainTxIsValid :: OnChainTx -> Bool Source #
outputsProduced :: OnChainTx -> Map TxIn TxOut Source #
Outputs added to the UTXO set by the OnChainTx
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 :: TxIn -> UtxoIndex -> Maybe TxOut Source #
Find an unspent transaction output by the TxOutRef
that spends it.
adjustTxOut :: PParams (BabbageEra StandardCrypto) -> TxOut -> ([Lovelace], 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 -> Lovelace 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.
genesisTxIn :: TxIn Source #
cardano-ledger validation rules require the presence of inputs and we have to provide a stub TxIn for the genesis transaction.
createGenesisTransaction :: Map CardanoAddress Value -> CardanoTx Source #
Instances
Instances
Eq NetworkId | |
Data NetworkId Source # | |
Defined in Ledger.Orphans 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-DlJBOMjUMEP4jWrRjidGIP" '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 #
Instances
data StakingCredential #