hydra-node-0.16.0: The Hydra node
Safe HaskellSafe-Inferred
LanguageGHC2021

Hydra.Ledger.Cardano

Synopsis

Documentation

adjustUTxO :: Tx -> UTxO -> UTxO Source #

Utility function to "adjust" a UTxO' set given a Tx

The inputs from the Tx are removed from the internal map of the UTxO' and the outputs added, correctly indexed by the TxIn. This function is useful to manually maintain a UTxO' set without caring too much about the Ledger rules.

genTxOutAdaOnly :: VerificationKey PaymentKey -> Gen (TxOut ctx) Source #

Generate an ada-only TxOut payed to an arbitrary public key.

genOneUTxOFor :: VerificationKey PaymentKey -> Gen UTxO Source #

Generate a single UTXO owned by vk.

genUTxOAdaOnlyOfSize :: Int -> Gen UTxO Source #

Generate a fixed size UTxO with ada-only outputs.

cardanoLedger :: Globals -> LedgerEnv LedgerEra -> Ledger Tx Source #

Use the cardano-ledger as an in-hydra Ledger.

fromChainSlot :: ChainSlot -> SlotNo Source #

Simple conversion from a generic slot to a specific local one.

mkSimpleTx Source #

Arguments

:: (TxIn, TxOut CtxUTxO) 
-> (AddressInEra, Value)

Recipient address and amount.

-> SigningKey PaymentKey

Sender's signing key.

-> Either TxBodyError Tx 

Create a zero-fee, payment cardano transaction.

mkRangedTx Source #

Arguments

:: (TxIn, TxOut CtxUTxO) 
-> (AddressInEra, Value)

Recipient address and amount.

-> SigningKey PaymentKey

Sender's signing key.

-> (Maybe TxValidityLowerBound, Maybe TxValidityUpperBound) 
-> Either TxBodyError Tx 

Create a zero-fee, payment cardano transaction with validity range.

genSigningKey :: Gen (SigningKey PaymentKey) Source #

genKeyPair :: Gen (VerificationKey PaymentKey, SigningKey PaymentKey) Source #

genSequenceOfSimplePaymentTransactions :: Gen (UTxO, [Tx]) Source #

Generates a sequence of simple "transfer" transactions for a single key. The kind of transactions produced by this generator is very limited, see generateOneTransfer.

generateOneTransfer :: NetworkId -> (UTxO, (VerificationKey PaymentKey, SigningKey PaymentKey), [Tx]) -> Int -> Gen (UTxO, (VerificationKey PaymentKey, SigningKey PaymentKey), [Tx]) Source #

genOutput :: forall ctx. VerificationKey PaymentKey -> Gen (TxOut ctx) Source #

genValue :: Gen Value Source #

genUTxOAlonzo :: Gen UTxO Source #

Generate Babbage era UTxO', which may contain arbitrary assets in TxOuts addressed to public keys *and* scripts. NOTE: This is not reducing size when generating assets in TxOuts, so will end up regularly with 300+ assets with generator size 30. NOTE: The Arbitrary TxIn instance from the ledger is producing colliding values, so we replace them.

genUTxOSized :: Int -> Gen UTxO Source #

Generate a Babbage era UTxO' with given number of outputs. See also genTxOut.

genTxOut :: Gen (TxOut ctx) Source #

Generate a Babbage era TxOut, which may contain arbitrary assets addressed to public keys and scripts, as well as datums.

NOTE: This generator does * not produce byron addresses as most of the cardano ecosystem dropped support for that (including plutus), * not produce reference scripts as they are not fully "visible" from plutus, * replace stake pointers with null references as nobody uses that.

genUTxO1 :: Gen (TxOut CtxUTxO) -> Gen UTxO Source #

Genereate a UTxO' with a single entry using given TxOut generator.

genTxOutByron :: Gen (TxOut ctx) Source #

Generate a TxOut with a byron address. This is usually not supported by Hydra or Plutus.

genTxOutWithReferenceScript :: Gen (TxOut ctx) Source #

Generate a TxOut with a reference script. The standard genTxOut is not including reference scripts, use this generator if you are interested in these cases.

genUTxOFor :: VerificationKey PaymentKey -> Gen UTxO Source #

Generate utxos owned by the given cardano key.

genAddressInEra :: NetworkId -> Gen AddressInEra Source #

NOTE: See note on mkVkAddress about NetworkId.

genAdaOnlyUTxO :: Gen UTxO Source #

Generate UTXO entries that do not contain any assets. Useful to test / measure cases where

adaOnly :: TxOut CtxUTxO -> TxOut CtxUTxO Source #

genUTxOWithSimplifiedAddresses :: Gen UTxO Source #

Generate "simplified" UTXO, ie. without some of the complexities required for backward-compatibility and obscure features.

shrinkUTxO :: UTxO -> [UTxO] Source #

shrinkValue :: Value -> [Value] Source #

data ShelleyGenesis c #

Constructors

ShelleyGenesis 

Fields

Instances

Instances details
Crypto c => FromJSON (ShelleyGenesis c) 
Instance details

Defined in Cardano.Ledger.Shelley.Genesis

Methods

parseJSON :: Value -> Parser (ShelleyGenesis c)

parseJSONList :: Value -> Parser [ShelleyGenesis c]

omittedField :: Maybe (ShelleyGenesis c)

Crypto c => ToJSON (ShelleyGenesis c) 
Instance details

Defined in Cardano.Ledger.Shelley.Genesis

Methods

toJSON :: ShelleyGenesis c -> Value

toEncoding :: ShelleyGenesis c -> Encoding

toJSONList :: [ShelleyGenesis c] -> Value

toEncodingList :: [ShelleyGenesis c] -> Encoding

omitField :: ShelleyGenesis c -> Bool

Generic (ShelleyGenesis c) 
Instance details

Defined in Cardano.Ledger.Shelley.Genesis

Associated Types

type Rep (ShelleyGenesis c) :: Type -> Type Source #

Crypto c => Show (ShelleyGenesis c) 
Instance details

Defined in Cardano.Ledger.Shelley.Genesis

Crypto c => FromCBOR (ShelleyGenesis c) 
Instance details

Defined in Cardano.Ledger.Shelley.Genesis

Methods

fromCBOR :: Decoder s (ShelleyGenesis c)

label :: Proxy (ShelleyGenesis c) -> Text

Crypto c => ToCBOR (ShelleyGenesis c) 
Instance details

Defined in Cardano.Ledger.Shelley.Genesis

Methods

toCBOR :: ShelleyGenesis c -> Encoding

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (ShelleyGenesis c) -> Size

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [ShelleyGenesis c] -> Size

Crypto c => DecCBOR (ShelleyGenesis c) 
Instance details

Defined in Cardano.Ledger.Shelley.Genesis

Methods

decCBOR :: Decoder s (ShelleyGenesis c)

dropCBOR :: Proxy (ShelleyGenesis c) -> Decoder s ()

label :: Proxy (ShelleyGenesis c) -> Text

Crypto c => EncCBOR (ShelleyGenesis c) 
Instance details

Defined in Cardano.Ledger.Shelley.Genesis

Methods

encCBOR :: ShelleyGenesis c -> Encoding

encodedSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy (ShelleyGenesis c) -> Size

encodedListSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy [ShelleyGenesis c] -> Size

Crypto c => Eq (ShelleyGenesis c) 
Instance details

Defined in Cardano.Ledger.Shelley.Genesis

Crypto c => NoThunks (ShelleyGenesis c) 
Instance details

Defined in Cardano.Ledger.Shelley.Genesis

Methods

noThunks :: Context -> ShelleyGenesis c -> IO (Maybe ThunkInfo)

wNoThunks :: Context -> ShelleyGenesis c -> IO (Maybe ThunkInfo)

showTypeOf :: Proxy (ShelleyGenesis c) -> String

type Rep (ShelleyGenesis c) 
Instance details

Defined in Cardano.Ledger.Shelley.Genesis

type Rep (ShelleyGenesis c) = D1 ('MetaData "ShelleyGenesis" "Cardano.Ledger.Shelley.Genesis" "cardano-ledger-shelley-1.9.0.0-7HgzAx4k96DEHFChwYPQhk" 'False) (C1 ('MetaCons "ShelleyGenesis" 'PrefixI 'True) (((S1 ('MetaSel ('Just "sgSystemStart") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 UTCTime) :*: (S1 ('MetaSel ('Just "sgNetworkMagic") 'NoSourceUnpackedness 'SourceStrict 'DecidedUnpack) (Rec0 Word32) :*: S1 ('MetaSel ('Just "sgNetworkId") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Network))) :*: ((S1 ('MetaSel ('Just "sgActiveSlotsCoeff") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 PositiveUnitInterval) :*: S1 ('MetaSel ('Just "sgSecurityParam") 'NoSourceUnpackedness 'SourceStrict 'DecidedUnpack) (Rec0 Word64)) :*: (S1 ('MetaSel ('Just "sgEpochLength") 'NoSourceUnpackedness 'SourceStrict 'DecidedUnpack) (Rec0 EpochSize) :*: S1 ('MetaSel ('Just "sgSlotsPerKESPeriod") 'NoSourceUnpackedness 'SourceStrict 'DecidedUnpack) (Rec0 Word64)))) :*: (((S1 ('MetaSel ('Just "sgMaxKESEvolutions") 'NoSourceUnpackedness 'SourceStrict 'DecidedUnpack) (Rec0 Word64) :*: S1 ('MetaSel ('Just "sgSlotLength") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 NominalDiffTimeMicro)) :*: (S1 ('MetaSel ('Just "sgUpdateQuorum") 'NoSourceUnpackedness 'SourceStrict 'DecidedUnpack) (Rec0 Word64) :*: S1 ('MetaSel ('Just "sgMaxLovelaceSupply") 'NoSourceUnpackedness 'SourceStrict 'DecidedUnpack) (Rec0 Word64))) :*: ((S1 ('MetaSel ('Just "sgProtocolParams") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (PParams (ShelleyEra c))) :*: S1 ('MetaSel ('Just "sgGenDelegs") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Map (KeyHash 'Genesis c) (GenDelegPair c)))) :*: (S1 ('MetaSel ('Just "sgInitialFunds") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (ListMap (Addr c) Coin)) :*: S1 ('MetaSel ('Just "sgStaking") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (ShelleyGenesisStaking c)))))))

type Tx = Tx Era #

Orphan instances

Arbitrary TxId Source # 
Instance details

Methods

arbitrary :: Gen TxId

shrink :: TxId -> [TxId]

Arbitrary AssetName Source # 
Instance details

Methods

arbitrary :: Gen AssetName

shrink :: AssetName -> [AssetName]

Arbitrary UTxO Source # 
Instance details

Methods

arbitrary :: Gen UTxO

shrink :: UTxO -> [UTxO]

Arbitrary Tx Source # 
Instance details

Methods

arbitrary :: Gen Tx

shrink :: Tx -> [Tx]

FromJSON Tx Source # 
Instance details

Methods

parseJSON :: Value -> Parser Tx

parseJSONList :: Value -> Parser [Tx]

omittedField :: Maybe Tx

ToJSON Tx Source # 
Instance details

Methods

toJSON :: Tx -> Value

toEncoding :: Tx -> Encoding

toJSONList :: [Tx] -> Value

toEncodingList :: [Tx] -> Encoding

omitField :: Tx -> Bool

FromCBOR UTxO Source # 
Instance details

Methods

fromCBOR :: Decoder s UTxO

label :: Proxy UTxO -> Text

FromCBOR Tx Source # 
Instance details

Methods

fromCBOR :: Decoder s Tx

label :: Proxy Tx -> Text

ToCBOR UTxO Source # 
Instance details

Methods

toCBOR :: UTxO -> Encoding

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy UTxO -> Size

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [UTxO] -> Size

ToCBOR Tx Source # 
Instance details

Methods

toCBOR :: Tx -> Encoding

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy Tx -> Size

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [Tx] -> Size

IsTx Tx Source # 
Instance details

Associated Types

type UTxOType Tx Source #

type TxIdType Tx Source #

type ValueType Tx Source #

Arbitrary (Hash PaymentKey) Source # 
Instance details

Methods

arbitrary :: Gen (Hash PaymentKey)

shrink :: Hash PaymentKey -> [Hash PaymentKey]

Arbitrary (VerificationKey PaymentKey) Source # 
Instance details

Methods

arbitrary :: Gen (VerificationKey PaymentKey)

shrink :: VerificationKey PaymentKey -> [VerificationKey PaymentKey]

Arbitrary (TxOut CtxUTxO) Source # 
Instance details

Methods

arbitrary :: Gen (TxOut CtxUTxO)

shrink :: TxOut CtxUTxO -> [TxOut CtxUTxO]