cardano-node-emulator-1.2.0.0
Safe HaskellNone
LanguageHaskell2010

Cardano.Node.Emulator.Internal.Node.Validation

Description

Transaction validation using 'cardano-ledger-specs'

Synopsis

Documentation

type EmulatorBlock = [Validated (Tx EmulatorEra)] Source #

data EmulatedLedgerState Source #

State of the ledger with configuration, mempool, and the blockchain.

newtype Coin #

Constructors

Coin 

Fields

Instances

Instances details
Enum Coin 
Instance details

Defined in Cardano.Ledger.Coin

Eq Coin 
Instance details

Defined in Cardano.Ledger.Coin

Methods

(==) :: Coin -> Coin -> Bool Source #

(/=) :: Coin -> Coin -> Bool Source #

Ord Coin 
Instance details

Defined in Cardano.Ledger.Coin

Show Coin 
Instance details

Defined in Cardano.Ledger.Coin

Generic Coin 
Instance details

Defined in Cardano.Ledger.Coin

Associated Types

type Rep Coin :: Type -> Type Source #

Methods

from :: Coin -> Rep Coin x Source #

to :: Rep Coin x -> Coin Source #

Semigroup Coin 
Instance details

Defined in Cardano.Ledger.Coin

Monoid Coin 
Instance details

Defined in Cardano.Ledger.Coin

NFData Coin 
Instance details

Defined in Cardano.Ledger.Coin

Methods

rnf :: Coin -> () Source #

FromJSON Coin 
Instance details

Defined in Cardano.Ledger.Coin

Methods

parseJSON :: Value -> Parser Coin

parseJSONList :: Value -> Parser [Coin]

ToJSON Coin 
Instance details

Defined in Cardano.Ledger.Coin

Methods

toJSON :: Coin -> Value

toEncoding :: Coin -> Encoding

toJSONList :: [Coin] -> Value

toEncodingList :: [Coin] -> Encoding

NoThunks Coin 
Instance details

Defined in Cardano.Ledger.Coin

Methods

noThunks :: Context -> Coin -> IO (Maybe ThunkInfo)

wNoThunks :: Context -> Coin -> IO (Maybe ThunkInfo)

showTypeOf :: Proxy Coin -> String

ToCBOR Coin 
Instance details

Defined in Cardano.Ledger.Coin

Methods

toCBOR :: Coin -> Encoding

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

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

FromCBOR Coin 
Instance details

Defined in Cardano.Ledger.Coin

Methods

fromCBOR :: Decoder s Coin

label :: Proxy Coin -> Text

Compactible Coin 
Instance details

Defined in Cardano.Ledger.Coin

Associated Types

data CompactForm Coin

Methods

toCompact :: Coin -> Maybe (CompactForm Coin)

fromCompact :: CompactForm Coin -> Coin

DecodeNonNegative Coin 
Instance details

Defined in Cardano.Ledger.Val

Methods

decodeNonNegative :: Decoder s Coin

DecodeMint Coin 
Instance details

Defined in Cardano.Ledger.Val

Methods

decodeMint :: Decoder s Coin

Val Coin 
Instance details

Defined in Cardano.Ledger.Val

Methods

zero :: Coin

(<+>) :: Coin -> Coin -> Coin

(<×>) :: Integral i => i -> Coin -> Coin

(<->) :: Coin -> Coin -> Coin

isZero :: Coin -> Bool

coin :: Coin -> Coin

inject :: Coin -> Coin

modifyCoin :: (Coin -> Coin) -> Coin -> Coin

size :: Coin -> Integer

pointwise :: (Integer -> Integer -> Bool) -> Coin -> Coin -> Bool

isAdaOnly :: Coin -> Bool

isAdaOnlyCompact :: CompactForm Coin -> Bool

injectCompact :: CompactForm Coin -> CompactForm Coin

Abelian Coin 
Instance details

Defined in Cardano.Ledger.Coin

HeapWords Coin 
Instance details

Defined in Cardano.Ledger.Coin

Methods

heapWords :: Coin -> Int

Group Coin 
Instance details

Defined in Cardano.Ledger.Coin

Methods

invert :: Coin -> Coin

(~~) :: Coin -> Coin -> Coin

pow :: Integral x => Coin -> x -> Coin

PartialOrd Coin 
Instance details

Defined in Cardano.Ledger.Coin

Methods

(<=) :: Coin -> Coin -> Bool

(>=) :: Coin -> Coin -> Bool

(==) :: Coin -> Coin -> Bool

(/=) :: Coin -> Coin -> Bool

(<) :: Coin -> Coin -> Bool

(>) :: Coin -> Coin -> Bool

compare :: Coin -> Coin -> Maybe Ordering

EncodeMint Coin 
Instance details

Defined in Cardano.Ledger.Val

Methods

encodeMint :: Coin -> Encoding

HasField "txfee" (TxBody era) Coin 
Instance details

Defined in Cardano.Ledger.ShelleyMA.TxBody

Methods

getField :: TxBody era -> Coin Source #

HasField "txfee" (TxBody era) Coin 
Instance details

Defined in Cardano.Ledger.Shelley.TxBody

Methods

getField :: TxBody era -> Coin Source #

HasField "txfee" (TxBody era) Coin 
Instance details

Defined in Cardano.Ledger.Babbage.TxBody

Methods

getField :: TxBody era -> Coin Source #

HasField "txfee" (TxBody era) Coin 
Instance details

Defined in Cardano.Ledger.Alonzo.TxBody

Methods

getField :: TxBody era -> Coin Source #

HasField "totalCollateral" (TxBody era) (StrictMaybe Coin) 
Instance details

Defined in Cardano.Ledger.Babbage.TxBody

Methods

getField :: TxBody era -> StrictMaybe Coin Source #

Eq (CompactForm Coin) 
Instance details

Defined in Cardano.Ledger.Coin

Methods

(==) :: CompactForm Coin -> CompactForm Coin -> Bool Source #

(/=) :: CompactForm Coin -> CompactForm Coin -> Bool Source #

Show (CompactForm Coin) 
Instance details

Defined in Cardano.Ledger.Coin

Methods

showsPrec :: Int -> CompactForm Coin -> ShowS Source #

show :: CompactForm Coin -> String Source #

showList :: [CompactForm Coin] -> ShowS Source #

NFData (CompactForm Coin) 
Instance details

Defined in Cardano.Ledger.Coin

Methods

rnf :: CompactForm Coin -> () Source #

NoThunks (CompactForm Coin) 
Instance details

Defined in Cardano.Ledger.Coin

Methods

noThunks :: Context -> CompactForm Coin -> IO (Maybe ThunkInfo)

wNoThunks :: Context -> CompactForm Coin -> IO (Maybe ThunkInfo)

showTypeOf :: Proxy (CompactForm Coin) -> String

ToCBOR (CompactForm Coin) 
Instance details

Defined in Cardano.Ledger.Coin

Methods

toCBOR :: CompactForm Coin -> Encoding

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

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

FromCBOR (CompactForm Coin) 
Instance details

Defined in Cardano.Ledger.Coin

Methods

fromCBOR :: Decoder s (CompactForm Coin)

label :: Proxy (CompactForm Coin) -> Text

HeapWords (CompactForm Coin) 
Instance details

Defined in Cardano.Ledger.Coin

Methods

heapWords :: CompactForm Coin -> Int

Prim (CompactForm Coin) 
Instance details

Defined in Cardano.Ledger.Coin

Methods

sizeOf# :: CompactForm Coin -> Int#

alignment# :: CompactForm Coin -> Int#

indexByteArray# :: ByteArray# -> Int# -> CompactForm Coin

readByteArray# :: MutableByteArray# s -> Int# -> State# s -> (# State# s, CompactForm Coin #)

writeByteArray# :: MutableByteArray# s -> Int# -> CompactForm Coin -> State# s -> State# s

setByteArray# :: MutableByteArray# s -> Int# -> Int# -> CompactForm Coin -> State# s -> State# s

indexOffAddr# :: Addr# -> Int# -> CompactForm Coin

readOffAddr# :: Addr# -> Int# -> State# s -> (# State# s, CompactForm Coin #)

writeOffAddr# :: Addr# -> Int# -> CompactForm Coin -> State# s -> State# s

setOffAddr# :: Addr# -> Int# -> Int# -> CompactForm Coin -> State# s -> State# s

type Rep Coin 
Instance details

Defined in Cardano.Ledger.Coin

type Rep Coin = D1 ('MetaData "Coin" "Cardano.Ledger.Coin" "cardano-ledger-core-0.1.0.0-L8b7mq3jAYajmqtKJU3j2" 'True) (C1 ('MetaCons "Coin" 'PrefixI 'True) (S1 ('MetaSel ('Just "unCoin") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Integer)))
newtype CompactForm Coin 
Instance details

Defined in Cardano.Ledger.Coin

newtype CompactForm Coin = CompactCoin Word64

newtype SlotNo #

Constructors

SlotNo 

Fields

Instances

Instances details
Bounded SlotNo 
Instance details

Defined in Cardano.Slotting.Slot

Enum SlotNo 
Instance details

Defined in Cardano.Slotting.Slot

Eq SlotNo 
Instance details

Defined in Cardano.Slotting.Slot

Num SlotNo 
Instance details

Defined in Cardano.Slotting.Slot

Ord SlotNo 
Instance details

Defined in Cardano.Slotting.Slot

Show SlotNo 
Instance details

Defined in Cardano.Slotting.Slot

Generic SlotNo 
Instance details

Defined in Cardano.Slotting.Slot

Associated Types

type Rep SlotNo :: Type -> Type Source #

NFData SlotNo 
Instance details

Defined in Cardano.Slotting.Slot

Methods

rnf :: SlotNo -> () Source #

Serialise SlotNo 
Instance details

Defined in Cardano.Slotting.Slot

Methods

encode :: SlotNo -> Encoding

decode :: Decoder s SlotNo

encodeList :: [SlotNo] -> Encoding

decodeList :: Decoder s [SlotNo]

FromJSON SlotNo 
Instance details

Defined in Cardano.Slotting.Slot

Methods

parseJSON :: Value -> Parser SlotNo

parseJSONList :: Value -> Parser [SlotNo]

ToJSON SlotNo 
Instance details

Defined in Cardano.Slotting.Slot

Methods

toJSON :: SlotNo -> Value

toEncoding :: SlotNo -> Encoding

toJSONList :: [SlotNo] -> Value

toEncodingList :: [SlotNo] -> Encoding

NoThunks SlotNo 
Instance details

Defined in Cardano.Slotting.Slot

Methods

noThunks :: Context -> SlotNo -> IO (Maybe ThunkInfo)

wNoThunks :: Context -> SlotNo -> IO (Maybe ThunkInfo)

showTypeOf :: Proxy SlotNo -> String

ToCBOR SlotNo 
Instance details

Defined in Cardano.Slotting.Slot

Methods

toCBOR :: SlotNo -> Encoding

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

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

FromCBOR SlotNo 
Instance details

Defined in Cardano.Slotting.Slot

Methods

fromCBOR :: Decoder s SlotNo

label :: Proxy SlotNo -> Text

HasField "ttl" (TxBody era) SlotNo 
Instance details

Defined in Cardano.Ledger.Shelley.TxBody

Methods

getField :: TxBody era -> SlotNo Source #

HasHeader block => Anchorable (WithOrigin SlotNo) (Anchor block) block 
Instance details

Defined in Ouroboros.Network.AnchoredFragment

Methods

asAnchor :: block -> Anchor block

getAnchorMeasure :: Proxy block -> Anchor block -> WithOrigin SlotNo

Anchorable (WithOrigin SlotNo) (HeaderState blk) (HeaderState blk) 
Instance details

Defined in Ouroboros.Consensus.HeaderValidation

Methods

asAnchor :: HeaderState blk -> HeaderState blk

getAnchorMeasure :: Proxy (HeaderState blk) -> HeaderState blk -> WithOrigin SlotNo

GetTip l => Anchorable (WithOrigin SlotNo) (Checkpoint l) (Checkpoint l) 
Instance details

Defined in Ouroboros.Consensus.Storage.LedgerDB.InMemory

Methods

asAnchor :: Checkpoint l -> Checkpoint l

getAnchorMeasure :: Proxy (Checkpoint l) -> Checkpoint l -> WithOrigin SlotNo

Embed (StakeCreds era) (Map (Credential 'Staking era) SlotNo) 
Instance details

Defined in Cardano.Ledger.Shelley.TxBody

Methods

toBase :: StakeCreds era -> Map (Credential 'Staking era) SlotNo

fromBase :: Map (Credential 'Staking era) SlotNo -> StakeCreds era

HasExp (StakeCreds era) (Map (Credential 'Staking era) SlotNo) 
Instance details

Defined in Cardano.Ledger.Shelley.TxBody

Methods

toExp :: StakeCreds era -> Exp (Map (Credential 'Staking era) SlotNo)

type Rep SlotNo 
Instance details

Defined in Cardano.Slotting.Slot

type Rep SlotNo = D1 ('MetaData "SlotNo" "Cardano.Slotting.Slot" "cardano-slotting-0.1.0.2-FgskX6mNhqABlt2HG3fNqN" 'True) (C1 ('MetaCons "SlotNo" 'PrefixI 'True) (S1 ('MetaSel ('Just "unSlotNo") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word64)))

type EmulatorEra = BabbageEra StandardCrypto Source #

The default era for the emulator

type CardanoLedgerError = Either ValidationErrorInPhase ToCardanoError Source #

initialState :: Params -> EmulatedLedgerState Source #

Initial ledger state for a distribution

hasValidationErrors :: Params -> SlotNo -> UtxoIndex -> Tx BabbageEra -> ValidationResult Source #

makeTransactionBody :: Params -> UTxO EmulatorEra -> CardanoBuildTx -> Either CardanoLedgerError (TxBody BabbageEra) Source #

validateCardanoTx :: Params -> Slot -> UtxoIndex -> CardanoTx -> ValidationResult Source #

unsafeMakeValid :: CardanoTx -> OnChainTx Source #

Modifying the state

makeBlock :: EmulatedLedgerState -> EmulatedLedgerState Source #

Make a block with all transactions that have been validated in the current block, add the block to the blockchain, and empty the current block.

nextSlot :: EmulatedLedgerState -> EmulatedLedgerState Source #

Increase the slot number by one

newtype UTxO era #

Constructors

UTxO 

Fields

  • unUTxO :: Map (TxIn (Crypto era)) (TxOut era)
     

Instances

Instances details
(Eq (TxOut era), Crypto (Crypto era)) => Eq (UTxO era) 
Instance details

Defined in Cardano.Ledger.Shelley.UTxO

Methods

(==) :: UTxO era -> UTxO era -> Bool Source #

(/=) :: UTxO era -> UTxO era -> Bool Source #

(Show (TxOut era), Crypto (Crypto era)) => Show (UTxO era) 
Instance details

Defined in Cardano.Ledger.Shelley.UTxO

Methods

showsPrec :: Int -> UTxO era -> ShowS Source #

show :: UTxO era -> String Source #

showList :: [UTxO era] -> ShowS Source #

Generic (UTxO era) 
Instance details

Defined in Cardano.Ledger.Shelley.UTxO

Associated Types

type Rep (UTxO era) :: Type -> Type Source #

Methods

from :: UTxO era -> Rep (UTxO era) x Source #

to :: Rep (UTxO era) x -> UTxO era Source #

Semigroup (UTxO era) 
Instance details

Defined in Cardano.Ledger.Shelley.UTxO

Methods

(<>) :: UTxO era -> UTxO era -> UTxO era Source #

sconcat :: NonEmpty (UTxO era) -> UTxO era Source #

stimes :: Integral b => b -> UTxO era -> UTxO era Source #

Crypto (Crypto era) => Monoid (UTxO era) 
Instance details

Defined in Cardano.Ledger.Shelley.UTxO

Methods

mempty :: UTxO era Source #

mappend :: UTxO era -> UTxO era -> UTxO era Source #

mconcat :: [UTxO era] -> UTxO era Source #

(Era era, NFData (TxOut era)) => NFData (UTxO era) 
Instance details

Defined in Cardano.Ledger.Shelley.UTxO

Methods

rnf :: UTxO era -> () Source #

Default (UTxO era) 
Instance details

Defined in Cardano.Ledger.Shelley.UTxO

Methods

def :: UTxO era

TransUTxO NoThunks era => NoThunks (UTxO era) 
Instance details

Defined in Cardano.Ledger.Shelley.UTxO

Methods

noThunks :: Context -> UTxO era -> IO (Maybe ThunkInfo)

wNoThunks :: Context -> UTxO era -> IO (Maybe ThunkInfo)

showTypeOf :: Proxy (UTxO era) -> String

(Era era, ToCBOR (TxOut era)) => ToCBOR (UTxO era) 
Instance details

Defined in Cardano.Ledger.Shelley.UTxO

Methods

toCBOR :: UTxO era -> Encoding

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

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

(FromCBOR (TxOut era), Era era) => FromCBOR (UTxO era) 
Instance details

Defined in Cardano.Ledger.Shelley.UTxO

Methods

fromCBOR :: Decoder s (UTxO era)

label :: Proxy (UTxO era) -> Text

(Crypto (Crypto era), FromSharedCBOR (TxOut era), Share (TxOut era) ~ Interns (Credential 'Staking (Crypto era))) => FromSharedCBOR (UTxO era) 
Instance details

Defined in Cardano.Ledger.Shelley.UTxO

Associated Types

type Share (UTxO era)

Methods

getShare :: UTxO era -> Share (UTxO era)

fromSharedCBOR :: Share (UTxO era) -> Decoder s (UTxO era)

fromSharedPlusCBOR :: StateT (Share (UTxO era)) (Decoder s) (UTxO era)

type Rep (UTxO era) 
Instance details

Defined in Cardano.Ledger.Shelley.UTxO

type Rep (UTxO era) = D1 ('MetaData "UTxO" "Cardano.Ledger.Shelley.UTxO" "cardano-ledger-shelley-0.1.0.0-IAEP382Vf9o9lj3qcjJd5h" 'True) (C1 ('MetaCons "UTxO" 'PrefixI 'True) (S1 ('MetaSel ('Just "unUTxO") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Map (TxIn (Crypto era)) (TxOut era)))))
type Share (UTxO era) 
Instance details

Defined in Cardano.Ledger.Shelley.UTxO

type Share (UTxO era) = Interns (Credential 'Staking (Crypto era))
type TranslationError (AllegraEra c) UTxO 
Instance details

Defined in Cardano.Ledger.Allegra.Translation

type TranslationError (AllegraEra c) UTxO = Void
type TranslationError (MaryEra c) UTxO 
Instance details

Defined in Cardano.Ledger.Mary.Translation

type TranslationError (MaryEra c) UTxO = Void
type TranslationError (AlonzoEra c) UTxO 
Instance details

Defined in Cardano.Ledger.Alonzo.Translation

type TranslationError (AlonzoEra c) UTxO = Void
type TranslationError (BabbageEra c) UTxO 
Instance details

Defined in Cardano.Ledger.Babbage.Translation

type TranslationError (BabbageEra c) UTxO = Void

Lenses

Etc.

emulatorGlobals :: Params -> Globals Source #

A sensible default Globals value for the emulator