hydra-cardano-api-0.19.0: A Haskell API for Cardano, tailored to the Hydra project.
Safe HaskellSafe-Inferred
LanguageGHC2021

Hydra.Cardano.Api

Description

A Haskell API for Cardano, tailored to the Hydra project.

This package provides a wrapper around the cardano-ledger, cardano-api and plutus libraries with extra utilities and function commonly used across the Hydra project.

NOTE: We always use the **latest era** available in our codebase, so to ease type signatures and notations, we specialize any type of the cardano-api normally parameterized by an era to the latest era Era. As a consequence, we've defined pattern synonyms for most constructors in the cardano-api to also get rid of era witnesses.

NOTE: This module also uses the **latest plutus version** available (currently PlutusScriptVersion). So make sure that you give it a plutus script of the right version (e.g. when compiling and serializing plutus-tx).

Synopsis

Common type-alias

data StandardCrypto #

Instances

Instances details
Crypto StandardCrypto 
Instance details

Defined in Cardano.Ledger.Crypto

Associated Types

type HASH StandardCrypto

type ADDRHASH StandardCrypto

type DSIGN StandardCrypto

type KES StandardCrypto

type VRF StandardCrypto

PraosCrypto StandardCrypto 
Instance details

Defined in Cardano.Protocol.TPraos.API

PraosCrypto StandardCrypto 
Instance details

Defined in Ouroboros.Consensus.Protocol.Praos

(CardanoHardForkConstraints StandardCrypto, IOLike m) => Protocol m (CardanoBlock StandardCrypto) 
Instance details

Defined in Cardano.Api.Protocol

Associated Types

data ProtocolInfoArgs (CardanoBlock StandardCrypto) #

Methods

protocolInfo :: ProtocolInfoArgs (CardanoBlock StandardCrypto) -> (ProtocolInfo (CardanoBlock StandardCrypto), m [BlockForging m (CardanoBlock StandardCrypto)]) #

(IOLike m, LedgerSupportsProtocol (ShelleyBlock (TPraos StandardCrypto) (ShelleyEra StandardCrypto))) => Protocol m (ShelleyBlockHFC (TPraos StandardCrypto) StandardShelley) 
Instance details

Defined in Cardano.Api.Protocol

Associated Types

data ProtocolInfoArgs (ShelleyBlockHFC (TPraos StandardCrypto) StandardShelley) #

Methods

protocolInfo :: ProtocolInfoArgs (ShelleyBlockHFC (TPraos StandardCrypto) StandardShelley) -> (ProtocolInfo (ShelleyBlockHFC (TPraos StandardCrypto) StandardShelley), m [BlockForging m (ShelleyBlockHFC (TPraos StandardCrypto) StandardShelley)]) #

ConvertLedgerEvent (HardForkBlock (CardanoEras StandardCrypto)) 
Instance details

Defined in Cardano.Api.LedgerEvents.ConvertLedgerEvent

Methods

toLedgerEvent :: WrapLedgerEvent (HardForkBlock (CardanoEras StandardCrypto)) -> Maybe LedgerEvent #

CardanoHardForkConstraints StandardCrypto => ProtocolClient (CardanoBlock StandardCrypto) 
Instance details

Defined in Cardano.Api.Protocol

Associated Types

data ProtocolClientInfoArgs (CardanoBlock StandardCrypto)

Methods

protocolClientInfo :: ProtocolClientInfoArgs (CardanoBlock StandardCrypto) -> ProtocolClientInfo (CardanoBlock StandardCrypto)

ConvertLedgerEvent (ShelleyBlock protocol (AllegraEra StandardCrypto)) 
Instance details

Defined in Cardano.Api.LedgerEvents.ConvertLedgerEvent

Methods

toLedgerEvent :: WrapLedgerEvent (ShelleyBlock protocol (AllegraEra StandardCrypto)) -> Maybe LedgerEvent #

ConvertLedgerEvent (ShelleyBlock protocol (AlonzoEra StandardCrypto)) 
Instance details

Defined in Cardano.Api.LedgerEvents.ConvertLedgerEvent

Methods

toLedgerEvent :: WrapLedgerEvent (ShelleyBlock protocol (AlonzoEra StandardCrypto)) -> Maybe LedgerEvent #

ConvertLedgerEvent (ShelleyBlock protocol (BabbageEra StandardCrypto)) 
Instance details

Defined in Cardano.Api.LedgerEvents.ConvertLedgerEvent

Methods

toLedgerEvent :: WrapLedgerEvent (ShelleyBlock protocol (BabbageEra StandardCrypto)) -> Maybe LedgerEvent #

ConvertLedgerEvent (ShelleyBlock protocol (ConwayEra StandardCrypto)) 
Instance details

Defined in Cardano.Api.LedgerEvents.ConvertLedgerEvent

Methods

toLedgerEvent :: WrapLedgerEvent (ShelleyBlock protocol (ConwayEra StandardCrypto)) -> Maybe LedgerEvent #

ConvertLedgerEvent (ShelleyBlock protocol (MaryEra StandardCrypto)) 
Instance details

Defined in Cardano.Api.LedgerEvents.ConvertLedgerEvent

Methods

toLedgerEvent :: WrapLedgerEvent (ShelleyBlock protocol (MaryEra StandardCrypto)) -> Maybe LedgerEvent #

ConvertLedgerEvent (ShelleyBlock protocol (ShelleyEra StandardCrypto)) 
Instance details

Defined in Cardano.Api.LedgerEvents.ConvertLedgerEvent

Methods

toLedgerEvent :: WrapLedgerEvent (ShelleyBlock protocol (ShelleyEra StandardCrypto)) -> Maybe LedgerEvent #

LedgerSupportsProtocol (ShelleyBlock (TPraos StandardCrypto) (ShelleyEra StandardCrypto)) => ProtocolClient (ShelleyBlockHFC (TPraos StandardCrypto) StandardShelley) 
Instance details

Defined in Cardano.Api.Protocol

Associated Types

data ProtocolClientInfoArgs (ShelleyBlockHFC (TPraos StandardCrypto) StandardShelley)

Methods

protocolClientInfo :: ProtocolClientInfoArgs (ShelleyBlockHFC (TPraos StandardCrypto) StandardShelley) -> ProtocolClientInfo (ShelleyBlockHFC (TPraos StandardCrypto) StandardShelley)

type ADDRHASH StandardCrypto 
Instance details

Defined in Cardano.Ledger.Crypto

type ADDRHASH StandardCrypto = Blake2b_224
type DSIGN StandardCrypto 
Instance details

Defined in Cardano.Ledger.Crypto

type DSIGN StandardCrypto = Ed25519DSIGN
type HASH StandardCrypto 
Instance details

Defined in Cardano.Ledger.Crypto

type HASH StandardCrypto = Blake2b_256
type KES StandardCrypto 
Instance details

Defined in Cardano.Ledger.Crypto

type KES StandardCrypto = Sum6KES Ed25519DSIGN Blake2b_256
type VRF StandardCrypto 
Instance details

Defined in Cardano.Ledger.Crypto

type VRF StandardCrypto = PraosVRF
data ProtocolClientInfoArgs (CardanoBlock StandardCrypto) 
Instance details

Defined in Cardano.Api.Protocol

data ProtocolClientInfoArgs (CardanoBlock StandardCrypto) = ProtocolClientInfoArgsCardano EpochSlots
data ProtocolInfoArgs (CardanoBlock StandardCrypto) 
Instance details

Defined in Cardano.Api.Protocol

data ProtocolInfoArgs (CardanoBlock StandardCrypto) = ProtocolInfoArgsCardano (CardanoProtocolParams StandardCrypto)
data ProtocolClientInfoArgs (ShelleyBlockHFC (TPraos StandardCrypto) StandardShelley) 
Instance details

Defined in Cardano.Api.Protocol

data ProtocolClientInfoArgs (ShelleyBlockHFC (TPraos StandardCrypto) StandardShelley) = ProtocolClientInfoArgsShelley
data ProtocolInfoArgs (ShelleyBlockHFC (TPraos StandardCrypto) StandardShelley) 
Instance details

Defined in Cardano.Api.Protocol

data ProtocolInfoArgs (ShelleyBlockHFC (TPraos StandardCrypto) StandardShelley) = ProtocolInfoArgsShelley (ShelleyGenesis StandardCrypto) (ProtocolParamsShelleyBased StandardCrypto) (ProtocolParams (ShelleyBlock (TPraos StandardCrypto) StandardShelley))

type LedgerEra = ShelleyLedgerEra Era Source #

Currently supported ledger era.

ledgerEraVersion :: Version Source #

Associated version for the fixed LedgerEra.

Wrapped Types

type AddressTypeInEra addrType = AddressTypeInEra addrType Era Source #

type ScriptWitness witCtx = ScriptWitness witCtx Era Source #

type Tx = Tx Era Source #

type TxIns buidl = [(TxIn, BuildTxWith buidl (Witness WitCtxTxIn Era))] Source #

type TxMintValue buidl = TxMintValue buidl Era Source #

type TxOut ctx = TxOut ctx Era Source #

type Witness witCtx = Witness witCtx Era Source #

pattern KeyWitness :: KeyWitnessInCtx ctx -> Witness ctx Source #

pattern Tx :: TxBody -> [KeyWitness] -> Tx Source #

pattern TxInsReference :: [TxIn] -> TxInsReference buidl Source #

pattern TxOut :: AddressInEra -> Value -> TxOutDatum ctx -> ReferenceScript -> TxOut ctx Source #

TxOut specialized for Era

pattern ShelleyTxBody :: TxBody LedgerEra -> [Script LedgerEra] -> TxBodyScriptData -> Maybe (AlonzoTxAuxData LedgerEra) -> TxScriptValidity -> TxBody Source #

pattern ShelleyKeyWitness :: WitVKey 'Witness StandardCrypto -> KeyWitness Source #

txIns :: TxBodyContent buidl -> TxIns buidl Source #

UTxO

newtype UTxO' out Source #

Newtype with phantom types mostly required to work around the poor interface of UTXO and provide Monoid and Foldable instances to make utxo manipulation bareable.

Constructors

UTxO (Map TxIn out) 

Instances

Instances details
Foldable UTxO' Source # 
Instance details

Defined in Cardano.Api.UTxO

Methods

fold :: Monoid m => UTxO' m -> m Source #

foldMap :: Monoid m => (a -> m) -> UTxO' a -> m Source #

foldMap' :: Monoid m => (a -> m) -> UTxO' a -> m Source #

foldr :: (a -> b -> b) -> b -> UTxO' a -> b Source #

foldr' :: (a -> b -> b) -> b -> UTxO' a -> b Source #

foldl :: (b -> a -> b) -> b -> UTxO' a -> b Source #

foldl' :: (b -> a -> b) -> b -> UTxO' a -> b Source #

foldr1 :: (a -> a -> a) -> UTxO' a -> a Source #

foldl1 :: (a -> a -> a) -> UTxO' a -> a Source #

toList :: UTxO' a -> [a] Source #

null :: UTxO' a -> Bool Source #

length :: UTxO' a -> Int Source #

elem :: Eq a => a -> UTxO' a -> Bool Source #

maximum :: Ord a => UTxO' a -> a Source #

minimum :: Ord a => UTxO' a -> a Source #

sum :: Num a => UTxO' a -> a Source #

product :: Num a => UTxO' a -> a Source #

Traversable UTxO' Source # 
Instance details

Defined in Cardano.Api.UTxO

Methods

traverse :: Applicative f => (a -> f b) -> UTxO' a -> f (UTxO' b) Source #

sequenceA :: Applicative f => UTxO' (f a) -> f (UTxO' a) Source #

mapM :: Monad m => (a -> m b) -> UTxO' a -> m (UTxO' b) Source #

sequence :: Monad m => UTxO' (m a) -> m (UTxO' a) Source #

Functor UTxO' Source # 
Instance details

Defined in Cardano.Api.UTxO

Methods

fmap :: (a -> b) -> UTxO' a -> UTxO' b Source #

(<$) :: a -> UTxO' b -> UTxO' a Source #

FromJSON out => FromJSON (UTxO' out) Source # 
Instance details

Defined in Cardano.Api.UTxO

Methods

parseJSON :: Value -> Parser (UTxO' out) #

parseJSONList :: Value -> Parser [UTxO' out] #

omittedField :: Maybe (UTxO' out) #

ToJSON out => ToJSON (UTxO' out) Source # 
Instance details

Defined in Cardano.Api.UTxO

Methods

toJSON :: UTxO' out -> Value #

toEncoding :: UTxO' out -> Encoding #

toJSONList :: [UTxO' out] -> Value #

toEncodingList :: [UTxO' out] -> Encoding #

omitField :: UTxO' out -> Bool #

Monoid (UTxO' out) Source # 
Instance details

Defined in Cardano.Api.UTxO

Methods

mempty :: UTxO' out Source #

mappend :: UTxO' out -> UTxO' out -> UTxO' out Source #

mconcat :: [UTxO' out] -> UTxO' out Source #

Semigroup (UTxO' out) Source # 
Instance details

Defined in Cardano.Api.UTxO

Methods

(<>) :: UTxO' out -> UTxO' out -> UTxO' out Source #

sconcat :: NonEmpty (UTxO' out) -> UTxO' out Source #

stimes :: Integral b => b -> UTxO' out -> UTxO' out Source #

Show out => Show (UTxO' out) Source # 
Instance details

Defined in Cardano.Api.UTxO

Methods

showsPrec :: Int -> UTxO' out -> ShowS Source #

show :: UTxO' out -> String Source #

showList :: [UTxO' out] -> ShowS Source #

Eq out => Eq (UTxO' out) Source # 
Instance details

Defined in Cardano.Api.UTxO

Methods

(==) :: UTxO' out -> UTxO' out -> Bool Source #

(/=) :: UTxO' out -> UTxO' out -> Bool Source #

Extras

class ToTxContext f where Source #

A convenient type-class for transforming types in CtxUTxO to CtxTx.

See also ToUtxoContext for the reverse.

Methods

toTxContext :: f CtxUTxO era -> f CtxTx era Source #

Instances

Instances details
ToTxContext TxOut Source # 
Instance details

Defined in Hydra.Cardano.Api.CtxTx

Methods

toTxContext :: forall (era :: k). TxOut CtxUTxO era -> TxOut CtxTx era Source #

ToTxContext TxOutDatum Source # 
Instance details

Defined in Hydra.Cardano.Api.CtxTx

Methods

toTxContext :: forall (era :: k). TxOutDatum CtxUTxO era -> TxOutDatum CtxTx era Source #

class ToUTxOContext f where Source #

A convenient type-class for transforming types in CtxTx to CtxUTxO.

See also ToTxContext for the reverse.

Methods

toUTxOContext :: f CtxTx era -> f CtxUTxO era Source #

Instances

Instances details
ToUTxOContext TxOut Source # 
Instance details

Defined in Hydra.Cardano.Api.CtxUTxO

Methods

toUTxOContext :: forall (era :: k). TxOut CtxTx era -> TxOut CtxUTxO era Source #

ToUTxOContext TxOutDatum Source # 
Instance details

Defined in Hydra.Cardano.Api.CtxUTxO

Methods

toUTxOContext :: forall (era :: k). TxOutDatum CtxTx era -> TxOutDatum CtxUTxO era Source #

type ToScriptData a = ToData a Source #

Data-types that can be marshalled into a generic ScriptData structure.

type FromScriptData a = FromData a Source #

Data-types that can be unmarshalled from a generic ScriptData structure.

fromLedgerValue :: MaryValue StandardCrypto -> Value Source #

Convert a cardano-ledger Value into a cardano-api Value.

toLedgerValue :: Value -> MaryValue StandardCrypto Source #

Convert a cardano-api Value into a cardano-ledger Value.

mkVkAddress :: IsShelleyBasedEra era => NetworkId -> VerificationKey PaymentKey -> AddressInEra era Source #

Construct a Shelley-style address from a verification key. This address has no stake rights.

TODO: NetworkId here is an annoying API because it requires a network magic for testnet addresses. Nevertheless, the network magic is only needed for Byron addresses; Shelley addresses use a different kind of network discriminant which is currently fully captured as 'Mainnet | Testnet'.

So, it would be a slightly better DX to use Mainnet | Testnet as an interface here since we are only constructing Shelley addresses.

genBlockHeader :: Gen BlockHeader Source #

Fully arbitrary block header with completely random hash.

genBlockHeaderHash :: Gen (Hash BlockHeader) Source #

Generate a random block header hash.

getChainPoint :: BlockHeader -> ChainPoint Source #

Get the chain point corresponding to a given BlockHeader.

modifyTxOutDatum :: (TxOutDatum ctx0 era -> TxOutDatum ctx1 era) -> TxOut ctx0 era -> TxOut ctx1 era Source #

Alter the datum of a TxOut with the given transformation.

toLedgerExUnits :: ExecutionUnits -> ExUnits Source #

Convert a cardano-api ExecutionUnits into a cardano-ledger ExUnits

toPlutusKeyHash :: Hash PaymentKey -> PubKeyHash Source #

Convert a cardano-api Hash into a plutus PubKeyHash

signWith :: forall era. IsShelleyBasedEra era => TxId -> SigningKey PaymentKey -> KeyWitness era Source #

Construct a KeyWitness from a transaction id and credentials.

fromLedgerScript :: (HasCallStack, AlonzoEraScript era) => AlonzoScript era -> PlutusScript lang Source #

Convert a cardano-ledger Script into a cardano-api Script

NOTE: This function is unsafe in two manners:

(a) If the given script is a timelock script, it throws an impure exception; (b) If the given script is in a wrong language, it silently coerces it.

fromLedgerData :: Data era -> HashableScriptData Source #

Convert a cardano-ledger script Data into a cardano-api ScriptDatum.

fromPlutusScript :: SerialisedScript -> PlutusScript lang Source #

Convert a serialized plutus script into a cardano-api Script.

mkScriptRef :: SerialisedScript -> ReferenceScript Era Source #

Construct a ReferenceScript from any given Plutus script.

NOTE: The script is treated as a PlutusScriptVersion

toScriptData :: ToScriptData a => a -> HashableScriptData Source #

Serialise some type into a generic script data.

mkScriptDatum :: ToScriptData a => a -> ScriptDatum WitCtxTxIn Source #

Construct a ScriptDatum for use as transaction witness.

getPaymentScriptHash :: AddressInEra era -> Maybe ScriptHash Source #

Extract the payment part of an address, as a script hash.

mkTxIn :: Tx era -> Word -> TxIn Source #

Create a TxIn (a.k.a UTXO) from a transaction and output index.

toLedgerTxIn :: TxIn -> TxIn StandardCrypto Source #

Convert a cardano-api TxIn into a cardano-ledger TxIn

signTx :: IsShelleyBasedEra era => SigningKey PaymentKey -> Tx era -> Tx era Source #

Sign transaction using the provided secret key It only works for tx not containing scripts. You can't sign a script utxo with this.

toLedgerPolicyID :: PolicyId -> PolicyID StandardCrypto Source #

Convert Cardano api PolicyId to Cardano ledger PolicyID.

findRedeemerSpending :: FromData a => Tx Era -> TxIn -> Maybe a Source #

Find and deserialise from ScriptData, a redeemer from the transaction associated to the given input.

mkTxOutValue :: forall era. IsShelleyBasedEra era => IsMaryBasedEra era => Value -> TxOutValue era Source #

Inject some Value into a TxOutValue

fromPlutusAddress :: IsShelleyBasedEra era => Network -> Address -> AddressInEra era Source #

Convert a plutus Address to an api AddressInEra. NOTE: Requires the Network discriminator (Testnet or Mainnet) because Plutus addresses are stripped off it.

unsafeScriptDataHashFromBytes :: HasCallStack => ByteString -> Hash ScriptData Source #

Unsafe wrap some bytes as a 'Hash ScriptData', relying on the fact that Plutus is using Blake2b_256 for hashing data (according to 'cardano-ledger').

Pre-condition: the input bytestring MUST be of length 32.

fromPlutusValue :: Value -> Maybe Value Source #

Convert a plutus Value into a cardano-api Value.

minUTxOValue :: PParams LedgerEra -> TxOut CtxTx Era -> Value Source #

Calculate minimum ada as Value for a TxOut.

txOuts' :: Tx era -> [TxOut CtxTx era] Source #

mkTxOutDatum :: forall era a. (ToScriptData a, IsAlonzoBasedEra era) => a -> TxOutDatum CtxTx era Source #

Construct a TxOutDatum to be included in the tx from some serialisable data.

toLedgerScriptValidity :: TxScriptValidity era -> IsValid Source #

Convert a cardano-api TxScriptValidity into a cardano-ledger IsValid boolean wrapper.

toLedgerTxId :: TxId -> TxId StandardCrypto Source #

Convert a cardano-api TxId into a cardano-ledger TxId.

fromLedgerTxIn :: TxIn StandardCrypto -> TxIn Source #

Convert a cardano-ledger TxIn into a cardano-api TxIn

txIns' :: Tx era -> [TxIn] Source #

Access inputs of a transaction, as an ordered list.

fromLedgerTxOut :: IsShelleyBasedEra era => TxOut (ShelleyLedgerEra era) -> TxOut ctx era Source #

Convert a cardano-ledger TxOut into a cardano-api TxOut

toLedgerTxOut :: IsShelleyBasedEra era => TxOut CtxUTxO era -> TxOut (ShelleyLedgerEra era) Source #

Convert a cardano-api TxOut into a cardano-ledger TxOut

renderUTxO :: IsString str => UTxO -> str Source #

Get a human-readable pretty text representation of a UTxO.

fromPlutusCurrencySymbol :: MonadFail m => CurrencySymbol -> m PolicyId Source #

Convert a plutus CurrencySymbol into a cardano-api PolicyId.

mkScriptWitness :: forall ctx era lang. (IsPlutusScriptLanguage lang, HasScriptLanguageInEra lang era) => PlutusScript lang -> ScriptDatum ctx -> ScriptRedeemer -> ScriptWitness ctx era Source #

Construct a full script witness from a datum, a redeemer and a full Script. That witness has no execution budget.

lookupRedeemer :: FromData a => PlutusPurpose AsIx LedgerEra -> TxBodyScriptData Era -> Maybe a Source #

toLedgerKeyWitness :: [KeyWitness era] -> Set (WitVKey 'Witness StandardCrypto) Source #

Convert a List of cardano-api's KeyWitness into a Set of cardano-ledger's WitVKey.

NOTE: KeyWitness is a bigger type than WitVKey witness, this function does not only the type conversion but also the selection of the right underlying constructors. That means the size of the resulting set may be smaller than the size of the list (but never bigger).

toLedgerBootstrapWitness :: [KeyWitness era] -> Set (BootstrapWitness StandardCrypto) Source #

Convert a List of cardano-api's KeyWitness into a Set of cardano-ledger's BootstrapWitness.

NOTE: See note on toLedgerKeyWitness.

fromLedgerTxWitness :: forall era. (IsShelleyBasedEra era, UsesStandardCrypto era, Era (ShelleyLedgerEra era)) => AlonzoTxWits (ShelleyLedgerEra era) -> [KeyWitness era] Source #

Convert a cardano-ledger's TxWitness object into a list of cardano-api's KeyWitness.

NOTE: this only concerns key and bootstrap witnesses. Scripts and auxiliary data are obviously not part of the resulting list.

toLedgerKeyHash :: Hash PaymentKey -> KeyHash 'Witness StandardCrypto Source #

Convert a cardano-api Hash into a cardano-ledger KeyHash

unsafePaymentKeyHashFromBytes :: HasCallStack => ByteString -> Hash PaymentKey Source #

Unsafe wrap some bytes as a 'Hash PaymentKey'.

Pre-condition: the input bytestring MUST be of length 28.

unsafeScriptHashFromBytes :: HasCallStack => ByteString -> ScriptHash Source #

Unsafe wrap some bytes as a ScriptHash, relying on the fact that Plutus is using Blake2b_224 for hashing data (according to 'cardano-ledger').

Pre-condition: the input bytestring MUST be of length 28.

fromLedgerExUnits :: ExUnits -> ExecutionUnits Source #

Convert a cardano-ledger ExUnits into a cardano-api ExecutionUnits

genBlockHeaderAt :: SlotNo -> Gen BlockHeader Source #

Generate a random block header with completely random hash, but at a certain slot.

genChainPoint :: Gen ChainPoint Source #

Generate a chain point with a likely invalid block header hash.

genChainPointAt :: SlotNo -> Gen ChainPoint Source #

Generate a chain point at given slot with a likely invalid block header hash.

mkScriptAddress :: forall lang era. (IsShelleyBasedEra era, IsPlutusScriptLanguage lang) => NetworkId -> PlutusScript lang -> AddressInEra era Source #

Construct a Shelley-style address from a Plutus script. This address has no stake rights.

fromLedgerAddr :: IsShelleyBasedEra era => Addr StandardCrypto -> AddressInEra era Source #

From a ledger Addr to an api AddressInEra

toLedgerAddr :: AddressInEra era -> Addr StandardCrypto Source #

From an api AddressInEra to a ledger Addr

fromScriptData :: FromScriptData a => HashableScriptData -> Maybe a Source #

Deserialise some generic script data into some type.

txOutScriptData :: TxOut CtxTx era -> Maybe HashableScriptData Source #

Get the HashableScriptData associated to the a TxOut. Note that this requires the CtxTx context. To get script data in a CtxUTxO context, see lookupScriptData.

lookupScriptData :: forall era. (UsesStandardCrypto era, Era (ShelleyLedgerEra era)) => Tx era -> TxOut CtxUTxO era -> Maybe HashableScriptData Source #

Lookup included datum of given TxOut.

toLedgerData :: Era era => HashableScriptData -> Data era Source #

Convert a cardano-api script data into a cardano-ledger script Data. XXX: This is a partial function. Ideally it would fall back to the Data portion in HashableScriptData.

toPlutusCurrencySymbol :: PolicyId -> CurrencySymbol Source #

Convert Cardano api PolicyId to Plutus CurrencySymbol.

fromLedgerTxId :: TxId StandardCrypto -> TxId Source #

Convert a cardano-ledger TxId into a cardano-api TxId.

withWitness :: TxIn -> (TxIn, BuildTxWith BuildTx (Witness WitCtxTxIn Era)) Source #

Attach some verification-key witness to a TxIn.

txInputSet :: Tx era -> Set TxIn Source #

Access inputs of a transaction, as an ordered set.

fromPlutusTxOutRef :: TxOutRef -> TxIn Source #

Convert a plutus' TxOutRef into a cardano-api TxIn

toPlutusTxOutRef :: TxIn -> TxOutRef Source #

Convert a cardano-api TxIn into a plutus TxOutRef.

genTxIn :: Gen TxIn Source #

A more random generator than the 'Arbitrary TxIn' from cardano-ledger. NOTE: This is using the Cardano ledger's deserialization framework using the latest protocol version via maxBound.

findRedeemerMinting :: FromData a => Tx Era -> PolicyId -> Maybe a Source #

findScriptMinting :: forall lang. Tx Era -> PolicyId -> Maybe (PlutusScript lang) Source #

txSpendingUTxO :: UTxO -> Tx Era Source #

Create a transaction spending all given UTxO.

fromLedgerTx :: IsShelleyBasedEra era => Tx (ShelleyLedgerEra era) -> Tx era Source #

Convert a cardano-ledger's Tx in the Babbage era into a cardano-api Tx.

utxoProducedByTx :: Tx Era -> UTxO Source #

Get the UTxO that are produced by some transaction. XXX: Defined here to avoid cyclic module dependency

txFee' :: Tx era -> Coin Source #

Get explicit fees allocated to a transaction.

toLedgerTx :: Tx era -> Tx (ShelleyLedgerEra era) Source #

Convert a cardano-api Tx into a matching cardano-ledger Tx.

recomputeIntegrityHash :: (AlonzoEraPParams ppera, AlonzoEraTxWits txera, AlonzoEraTxBody txera, EraTx txera) => PParams ppera -> [Language] -> Tx txera -> Tx txera Source #

Compute the integrity hash of a transaction using a list of plutus languages.

convertConwayTx :: Tx Conway -> Tx Babbage Source #

Explicit downgrade from Conway to Babbage era.

XXX: This will invalidate the script integrity hash as datums and redeemers are serialized differently.

XXX: This is not a complete mapping and does silently drop things like protocol updates, certificates and voting procedures.

mkTxOutDatumHash :: forall era a ctx. (ToScriptData a, IsAlonzoBasedEra era) => a -> TxOutDatum ctx era Source #

Construct a TxOutDatum as a ScriptData hash from some serialisable data.

mkTxOutDatumInline :: forall era a ctx. (ToScriptData a, IsBabbageBasedEra era) => a -> TxOutDatum ctx era Source #

Construct an inline TxOutDatum from some serialisable data.

valueSize :: Value -> Int Source #

Count number of assets in a Value.

txMintAssets :: Tx era -> [(AssetId, Quantity)] Source #

Access minted assets of a transaction, as an ordered association list.

fromLedgerMultiAsset :: MultiAsset StandardCrypto -> Value Source #

Convert a cardano-ledger MultiAsset into a cardano-api Value. The cardano-api currently does not have an asset-only type. So this conversion will construct a Value with no AdaAssetId entry in it.

toPlutusValue :: Value -> Value Source #

Convert a cardano-api Value into a plutus Value

setMinUTxOValue :: PParams LedgerEra -> TxOut CtxUTxO Era -> TxOut ctx Era Source #

Modify a TxOut to set the minimum ada on the value.

mkTxOutAutoBalance :: PParams LedgerEra -> AddressInEra Era -> Value -> TxOutDatum CtxTx Era -> ReferenceScript Era -> TxOut CtxTx Era Source #

Automatically balance a given output with the minimum required amount. Number of assets, presence of datum and/or reference scripts may affect this minimum value.

modifyTxOutValue :: IsMaryBasedEra era => IsShelleyBasedEra era => (Value -> Value) -> TxOut ctx era -> TxOut ctx era Source #

Alter the value of a TxOut with the given transformation.

modifyTxOutAddress :: (AddressInEra era -> AddressInEra era) -> TxOut ctx era -> TxOut ctx era Source #

Alter the address of a TxOut with the given transformation.

findTxOutByAddress :: AddressInEra era -> Tx era -> Maybe (TxIn, TxOut CtxTx era) Source #

Find first TxOut which pays to given address and also return the corresponding TxIn to reference it.

findTxOutByScript :: forall lang. IsPlutusScriptLanguage lang => UTxO -> PlutusScript lang -> Maybe (TxIn, TxOut CtxUTxO Era) Source #

Find a single script output in some UTxO

isVkTxOut :: forall ctx era. VerificationKey PaymentKey -> TxOut ctx era -> Bool Source #

Predicate to find or filter TxOut owned by a key. This is better than comparing the full address as it does not require a network discriminator.

isScriptTxOut :: forall lang ctx era. IsPlutusScriptLanguage lang => PlutusScript lang -> TxOut ctx era -> Bool Source #

Predicate to find or filter TxOut which are governed by some script. This is better than comparing the full address as it does not require a network discriminator.

fromPlutusTxOut :: forall era. (IsMaryBasedEra era, IsAlonzoBasedEra era, IsBabbageBasedEra era, IsShelleyBasedEra era) => Network -> TxOut -> Maybe (TxOut CtxUTxO era) Source #

Convert a plutus TxOut into a cardano-api TxOut. NOTE: Reference scripts are not resolvable right now. NOTE: Requires the Network discriminator (Testnet or Mainnet) because Plutus addresses are stripped off it.

toPlutusTxOut :: HasCallStack => TxOut CtxUTxO Era -> Maybe TxOut Source #

Convert a cardano-api TxOut into a plutus TxOut. Returns Nothing if a byron address is used in the given TxOut.

utxoFromTx :: Tx Era -> UTxO Source #

Construct a UTxO from a transaction. This constructs artificial TxIn (a.k.a output reference) from the transaction itself, zipping them to the outputs they correspond to.

resolveInputsUTxO :: UTxO -> Tx Era -> UTxO Source #

Resolve tx inputs in a given UTxO

mkScriptReference :: forall ctx era lang. (IsPlutusScriptLanguage lang, HasScriptLanguageInEra lang era) => TxIn -> PlutusScript lang -> ScriptDatum ctx -> ScriptRedeemer -> ScriptWitness ctx era Source #

Construct a reference script witness, only referring to a TxIn which is expected to contain the given script (only required to satisfy types).

Re-exports from cardano-api

class Error e where #

Methods

prettyError :: e -> Doc ann #

Instances

Instances details
Error IOException 
Instance details

Defined in Cardano.Api.Error

Methods

prettyError :: IOException -> Doc ann #

Error InputDecodeError 
Instance details

Defined in Cardano.Api.DeserialiseAnyOf

Error ErrorAsException 
Instance details

Defined in Cardano.Api.Error

Methods

prettyError :: ErrorAsException -> Doc ann #

Error ScriptExecutionError 
Instance details

Defined in Cardano.Api.Fees

Error FoldBlocksError 
Instance details

Defined in Cardano.Api.LedgerState

Methods

prettyError :: FoldBlocksError -> Doc ann #

Error GenesisConfigError 
Instance details

Defined in Cardano.Api.LedgerState

Error InitialLedgerStateError 
Instance details

Defined in Cardano.Api.LedgerState

Error LeadershipError 
Instance details

Defined in Cardano.Api.LedgerState

Methods

prettyError :: LeadershipError -> Doc ann #

Error LedgerStateError 
Instance details

Defined in Cardano.Api.LedgerState

Error OperationalCertIssueError 
Instance details

Defined in Cardano.Api.OperationalCertificate

Error ProtocolParametersConversionError 
Instance details

Defined in Cardano.Api.ProtocolParameters

Error ProtocolParametersError 
Instance details

Defined in Cardano.Api.ProtocolParameters

Error ScriptDataJsonBytesError 
Instance details

Defined in Cardano.Api.ScriptData

Error ScriptDataJsonError 
Instance details

Defined in Cardano.Api.ScriptData

Error ScriptDataJsonSchemaError 
Instance details

Defined in Cardano.Api.ScriptData

Error ScriptDataRangeError 
Instance details

Defined in Cardano.Api.ScriptData

Error Bech32DecodeError 
Instance details

Defined in Cardano.Api.SerialiseBech32

Error JsonDecodeError 
Instance details

Defined in Cardano.Api.SerialiseJSON

Methods

prettyError :: JsonDecodeError -> Doc ann #

Error TextEnvelopeCddlError 
Instance details

Defined in Cardano.Api.SerialiseLedgerCddl

Error RawBytesHexError 
Instance details

Defined in Cardano.Api.SerialiseRaw

Error TextEnvelopeError 
Instance details

Defined in Cardano.Api.SerialiseTextEnvelope

Error StakePoolMetadataValidationError 
Instance details

Defined in Cardano.Api.StakePoolMetadata

Error TxBodyError 
Instance details

Defined in Cardano.Api.Tx.Body

Methods

prettyError :: TxBodyError -> Doc ann #

Error TxMetadataJsonError 
Instance details

Defined in Cardano.Api.TxMetadata

Error TxMetadataJsonSchemaError 
Instance details

Defined in Cardano.Api.TxMetadata

Error TxMetadataRangeError 
Instance details

Defined in Cardano.Api.TxMetadata

Error () 
Instance details

Defined in Cardano.Api.Error

Methods

prettyError :: () -> Doc ann #

Error e => Error (FileError e) 
Instance details

Defined in Cardano.Api.Error

Methods

prettyError :: FileError e -> Doc ann #

Error (AutoBalanceError era) 
Instance details

Defined in Cardano.Api.Fees

Methods

prettyError :: AutoBalanceError era -> Doc ann #

Error (TransactionValidityError era) 
Instance details

Defined in Cardano.Api.Fees

Error (TxBodyErrorAutoBalance era) 
Instance details

Defined in Cardano.Api.Fees

Error (TxFeeEstimationError era) 
Instance details

Defined in Cardano.Api.Fees

Methods

prettyError :: TxFeeEstimationError era -> Doc ann #

data Doc ann #

Instances

Instances details
Functor Doc 
Instance details

Defined in Prettyprinter.Internal

Methods

fmap :: (a -> b) -> Doc a -> Doc b Source #

(<$) :: a -> Doc b -> Doc a Source #

IsString (Doc ann) 
Instance details

Defined in Prettyprinter.Internal

Methods

fromString :: String -> Doc ann Source #

Monoid (Doc ann) 
Instance details

Defined in Prettyprinter.Internal

Methods

mempty :: Doc ann Source #

mappend :: Doc ann -> Doc ann -> Doc ann Source #

mconcat :: [Doc ann] -> Doc ann Source #

Semigroup (Doc ann) 
Instance details

Defined in Prettyprinter.Internal

Methods

(<>) :: Doc ann -> Doc ann -> Doc ann Source #

sconcat :: NonEmpty (Doc ann) -> Doc ann Source #

stimes :: Integral b => b -> Doc ann -> Doc ann Source #

Generic (Doc ann) 
Instance details

Defined in Prettyprinter.Internal

Associated Types

type Rep (Doc ann) :: Type -> Type Source #

Methods

from :: Doc ann -> Rep (Doc ann) x Source #

to :: Rep (Doc ann) x -> Doc ann Source #

Show (Doc ann) 
Instance details

Defined in Prettyprinter.Internal

Methods

showsPrec :: Int -> Doc ann -> ShowS Source #

show :: Doc ann -> String Source #

showList :: [Doc ann] -> ShowS Source #

type Rep (Doc ann) 
Instance details

Defined in Prettyprinter.Internal

type Rep (Doc ann) = D1 ('MetaData "Doc" "Prettyprinter.Internal" "prettyprinter-1.7.1-60yVE7QePDs8FHIPsacPFF" 'False) (((C1 ('MetaCons "Fail" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Empty" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Char" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedUnpack) (Rec0 Char)))) :+: (C1 ('MetaCons "Text" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedUnpack) (Rec0 Int) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text)) :+: (C1 ('MetaCons "Line" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "FlatAlt" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Doc ann)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Doc ann)))))) :+: ((C1 ('MetaCons "Cat" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Doc ann)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Doc ann))) :+: (C1 ('MetaCons "Nest" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedUnpack) (Rec0 Int) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Doc ann))) :+: C1 ('MetaCons "Union" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Doc ann)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Doc ann))))) :+: ((C1 ('MetaCons "Column" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Int -> Doc ann))) :+: C1 ('MetaCons "WithPageWidth" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (PageWidth -> Doc ann)))) :+: (C1 ('MetaCons "Nesting" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Int -> Doc ann))) :+: C1 ('MetaCons "Annotated" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ann) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Doc ann)))))))

class Pretty a where #

Minimal complete definition

pretty

Methods

pretty :: a -> Doc ann #

prettyList :: [a] -> Doc ann #

Instances

Instances details
Pretty Void 
Instance details

Defined in Prettyprinter.Internal

Methods

pretty :: Void -> Doc ann #

prettyList :: [Void] -> Doc ann #

Pretty Int16 
Instance details

Defined in Prettyprinter.Internal

Methods

pretty :: Int16 -> Doc ann #

prettyList :: [Int16] -> Doc ann #

Pretty Int32 
Instance details

Defined in Prettyprinter.Internal

Methods

pretty :: Int32 -> Doc ann #

prettyList :: [Int32] -> Doc ann #

Pretty Int64 
Instance details

Defined in Prettyprinter.Internal

Methods

pretty :: Int64 -> Doc ann #

prettyList :: [Int64] -> Doc ann #

Pretty Int8 
Instance details

Defined in Prettyprinter.Internal

Methods

pretty :: Int8 -> Doc ann #

prettyList :: [Int8] -> Doc ann #

Pretty Word16 
Instance details

Defined in Prettyprinter.Internal

Methods

pretty :: Word16 -> Doc ann #

prettyList :: [Word16] -> Doc ann #

Pretty Word32 
Instance details

Defined in Prettyprinter.Internal

Methods

pretty :: Word32 -> Doc ann #

prettyList :: [Word32] -> Doc ann #

Pretty Word64 
Instance details

Defined in Prettyprinter.Internal

Methods

pretty :: Word64 -> Doc ann #

prettyList :: [Word64] -> Doc ann #

Pretty Word8 
Instance details

Defined in Prettyprinter.Internal

Methods

pretty :: Word8 -> Doc ann #

prettyList :: [Word8] -> Doc ann #

Pretty AnyCardanoEra 
Instance details

Defined in Cardano.Api.Eras.Core

Methods

pretty :: AnyCardanoEra -> Doc ann #

prettyList :: [AnyCardanoEra] -> Doc ann #

Pretty TxOutInAnyEra 
Instance details

Defined in Cardano.Api.Tx.Body

Methods

pretty :: TxOutInAnyEra -> Doc ann #

prettyList :: [TxOutInAnyEra] -> Doc ann #

Pretty TxIn 
Instance details

Defined in Cardano.Api.TxIn

Methods

pretty :: TxIn -> Doc ann #

prettyList :: [TxIn] -> Doc ann #

Pretty Data 
Instance details

Defined in PlutusCore.Data

Methods

pretty :: Data -> Doc ann #

prettyList :: [Data] -> Doc ann #

Pretty ParserError 
Instance details

Defined in PlutusCore.Error

Methods

pretty :: ParserError -> Doc ann #

prettyList :: [ParserError] -> Doc ann #

Pretty ParserErrorBundle 
Instance details

Defined in PlutusCore.Error

Methods

pretty :: ParserErrorBundle -> Doc ann #

prettyList :: [ParserErrorBundle] -> Doc ann #

Pretty CostModelApplyError 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostModelInterface

Methods

pretty :: CostModelApplyError -> Doc ann #

prettyList :: [CostModelApplyError] -> Doc ann #

Pretty CostModelApplyWarn 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostModelInterface

Methods

pretty :: CostModelApplyWarn -> Doc ann #

prettyList :: [CostModelApplyWarn] -> Doc ann #

Pretty ScriptDecodeError 
Instance details

Defined in PlutusLedgerApi.Common.SerialisedScript

Methods

pretty :: ScriptDecodeError -> Doc ann #

prettyList :: [ScriptDecodeError] -> Doc ann #

Pretty Address 
Instance details

Defined in PlutusLedgerApi.V1.Address

Methods

pretty :: Address -> Doc ann #

prettyList :: [Address] -> Doc ann #

Pretty Credential 
Instance details

Defined in PlutusLedgerApi.V1.Credential

Methods

pretty :: Credential -> Doc ann #

prettyList :: [Credential] -> Doc ann #

Pretty StakingCredential 
Instance details

Defined in PlutusLedgerApi.V1.Credential

Methods

pretty :: StakingCredential -> Doc ann #

prettyList :: [StakingCredential] -> Doc ann #

Pretty PubKeyHash 
Instance details

Defined in PlutusLedgerApi.V1.Crypto

Methods

pretty :: PubKeyHash -> Doc ann #

prettyList :: [PubKeyHash] -> Doc ann #

Pretty Context 
Instance details

Defined in PlutusLedgerApi.V1.Scripts

Methods

pretty :: Context -> Doc ann #

prettyList :: [Context] -> Doc ann #

Pretty Datum 
Instance details

Defined in PlutusLedgerApi.V1.Scripts

Methods

pretty :: Datum -> Doc ann #

prettyList :: [Datum] -> Doc ann #

Pretty DatumHash 
Instance details

Defined in PlutusLedgerApi.V1.Scripts

Methods

pretty :: DatumHash -> Doc ann #

prettyList :: [DatumHash] -> Doc ann #

Pretty Redeemer 
Instance details

Defined in PlutusLedgerApi.V1.Scripts

Methods

pretty :: Redeemer -> Doc ann #

prettyList :: [Redeemer] -> Doc ann #

Pretty RedeemerHash 
Instance details

Defined in PlutusLedgerApi.V1.Scripts

Methods

pretty :: RedeemerHash -> Doc ann #

prettyList :: [RedeemerHash] -> Doc ann #

Pretty ScriptHash 
Instance details

Defined in PlutusLedgerApi.V1.Scripts

Methods

pretty :: ScriptHash -> Doc ann #

prettyList :: [ScriptHash] -> Doc ann #

Pretty TxId 
Instance details

Defined in PlutusLedgerApi.V1.Tx

Methods

pretty :: TxId -> Doc ann #

prettyList :: [TxId] -> Doc ann #

Pretty TxOut 
Instance details

Defined in PlutusLedgerApi.V1.Tx

Methods

pretty :: TxOut -> Doc ann #

prettyList :: [TxOut] -> Doc ann #

Pretty TxOutRef 
Instance details

Defined in PlutusLedgerApi.V1.Tx

Methods

pretty :: TxOutRef -> Doc ann #

prettyList :: [TxOutRef] -> Doc ann #

Pretty AssetClass 
Instance details

Defined in PlutusLedgerApi.V1.Value

Methods

pretty :: AssetClass -> Doc ann #

prettyList :: [AssetClass] -> Doc ann #

Pretty CurrencySymbol 
Instance details

Defined in PlutusLedgerApi.V1.Value

Methods

pretty :: CurrencySymbol -> Doc ann #

prettyList :: [CurrencySymbol] -> Doc ann #

Pretty Lovelace 
Instance details

Defined in PlutusLedgerApi.V1.Value

Methods

pretty :: Lovelace -> Doc ann #

prettyList :: [Lovelace] -> Doc ann #

Pretty TokenName 
Instance details

Defined in PlutusLedgerApi.V1.Value

Methods

pretty :: TokenName -> Doc ann #

prettyList :: [TokenName] -> Doc ann #

Pretty Value 
Instance details

Defined in PlutusLedgerApi.V1.Value

Methods

pretty :: Value -> Doc ann #

prettyList :: [Value] -> Doc ann #

Pretty OutputDatum 
Instance details

Defined in PlutusLedgerApi.V2.Tx

Methods

pretty :: OutputDatum -> Doc ann #

prettyList :: [OutputDatum] -> Doc ann #

Pretty TxOut 
Instance details

Defined in PlutusLedgerApi.V2.Tx

Methods

pretty :: TxOut -> Doc ann #

prettyList :: [TxOut] -> Doc ann #

Pretty BuiltinBLS12_381_G1_Element 
Instance details

Defined in PlutusTx.Builtins.Internal

Methods

pretty :: BuiltinBLS12_381_G1_Element -> Doc ann #

prettyList :: [BuiltinBLS12_381_G1_Element] -> Doc ann #

Pretty BuiltinBLS12_381_G2_Element 
Instance details

Defined in PlutusTx.Builtins.Internal

Methods

pretty :: BuiltinBLS12_381_G2_Element -> Doc ann #

prettyList :: [BuiltinBLS12_381_G2_Element] -> Doc ann #

Pretty BuiltinBLS12_381_MlResult 
Instance details

Defined in PlutusTx.Builtins.Internal

Methods

pretty :: BuiltinBLS12_381_MlResult -> Doc ann #

prettyList :: [BuiltinBLS12_381_MlResult] -> Doc ann #

Pretty BuiltinByteString 
Instance details

Defined in PlutusTx.Builtins.Internal

Methods

pretty :: BuiltinByteString -> Doc ann #

prettyList :: [BuiltinByteString] -> Doc ann #

Pretty BuiltinData 
Instance details

Defined in PlutusTx.Builtins.Internal

Methods

pretty :: BuiltinData -> Doc ann #

prettyList :: [BuiltinData] -> Doc ann #

Pretty Text 
Instance details

Defined in Prettyprinter.Internal

Methods

pretty :: Text -> Doc ann #

prettyList :: [Text] -> Doc ann #

Pretty Text 
Instance details

Defined in Prettyprinter.Internal

Methods

pretty :: Text -> Doc ann #

prettyList :: [Text] -> Doc ann #

Pretty Integer 
Instance details

Defined in Prettyprinter.Internal

Methods

pretty :: Integer -> Doc ann #

prettyList :: [Integer] -> Doc ann #

Pretty Natural 
Instance details

Defined in Prettyprinter.Internal

Methods

pretty :: Natural -> Doc ann #

prettyList :: [Natural] -> Doc ann #

Pretty () 
Instance details

Defined in Prettyprinter.Internal

Methods

pretty :: () -> Doc ann #

prettyList :: [()] -> Doc ann #

Pretty Bool 
Instance details

Defined in Prettyprinter.Internal

Methods

pretty :: Bool -> Doc ann #

prettyList :: [Bool] -> Doc ann #

Pretty Char 
Instance details

Defined in Prettyprinter.Internal

Methods

pretty :: Char -> Doc ann #

prettyList :: [Char] -> Doc ann #

Pretty Double 
Instance details

Defined in Prettyprinter.Internal

Methods

pretty :: Double -> Doc ann #

prettyList :: [Double] -> Doc ann #

Pretty Float 
Instance details

Defined in Prettyprinter.Internal

Methods

pretty :: Float -> Doc ann #

prettyList :: [Float] -> Doc ann #

Pretty Int 
Instance details

Defined in Prettyprinter.Internal

Methods

pretty :: Int -> Doc ann #

prettyList :: [Int] -> Doc ann #

Pretty Word 
Instance details

Defined in Prettyprinter.Internal

Methods

pretty :: Word -> Doc ann #

prettyList :: [Word] -> Doc ann #

Pretty a => Pretty (Identity a) 
Instance details

Defined in Prettyprinter.Internal

Methods

pretty :: Identity a -> Doc ann #

prettyList :: [Identity a] -> Doc ann #

Pretty a => Pretty (NonEmpty a) 
Instance details

Defined in Prettyprinter.Internal

Methods

pretty :: NonEmpty a -> Doc ann #

prettyList :: [NonEmpty a] -> Doc ann #

Pretty (ShelleyBasedEra era) 
Instance details

Defined in Cardano.Api.Eon.ShelleyBasedEra

Methods

pretty :: ShelleyBasedEra era -> Doc ann #

prettyList :: [ShelleyBasedEra era] -> Doc ann #

Pretty (CardanoEra era) 
Instance details

Defined in Cardano.Api.Eras.Core

Methods

pretty :: CardanoEra era -> Doc ann #

prettyList :: [CardanoEra era] -> Doc ann #

Show a => Pretty (ShowOf a) 
Instance details

Defined in Cardano.Api.Via.ShowOf

Methods

pretty :: ShowOf a -> Doc ann #

prettyList :: [ShowOf a] -> Doc ann #

Pretty (PlutusScriptContext l) => Pretty (LegacyPlutusArgs l) 
Instance details

Defined in Cardano.Ledger.Plutus.Language

Methods

pretty :: LegacyPlutusArgs l -> Doc ann #

prettyList :: [LegacyPlutusArgs l] -> Doc ann #

Pretty (PlutusArgs 'PlutusV1) 
Instance details

Defined in Cardano.Ledger.Plutus.Language

Methods

pretty :: PlutusArgs 'PlutusV1 -> Doc ann #

prettyList :: [PlutusArgs 'PlutusV1] -> Doc ann #

Pretty (PlutusArgs 'PlutusV2) 
Instance details

Defined in Cardano.Ledger.Plutus.Language

Methods

pretty :: PlutusArgs 'PlutusV2 -> Doc ann #

prettyList :: [PlutusArgs 'PlutusV2] -> Doc ann #

Pretty (PlutusArgs 'PlutusV3) 
Instance details

Defined in Cardano.Ledger.Plutus.Language

Methods

pretty :: PlutusArgs 'PlutusV3 -> Doc ann #

prettyList :: [PlutusArgs 'PlutusV3] -> Doc ann #

Pretty (DefaultUni a) 
Instance details

Defined in PlutusCore.Default.Universe

Methods

pretty :: DefaultUni a -> Doc ann #

prettyList :: [DefaultUni a] -> Doc ann #

Pretty ann => Pretty (UniqueError ann) 
Instance details

Defined in PlutusCore.Error

Methods

pretty :: UniqueError ann -> Doc ann0 #

prettyList :: [UniqueError ann] -> Doc ann0 #

Pretty (SomeTypeIn DefaultUni) 
Instance details

Defined in PlutusCore.Default.Universe

Methods

pretty :: SomeTypeIn DefaultUni -> Doc ann #

prettyList :: [SomeTypeIn DefaultUni] -> Doc ann #

Show a => Pretty (PrettyShow a) 
Instance details

Defined in Prettyprinter.Extras

Methods

pretty :: PrettyShow a -> Doc ann #

prettyList :: [PrettyShow a] -> Doc ann #

Pretty a => Pretty (Maybe a) 
Instance details

Defined in Prettyprinter.Internal

Methods

pretty :: Maybe a -> Doc ann #

prettyList :: [Maybe a] -> Doc ann #

Pretty a => Pretty [a] 
Instance details

Defined in Prettyprinter.Internal

Methods

pretty :: [a] -> Doc ann #

prettyList :: [[a]] -> Doc ann #

(Foldable f, Pretty a) => Pretty (PrettyFoldable f a) 
Instance details

Defined in Prettyprinter.Extras

Methods

pretty :: PrettyFoldable f a -> Doc ann #

prettyList :: [PrettyFoldable f a] -> Doc ann #

(Pretty a1, Pretty a2) => Pretty (a1, a2) 
Instance details

Defined in Prettyprinter.Internal

Methods

pretty :: (a1, a2) -> Doc ann #

prettyList :: [(a1, a2)] -> Doc ann #

Pretty a => Pretty (Const a b) 
Instance details

Defined in Prettyprinter.Internal

Methods

pretty :: Const a b -> Doc ann #

prettyList :: [Const a b] -> Doc ann #

(Pretty a1, Pretty a2, Pretty a3) => Pretty (a1, a2, a3) 
Instance details

Defined in Prettyprinter.Internal

Methods

pretty :: (a1, a2, a3) -> Doc ann #

prettyList :: [(a1, a2, a3)] -> Doc ann #

class (Eq (VerificationKey keyrole), Show (VerificationKey keyrole), SerialiseAsRawBytes (Hash keyrole), HasTextEnvelope (VerificationKey keyrole), HasTextEnvelope (SigningKey keyrole)) => Key keyrole where #

Associated Types

data VerificationKey keyrole #

data SigningKey keyrole #

Instances

Instances details
Key ByronKey 
Instance details

Defined in Cardano.Api.Keys.Byron

Associated Types

data VerificationKey ByronKey #

data SigningKey ByronKey #

Key ByronKeyLegacy 
Instance details

Defined in Cardano.Api.Keys.Byron

Key KesKey 
Instance details

Defined in Cardano.Api.Keys.Praos

Associated Types

data VerificationKey KesKey #

data SigningKey KesKey #

Key VrfKey 
Instance details

Defined in Cardano.Api.Keys.Praos

Associated Types

data VerificationKey VrfKey #

data SigningKey VrfKey #

Key CommitteeColdExtendedKey 
Instance details

Defined in Cardano.Api.Keys.Shelley

Key CommitteeColdKey 
Instance details

Defined in Cardano.Api.Keys.Shelley

Key CommitteeHotExtendedKey 
Instance details

Defined in Cardano.Api.Keys.Shelley

Key CommitteeHotKey 
Instance details

Defined in Cardano.Api.Keys.Shelley

Key DRepExtendedKey 
Instance details

Defined in Cardano.Api.Keys.Shelley