plutus-ledger-1.1.0.0: Wallet API
Safe HaskellNone
LanguageHaskell2010

Ledger

Synopsis

Documentation

examplePlutusScriptAlwaysFails :: WitCtx witctx -> PlutusScript PlutusScriptV1 Source #

An example Plutus script that always fails, irrespective of inputs.

For example, if one were to use this for a payment address then it would be impossible for anyone to ever spend from it.

The exact script depends on the context in which it is to be used.

examplePlutusScriptAlwaysSucceeds :: WitCtx witctx -> PlutusScript PlutusScriptV1 Source #

An example Plutus script that always succeeds, irrespective of inputs.

For example, if one were to use this for a payment address then it would allow anyone to spend from it.

The exact script depends on the context in which it is to be used.

data WitCtx witctx where Source #

This GADT provides a value-level representation of all the witness contexts. This enables pattern matching on the context to allow them to be treated in a non-uniform way.

data Language Source #

Non-Native Script language. This is an Enumerated type. This is expected to be an open type. We will add new Constuctors to this type as additional Non-Native scripting language as are added. We use an enumerated type for two reasons. 1) We can write total functions by case analysis over the constructors 2) We will use DataKinds to make some datatypes indexed by Language For now, the only Non-Native Scriting language is Plutus We might add new languages in the futures.

Note that the the serialization of Language depends on the ordering.

Constructors

PlutusV1 
PlutusV2 

Instances

Instances details
Bounded Language 
Instance details

Defined in Cardano.Ledger.Alonzo.Language

Enum Language 
Instance details

Defined in Cardano.Ledger.Alonzo.Language

Eq Language 
Instance details

Defined in Cardano.Ledger.Alonzo.Language

Ord Language 
Instance details

Defined in Cardano.Ledger.Alonzo.Language

Show Language 
Instance details

Defined in Cardano.Ledger.Alonzo.Language

Ix Language 
Instance details

Defined in Cardano.Ledger.Alonzo.Language

Generic Language 
Instance details

Defined in Cardano.Ledger.Alonzo.Language

Associated Types

type Rep Language :: Type -> Type Source #

NFData Language 
Instance details

Defined in Cardano.Ledger.Alonzo.Language

Methods

rnf :: Language -> () Source #

FromCBOR Language 
Instance details

Defined in Cardano.Ledger.Alonzo.Language

ToCBOR Language 
Instance details

Defined in Cardano.Ledger.Alonzo.Language

Methods

toCBOR :: Language -> Encoding Source #

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy Language -> Size Source #

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [Language] -> Size Source #

NoThunks Language 
Instance details

Defined in Cardano.Ledger.Alonzo.Language

ToSchema Language Source # 
Instance details

Defined in Ledger.Orphans

type Rep Language 
Instance details

Defined in Cardano.Ledger.Alonzo.Language

type Rep Language = D1 ('MetaData "Language" "Cardano.Ledger.Alonzo.Language" "cardano-ledger-alonzo-0.1.0.0-NThdmINrvW30AlLdZjZ0g" 'False) (C1 ('MetaCons "PlutusV1" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "PlutusV2" 'PrefixI 'False) (U1 :: Type -> Type))

data ExBudget Source #

Constructors

ExBudget 

Instances

Instances details
Eq ExBudget 
Instance details

Defined in PlutusCore.Evaluation.Machine.ExBudget

Show ExBudget 
Instance details

Defined in PlutusCore.Evaluation.Machine.ExBudget

Generic ExBudget 
Instance details

Defined in PlutusCore.Evaluation.Machine.ExBudget

Associated Types

type Rep ExBudget :: Type -> Type Source #

Semigroup ExBudget 
Instance details

Defined in PlutusCore.Evaluation.Machine.ExBudget

Monoid ExBudget 
Instance details

Defined in PlutusCore.Evaluation.Machine.ExBudget

NFData ExBudget 
Instance details

Defined in PlutusCore.Evaluation.Machine.ExBudget

Methods

rnf :: ExBudget -> () Source #

ToJSON ExBudget 
Instance details

Defined in PlutusCore.Evaluation.Machine.ExBudget

FromJSON ExBudget 
Instance details

Defined in PlutusCore.Evaluation.Machine.ExBudget

NoThunks ExBudget 
Instance details

Defined in PlutusCore.Evaluation.Machine.ExBudget

Pretty ExBudget 
Instance details

Defined in PlutusCore.Evaluation.Machine.ExBudget

Methods

pretty :: ExBudget -> Doc ann Source #

prettyList :: [ExBudget] -> Doc ann Source #

Lift ExBudget 
Instance details

Defined in PlutusCore.Evaluation.Machine.ExBudget

PrettyBy config ExBudget 
Instance details

Defined in PlutusCore.Evaluation.Machine.ExBudget

Methods

prettyBy :: config -> ExBudget -> Doc ann Source #

prettyListBy :: config -> [ExBudget] -> Doc ann Source #

type Rep ExBudget 
Instance details

Defined in PlutusCore.Evaluation.Machine.ExBudget

type Rep ExBudget = D1 ('MetaData "ExBudget" "PlutusCore.Evaluation.Machine.ExBudget" "plutus-core-1.0.0.1-AYZ1DL3hDMt58i5HNUtSdG" 'False) (C1 ('MetaCons "ExBudget" 'PrefixI 'True) (S1 ('MetaSel ('Just "exBudgetCPU") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedUnpack) (Rec0 ExCPU) :*: S1 ('MetaSel ('Just "exBudgetMemory") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedUnpack) (Rec0 ExMemory)))

newtype ExMemory Source #

Counts size in machine words.

Constructors

ExMemory CostingInteger 

Instances

Instances details
Eq ExMemory 
Instance details

Defined in PlutusCore.Evaluation.Machine.ExMemory

Num ExMemory 
Instance details

Defined in PlutusCore.Evaluation.Machine.ExMemory

Ord ExMemory 
Instance details

Defined in PlutusCore.Evaluation.Machine.ExMemory

Show ExMemory 
Instance details

Defined in PlutusCore.Evaluation.Machine.ExMemory

Generic ExMemory 
Instance details

Defined in PlutusCore.Evaluation.Machine.ExMemory

Associated Types

type Rep ExMemory :: Type -> Type Source #

Semigroup ExMemory 
Instance details

Defined in PlutusCore.Evaluation.Machine.ExMemory

Monoid ExMemory 
Instance details

Defined in PlutusCore.Evaluation.Machine.ExMemory

NFData ExMemory 
Instance details

Defined in PlutusCore.Evaluation.Machine.ExMemory

Methods

rnf :: ExMemory -> () Source #

ToJSON ExMemory 
Instance details

Defined in PlutusCore.Evaluation.Machine.ExMemory

FromJSON ExMemory 
Instance details

Defined in PlutusCore.Evaluation.Machine.ExMemory

NoThunks ExMemory 
Instance details

Defined in PlutusCore.Evaluation.Machine.ExMemory

Pretty ExMemory 
Instance details

Defined in PlutusCore.Evaluation.Machine.ExMemory

Methods

pretty :: ExMemory -> Doc ann Source #

prettyList :: [ExMemory] -> Doc ann Source #

ExMemoryUsage ExMemory 
Instance details

Defined in PlutusCore.Evaluation.Machine.ExMemory

Lift ExMemory 
Instance details

Defined in PlutusCore.Evaluation.Machine.ExMemory

PrettyBy config ExMemory 
Instance details

Defined in PlutusCore.Evaluation.Machine.ExMemory

Methods

prettyBy :: config -> ExMemory -> Doc ann Source #

prettyListBy :: config -> [ExMemory] -> Doc ann Source #

type Rep ExMemory 
Instance details

Defined in PlutusCore.Evaluation.Machine.ExMemory

type Rep ExMemory = D1 ('MetaData "ExMemory" "PlutusCore.Evaluation.Machine.ExMemory" "plutus-core-1.0.0.1-AYZ1DL3hDMt58i5HNUtSdG" 'True) (C1 ('MetaCons "ExMemory" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 CostingInteger)))

newtype ExCPU Source #

Counts CPU units in picoseconds: maximum value for SatInt is 2^63 ps, or appproximately 106 days.

Constructors

ExCPU CostingInteger 

Instances

Instances details
Eq ExCPU 
Instance details

Defined in PlutusCore.Evaluation.Machine.ExMemory

Methods

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

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

Num ExCPU 
Instance details

Defined in PlutusCore.Evaluation.Machine.ExMemory

Ord ExCPU 
Instance details

Defined in PlutusCore.Evaluation.Machine.ExMemory

Show ExCPU 
Instance details

Defined in PlutusCore.Evaluation.Machine.ExMemory

Generic ExCPU 
Instance details

Defined in PlutusCore.Evaluation.Machine.ExMemory

Associated Types

type Rep ExCPU :: Type -> Type Source #

Methods

from :: ExCPU -> Rep ExCPU x Source #

to :: Rep ExCPU x -> ExCPU Source #

Semigroup ExCPU 
Instance details

Defined in PlutusCore.Evaluation.Machine.ExMemory

Monoid ExCPU 
Instance details

Defined in PlutusCore.Evaluation.Machine.ExMemory

NFData ExCPU 
Instance details

Defined in PlutusCore.Evaluation.Machine.ExMemory

Methods

rnf :: ExCPU -> () Source #

ToJSON ExCPU 
Instance details

Defined in PlutusCore.Evaluation.Machine.ExMemory

FromJSON ExCPU 
Instance details

Defined in PlutusCore.Evaluation.Machine.ExMemory

NoThunks ExCPU 
Instance details

Defined in PlutusCore.Evaluation.Machine.ExMemory

Pretty ExCPU 
Instance details

Defined in PlutusCore.Evaluation.Machine.ExMemory

Methods

pretty :: ExCPU -> Doc ann Source #

prettyList :: [ExCPU] -> Doc ann Source #

Lift ExCPU 
Instance details

Defined in PlutusCore.Evaluation.Machine.ExMemory

PrettyBy config ExCPU 
Instance details

Defined in PlutusCore.Evaluation.Machine.ExMemory

Methods

prettyBy :: config -> ExCPU -> Doc ann Source #

prettyListBy :: config -> [ExCPU] -> Doc ann Source #

type Rep ExCPU 
Instance details

Defined in PlutusCore.Evaluation.Machine.ExMemory

type Rep ExCPU = D1 ('MetaData "ExCPU" "PlutusCore.Evaluation.Machine.ExMemory" "plutus-core-1.0.0.1-AYZ1DL3hDMt58i5HNUtSdG" 'True) (C1 ('MetaCons "ExCPU" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 CostingInteger)))

data SatInt Source #

Instances

Instances details
Bounded SatInt 
Instance details

Defined in Data.SatInt

Enum SatInt 
Instance details

Defined in Data.SatInt

Eq SatInt 
Instance details

Defined in Data.SatInt

Integral SatInt 
Instance details

Defined in Data.SatInt

Num SatInt

In the Num instance, we plug in our own addition, multiplication and subtraction function that perform overflow-checking.

Instance details

Defined in Data.SatInt

Ord SatInt 
Instance details

Defined in Data.SatInt

Read SatInt 
Instance details

Defined in Data.SatInt

Real SatInt 
Instance details

Defined in Data.SatInt

Show SatInt 
Instance details

Defined in Data.SatInt

Generic SatInt 
Instance details

Defined in Data.SatInt

Associated Types

type Rep SatInt :: Type -> Type Source #

NFData SatInt 
Instance details

Defined in Data.SatInt

Methods

rnf :: SatInt -> () Source #

ToJSON SatInt 
Instance details

Defined in Data.SatInt

FromJSON SatInt 
Instance details

Defined in Data.SatInt

Bits SatInt 
Instance details

Defined in Data.SatInt

FiniteBits SatInt 
Instance details

Defined in Data.SatInt

FromField SatInt 
Instance details

Defined in Data.SatInt

Prim SatInt 
Instance details

Defined in Data.SatInt

NoThunks SatInt 
Instance details

Defined in Data.SatInt

ExMemoryUsage SatInt 
Instance details

Defined in PlutusCore.Evaluation.Machine.ExMemory

Lift SatInt 
Instance details

Defined in Data.SatInt

type Rep SatInt 
Instance details

Defined in Data.SatInt

type Rep SatInt = D1 ('MetaData "SatInt" "Data.SatInt" "plutus-core-1.0.0.1-AYZ1DL3hDMt58i5HNUtSdG" 'True) (C1 ('MetaCons "SI" 'PrefixI 'True) (S1 ('MetaSel ('Just "unSatInt") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int)))

spendsOutput :: TxInfo -> TxId -> Integer -> Bool Source #

Check if the pending transaction spends a specific transaction output (identified by the hash of a transaction and an index into that transactions' outputs)

ownCurrencySymbol :: ScriptContext -> CurrencySymbol Source #

The CurrencySymbol of the current validator script.

valueProduced :: TxInfo -> Value Source #

Get the total value of outputs produced by this transaction.

valueSpent :: TxInfo -> Value Source #

Get the total value of inputs spent by this transaction.

valuePaidTo :: TxInfo -> PubKeyHash -> Value Source #

Get the total value paid to a public key address by a pending transaction.

pubKeyOutputsAt :: PubKeyHash -> TxInfo -> [Value] Source #

Get the values paid to a public key address by a pending transaction.

valueLockedBy :: TxInfo -> ValidatorHash -> Value Source #

Get the total value locked by the given validator in this transaction.

scriptOutputsAt :: ValidatorHash -> TxInfo -> [(DatumHash, Value)] Source #

Get the list of TxOut outputs of the pending transaction at a given script address.

ownHash :: ScriptContext -> ValidatorHash Source #

Get the hash of the validator script that is currently being validated.

ownHashes :: ScriptContext -> (ValidatorHash, DatumHash) Source #

Get the validator and datum hashes of the output that is curently being validated

pubKeyOutput :: TxOut -> Maybe PubKeyHash Source #

Get the public key hash that locks the transaction output, if any.

txSignedBy :: TxInfo -> PubKeyHash -> Bool Source #

Check if a transaction was signed by the given public key.

findContinuingOutputs :: ScriptContext -> [Integer] Source #

Finds all the outputs that pay to the same script address that we are currently spending from, if any.

findDatumHash :: Datum -> TxInfo -> Maybe DatumHash Source #

Find the hash of a datum, if it is part of the pending transaction's hashes

findDatum :: DatumHash -> TxInfo -> Maybe Datum Source #

Find the data corresponding to a data hash, if there is one

findOwnInput :: ScriptContext -> Maybe TxInInfo Source #

Find the input currently being validated.

data TxInInfo Source #

An input of a pending transaction.

Instances

Instances details
Eq TxInInfo 
Instance details

Defined in Plutus.V1.Ledger.Contexts

Show TxInInfo 
Instance details

Defined in Plutus.V1.Ledger.Contexts

Generic TxInInfo 
Instance details

Defined in Plutus.V1.Ledger.Contexts

Associated Types

type Rep TxInInfo :: Type -> Type Source #

Pretty TxInInfo 
Instance details

Defined in Plutus.V1.Ledger.Contexts

Methods

pretty :: TxInInfo -> Doc ann Source #

prettyList :: [TxInInfo] -> Doc ann Source #

UnsafeFromData TxInInfo 
Instance details

Defined in Plutus.V1.Ledger.Contexts

FromData TxInInfo 
Instance details

Defined in Plutus.V1.Ledger.Contexts

ToData TxInInfo 
Instance details

Defined in Plutus.V1.Ledger.Contexts

Eq TxInInfo 
Instance details

Defined in Plutus.V1.Ledger.Contexts

Methods

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

Lift DefaultUni TxInInfo 
Instance details

Defined in Plutus.V1.Ledger.Contexts

Typeable DefaultUni TxInInfo 
Instance details

Defined in Plutus.V1.Ledger.Contexts

type Rep TxInInfo 
Instance details

Defined in Plutus.V1.Ledger.Contexts

type Rep TxInInfo = D1 ('MetaData "TxInInfo" "Plutus.V1.Ledger.Contexts" "plutus-ledger-api-1.0.0.1-EUjexvcAhXiGIaLon6olWb" 'False) (C1 ('MetaCons "TxInInfo" 'PrefixI 'True) (S1 ('MetaSel ('Just "txInInfoOutRef") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 TxOutRef) :*: S1 ('MetaSel ('Just "txInInfoResolved") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 TxOut)))

data ScriptPurpose Source #

Purpose of the script that is currently running

Instances

Instances details
Eq ScriptPurpose 
Instance details

Defined in Plutus.V1.Ledger.Contexts

Ord ScriptPurpose Source # 
Instance details

Defined in Ledger.Contexts.Orphans

Show ScriptPurpose 
Instance details

Defined in Plutus.V1.Ledger.Contexts

Generic ScriptPurpose 
Instance details

Defined in Plutus.V1.Ledger.Contexts

Associated Types

type Rep ScriptPurpose :: Type -> Type Source #

Pretty ScriptPurpose 
Instance details

Defined in Plutus.V1.Ledger.Contexts

UnsafeFromData ScriptPurpose 
Instance details

Defined in Plutus.V1.Ledger.Contexts

FromData ScriptPurpose 
Instance details

Defined in Plutus.V1.Ledger.Contexts

ToData ScriptPurpose 
Instance details

Defined in Plutus.V1.Ledger.Contexts

Eq ScriptPurpose 
Instance details

Defined in Plutus.V1.Ledger.Contexts

Lift DefaultUni ScriptPurpose 
Instance details

Defined in Plutus.V1.Ledger.Contexts

Typeable DefaultUni ScriptPurpose 
Instance details

Defined in Plutus.V1.Ledger.Contexts

type Rep ScriptPurpose 
Instance details

Defined in Plutus.V1.Ledger.Contexts

data TxInfo Source #

A pending transaction. This is the view as seen by validator scripts, so some details are stripped out.

Constructors

TxInfo 

Fields

Instances

Instances details
Eq TxInfo 
Instance details

Defined in Plutus.V1.Ledger.Contexts

Show TxInfo 
Instance details

Defined in Plutus.V1.Ledger.Contexts

Generic TxInfo 
Instance details

Defined in Plutus.V1.Ledger.Contexts

Associated Types

type Rep TxInfo :: Type -> Type Source #

Pretty TxInfo 
Instance details

Defined in Plutus.V1.Ledger.Contexts

Methods

pretty :: TxInfo -> Doc ann Source #

prettyList :: [TxInfo] -> Doc ann Source #

UnsafeFromData TxInfo 
Instance details

Defined in Plutus.V1.Ledger.Contexts

FromData TxInfo 
Instance details

Defined in Plutus.V1.Ledger.Contexts

ToData TxInfo 
Instance details

Defined in Plutus.V1.Ledger.Contexts

Eq TxInfo 
Instance details

Defined in Plutus.V1.Ledger.Contexts

Methods

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

Lift DefaultUni TxInfo 
Instance details

Defined in Plutus.V1.Ledger.Contexts

Typeable DefaultUni TxInfo 
Instance details

Defined in Plutus.V1.Ledger.Contexts

type Rep TxInfo 
Instance details

Defined in Plutus.V1.Ledger.Contexts

data ScriptContext Source #

Instances

Instances details
Eq ScriptContext 
Instance details

Defined in Plutus.V1.Ledger.Contexts

Show ScriptContext 
Instance details

Defined in Plutus.V1.Ledger.Contexts

Generic ScriptContext 
Instance details

Defined in Plutus.V1.Ledger.Contexts

Associated Types

type Rep ScriptContext :: Type -> Type Source #

Pretty ScriptContext 
Instance details

Defined in Plutus.V1.Ledger.Contexts

UnsafeFromData ScriptContext 
Instance details

Defined in Plutus.V1.Ledger.Contexts

FromData ScriptContext 
Instance details

Defined in Plutus.V1.Ledger.Contexts

ToData ScriptContext 
Instance details

Defined in Plutus.V1.Ledger.Contexts

IsScriptContext ScriptContext 
Instance details

Defined in Plutus.Script.Utils.Typed

Eq ScriptContext 
Instance details

Defined in Plutus.V1.Ledger.Contexts

Lift DefaultUni ScriptContext 
Instance details

Defined in Plutus.V1.Ledger.Contexts

Typeable DefaultUni ScriptContext 
Instance details

Defined in Plutus.V1.Ledger.Contexts

type Rep ScriptContext 
Instance details

Defined in Plutus.V1.Ledger.Contexts

type Rep ScriptContext = D1 ('MetaData "ScriptContext" "Plutus.V1.Ledger.Contexts" "plutus-ledger-api-1.0.0.1-EUjexvcAhXiGIaLon6olWb" 'False) (C1 ('MetaCons "ScriptContext" 'PrefixI 'True) (S1 ('MetaSel ('Just "scriptContextTxInfo") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 TxInfo) :*: S1 ('MetaSel ('Just "scriptContextPurpose") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ScriptPurpose)))

pubKeyHashTxOut :: Value -> PubKeyHash -> TxOut Source #

Create a transaction output locked by a public key.

isPayToScriptOut :: TxOut -> Bool Source #

Whether the output is a pay-to-script output.

isPubKeyOut :: TxOut -> Bool Source #

Whether the output is a pay-to-pubkey output.

txOutDatum :: TxOut -> Maybe DatumHash Source #

The datum attached to a TxOut, if there is one.

newtype TxId Source #

A transaction ID, using a SHA256 hash as the transaction id.

Constructors

TxId 

Instances

Instances details
Eq TxId 
Instance details

Defined in Plutus.V1.Ledger.Tx

Methods

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

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

Ord TxId 
Instance details

Defined in Plutus.V1.Ledger.Tx

Show TxId 
Instance details

Defined in Plutus.V1.Ledger.Tx

IsString TxId 
Instance details

Defined in Plutus.V1.Ledger.Tx

Generic TxId 
Instance details

Defined in Plutus.V1.Ledger.Tx

Associated Types

type Rep TxId :: Type -> Type Source #

Methods

from :: TxId -> Rep TxId x Source #

to :: Rep TxId x -> TxId Source #

NFData TxId 
Instance details

Defined in Plutus.V1.Ledger.Tx

Methods

rnf :: TxId -> () Source #

ToJSON TxId Source # 
Instance details

Defined in Ledger.Tx.Orphans.V1

ToJSONKey TxId Source # 
Instance details

Defined in Ledger.Tx.Orphans.V1

FromJSON TxId Source # 
Instance details

Defined in Ledger.Tx.Orphans.V1

FromJSONKey TxId Source # 
Instance details

Defined in Ledger.Tx.Orphans.V1

ByteArrayAccess TxId Source #

ByteArrayAccess instance for signing support

Instance details

Defined in Ledger.Orphans

Methods

length :: TxId -> Int Source #

withByteArray :: TxId -> (Ptr p -> IO a) -> IO a Source #

copyByteArrayToPtr :: TxId -> Ptr p -> IO () Source #

ToSchema TxId Source # 
Instance details

Defined in Ledger.Orphans

Pretty TxId 
Instance details

Defined in Plutus.V1.Ledger.Tx

Methods

pretty :: TxId -> Doc ann Source #

prettyList :: [TxId] -> Doc ann Source #

Serialise TxId Source # 
Instance details

Defined in Ledger.Tx.Orphans.V1

UnsafeFromData TxId 
Instance details

Defined in Plutus.V1.Ledger.Tx

FromData TxId 
Instance details

Defined in Plutus.V1.Ledger.Tx

ToData TxId 
Instance details

Defined in Plutus.V1.Ledger.Tx

Ord TxId 
Instance details

Defined in Plutus.V1.Ledger.Tx

Eq TxId 
Instance details

Defined in Plutus.V1.Ledger.Tx

Methods

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

Lift DefaultUni TxId 
Instance details

Defined in Plutus.V1.Ledger.Tx

Typeable DefaultUni TxId 
Instance details

Defined in Plutus.V1.Ledger.Tx

type Rep TxId 
Instance details

Defined in Plutus.V1.Ledger.Tx

type Rep TxId = D1 ('MetaData "TxId" "Plutus.V1.Ledger.Tx" "plutus-ledger-api-1.0.0.1-EUjexvcAhXiGIaLon6olWb" 'True) (C1 ('MetaCons "TxId" 'PrefixI 'True) (S1 ('MetaSel ('Just "getTxId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 BuiltinByteString)))

data ScriptTag Source #

A tag indicating the type of script that we are pointing to.

Constructors

Spend 
Mint 
Cert 
Reward 

Instances

Instances details
Eq ScriptTag 
Instance details

Defined in Plutus.V1.Ledger.Tx

Ord ScriptTag 
Instance details

Defined in Plutus.V1.Ledger.Tx

Show ScriptTag 
Instance details

Defined in Plutus.V1.Ledger.Tx

Generic ScriptTag 
Instance details

Defined in Plutus.V1.Ledger.Tx

Associated Types

type Rep ScriptTag :: Type -> Type Source #

NFData ScriptTag 
Instance details

Defined in Plutus.V1.Ledger.Tx

Methods

rnf :: ScriptTag -> () Source #

ToJSON ScriptTag Source # 
Instance details

Defined in Ledger.Tx.Orphans.V1

FromJSON ScriptTag Source # 
Instance details

Defined in Ledger.Tx.Orphans.V1

ToSchema ScriptTag Source # 
Instance details

Defined in Ledger.Orphans

Serialise ScriptTag Source # 
Instance details

Defined in Ledger.Tx.Orphans.V1

type Rep ScriptTag 
Instance details

Defined in Plutus.V1.Ledger.Tx

type Rep ScriptTag = D1 ('MetaData "ScriptTag" "Plutus.V1.Ledger.Tx" "plutus-ledger-api-1.0.0.1-EUjexvcAhXiGIaLon6olWb" 'False) ((C1 ('MetaCons "Spend" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Mint" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Cert" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Reward" 'PrefixI 'False) (U1 :: Type -> Type)))

data RedeemerPtr Source #

A redeemer pointer is a pair of a script type tag t and an index i, picking out the ith script of type t in the transaction.

Instances

Instances details
Eq RedeemerPtr 
Instance details

Defined in Plutus.V1.Ledger.Tx

Ord RedeemerPtr 
Instance details

Defined in Plutus.V1.Ledger.Tx

Show RedeemerPtr 
Instance details

Defined in Plutus.V1.Ledger.Tx

Generic RedeemerPtr 
Instance details

Defined in Plutus.V1.Ledger.Tx

Associated Types

type Rep RedeemerPtr :: Type -> Type Source #

NFData RedeemerPtr 
Instance details

Defined in Plutus.V1.Ledger.Tx

Methods

rnf :: RedeemerPtr -> () Source #

ToJSON RedeemerPtr Source # 
Instance details

Defined in Ledger.Tx.Orphans.V1

ToJSONKey RedeemerPtr Source # 
Instance details

Defined in Ledger.Tx.Orphans.V1

FromJSON RedeemerPtr Source # 
Instance details

Defined in Ledger.Tx.Orphans.V1

FromJSONKey RedeemerPtr Source # 
Instance details

Defined in Ledger.Tx.Orphans.V1

ToSchema RedeemerPtr Source # 
Instance details

Defined in Ledger.Orphans

Serialise RedeemerPtr Source # 
Instance details

Defined in Ledger.Tx.Orphans.V1

type Rep RedeemerPtr 
Instance details

Defined in Plutus.V1.Ledger.Tx

type Rep RedeemerPtr = D1 ('MetaData "RedeemerPtr" "Plutus.V1.Ledger.Tx" "plutus-ledger-api-1.0.0.1-EUjexvcAhXiGIaLon6olWb" 'False) (C1 ('MetaCons "RedeemerPtr" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ScriptTag) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Integer)))

data TxOutRef Source #

A reference to a transaction output. This is a pair of a transaction reference, and an index indicating which of the outputs of that transaction we are referring to.

Constructors

TxOutRef 

Fields

Instances

Instances details
Eq TxOutRef 
Instance details

Defined in Plutus.V1.Ledger.Tx

Ord TxOutRef 
Instance details

Defined in Plutus.V1.Ledger.Tx

Show TxOutRef 
Instance details

Defined in Plutus.V1.Ledger.Tx

Generic TxOutRef 
Instance details

Defined in Plutus.V1.Ledger.Tx

Associated Types

type Rep TxOutRef :: Type -> Type Source #

NFData TxOutRef 
Instance details

Defined in Plutus.V1.Ledger.Tx

Methods

rnf :: TxOutRef -> () Source #

ToJSON TxOutRef Source # 
Instance details

Defined in Ledger.Tx.Orphans.V1

ToJSONKey TxOutRef Source # 
Instance details

Defined in Ledger.Tx.Orphans.V1

FromJSON TxOutRef Source # 
Instance details

Defined in Ledger.Tx.Orphans.V1

FromJSONKey TxOutRef Source # 
Instance details

Defined in Ledger.Tx.Orphans.V1

ToSchema TxOutRef Source # 
Instance details

Defined in Ledger.Orphans

Pretty TxOutRef 
Instance details

Defined in Plutus.V1.Ledger.Tx

Methods

pretty :: TxOutRef -> Doc ann Source #

prettyList :: [TxOutRef] -> Doc ann Source #

Serialise TxOutRef Source # 
Instance details

Defined in Ledger.Tx.Orphans.V1

UnsafeFromData TxOutRef 
Instance details

Defined in Plutus.V1.Ledger.Tx

FromData TxOutRef 
Instance details

Defined in Plutus.V1.Ledger.Tx

ToData TxOutRef 
Instance details

Defined in Plutus.V1.Ledger.Tx

Eq TxOutRef 
Instance details

Defined in Plutus.V1.Ledger.Tx

Methods

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

Lift DefaultUni TxOutRef 
Instance details

Defined in Plutus.V1.Ledger.Tx

Typeable DefaultUni TxOutRef 
Instance details

Defined in Plutus.V1.Ledger.Tx

type Rep TxOutRef 
Instance details

Defined in Plutus.V1.Ledger.Tx

type Rep TxOutRef = D1 ('MetaData "TxOutRef" "Plutus.V1.Ledger.Tx" "plutus-ledger-api-1.0.0.1-EUjexvcAhXiGIaLon6olWb" 'False) (C1 ('MetaCons "TxOutRef" 'PrefixI 'True) (S1 ('MetaSel ('Just "txOutRefId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 TxId) :*: S1 ('MetaSel ('Just "txOutRefIdx") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Integer)))

stakingCredential :: Address -> Maybe StakingCredential Source #

The staking credential of an address (if any)

scriptHashAddress :: ValidatorHash -> Address Source #

The address that should be used by a transaction output locked by the given validator script hash.

toValidatorHash :: Address -> Maybe ValidatorHash Source #

The validator hash of the address, if any

toPubKeyHash :: Address -> Maybe PubKeyHash Source #

The PubKeyHash of the address, if any

data Address Source #

Address with two kinds of credentials, normal and staking.

Instances

Instances details
Eq Address 
Instance details

Defined in Plutus.V1.Ledger.Address

Ord Address 
Instance details

Defined in Plutus.V1.Ledger.Address

Show Address 
Instance details

Defined in Plutus.V1.Ledger.Address

Generic Address 
Instance details

Defined in Plutus.V1.Ledger.Address

Associated Types

type Rep Address :: Type -> Type Source #

NFData Address 
Instance details

Defined in Plutus.V1.Ledger.Address

Methods

rnf :: Address -> () Source #

ToJSON Address Source # 
Instance details

Defined in Ledger.Address.Orphans

FromJSON Address Source # 
Instance details

Defined in Ledger.Address.Orphans

ToSchema Address Source # 
Instance details

Defined in Ledger.Address.Orphans

Pretty Address 
Instance details

Defined in Plutus.V1.Ledger.Address

Methods

pretty :: Address -> Doc ann Source #

prettyList :: [Address] -> Doc ann Source #

Serialise Address Source # 
Instance details

Defined in Ledger.Address.Orphans

UnsafeFromData Address 
Instance details

Defined in Plutus.V1.Ledger.Address

FromData Address 
Instance details

Defined in Plutus.V1.Ledger.Address

ToData Address 
Instance details

Defined in Plutus.V1.Ledger.Address

Eq Address 
Instance details

Defined in Plutus.V1.Ledger.Address

Methods

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

Lift DefaultUni Address 
Instance details

Defined in Plutus.V1.Ledger.Address

Typeable DefaultUni Address 
Instance details

Defined in Plutus.V1.Ledger.Address

type Rep Address 
Instance details

Defined in Plutus.V1.Ledger.Address

type Rep Address = D1 ('MetaData "Address" "Plutus.V1.Ledger.Address" "plutus-ledger-api-1.0.0.1-EUjexvcAhXiGIaLon6olWb" 'False) (C1 ('MetaCons "Address" 'PrefixI 'True) (S1 ('MetaSel ('Just "addressCredential") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Credential) :*: S1 ('MetaSel ('Just "addressStakingCredential") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe StakingCredential))))

newtype PubKeyHash Source #

The hash of a public key. This is frequently used to identify the public key, rather than the key itself.

Instances

Instances details
Eq PubKeyHash 
Instance details

Defined in Plutus.V1.Ledger.Crypto

Ord PubKeyHash 
Instance details

Defined in Plutus.V1.Ledger.Crypto

Show PubKeyHash 
Instance details

Defined in Plutus.V1.Ledger.Crypto

IsString PubKeyHash 
Instance details

Defined in Plutus.V1.Ledger.Crypto

Generic PubKeyHash 
Instance details

Defined in Plutus.V1.Ledger.Crypto

Associated Types

type Rep PubKeyHash :: Type -> Type Source #

NFData PubKeyHash 
Instance details

Defined in Plutus.V1.Ledger.Crypto

Methods

rnf :: PubKeyHash -> () Source #

Hashable PubKeyHash Source # 
Instance details

Defined in Ledger.Crypto.Orphans

ToJSON PubKeyHash Source # 
Instance details

Defined in Ledger.Crypto.Orphans

ToJSONKey PubKeyHash Source # 
Instance details

Defined in Ledger.Crypto.Orphans

FromJSON PubKeyHash Source # 
Instance details

Defined in Ledger.Crypto.Orphans

FromJSONKey PubKeyHash Source # 
Instance details

Defined in Ledger.Crypto.Orphans

Newtype PubKeyHash Source # 
Instance details

Defined in Ledger.Crypto.Orphans

Associated Types

type O PubKeyHash Source #

ToSchema PubKeyHash Source # 
Instance details

Defined in Ledger.Crypto.Orphans

Pretty PubKeyHash 
Instance details

Defined in Plutus.V1.Ledger.Crypto

Serialise PubKeyHash Source # 
Instance details

Defined in Ledger.Crypto.Orphans

UnsafeFromData PubKeyHash 
Instance details

Defined in Plutus.V1.Ledger.Crypto

FromData PubKeyHash 
Instance details

Defined in Plutus.V1.Ledger.Crypto

ToData PubKeyHash 
Instance details

Defined in Plutus.V1.Ledger.Crypto

Ord PubKeyHash 
Instance details

Defined in Plutus.V1.Ledger.Crypto

Eq PubKeyHash 
Instance details

Defined in Plutus.V1.Ledger.Crypto

Lift DefaultUni PubKeyHash 
Instance details

Defined in Plutus.V1.Ledger.Crypto

Typeable DefaultUni PubKeyHash 
Instance details

Defined in Plutus.V1.Ledger.Crypto

type Rep PubKeyHash 
Instance details

Defined in Plutus.V1.Ledger.Crypto

type Rep PubKeyHash = D1 ('MetaData "PubKeyHash" "Plutus.V1.Ledger.Crypto" "plutus-ledger-api-1.0.0.1-EUjexvcAhXiGIaLon6olWb" 'True) (C1 ('MetaCons "PubKeyHash" 'PrefixI 'True) (S1 ('MetaSel ('Just "getPubKeyHash") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 BuiltinByteString)))
type O PubKeyHash Source # 
Instance details

Defined in Ledger.Crypto.Orphans

unitRedeemer :: Redeemer Source #

() as a redeemer.

unitDatum :: Datum Source #

() as a datum.

runMintingPolicyScript :: MonadError ScriptError m => Context -> MintingPolicy -> Redeemer -> m (ExBudget, [Text]) Source #

Evaluate a MintingPolicy with its Context and Redeemer, returning the log.

runScript :: MonadError ScriptError m => Context -> Validator -> Datum -> Redeemer -> m (ExBudget, [Text]) Source #

Evaluate a Validator with its Context, Datum, and Redeemer, returning the log.

evaluateScript :: MonadError ScriptError m => Script -> m (ExBudget, [Text]) Source #

Evaluate a script, returning the trace log.

fromCompiledCode :: CompiledCode a -> Script Source #

Turn a CompiledCode (usually produced by compile) into a Script for use with this package.

scriptSize :: Script -> Integer Source #

The size of a Script. No particular interpretation is given to this, other than that it is proportional to the serialized size of the script.

newtype Script Source #

A script on the chain. This is an opaque type as far as the chain is concerned.

Instances

Instances details
Eq Script

Note [Using Flat inside CBOR instance of Script] `plutus-ledger` uses CBOR for data serialisation and `plutus-core` uses Flat. The choice to use Flat was made to have a more efficient (most wins are in uncompressed size) data serialisation format and use less space on-chain.

To make `plutus-ledger` work with scripts serialised with Flat, and keep the CBOR format otherwise we have defined a Serialise instance for Script, which is a wrapper over Programs serialised with Flat. The instance will see programs as an opaque ByteString, which is the result of encoding programs using Flat.

Because Flat is not self-describing and it gets used in the encoding of Programs, data structures that include scripts (for example, transactions) no-longer benefit for CBOR's ability to self-describe it's format.

Instance details

Defined in Plutus.V1.Ledger.Scripts

Ord Script 
Instance details

Defined in Plutus.V1.Ledger.Scripts

Show Script 
Instance details

Defined in Plutus.V1.Ledger.Scripts

Generic Script 
Instance details

Defined in Plutus.V1.Ledger.Scripts

Associated Types

type Rep Script :: Type -> Type Source #

NFData Script 
Instance details

Defined in Plutus.V1.Ledger.Scripts

Methods

rnf :: Script -> () Source #

ToJSON Script Source # 
Instance details

Defined in Ledger.Scripts.Orphans

FromJSON Script Source # 
Instance details

Defined in Ledger.Scripts.Orphans

ToSchema Script Source # 
Instance details

Defined in Ledger.Orphans

Serialise Script 
Instance details

Defined in Plutus.V1.Ledger.Scripts

type Rep Script 
Instance details

Defined in Plutus.V1.Ledger.Scripts

type Rep Script = D1 ('MetaData "Script" "Plutus.V1.Ledger.Scripts" "plutus-ledger-api-1.0.0.1-EUjexvcAhXiGIaLon6olWb" 'True) (C1 ('MetaCons "Script" 'PrefixI 'True) (S1 ('MetaSel ('Just "unScript") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Program DeBruijn DefaultUni DefaultFun ()))))

data ScriptError Source #

Constructors

EvaluationError [Text] String

Expected behavior of the engine (e.g. user-provided error)

EvaluationException String String

Unexpected behavior of the engine (a bug)

Instances

Instances details
Eq ScriptError 
Instance details

Defined in Plutus.V1.Ledger.Scripts

Show ScriptError 
Instance details

Defined in Plutus.V1.Ledger.Scripts

Generic ScriptError 
Instance details

Defined in Plutus.V1.Ledger.Scripts

Associated Types

type Rep ScriptError :: Type -> Type Source #

NFData ScriptError 
Instance details

Defined in Plutus.V1.Ledger.Scripts

Methods

rnf :: ScriptError -> () Source #

ToJSON ScriptError Source # 
Instance details

Defined in Ledger.Orphans

FromJSON ScriptError Source # 
Instance details

Defined in Ledger.Orphans

type Rep ScriptError 
Instance details

Defined in Plutus.V1.Ledger.Scripts

newtype Validator Source #

Validator is a wrapper around Scripts which are used as validators in transaction outputs.

Constructors

Validator 

Fields

Instances

Instances details
Eq Validator 
Instance details

Defined in Plutus.V1.Ledger.Scripts

Ord Validator 
Instance details

Defined in Plutus.V1.Ledger.Scripts

Show Validator 
Instance details

Defined in Plutus.V1.Ledger.Scripts

Generic Validator 
Instance details

Defined in Plutus.V1.Ledger.Scripts

Associated Types

type Rep Validator :: Type -> Type Source #

NFData Validator 
Instance details

Defined in Plutus.V1.Ledger.Scripts

Methods

rnf :: Validator -> () Source #

ToJSON Validator Source # 
Instance details

Defined in Ledger.Scripts.Orphans

FromJSON Validator Source # 
Instance details

Defined in Ledger.Scripts.Orphans

ToSchema Validator Source # 
Instance details

Defined in Ledger.Orphans

Pretty Validator 
Instance details

Defined in Plutus.V1.Ledger.Scripts

Methods

pretty :: Validator -> Doc ann Source #

prettyList :: [Validator] -> Doc ann Source #

Serialise Validator 
Instance details

Defined in Plutus.V1.Ledger.Scripts

type Rep Validator 
Instance details

Defined in Plutus.V1.Ledger.Scripts

type Rep Validator = D1 ('MetaData "Validator" "Plutus.V1.Ledger.Scripts" "plutus-ledger-api-1.0.0.1-EUjexvcAhXiGIaLon6olWb" 'True) (C1 ('MetaCons "Validator" 'PrefixI 'True) (S1 ('MetaSel ('Just "getValidator") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Script)))

newtype Datum Source #

Datum is a wrapper around Data values which are used as data in transaction outputs.

Constructors

Datum 

Instances

Instances details
Eq Datum 
Instance details

Defined in Plutus.V1.Ledger.Scripts

Methods

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

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

Ord Datum 
Instance details

Defined in Plutus.V1.Ledger.Scripts

Show Datum 
Instance details

Defined in Plutus.V1.Ledger.Scripts

Generic Datum 
Instance details

Defined in Plutus.V1.Ledger.Scripts

Associated Types

type Rep Datum :: Type -> Type Source #

Methods

from :: Datum -> Rep Datum x Source #

to :: Rep Datum x -> Datum Source #

NFData Datum 
Instance details

Defined in Plutus.V1.Ledger.Scripts

Methods

rnf :: Datum -> () Source #

ToJSON Datum Source # 
Instance details

Defined in Ledger.Scripts.Orphans

FromJSON Datum Source # 
Instance details

Defined in Ledger.Scripts.Orphans

ToSchema Datum Source # 
Instance details

Defined in Ledger.Scripts.Orphans

Pretty Datum 
Instance details

Defined in Plutus.V1.Ledger.Scripts

Methods

pretty :: Datum -> Doc ann Source #

prettyList :: [Datum] -> Doc ann Source #

Serialise Datum Source # 
Instance details

Defined in Ledger.Scripts.Orphans

UnsafeFromData Datum 
Instance details

Defined in Plutus.V1.Ledger.Scripts

FromData Datum 
Instance details

Defined in Plutus.V1.Ledger.Scripts

ToData Datum 
Instance details

Defined in Plutus.V1.Ledger.Scripts

Eq Datum 
Instance details

Defined in Plutus.V1.Ledger.Scripts

Methods

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

Lift DefaultUni Datum 
Instance details

Defined in Plutus.V1.Ledger.Scripts

Typeable DefaultUni Datum 
Instance details

Defined in Plutus.V1.Ledger.Scripts

type Rep Datum 
Instance details

Defined in Plutus.V1.Ledger.Scripts

type Rep Datum = D1 ('MetaData "Datum" "Plutus.V1.Ledger.Scripts" "plutus-ledger-api-1.0.0.1-EUjexvcAhXiGIaLon6olWb" 'True) (C1 ('MetaCons "Datum" 'PrefixI 'True) (S1 ('MetaSel ('Just "getDatum") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 BuiltinData)))

newtype Redeemer Source #

Redeemer is a wrapper around Data values that are used as redeemers in transaction inputs.

Constructors

Redeemer 

Instances

Instances details
Eq Redeemer 
Instance details

Defined in Plutus.V1.Ledger.Scripts

Ord Redeemer 
Instance details

Defined in Plutus.V1.Ledger.Scripts

Show Redeemer 
Instance details

Defined in Plutus.V1.Ledger.Scripts

Generic Redeemer 
Instance details

Defined in Plutus.V1.Ledger.Scripts

Associated Types

type Rep Redeemer :: Type -> Type Source #

NFData Redeemer 
Instance details

Defined in Plutus.V1.Ledger.Scripts

Methods

rnf :: Redeemer -> () Source #

ToJSON Redeemer Source # 
Instance details

Defined in Ledger.Scripts.Orphans

FromJSON Redeemer Source # 
Instance details

Defined in Ledger.Scripts.Orphans

ToSchema Redeemer Source # 
Instance details

Defined in Ledger.Orphans

Pretty Redeemer 
Instance details

Defined in Plutus.V1.Ledger.Scripts

Methods

pretty :: Redeemer -> Doc ann Source #

prettyList :: [Redeemer] -> Doc ann Source #

Serialise Redeemer Source # 
Instance details

Defined in Ledger.Scripts.Orphans

UnsafeFromData Redeemer 
Instance details

Defined in Plutus.V1.Ledger.Scripts

FromData Redeemer 
Instance details

Defined in Plutus.V1.Ledger.Scripts

ToData Redeemer 
Instance details

Defined in Plutus.V1.Ledger.Scripts

Eq Redeemer 
Instance details

Defined in Plutus.V1.Ledger.Scripts

Methods

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

Lift DefaultUni Redeemer 
Instance details

Defined in Plutus.V1.Ledger.Scripts

Typeable DefaultUni Redeemer 
Instance details

Defined in Plutus.V1.Ledger.Scripts

type Rep Redeemer 
Instance details

Defined in Plutus.V1.Ledger.Scripts

type Rep Redeemer = D1 ('MetaData "Redeemer" "Plutus.V1.Ledger.Scripts" "plutus-ledger-api-1.0.0.1-EUjexvcAhXiGIaLon6olWb" 'True) (C1 ('MetaCons "Redeemer" 'PrefixI 'True) (S1 ('MetaSel ('Just "getRedeemer") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 BuiltinData)))

newtype MintingPolicy Source #

MintingPolicy is a wrapper around Scripts which are used as validators for minting constraints.

Constructors

MintingPolicy 

Instances

Instances details
Eq MintingPolicy 
Instance details

Defined in Plutus.V1.Ledger.Scripts

Ord MintingPolicy 
Instance details

Defined in Plutus.V1.Ledger.Scripts

Show MintingPolicy 
Instance details

Defined in Plutus.V1.Ledger.Scripts

Generic MintingPolicy 
Instance details

Defined in Plutus.V1.Ledger.Scripts

Associated Types

type Rep MintingPolicy :: Type -> Type Source #

NFData MintingPolicy 
Instance details

Defined in Plutus.V1.Ledger.Scripts

Methods

rnf :: MintingPolicy -> () Source #

ToJSON MintingPolicy Source # 
Instance details

Defined in Ledger.Scripts.Orphans

FromJSON MintingPolicy Source # 
Instance details

Defined in Ledger.Scripts.Orphans

ToSchema MintingPolicy Source # 
Instance details

Defined in Ledger.Orphans

Pretty MintingPolicy 
Instance details

Defined in Plutus.V1.Ledger.Scripts

Serialise MintingPolicy 
Instance details

Defined in Plutus.V1.Ledger.Scripts

type Rep MintingPolicy 
Instance details

Defined in Plutus.V1.Ledger.Scripts

type Rep MintingPolicy = D1 ('MetaData "MintingPolicy" "Plutus.V1.Ledger.Scripts" "plutus-ledger-api-1.0.0.1-EUjexvcAhXiGIaLon6olWb" 'True) (C1 ('MetaCons "MintingPolicy" 'PrefixI 'True) (S1 ('MetaSel ('Just "getMintingPolicy") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Script)))

newtype StakeValidator Source #

StakeValidator is a wrapper around Scripts which are used as validators for withdrawals and stake address certificates.

Constructors

StakeValidator 

Instances

Instances details
Eq StakeValidator 
Instance details

Defined in Plutus.V1.Ledger.Scripts

Ord StakeValidator 
Instance details

Defined in Plutus.V1.Ledger.Scripts

Show StakeValidator 
Instance details

Defined in Plutus.V1.Ledger.Scripts

Generic StakeValidator 
Instance details

Defined in Plutus.V1.Ledger.Scripts

Associated Types

type Rep StakeValidator :: Type -> Type Source #

NFData StakeValidator 
Instance details

Defined in Plutus.V1.Ledger.Scripts

Methods

rnf :: StakeValidator -> () Source #

ToJSON StakeValidator Source # 
Instance details

Defined in Ledger.Scripts.Orphans

FromJSON StakeValidator Source # 
Instance details

Defined in Ledger.Scripts.Orphans

ToSchema StakeValidator Source # 
Instance details

Defined in Ledger.Orphans

Pretty StakeValidator 
Instance details

Defined in Plutus.V1.Ledger.Scripts

Serialise StakeValidator 
Instance details

Defined in Plutus.V1.Ledger.Scripts

type Rep StakeValidator 
Instance details

Defined in Plutus.V1.Ledger.Scripts

type Rep StakeValidator = D1 ('MetaData "StakeValidator" "Plutus.V1.Ledger.Scripts" "plutus-ledger-api-1.0.0.1-EUjexvcAhXiGIaLon6olWb" 'True) (C1 ('MetaCons "StakeValidator" 'PrefixI 'True) (S1 ('MetaSel ('Just "getStakeValidator") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Script)))

newtype ScriptHash Source #

Script runtime representation of a Digest SHA256.

Instances

Instances details
Eq ScriptHash 
Instance details

Defined in Plutus.V1.Ledger.Scripts

Ord ScriptHash 
Instance details

Defined in Plutus.V1.Ledger.Scripts

Show ScriptHash 
Instance details

Defined in Plutus.V1.Ledger.Scripts

IsString ScriptHash 
Instance details

Defined in Plutus.V1.Ledger.Scripts

Generic ScriptHash 
Instance details

Defined in Plutus.V1.Ledger.Scripts

Associated Types

type Rep ScriptHash :: Type -> Type Source #

NFData ScriptHash 
Instance details

Defined in Plutus.V1.Ledger.Scripts

Methods

rnf :: ScriptHash -> () Source #

Hashable ScriptHash Source # 
Instance details

Defined in Ledger.Scripts.Orphans

ToJSON ScriptHash Source # 
Instance details

Defined in Ledger.Scripts.Orphans

ToJSONKey ScriptHash Source # 
Instance details

Defined in Ledger.Scripts.Orphans

FromJSON ScriptHash Source # 
Instance details

Defined in Ledger.Scripts.Orphans

FromJSONKey ScriptHash Source # 
Instance details

Defined in Ledger.Scripts.Orphans

ToSchema ScriptHash Source # 
Instance details

Defined in Ledger.Orphans

Pretty ScriptHash 
Instance details

Defined in Plutus.V1.Ledger.Scripts

Serialise ScriptHash Source # 
Instance details

Defined in Ledger.Scripts.Orphans

UnsafeFromData ScriptHash 
Instance details

Defined in Plutus.V1.Ledger.Scripts

FromData ScriptHash 
Instance details

Defined in Plutus.V1.Ledger.Scripts

ToData ScriptHash 
Instance details

Defined in Plutus.V1.Ledger.Scripts

Ord ScriptHash 
Instance details

Defined in Plutus.V1.Ledger.Scripts

Eq ScriptHash 
Instance details

Defined in Plutus.V1.Ledger.Scripts

Lift DefaultUni ScriptHash 
Instance details

Defined in Plutus.V1.Ledger.Scripts

Typeable DefaultUni ScriptHash 
Instance details

Defined in Plutus.V1.Ledger.Scripts

type Rep ScriptHash 
Instance details

Defined in Plutus.V1.Ledger.Scripts

type Rep ScriptHash = D1 ('MetaData "ScriptHash" "Plutus.V1.Ledger.Scripts" "plutus-ledger-api-1.0.0.1-EUjexvcAhXiGIaLon6olWb" 'True) (C1 ('MetaCons "ScriptHash" 'PrefixI 'True) (S1 ('MetaSel ('Just "getScriptHash") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 BuiltinByteString)))

newtype ValidatorHash Source #

Script runtime representation of a Digest SHA256.

Instances

Instances details
Eq ValidatorHash 
Instance details

Defined in Plutus.V1.Ledger.Scripts

Ord ValidatorHash 
Instance details

Defined in Plutus.V1.Ledger.Scripts

Show ValidatorHash 
Instance details

Defined in Plutus.V1.Ledger.Scripts

IsString ValidatorHash 
Instance details

Defined in Plutus.V1.Ledger.Scripts

Generic ValidatorHash 
Instance details

Defined in Plutus.V1.Ledger.Scripts

Associated Types

type Rep ValidatorHash :: Type -> Type Source #

NFData ValidatorHash 
Instance details

Defined in Plutus.V1.Ledger.Scripts

Methods

rnf :: ValidatorHash -> () Source #

Hashable ValidatorHash Source # 
Instance details

Defined in Ledger.Scripts.Orphans

ToJSON ValidatorHash Source # 
Instance details

Defined in Ledger.Scripts.Orphans

ToJSONKey ValidatorHash Source # 
Instance details

Defined in Ledger.Scripts.Orphans

FromJSON ValidatorHash Source # 
Instance details

Defined in Ledger.Scripts.Orphans

FromJSONKey ValidatorHash Source # 
Instance details

Defined in Ledger.Scripts.Orphans

ToSchema ValidatorHash Source # 
Instance details

Defined in Ledger.Scripts.Orphans

Pretty ValidatorHash 
Instance details

Defined in Plutus.V1.Ledger.Scripts

Serialise ValidatorHash Source # 
Instance details

Defined in Ledger.Scripts.Orphans

UnsafeFromData ValidatorHash 
Instance details

Defined in Plutus.V1.Ledger.Scripts

FromData ValidatorHash 
Instance details

Defined in Plutus.V1.Ledger.Scripts

ToData ValidatorHash 
Instance details

Defined in Plutus.V1.Ledger.Scripts

Ord ValidatorHash 
Instance details

Defined in Plutus.V1.Ledger.Scripts

Eq ValidatorHash 
Instance details

Defined in Plutus.V1.Ledger.Scripts

Lift DefaultUni ValidatorHash 
Instance details

Defined in Plutus.V1.Ledger.Scripts

Typeable DefaultUni ValidatorHash 
Instance details

Defined in Plutus.V1.Ledger.Scripts

type Rep ValidatorHash 
Instance details

Defined in Plutus.V1.Ledger.Scripts

type Rep ValidatorHash = D1 ('MetaData "ValidatorHash" "Plutus.V1.Ledger.Scripts" "plutus-ledger-api-1.0.0.1-EUjexvcAhXiGIaLon6olWb" 'True) (C1 ('MetaCons "ValidatorHash" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 BuiltinByteString)))

newtype DatumHash Source #

Script runtime representation of a Digest SHA256.

Instances

Instances details
Eq DatumHash 
Instance details

Defined in Plutus.V1.Ledger.Scripts

Ord DatumHash 
Instance details

Defined in Plutus.V1.Ledger.Scripts

Show DatumHash 
Instance details

Defined in Plutus.V1.Ledger.Scripts

IsString DatumHash 
Instance details

Defined in Plutus.V1.Ledger.Scripts

Generic DatumHash 
Instance details

Defined in Plutus.V1.Ledger.Scripts

Associated Types

type Rep DatumHash :: Type -> Type Source #

NFData DatumHash 
Instance details

Defined in Plutus.V1.Ledger.Scripts

Methods

rnf :: DatumHash -> () Source #

Hashable DatumHash Source # 
Instance details

Defined in Ledger.Scripts.Orphans

ToJSON DatumHash Source # 
Instance details

Defined in Ledger.Scripts.Orphans

ToJSONKey DatumHash Source # 
Instance details

Defined in Ledger.Scripts.Orphans

FromJSON DatumHash Source # 
Instance details

Defined in Ledger.Scripts.Orphans

FromJSONKey DatumHash Source # 
Instance details

Defined in Ledger.Scripts.Orphans

ToSchema DatumHash Source # 
Instance details

Defined in Ledger.Scripts.Orphans

Pretty DatumHash 
Instance details

Defined in Plutus.V1.Ledger.Scripts

Methods

pretty :: DatumHash -> Doc ann Source #

prettyList :: [DatumHash] -> Doc ann Source #

Serialise DatumHash Source # 
Instance details

Defined in Ledger.Scripts.Orphans

UnsafeFromData DatumHash 
Instance details

Defined in Plutus.V1.Ledger.Scripts

FromData DatumHash 
Instance details

Defined in Plutus.V1.Ledger.Scripts

ToData DatumHash 
Instance details

Defined in Plutus.V1.Ledger.Scripts

Ord DatumHash 
Instance details

Defined in Plutus.V1.Ledger.Scripts

Eq DatumHash 
Instance details

Defined in Plutus.V1.Ledger.Scripts

Lift DefaultUni DatumHash 
Instance details

Defined in Plutus.V1.Ledger.Scripts

Typeable DefaultUni DatumHash 
Instance details

Defined in Plutus.V1.Ledger.Scripts

type Rep DatumHash 
Instance details

Defined in Plutus.V1.Ledger.Scripts

type Rep DatumHash = D1 ('MetaData "DatumHash" "Plutus.V1.Ledger.Scripts" "plutus-ledger-api-1.0.0.1-EUjexvcAhXiGIaLon6olWb" 'True) (C1 ('MetaCons "DatumHash" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 BuiltinByteString)))

newtype RedeemerHash Source #

Script runtime representation of a Digest SHA256.

Instances

Instances details
Eq RedeemerHash 
Instance details

Defined in Plutus.V1.Ledger.Scripts

Ord RedeemerHash 
Instance details

Defined in Plutus.V1.Ledger.Scripts

Show RedeemerHash 
Instance details

Defined in Plutus.V1.Ledger.Scripts

IsString RedeemerHash 
Instance details

Defined in Plutus.V1.Ledger.Scripts

Generic RedeemerHash 
Instance details

Defined in Plutus.V1.Ledger.Scripts

Associated Types

type Rep RedeemerHash :: Type -> Type Source #

NFData RedeemerHash 
Instance details

Defined in Plutus.V1.Ledger.Scripts

Methods

rnf :: RedeemerHash -> () Source #

Hashable RedeemerHash Source # 
Instance details

Defined in Ledger.Scripts.Orphans

ToJSON RedeemerHash Source # 
Instance details

Defined in Ledger.Scripts.Orphans

ToJSONKey RedeemerHash Source # 
Instance details

Defined in Ledger.Scripts.Orphans

FromJSON RedeemerHash Source # 
Instance details

Defined in Ledger.Scripts.Orphans

FromJSONKey RedeemerHash Source # 
Instance details

Defined in Ledger.Scripts.Orphans

ToSchema RedeemerHash Source # 
Instance details

Defined in Ledger.Orphans

Pretty RedeemerHash 
Instance details

Defined in Plutus.V1.Ledger.Scripts

Serialise RedeemerHash Source # 
Instance details

Defined in Ledger.Scripts.Orphans

UnsafeFromData RedeemerHash 
Instance details

Defined in Plutus.V1.Ledger.Scripts

FromData RedeemerHash 
Instance details

Defined in Plutus.V1.Ledger.Scripts

ToData RedeemerHash 
Instance details

Defined in Plutus.V1.Ledger.Scripts

Ord RedeemerHash 
Instance details

Defined in Plutus.V1.Ledger.Scripts

Eq RedeemerHash 
Instance details

Defined in Plutus.V1.Ledger.Scripts

Lift DefaultUni RedeemerHash 
Instance details

Defined in Plutus.V1.Ledger.Scripts

Typeable DefaultUni RedeemerHash 
Instance details

Defined in Plutus.V1.Ledger.Scripts

type Rep RedeemerHash 
Instance details

Defined in Plutus.V1.Ledger.Scripts

type Rep RedeemerHash = D1 ('MetaData "RedeemerHash" "Plutus.V1.Ledger.Scripts" "plutus-ledger-api-1.0.0.1-EUjexvcAhXiGIaLon6olWb" 'True) (C1 ('MetaCons "RedeemerHash" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 BuiltinByteString)))

newtype MintingPolicyHash Source #

Script runtime representation of a Digest SHA256.

Instances

Instances details
Eq MintingPolicyHash 
Instance details

Defined in Plutus.V1.Ledger.Scripts

Ord MintingPolicyHash 
Instance details

Defined in Plutus.V1.Ledger.Scripts

Show MintingPolicyHash 
Instance details

Defined in Plutus.V1.Ledger.Scripts

IsString MintingPolicyHash 
Instance details

Defined in Plutus.V1.Ledger.Scripts

Generic MintingPolicyHash 
Instance details

Defined in Plutus.V1.Ledger.Scripts

Associated Types

type Rep MintingPolicyHash :: Type -> Type Source #

NFData MintingPolicyHash 
Instance details

Defined in Plutus.V1.Ledger.Scripts

Methods

rnf :: MintingPolicyHash -> () Source #

Hashable MintingPolicyHash Source # 
Instance details

Defined in Ledger.Scripts.Orphans

ToJSON MintingPolicyHash Source # 
Instance details

Defined in Ledger.Scripts.Orphans

ToJSONKey MintingPolicyHash Source # 
Instance details

Defined in Ledger.Scripts.Orphans

FromJSON MintingPolicyHash Source # 
Instance details

Defined in Ledger.Scripts.Orphans

FromJSONKey MintingPolicyHash Source # 
Instance details

Defined in Ledger.Scripts.Orphans

ToSchema MintingPolicyHash Source # 
Instance details

Defined in Ledger.Orphans

Pretty MintingPolicyHash 
Instance details

Defined in Plutus.V1.Ledger.Scripts

Serialise MintingPolicyHash Source # 
Instance details

Defined in Ledger.Scripts.Orphans

UnsafeFromData MintingPolicyHash 
Instance details

Defined in Plutus.V1.Ledger.Scripts

FromData MintingPolicyHash 
Instance details

Defined in Plutus.V1.Ledger.Scripts

ToData MintingPolicyHash 
Instance details

Defined in Plutus.V1.Ledger.Scripts

Ord MintingPolicyHash 
Instance details

Defined in Plutus.V1.Ledger.Scripts

Eq MintingPolicyHash 
Instance details

Defined in Plutus.V1.Ledger.Scripts

Lift DefaultUni MintingPolicyHash 
Instance details

Defined in Plutus.V1.Ledger.Scripts

Typeable DefaultUni MintingPolicyHash 
Instance details

Defined in Plutus.V1.Ledger.Scripts

type Rep MintingPolicyHash 
Instance details

Defined in Plutus.V1.Ledger.Scripts

type Rep MintingPolicyHash = D1 ('MetaData "MintingPolicyHash" "Plutus.V1.Ledger.Scripts" "plutus-ledger-api-1.0.0.1-EUjexvcAhXiGIaLon6olWb" 'True) (C1 ('MetaCons "MintingPolicyHash" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 BuiltinByteString)))

newtype StakeValidatorHash Source #

Script runtime representation of a Digest SHA256.

Instances

Instances details
Eq StakeValidatorHash 
Instance details

Defined in Plutus.V1.Ledger.Scripts

Ord StakeValidatorHash 
Instance details

Defined in Plutus.V1.Ledger.Scripts

Show StakeValidatorHash 
Instance details

Defined in Plutus.V1.Ledger.Scripts

IsString StakeValidatorHash 
Instance details

Defined in Plutus.V1.Ledger.Scripts

Generic StakeValidatorHash 
Instance details

Defined in Plutus.V1.Ledger.Scripts

Associated Types

type Rep StakeValidatorHash :: Type -> Type Source #

NFData StakeValidatorHash 
Instance details

Defined in Plutus.V1.Ledger.Scripts

Methods

rnf :: StakeValidatorHash -> () Source #

Hashable StakeValidatorHash Source # 
Instance details

Defined in Ledger.Scripts.Orphans

ToJSON StakeValidatorHash Source # 
Instance details

Defined in Ledger.Scripts.Orphans

ToJSONKey StakeValidatorHash Source # 
Instance details

Defined in Ledger.Scripts.Orphans

FromJSON StakeValidatorHash Source # 
Instance details

Defined in Ledger.Scripts.Orphans

FromJSONKey StakeValidatorHash Source # 
Instance details

Defined in Ledger.Scripts.Orphans

ToSchema StakeValidatorHash Source # 
Instance details

Defined in Ledger.Scripts.Orphans

Pretty StakeValidatorHash 
Instance details

Defined in Plutus.V1.Ledger.Scripts

Serialise StakeValidatorHash Source # 
Instance details

Defined in Ledger.Scripts.Orphans

UnsafeFromData StakeValidatorHash 
Instance details

Defined in Plutus.V1.Ledger.Scripts

FromData StakeValidatorHash 
Instance details

Defined in Plutus.V1.Ledger.Scripts

ToData StakeValidatorHash 
Instance details

Defined in Plutus.V1.Ledger.Scripts

Ord StakeValidatorHash 
Instance details

Defined in Plutus.V1.Ledger.Scripts

Eq StakeValidatorHash 
Instance details

Defined in Plutus.V1.Ledger.Scripts

Lift DefaultUni StakeValidatorHash 
Instance details

Defined in Plutus.V1.Ledger.Scripts

Typeable DefaultUni StakeValidatorHash 
Instance details

Defined in Plutus.V1.Ledger.Scripts

type Rep StakeValidatorHash 
Instance details

Defined in Plutus.V1.Ledger.Scripts

type Rep StakeValidatorHash = D1 ('MetaData "StakeValidatorHash" "Plutus.V1.Ledger.Scripts" "plutus-ledger-api-1.0.0.1-EUjexvcAhXiGIaLon6olWb" 'True) (C1 ('MetaCons "StakeValidatorHash" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 BuiltinByteString)))

newtype Context Source #

Information about the state of the blockchain and about the transaction that is currently being validated, represented as a value in Data.

Constructors

Context BuiltinData 

newtype POSIXTime Source #

POSIX time is measured as the number of milliseconds since 1970-01-01T00:00:00Z

Constructors

POSIXTime 

Instances

Instances details
Enum POSIXTime 
Instance details

Defined in Plutus.V1.Ledger.Time

Eq POSIXTime 
Instance details

Defined in Plutus.V1.Ledger.Time

Integral POSIXTime 
Instance details

Defined in Plutus.V1.Ledger.Time

Num POSIXTime 
Instance details

Defined in Plutus.V1.Ledger.Time

Ord POSIXTime 
Instance details

Defined in Plutus.V1.Ledger.Time

Real POSIXTime 
Instance details

Defined in Plutus.V1.Ledger.Time

Show POSIXTime 
Instance details

Defined in Plutus.V1.Ledger.Time

Generic POSIXTime 
Instance details

Defined in Plutus.V1.Ledger.Time

Associated Types

type Rep POSIXTime :: Type -> Type Source #

NFData POSIXTime 
Instance details

Defined in Plutus.V1.Ledger.Time

Methods

rnf :: POSIXTime -> () Source #

Hashable POSIXTime Source # 
Instance details

Defined in Ledger.Orphans

ToJSON POSIXTime Source #

Custom ToJSON instance which allows to simply convert a POSIXTime value to a JSON number.

Instance details

Defined in Ledger.Orphans

FromJSON POSIXTime Source #

Custom FromJSON instance which allows to parse a JSON number to a POSIXTime value. The parsed JSON value MUST be an Integer or else the parsing fails.

Instance details

Defined in Ledger.Orphans

ToSchema POSIXTime Source # 
Instance details

Defined in Ledger.Orphans

Pretty POSIXTime 
Instance details

Defined in Plutus.V1.Ledger.Time

Methods

pretty :: POSIXTime -> Doc ann Source #

prettyList :: [POSIXTime] -> Doc ann Source #

Serialise POSIXTime Source # 
Instance details

Defined in Ledger.Orphans

UnsafeFromData POSIXTime 
Instance details

Defined in Plutus.V1.Ledger.Time

FromData POSIXTime 
Instance details

Defined in Plutus.V1.Ledger.Time

ToData POSIXTime 
Instance details

Defined in Plutus.V1.Ledger.Time

Enum POSIXTime 
Instance details

Defined in Plutus.V1.Ledger.Time

AdditiveSemigroup POSIXTime 
Instance details

Defined in Plutus.V1.Ledger.Time

AdditiveMonoid POSIXTime 
Instance details

Defined in Plutus.V1.Ledger.Time

AdditiveGroup POSIXTime 
Instance details

Defined in Plutus.V1.Ledger.Time

Ord POSIXTime 
Instance details

Defined in Plutus.V1.Ledger.Time

Eq POSIXTime 
Instance details

Defined in Plutus.V1.Ledger.Time

Lift DefaultUni POSIXTime 
Instance details

Defined in Plutus.V1.Ledger.Time

Typeable DefaultUni POSIXTime 
Instance details

Defined in Plutus.V1.Ledger.Time

type Rep POSIXTime 
Instance details

Defined in Plutus.V1.Ledger.Time

type Rep POSIXTime = D1 ('MetaData "POSIXTime" "Plutus.V1.Ledger.Time" "plutus-ledger-api-1.0.0.1-EUjexvcAhXiGIaLon6olWb" 'True) (C1 ('MetaCons "POSIXTime" 'PrefixI 'True) (S1 ('MetaSel ('Just "getPOSIXTime") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Integer)))

newtype DiffMilliSeconds Source #

This is a length of time, as measured by a number of milliseconds.

Instances

Instances details
Enum DiffMilliSeconds 
Instance details

Defined in Plutus.V1.Ledger.Time

Eq DiffMilliSeconds 
Instance details

Defined in Plutus.V1.Ledger.Time

Integral DiffMilliSeconds 
Instance details

Defined in Plutus.V1.Ledger.Time

Num DiffMilliSeconds 
Instance details

Defined in Plutus.V1.Ledger.Time

Ord DiffMilliSeconds 
Instance details

Defined in Plutus.V1.Ledger.Time

Real DiffMilliSeconds 
Instance details

Defined in Plutus.V1.Ledger.Time

Show DiffMilliSeconds 
Instance details

Defined in Plutus.V1.Ledger.Time

Generic DiffMilliSeconds 
Instance details

Defined in Plutus.V1.Ledger.Time

Associated Types

type Rep DiffMilliSeconds :: Type -> Type Source #

NFData DiffMilliSeconds 
Instance details

Defined in Plutus.V1.Ledger.Time

Methods

rnf :: DiffMilliSeconds -> () Source #

ToSchema DiffMilliSeconds Source # 
Instance details

Defined in Ledger.Orphans

UnsafeFromData DiffMilliSeconds 
Instance details

Defined in Plutus.V1.Ledger.Time

FromData DiffMilliSeconds 
Instance details

Defined in Plutus.V1.Ledger.Time

ToData DiffMilliSeconds 
Instance details

Defined in Plutus.V1.Ledger.Time

AdditiveSemigroup DiffMilliSeconds 
Instance details

Defined in Plutus.V1.Ledger.Time

AdditiveMonoid DiffMilliSeconds 
Instance details

Defined in Plutus.V1.Ledger.Time

AdditiveGroup DiffMilliSeconds 
Instance details

Defined in Plutus.V1.Ledger.Time

Ord DiffMilliSeconds 
Instance details

Defined in Plutus.V1.Ledger.Time

Eq DiffMilliSeconds 
Instance details

Defined in Plutus.V1.Ledger.Time

Lift DefaultUni DiffMilliSeconds 
Instance details

Defined in Plutus.V1.Ledger.Time

Typeable DefaultUni DiffMilliSeconds 
Instance details

Defined in Plutus.V1.Ledger.Time

type Rep DiffMilliSeconds 
Instance details

Defined in Plutus.V1.Ledger.Time

type Rep DiffMilliSeconds = D1 ('MetaData "DiffMilliSeconds" "Plutus.V1.Ledger.Time" "plutus-ledger-api-1.0.0.1-EUjexvcAhXiGIaLon6olWb" 'True) (C1 ('MetaCons "DiffMilliSeconds" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Integer)))

after :: Ord a => a -> Interval a -> Bool Source #

Check if a value is later than the end of a Interval.

before :: Ord a => a -> Interval a -> Bool Source #

Check if a value is earlier than the beginning of an Interval.

isEmpty :: (Enum a, Ord a) => Interval a -> Bool Source #

Check if an Interval is empty.

contains :: Ord a => Interval a -> Interval a -> Bool Source #

a contains b is true if the Interval b is entirely contained in a. That is, a contains b if for every entry s, if member s b then member s a.

hull :: Ord a => Interval a -> Interval a -> Interval a Source #

'hull a b' is the smallest interval containing a and b.

intersection :: Ord a => Interval a -> Interval a -> Interval a Source #

'intersection a b' is the largest interval that is contained in a and in b, if it exists.

overlaps :: (Enum a, Ord a) => Interval a -> Interval a -> Bool Source #

Check whether two intervals overlap, that is, whether there is a value that is a member of both intervals.

member :: Ord a => a -> Interval a -> Bool Source #

Check whether a value is in an interval.

never :: Interval a Source #

An Interval that is empty.

always :: Interval a Source #

An Interval that covers every slot.

to :: a -> Interval a Source #

to a is an Interval that includes all values that are smaller than or equal to a.

from :: a -> Interval a Source #

from a is an Interval that includes all values that are greater than or equal to a.

interval :: a -> a -> Interval a Source #

interval a b includes all values that are greater than or equal to a and smaller than or equal to b. Therefore it includes a and b.

data Interval a Source #

An interval of as.

The interval may be either closed or open at either end, meaning that the endpoints may or may not be included in the interval.

The interval can also be unbounded on either side.

Constructors

Interval 

Fields

Instances

Instances details
Functor Interval 
Instance details

Defined in Plutus.V1.Ledger.Interval

Methods

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

(Typeable DefaultUni a, Lift DefaultUni (LowerBound a), Lift DefaultUni (UpperBound a)) => Lift DefaultUni (Interval a) 
Instance details

Defined in Plutus.V1.Ledger.Interval

Eq a => Eq (Interval a) 
Instance details

Defined in Plutus.V1.Ledger.Interval

Methods

(==) :: Interval a -> Interval a -> Bool Source #

(/=) :: Interval a -> Interval a -> Bool Source #

Ord a => Ord (Interval a) 
Instance details

Defined in Plutus.V1.Ledger.Interval

Show a => Show (Interval a) 
Instance details

Defined in Plutus.V1.Ledger.Interval

Generic (Interval a) 
Instance details

Defined in Plutus.V1.Ledger.Interval

Associated Types

type Rep (Interval a) :: Type -> Type Source #

Methods

from :: Interval a -> Rep (Interval a) x Source #

to :: Rep (Interval a) x -> Interval a Source #

NFData a => NFData (Interval a) 
Instance details

Defined in Plutus.V1.Ledger.Interval

Methods

rnf :: Interval a -> () Source #

Hashable a => Hashable (Interval a) Source # 
Instance details

Defined in Ledger.Slot

ToJSON a => ToJSON (Interval a) Source # 
Instance details

Defined in Ledger.Slot

FromJSON a => FromJSON (Interval a) Source # 
Instance details

Defined in Ledger.Slot

ToSchema a => ToSchema (Interval a) Source # 
Instance details

Defined in Ledger.Orphans

Pretty a => Pretty (Interval a) 
Instance details

Defined in Plutus.V1.Ledger.Interval

Methods

pretty :: Interval a -> Doc ann Source #

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

Serialise a => Serialise (Interval a) Source # 
Instance details

Defined in Ledger.Slot

UnsafeFromData a => UnsafeFromData (Interval a) 
Instance details

Defined in Plutus.V1.Ledger.Interval

FromData a => FromData (Interval a) 
Instance details

Defined in Plutus.V1.Ledger.Interval

ToData a => ToData (Interval a) 
Instance details

Defined in Plutus.V1.Ledger.Interval

Ord a => JoinSemiLattice (Interval a) 
Instance details

Defined in Plutus.V1.Ledger.Interval

Methods

(\/) :: Interval a -> Interval a -> Interval a Source #

Ord a => MeetSemiLattice (Interval a) 
Instance details

Defined in Plutus.V1.Ledger.Interval

Methods

(/\) :: Interval a -> Interval a -> Interval a Source #

Ord a => BoundedJoinSemiLattice (Interval a) 
Instance details

Defined in Plutus.V1.Ledger.Interval

Methods

bottom :: Interval a Source #

Ord a => BoundedMeetSemiLattice (Interval a) 
Instance details

Defined in Plutus.V1.Ledger.Interval

Methods

top :: Interval a Source #

Eq a => Eq (Interval a) 
Instance details

Defined in Plutus.V1.Ledger.Interval

Methods

(==) :: Interval a -> Interval a -> Bool Source #

Typeable DefaultUni Interval 
Instance details

Defined in Plutus.V1.Ledger.Interval

type Rep (Interval a) 
Instance details

Defined in Plutus.V1.Ledger.Interval

type Rep (Interval a) = D1 ('MetaData "Interval" "Plutus.V1.Ledger.Interval" "plutus-ledger-api-1.0.0.1-EUjexvcAhXiGIaLon6olWb" '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))))

data Extended a Source #

A set extended with a positive and negative infinity.

Constructors

NegInf 
Finite a 
PosInf 

Instances

Instances details
Functor Extended 
Instance details

Defined in Plutus.V1.Ledger.Interval

Methods

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

(Typeable DefaultUni a, Lift DefaultUni a) => Lift DefaultUni (Extended a) 
Instance details

Defined in Plutus.V1.Ledger.Interval

Eq a => Eq (Extended a) 
Instance details

Defined in Plutus.V1.Ledger.Interval

Methods

(==) :: Extended a -> Extended a -> Bool Source #

(/=) :: Extended a -> Extended a -> Bool Source #

Ord a => Ord (Extended a) 
Instance details

Defined in Plutus.V1.Ledger.Interval

Show a => Show (Extended a) 
Instance details

Defined in Plutus.V1.Ledger.Interval

Generic (Extended a) 
Instance details

Defined in Plutus.V1.Ledger.Interval

Associated Types

type Rep (Extended a) :: Type -> Type Source #

Methods

from :: Extended a -> Rep (Extended a) x Source #

to :: Rep (Extended a) x -> Extended a Source #

NFData a => NFData (Extended a) 
Instance details

Defined in Plutus.V1.Ledger.Interval

Methods

rnf :: Extended a -> () Source #

Hashable a => Hashable (Extended a) Source # 
Instance details

Defined in Ledger.Slot

ToJSON a => ToJSON (Extended a) Source # 
Instance details

Defined in Ledger.Slot

FromJSON a => FromJSON (Extended a) Source # 
Instance details

Defined in Ledger.Slot

ToSchema a => ToSchema (Extended a) Source # 
Instance details

Defined in Ledger.Orphans

Pretty a => Pretty (Extended a) 
Instance details

Defined in Plutus.V1.Ledger.Interval

Methods

pretty :: Extended a -> Doc ann Source #

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

Serialise a => Serialise (Extended a) Source # 
Instance details

Defined in Ledger.Slot

UnsafeFromData a => UnsafeFromData (Extended a) 
Instance details

Defined in Plutus.V1.Ledger.Interval

FromData a => FromData (Extended a) 
Instance details

Defined in Plutus.V1.Ledger.Interval

ToData a => ToData (Extended a) 
Instance details

Defined in Plutus.V1.Ledger.Interval

Ord a => Ord (Extended a) 
Instance details

Defined in Plutus.V1.Ledger.Interval

Eq a => Eq (Extended a) 
Instance details

Defined in Plutus.V1.Ledger.Interval

Methods

(==) :: Extended a -> Extended a -> Bool Source #

Typeable DefaultUni Extended 
Instance details

Defined in Plutus.V1.Ledger.Interval

type Rep (Extended a) 
Instance details

Defined in Plutus.V1.Ledger.Interval

type Rep (Extended a) = D1 ('MetaData "Extended" "Plutus.V1.Ledger.Interval" "plutus-ledger-api-1.0.0.1-EUjexvcAhXiGIaLon6olWb" '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)))

type Closure = Bool Source #

Whether a bound is inclusive or not.

data UpperBound a Source #

The upper bound of an interval.

Constructors

UpperBound (Extended a) Closure 

Instances

Instances details
Functor UpperBound 
Instance details

Defined in Plutus.V1.Ledger.Interval

Methods

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

(Typeable DefaultUni a, Lift DefaultUni (Extended a)) => Lift DefaultUni (UpperBound a) 
Instance details

Defined in Plutus.V1.Ledger.Interval

Eq a => Eq (UpperBound a) 
Instance details

Defined in Plutus.V1.Ledger.Interval

Ord a => Ord (UpperBound a) 
Instance details

Defined in Plutus.V1.Ledger.Interval

Show a => Show (UpperBound a) 
Instance details

Defined in Plutus.V1.Ledger.Interval

Generic (UpperBound a) 
Instance details

Defined in Plutus.V1.Ledger.Interval

Associated Types

type Rep (UpperBound a) :: Type -> Type Source #

Methods

from :: UpperBound a -> Rep (UpperBound a) x Source #

to :: Rep (UpperBound a) x -> UpperBound a Source #

NFData a => NFData (UpperBound a) 
Instance details

Defined in Plutus.V1.Ledger.Interval

Methods

rnf :: UpperBound a -> () Source #

Hashable a => Hashable (UpperBound a) Source # 
Instance details

Defined in Ledger.Slot

ToJSON a => ToJSON (UpperBound a) Source # 
Instance details

Defined in Ledger.Slot

FromJSON a => FromJSON (UpperBound a) Source # 
Instance details

Defined in Ledger.Slot

ToSchema a => ToSchema (UpperBound a) Source # 
Instance details

Defined in Ledger.Orphans

Pretty a => Pretty (UpperBound a) 
Instance details

Defined in Plutus.V1.Ledger.Interval

Methods

pretty :: UpperBound a -> Doc ann Source #

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

Serialise a => Serialise (UpperBound a) Source # 
Instance details

Defined in Ledger.Slot

UnsafeFromData a => UnsafeFromData (UpperBound a) 
Instance details

Defined in Plutus.V1.Ledger.Interval

FromData a => FromData (UpperBound a) 
Instance details

Defined in Plutus.V1.Ledger.Interval

ToData a => ToData (UpperBound a) 
Instance details

Defined in Plutus.V1.Ledger.Interval

Ord a => Ord (UpperBound a) 
Instance details

Defined in Plutus.V1.Ledger.Interval

Eq a => Eq (UpperBound a) 
Instance details

Defined in Plutus.V1.Ledger.Interval

Methods

(==) :: UpperBound a -> UpperBound a -> Bool Source #

Typeable DefaultUni UpperBound 
Instance details

Defined in Plutus.V1.Ledger.Interval

type Rep (UpperBound a) 
Instance details

Defined in Plutus.V1.Ledger.Interval

type Rep (UpperBound a) = D1 ('MetaData "UpperBound" "Plutus.V1.Ledger.Interval" "plutus-ledger-api-1.0.0.1-EUjexvcAhXiGIaLon6olWb" 'False) (C1 ('MetaCons "UpperBound" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Extended a)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Closure)))

data LowerBound a Source #

The lower bound of an interval.

Constructors

LowerBound (Extended a) Closure 

Instances

Instances details
Functor LowerBound 
Instance details

Defined in Plutus.V1.Ledger.Interval

Methods

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

(Typeable DefaultUni a, Lift DefaultUni (Extended a)) => Lift DefaultUni (LowerBound a) 
Instance details

Defined in Plutus.V1.Ledger.Interval

Eq a => Eq (LowerBound a) 
Instance details

Defined in Plutus.V1.Ledger.Interval

Ord a => Ord (LowerBound a) 
Instance details

Defined in Plutus.V1.Ledger.Interval

Show a => Show (LowerBound a) 
Instance details

Defined in Plutus.V1.Ledger.Interval

Generic (LowerBound a) 
Instance details

Defined in Plutus.V1.Ledger.Interval

Associated Types

type Rep (LowerBound a) :: Type -> Type Source #

Methods

from :: LowerBound a -> Rep (LowerBound a) x Source #

to :: Rep (LowerBound a) x -> LowerBound a Source #

NFData a => NFData (LowerBound a) 
Instance details

Defined in Plutus.V1.Ledger.Interval

Methods

rnf :: LowerBound a -> () Source #

Hashable a => Hashable (LowerBound a) Source # 
Instance details

Defined in Ledger.Slot

ToJSON a => ToJSON (LowerBound a) Source # 
Instance details

Defined in Ledger.Slot

FromJSON a => FromJSON (LowerBound a) Source # 
Instance details

Defined in Ledger.Slot

ToSchema a => ToSchema (LowerBound a) Source # 
Instance details

Defined in Ledger.Orphans

Pretty a => Pretty (LowerBound a) 
Instance details

Defined in Plutus.V1.Ledger.Interval

Methods

pretty :: LowerBound a -> Doc ann Source #

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

Serialise a => Serialise (LowerBound a) Source # 
Instance details

Defined in Ledger.Slot

UnsafeFromData a => UnsafeFromData (LowerBound a) 
Instance details

Defined in Plutus.V1.Ledger.Interval

FromData a => FromData (LowerBound a) 
Instance details

Defined in Plutus.V1.Ledger.Interval

ToData a => ToData (LowerBound a) 
Instance details

Defined in Plutus.V1.Ledger.Interval

Ord a => Ord (LowerBound a) 
Instance details

Defined in Plutus.V1.Ledger.Interval

Eq a => Eq (LowerBound a) 
Instance details

Defined in Plutus.V1.Ledger.Interval

Methods

(==) :: LowerBound a -> LowerBound a -> Bool Source #

Typeable DefaultUni LowerBound 
Instance details

Defined in Plutus.V1.Ledger.Interval

type Rep (LowerBound a) 
Instance details

Defined in Plutus.V1.Ledger.Interval

type Rep (LowerBound a) = D1 ('MetaData "LowerBound" "Plutus.V1.Ledger.Interval" "plutus-ledger-api-1.0.0.1-EUjexvcAhXiGIaLon6olWb" 'False) (C1 ('MetaCons "LowerBound" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Extended a)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Closure)))

datumHash :: Datum -> DatumHash Source #

Hash a 'PV1.Datum builtin data.

scriptCurrencySymbol :: Versioned MintingPolicy -> CurrencySymbol Source #

The CurrencySymbol of a MintingPolicy.

data Versioned script Source #

A script of some kind with its Plutus language version

Constructors

Versioned 

Fields

Instances

Instances details
Functor Versioned 
Instance details

Defined in Plutus.Script.Utils.Scripts

Methods

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

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

Eq script => Eq (Versioned script) 
Instance details

Defined in Plutus.Script.Utils.Scripts

Methods

(==) :: Versioned script -> Versioned script -> Bool Source #

(/=) :: Versioned script -> Versioned script -> Bool Source #

Ord script => Ord (Versioned script) 
Instance details

Defined in Plutus.Script.Utils.Scripts

Methods

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) 
Instance details

Defined in Plutus.Script.Utils.Scripts

Methods

showsPrec :: Int -> Versioned script -> ShowS Source #

show :: Versioned script -> String Source #

showList :: [Versioned script] -> ShowS Source #

Generic (Versioned script) 
Instance details

Defined in Plutus.Script.Utils.Scripts

Associated Types

type Rep (Versioned script) :: Type -> Type Source #

Methods

from :: Versioned script -> Rep (Versioned script) x Source #

to :: Rep (Versioned script) x -> Versioned script Source #

NFData script => NFData (Versioned script) 
Instance details

Defined in Plutus.Script.Utils.Scripts

Methods

rnf :: Versioned script -> () Source #

ToJSON script => ToJSON (Versioned script) 
Instance details

Defined in Plutus.Script.Utils.Scripts

FromJSON script => FromJSON (Versioned script) 
Instance details

Defined in Plutus.Script.Utils.Scripts

ToSchema script => ToSchema (Versioned script) Source # 
Instance details

Defined in Ledger.Orphans

Pretty script => Pretty (Versioned script) 
Instance details

Defined in Plutus.Script.Utils.Scripts

Methods

pretty :: Versioned script -> Doc ann Source #

prettyList :: [Versioned script] -> Doc ann Source #

Serialise script => Serialise (Versioned script) 
Instance details

Defined in Plutus.Script.Utils.Scripts

type Rep (Versioned script) 
Instance details

Defined in Plutus.Script.Utils.Scripts

type Rep (Versioned script) = D1 ('MetaData "Versioned" "Plutus.Script.Utils.Scripts" "plutus-script-utils-1.1.0.0-IFwyzE6CIQ44doxQRh05YH" 'False) (C1 ('MetaCons "Versioned" 'PrefixI 'True) (S1 ('MetaSel ('Just "unversioned") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 script) :*: S1 ('MetaSel ('Just "version") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Language)))

newtype Slot Source #

The slot number. This is a good proxy for time, since on the Cardano blockchain slots pass at a constant rate.

Constructors

Slot 

Fields

Instances

Instances details
Enum Slot Source # 
Instance details

Defined in Ledger.Slot

Eq Slot Source # 
Instance details

Defined in Ledger.Slot

Methods

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

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

Integral Slot Source # 
Instance details

Defined in Ledger.Slot

Data Slot Source # 
Instance details

Defined in Ledger.Slot

Methods

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 # 
Instance details

Defined in Ledger.Slot

Ord Slot Source # 
Instance details

Defined in Ledger.Slot

Real Slot Source # 
Instance details

Defined in Ledger.Slot

Show Slot Source # 
Instance details

Defined in Ledger.Slot

Generic Slot Source # 
Instance details

Defined in Ledger.Slot

Associated Types

type Rep Slot :: Type -> Type Source #

Methods

from :: Slot -> Rep Slot x Source #

to :: Rep Slot x -> Slot Source #

NFData Slot Source # 
Instance details

Defined in Ledger.Slot

Methods

rnf :: Slot -> () Source #

Hashable Slot Source # 
Instance details

Defined in Ledger.Slot

ToJSON Slot Source # 
Instance details

Defined in Ledger.Slot

ToJSONKey Slot Source # 
Instance details

Defined in Ledger.Slot

FromJSON Slot Source # 
Instance details

Defined in Ledger.Slot

FromJSONKey Slot Source # 
Instance details

Defined in Ledger.Slot

ToSchema Slot Source # 
Instance details

Defined in Ledger.Orphans

Pretty Slot Source # 
Instance details

Defined in Ledger.Slot

Methods

pretty :: Slot -> Doc ann Source #

prettyList :: [Slot] -> Doc ann Source #

Serialise Slot Source # 
Instance details

Defined in Ledger.Slot

UnsafeFromData Slot Source # 
Instance details

Defined in Ledger.Slot

FromData Slot Source # 
Instance details

Defined in Ledger.Slot

ToData Slot Source # 
Instance details

Defined in Ledger.Slot

Enum Slot Source # 
Instance details

Defined in Ledger.Slot

AdditiveSemigroup Slot Source # 
Instance details

Defined in Ledger.Slot

Methods

(+) :: Slot -> Slot -> Slot Source #

AdditiveMonoid Slot Source # 
Instance details

Defined in Ledger.Slot

Methods

zero :: Slot Source #

AdditiveGroup Slot Source # 
Instance details

Defined in Ledger.Slot

Methods

(-) :: Slot -> Slot -> Slot Source #

Ord Slot Source # 
Instance details

Defined in Ledger.Slot

Eq Slot Source # 
Instance details

Defined in Ledger.Slot

Methods

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

Lift DefaultUni Slot Source # 
Instance details

Defined in Ledger.Slot

Typeable DefaultUni Slot Source # 
Instance details

Defined in Ledger.Slot

type Rep Slot Source # 
Instance details

Defined in Ledger.Slot

type Rep Slot = D1 ('MetaData "Slot" "Ledger.Slot" "plutus-ledger-1.1.0.0-JskZbcPMCdRJVHaAZ0to82" 'True) (C1 ('MetaCons "Slot" 'PrefixI 'True) (S1 ('MetaSel ('Just "getSlot") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Integer)))

width :: SlotRange -> Maybe Integer Source #

Number of Slots covered by the interval, if finite. width (from x) == Nothing.

noAdaValue :: Value -> Value Source #

Value without any Ada.

newtype Signature Source #

A message with a cryptographic signature.

Constructors

Signature 

Instances

Instances details
Eq Signature Source # 
Instance details

Defined in Ledger.Crypto

Ord Signature Source # 
Instance details

Defined in Ledger.Crypto

Show Signature Source # 
Instance details

Defined in Ledger.Crypto

Generic Signature Source # 
Instance details

Defined in Ledger.Crypto

Associated Types

type Rep Signature :: Type -> Type Source #

NFData Signature Source # 
Instance details

Defined in Ledger.Crypto

Methods

rnf :: Signature -> () Source #

ToJSON Signature Source # 
Instance details

Defined in Ledger.Crypto

FromJSON Signature Source # 
Instance details

Defined in Ledger.Crypto

ToSchema Signature Source # 
Instance details

Defined in Ledger.Orphans

Pretty Signature Source # 
Instance details

Defined in Ledger.Crypto

Methods

pretty :: Signature -> Doc ann Source #

prettyList :: [Signature] -> Doc ann Source #

Serialise Signature Source # 
Instance details

Defined in Ledger.Crypto

UnsafeFromData Signature Source # 
Instance details

Defined in Ledger.Crypto

FromData Signature Source # 
Instance details

Defined in Ledger.Crypto

ToData Signature Source # 
Instance details

Defined in Ledger.Crypto

Ord Signature Source # 
Instance details

Defined in Ledger.Crypto

Eq Signature Source # 
Instance details

Defined in Ledger.Crypto

Lift DefaultUni Signature Source # 
Instance details

Defined in Ledger.Crypto

Typeable DefaultUni Signature Source # 
Instance details

Defined in Ledger.Crypto

type Rep Signature Source # 
Instance details

Defined in Ledger.Crypto

type Rep Signature = D1 ('MetaData "Signature" "Ledger.Crypto" "plutus-ledger-1.1.0.0-JskZbcPMCdRJVHaAZ0to82" 'True) (C1 ('MetaCons "Signature" 'PrefixI 'True) (S1 ('MetaSel ('Just "getSignature") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 BuiltinByteString)))

newtype Passphrase Source #

Passphrase newtype to mark intent

Constructors

Passphrase 

Instances

Instances details
Show Passphrase Source # 
Instance details

Defined in Ledger.Crypto

IsString Passphrase Source # 
Instance details

Defined in Ledger.Crypto

newtype PubKey Source #

Constructors

PubKey 

Instances

Instances details
Eq PubKey Source # 
Instance details

Defined in Ledger.Crypto

Ord PubKey Source # 
Instance details

Defined in Ledger.Crypto

Show PubKey Source # 
Instance details

Defined in Ledger.Crypto

IsString PubKey Source # 
Instance details

Defined in Ledger.Crypto

Generic PubKey Source # 
Instance details

Defined in Ledger.Crypto

Associated Types

type Rep PubKey :: Type -> Type Source #

NFData PubKey Source # 
Instance details

Defined in Ledger.Crypto

Methods

rnf :: PubKey -> () Source #

ToJSON PubKey Source # 
Instance details

Defined in Ledger.Crypto

ToJSONKey PubKey Source # 
Instance details

Defined in Ledger.Crypto

FromJSON PubKey Source # 
Instance details

Defined in Ledger.Crypto

FromJSONKey PubKey Source # 
Instance details

Defined in Ledger.Crypto

Newtype PubKey Source # 
Instance details

Defined in Ledger.Crypto

Associated Types

type O PubKey Source #

ToSchema PubKey Source # 
Instance details

Defined in Ledger.Orphans

Pretty PubKey Source # 
Instance details

Defined in Ledger.Crypto

Methods

pretty :: PubKey -> Doc ann Source #

prettyList :: [PubKey] -> Doc ann Source #

Serialise PubKey Source # 
Instance details

Defined in Ledger.Crypto

UnsafeFromData PubKey Source # 
Instance details

Defined in Ledger.Crypto

FromData PubKey Source # 
Instance details

Defined in Ledger.Crypto

ToData PubKey Source # 
Instance details

Defined in Ledger.Crypto

Ord PubKey Source # 
Instance details

Defined in Ledger.Crypto

Eq PubKey Source # 
Instance details

Defined in Ledger.Crypto

Methods

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

Lift DefaultUni PubKey Source # 
Instance details

Defined in Ledger.Crypto

Typeable DefaultUni PubKey Source # 
Instance details

Defined in Ledger.Crypto

type Rep PubKey Source # 
Instance details

Defined in Ledger.Crypto

type Rep PubKey = D1 ('MetaData "PubKey" "Ledger.Crypto" "plutus-ledger-1.1.0.0-JskZbcPMCdRJVHaAZ0to82" 'True) (C1 ('MetaCons "PubKey" 'PrefixI 'True) (S1 ('MetaSel ('Just "getPubKey") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 LedgerBytes)))
type O PubKey Source # 
Instance details

Defined in Ledger.Crypto

type O PubKey = GO (Rep PubKey)

newtype PrivateKey Source #

A cryptographic private key.

Constructors

PrivateKey 

Instances

Instances details
Eq PrivateKey Source # 
Instance details

Defined in Ledger.Crypto

Ord PrivateKey Source # 
Instance details

Defined in Ledger.Crypto

Show PrivateKey Source # 
Instance details

Defined in Ledger.Crypto

Generic PrivateKey Source # 
Instance details

Defined in Ledger.Crypto

Associated Types

type Rep PrivateKey :: Type -> Type Source #

Hashable PrivateKey Source # 
Instance details

Defined in Ledger.Crypto

ToJSON PrivateKey Source # 
Instance details

Defined in Ledger.Crypto

ToJSONKey PrivateKey Source # 
Instance details

Defined in Ledger.Crypto

FromJSON PrivateKey Source # 
Instance details

Defined in Ledger.Crypto

FromJSONKey PrivateKey Source # 
Instance details

Defined in Ledger.Crypto

ToHttpApiData PrivateKey Source # 
Instance details

Defined in Ledger.Orphans

FromHttpApiData PrivateKey Source # 
Instance details

Defined in Ledger.Orphans

Newtype PrivateKey Source # 
Instance details

Defined in Ledger.Crypto

Associated Types

type O PrivateKey Source #

Pretty PrivateKey Source # 
Instance details

Defined in Ledger.Crypto

Serialise PrivateKey Source # 
Instance details

Defined in Ledger.Crypto

UnsafeFromData PrivateKey Source # 
Instance details

Defined in Ledger.Crypto

FromData PrivateKey Source # 
Instance details

Defined in Ledger.Crypto

ToData PrivateKey Source # 
Instance details

Defined in Ledger.Crypto

Ord PrivateKey Source # 
Instance details

Defined in Ledger.Crypto

Eq PrivateKey Source # 
Instance details

Defined in Ledger.Crypto

Lift DefaultUni PrivateKey Source # 
Instance details

Defined in Ledger.Crypto

Typeable DefaultUni PrivateKey Source # 
Instance details

Defined in Ledger.Crypto

type Rep PrivateKey Source # 
Instance details

Defined in Ledger.Crypto

type Rep PrivateKey = D1 ('MetaData "PrivateKey" "Ledger.Crypto" "plutus-ledger-1.1.0.0-JskZbcPMCdRJVHaAZ0to82" 'True) (C1 ('MetaCons "PrivateKey" 'PrefixI 'True) (S1 ('MetaSel ('Just "getPrivateKey") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 LedgerBytes)))
type O PrivateKey Source # 
Instance details

Defined in Ledger.Crypto

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.

newtype PaymentPubKey Source #

Constructors

PaymentPubKey 

Instances

Instances details
Eq PaymentPubKey Source # 
Instance details

Defined in Ledger.Address

Ord PaymentPubKey Source # 
Instance details

Defined in Ledger.Address

Show PaymentPubKey Source # 
Instance details

Defined in Ledger.Address

Generic PaymentPubKey Source # 
Instance details

Defined in Ledger.Address

Associated Types

type Rep PaymentPubKey :: Type -> Type Source #

ToJSON PaymentPubKey Source # 
Instance details

Defined in Ledger.Address

ToJSONKey PaymentPubKey Source # 
Instance details

Defined in Ledger.Address

FromJSON PaymentPubKey Source # 
Instance details

Defined in Ledger.Address

FromJSONKey PaymentPubKey Source # 
Instance details

Defined in Ledger.Address

ToSchema PaymentPubKey Source # 
Instance details

Defined in Ledger.Address

Pretty PaymentPubKey Source # 
Instance details

Defined in Ledger.Address

Serialise PaymentPubKey Source # 
Instance details

Defined in Ledger.Address

UnsafeFromData PaymentPubKey Source # 
Instance details

Defined in Ledger.Address

FromData PaymentPubKey Source # 
Instance details

Defined in Ledger.Address

ToData PaymentPubKey Source # 
Instance details

Defined in Ledger.Address

Ord PaymentPubKey Source # 
Instance details

Defined in Ledger.Address

Eq PaymentPubKey Source # 
Instance details

Defined in Ledger.Address

Lift DefaultUni PaymentPubKey Source # 
Instance details

Defined in Ledger.Address

Typeable DefaultUni PaymentPubKey Source # 
Instance details

Defined in Ledger.Address

type Rep PaymentPubKey Source # 
Instance details

Defined in Ledger.Address

type Rep PaymentPubKey = D1 ('MetaData "PaymentPubKey" "Ledger.Address" "plutus-ledger-1.1.0.0-JskZbcPMCdRJVHaAZ0to82" 'True) (C1 ('MetaCons "PaymentPubKey" 'PrefixI 'True) (S1 ('MetaSel ('Just "unPaymentPubKey") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 PubKey)))

newtype PaymentPubKeyHash Source #

Instances

Instances details
Eq PaymentPubKeyHash Source # 
Instance details

Defined in Ledger.Address

Ord PaymentPubKeyHash Source # 
Instance details

Defined in Ledger.Address

Show PaymentPubKeyHash Source # 
Instance details

Defined in Ledger.Address

Generic PaymentPubKeyHash Source # 
Instance details

Defined in Ledger.Address

Associated Types

type Rep PaymentPubKeyHash :: Type -> Type Source #

Hashable PaymentPubKeyHash Source # 
Instance details

Defined in Ledger.Address

ToJSON PaymentPubKeyHash Source # 
Instance details

Defined in Ledger.Address

ToJSONKey PaymentPubKeyHash Source # 
Instance details

Defined in Ledger.Address

FromJSON PaymentPubKeyHash Source # 
Instance details

Defined in Ledger.Address

FromJSONKey PaymentPubKeyHash Source # 
Instance details

Defined in Ledger.Address

ToSchema PaymentPubKeyHash Source # 
Instance details

Defined in Ledger.Address

Pretty PaymentPubKeyHash Source # 
Instance details

Defined in Ledger.Address

Serialise PaymentPubKeyHash Source # 
Instance details

Defined in Ledger.Address

UnsafeFromData PaymentPubKeyHash Source # 
Instance details

Defined in Ledger.Address

FromData PaymentPubKeyHash Source # 
Instance details

Defined in Ledger.Address

ToData PaymentPubKeyHash Source # 
Instance details

Defined in Ledger.Address

Ord PaymentPubKeyHash Source # 
Instance details

Defined in Ledger.Address

Eq PaymentPubKeyHash Source # 
Instance details

Defined in Ledger.Address

Lift DefaultUni PaymentPubKeyHash Source # 
Instance details

Defined in Ledger.Address

Typeable DefaultUni PaymentPubKeyHash Source # 
Instance details

Defined in Ledger.Address

type Rep PaymentPubKeyHash Source # 
Instance details

Defined in Ledger.Address

type Rep PaymentPubKeyHash = D1 ('MetaData "PaymentPubKeyHash" "Ledger.Address" "plutus-ledger-1.1.0.0-JskZbcPMCdRJVHaAZ0to82" 'True) (C1 ('MetaCons "PaymentPubKeyHash" 'PrefixI 'True) (S1 ('MetaSel ('Just "unPaymentPubKeyHash") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 PubKeyHash)))

newtype StakePubKey Source #

Constructors

StakePubKey 

Instances

Instances details
Eq StakePubKey Source # 
Instance details

Defined in Ledger.Address

Ord StakePubKey Source # 
Instance details

Defined in Ledger.Address

Show StakePubKey Source # 
Instance details

Defined in Ledger.Address

Generic StakePubKey Source # 
Instance details

Defined in Ledger.Address

Associated Types

type Rep StakePubKey :: Type -> Type Source #

ToJSON StakePubKey Source # 
Instance details

Defined in Ledger.Address

ToJSONKey StakePubKey Source # 
Instance details

Defined in Ledger.Address

FromJSON StakePubKey Source # 
Instance details

Defined in Ledger.Address

FromJSONKey StakePubKey Source # 
Instance details

Defined in Ledger.Address

ToSchema StakePubKey Source # 
Instance details

Defined in Ledger.Address

Pretty StakePubKey Source # 
Instance details

Defined in Ledger.Address

Serialise StakePubKey Source # 
Instance details

Defined in Ledger.Address

UnsafeFromData StakePubKey Source # 
Instance details

Defined in Ledger.Address

FromData StakePubKey Source # 
Instance details

Defined in Ledger.Address

ToData StakePubKey Source # 
Instance details

Defined in Ledger.Address

Ord StakePubKey Source # 
Instance details

Defined in Ledger.Address

Eq StakePubKey Source # 
Instance details

Defined in Ledger.Address

Lift DefaultUni StakePubKey Source # 
Instance details

Defined in Ledger.Address

Typeable DefaultUni StakePubKey Source # 
Instance details

Defined in Ledger.Address

type Rep StakePubKey Source # 
Instance details

Defined in Ledger.Address

type Rep StakePubKey = D1 ('MetaData "StakePubKey" "Ledger.Address" "plutus-ledger-1.1.0.0-JskZbcPMCdRJVHaAZ0to82" 'True) (C1 ('MetaCons "StakePubKey" 'PrefixI 'True) (S1 ('MetaSel ('Just "unStakePubKey") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 PubKey)))

newtype StakePubKeyHash Source #

Instances

Instances details
Eq StakePubKeyHash Source # 
Instance details

Defined in Ledger.Address

Ord StakePubKeyHash Source # 
Instance details

Defined in Ledger.Address

Show StakePubKeyHash Source # 
Instance details

Defined in Ledger.Address

Generic StakePubKeyHash Source # 
Instance details

Defined in Ledger.Address

Associated Types

type Rep StakePubKeyHash :: Type -> Type Source #

Hashable StakePubKeyHash Source # 
Instance details

Defined in Ledger.Address

ToJSON StakePubKeyHash Source # 
Instance details

Defined in Ledger.Address

ToJSONKey StakePubKeyHash Source # 
Instance details

Defined in Ledger.Address

FromJSON StakePubKeyHash Source # 
Instance details

Defined in Ledger.Address

FromJSONKey StakePubKeyHash Source # 
Instance details

Defined in Ledger.Address

ToSchema StakePubKeyHash Source # 
Instance details

Defined in Ledger.Address

Pretty StakePubKeyHash Source # 
Instance details

Defined in Ledger.Address

Serialise StakePubKeyHash Source # 
Instance details

Defined in Ledger.Address

UnsafeFromData StakePubKeyHash Source # 
Instance details

Defined in Ledger.Address

FromData StakePubKeyHash Source # 
Instance details

Defined in Ledger.Address

ToData StakePubKeyHash Source # 
Instance details

Defined in Ledger.Address

Ord StakePubKeyHash Source # 
Instance details

Defined in Ledger.Address

Eq StakePubKeyHash Source # 
Instance details

Defined in Ledger.Address

Lift DefaultUni StakePubKeyHash Source # 
Instance details

Defined in Ledger.Address

Typeable DefaultUni StakePubKeyHash Source # 
Instance details

Defined in Ledger.Address

type Rep StakePubKeyHash Source # 
Instance details

Defined in Ledger.Address

type Rep StakePubKeyHash = D1 ('MetaData "StakePubKeyHash" "Ledger.Address" "plutus-ledger-1.1.0.0-JskZbcPMCdRJVHaAZ0to82" 'True) (C1 ('MetaCons "StakePubKeyHash" 'PrefixI 'True) (S1 ('MetaSel ('Just "unStakePubKeyHash") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 PubKeyHash)))

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).

data ToCardanoError Source #

Instances

Instances details
Eq ToCardanoError Source # 
Instance details

Defined in Ledger.Tx.CardanoAPI.Internal

Show ToCardanoError Source # 
Instance details

Defined in Ledger.Tx.CardanoAPI.Internal

Generic ToCardanoError Source # 
Instance details

Defined in Ledger.Tx.CardanoAPI.Internal

Associated Types

type Rep ToCardanoError :: Type -> Type Source #

ToJSON ToCardanoError Source # 
Instance details

Defined in Ledger.Tx.CardanoAPI.Internal

FromJSON ToCardanoError Source # 
Instance details

Defined in Ledger.Tx.CardanoAPI.Internal

Pretty ToCardanoError Source # 
Instance details

Defined in Ledger.Tx.CardanoAPI.Internal

type Rep ToCardanoError Source # 
Instance details

Defined in Ledger.Tx.CardanoAPI.Internal

type Rep ToCardanoError = D1 ('MetaData "ToCardanoError" "Ledger.Tx.CardanoAPI.Internal" "plutus-ledger-1.1.0.0-JskZbcPMCdRJVHaAZ0to82" 'False) (((C1 ('MetaCons "TxBodyError" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String)) :+: (C1 ('MetaCons "DeserialisationError" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "InvalidValidityRange" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "ValueNotPureAda" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "OutputHasZeroAda" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "StakingPointersNotSupported" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "SimpleScriptsNotSupportedToCardano" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: (((C1 ('MetaCons "MissingInputValidator" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "MissingDatum" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "MissingMintingPolicy" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ScriptPurposeNotSupported" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ScriptTag)))) :+: ((C1 ('MetaCons "MissingMintingPolicyRedeemer" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "MissingStakeValidator" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "UnsupportedPlutusVersion" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Language)) :+: C1 ('MetaCons "Tag" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ToCardanoError))))))

data SomeCardanoApiTx where Source #

Cardano tx from any era.

Constructors

SomeTx :: IsCardanoEra era => Tx era -> EraInMode era CardanoMode -> SomeCardanoApiTx 

Bundled Patterns

pattern CardanoApiEmulatorEraTx :: Tx BabbageEra -> SomeCardanoApiTx 

Instances

Instances details
Eq SomeCardanoApiTx Source # 
Instance details

Defined in Ledger.Tx.CardanoAPI.Internal

Show SomeCardanoApiTx Source # 
Instance details

Defined in Ledger.Tx.CardanoAPI.Internal

ToJSON SomeCardanoApiTx Source # 
Instance details

Defined in Ledger.Tx.CardanoAPI.Internal

FromJSON SomeCardanoApiTx Source #

Converting SomeCardanoApiTx to JSON.

If the "tx" field is from an unknown era, the JSON parser will print an error at runtime while parsing.

Instance details

Defined in Ledger.Tx.CardanoAPI.Internal

ToSchema SomeCardanoApiTx Source # 
Instance details

Defined in Ledger.Tx.CardanoAPI.Internal

Pretty SomeCardanoApiTx Source # 
Instance details

Defined in Ledger.Tx

Serialise SomeCardanoApiTx Source # 
Instance details

Defined in Ledger.Tx.CardanoAPI.Internal

data TxOutTx Source #

A TxOut along with the Tx it comes from, which may have additional information e.g. the full data script that goes with the TxOut.

Constructors

TxOutTx 

Fields

Instances

Instances details
Eq TxOutTx Source # 
Instance details

Defined in Ledger.Tx.Internal

Show TxOutTx Source # 
Instance details

Defined in Ledger.Tx.Internal

Generic TxOutTx Source # 
Instance details

Defined in Ledger.Tx.Internal

Associated Types

type Rep TxOutTx :: Type -> Type Source #

ToJSON TxOutTx Source # 
Instance details

Defined in Ledger.Tx.Internal

FromJSON TxOutTx Source # 
Instance details

Defined in Ledger.Tx.Internal

Serialise TxOutTx Source # 
Instance details

Defined in Ledger.Tx.Internal

type Rep TxOutTx Source # 
Instance details

Defined in Ledger.Tx.Internal

type Rep TxOutTx = D1 ('MetaData "TxOutTx" "Ledger.Tx.Internal" "plutus-ledger-1.1.0.0-JskZbcPMCdRJVHaAZ0to82" 'False) (C1 ('MetaCons "TxOutTx" 'PrefixI 'True) (S1 ('MetaSel ('Just "txOutTxTx") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Tx) :*: S1 ('MetaSel ('Just "txOutTxOut") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 TxOut)))

data TxStripped Source #

A babbage era transaction without witnesses for its inputs.

Constructors

TxStripped 

Fields

Instances

Instances details
Eq TxStripped Source # 
Instance details

Defined in Ledger.Tx.Internal

Show TxStripped Source # 
Instance details

Defined in Ledger.Tx.Internal

Generic TxStripped Source # 
Instance details

Defined in Ledger.Tx.Internal

Associated Types

type Rep TxStripped :: Type -> Type Source #

Serialise TxStripped Source # 
Instance details

Defined in Ledger.Tx.Internal

type Rep TxStripped Source # 
Instance details

Defined in Ledger.Tx.Internal

type Rep TxStripped = D1 ('MetaData "TxStripped" "Ledger.Tx.Internal" "plutus-ledger-1.1.0.0-JskZbcPMCdRJVHaAZ0to82" 'False) (C1 ('MetaCons "TxStripped" 'PrefixI 'True) ((S1 ('MetaSel ('Just "txStrippedInputs") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [TxOutRef]) :*: S1 ('MetaSel ('Just "txStrippedReferenceInputs") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [TxOutRef])) :*: (S1 ('MetaSel ('Just "txStrippedOutputs") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [TxOut]) :*: (S1 ('MetaSel ('Just "txStrippedMint") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Value) :*: S1 ('MetaSel ('Just "txStrippedFee") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Value)))))

data Tx Source #

A Babbage-era transaction, including witnesses for its inputs.

Constructors

Tx 

Fields

Instances

Instances details
Eq Tx Source # 
Instance details

Defined in Ledger.Tx.Internal

Methods

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

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

Show Tx Source # 
Instance details

Defined in Ledger.Tx.Internal

Generic Tx Source # 
Instance details

Defined in Ledger.Tx.Internal

Associated Types

type Rep Tx :: Type -> Type Source #

Methods

from :: Tx -> Rep Tx x Source #

to :: Rep Tx x -> Tx Source #

Semigroup Tx Source # 
Instance details

Defined in Ledger.Tx.Internal

Methods

(<>) :: Tx -> Tx -> Tx Source #

sconcat :: NonEmpty Tx -> Tx Source #

stimes :: Integral b => b -> Tx -> Tx Source #

Monoid Tx Source # 
Instance details

Defined in Ledger.Tx.Internal

Methods

mempty :: Tx Source #

mappend :: Tx -> Tx -> Tx Source #

mconcat :: [Tx] -> Tx Source #

NFData Tx Source # 
Instance details

Defined in Ledger.Tx.Internal

Methods

rnf :: Tx -> () Source #

ToJSON Tx Source # 
Instance details

Defined in Ledger.Tx.Internal

FromJSON Tx Source # 
Instance details

Defined in Ledger.Tx.Internal

ByteArrayAccess Tx Source # 
Instance details

Defined in Ledger.Tx.Internal

Methods

length :: Tx -> Int Source #

withByteArray :: Tx -> (Ptr p -> IO a) -> IO a Source #

copyByteArrayToPtr :: Tx -> Ptr p -> IO () Source #

ToSchema Tx Source # 
Instance details

Defined in Ledger.Tx.Internal

Pretty Tx Source # 
Instance details

Defined in Ledger.Tx

Methods

pretty :: Tx -> Doc ann Source #

prettyList :: [Tx] -> Doc ann Source #

Serialise Tx Source # 
Instance details

Defined in Ledger.Tx.Internal

type Rep Tx Source # 
Instance details

Defined in Ledger.Tx.Internal

type Rep Tx = D1 ('MetaData "Tx" "Ledger.Tx.Internal" "plutus-ledger-1.1.0.0-JskZbcPMCdRJVHaAZ0to82" 'False) (C1 ('MetaCons "Tx" 'PrefixI 'True) ((((S1 ('MetaSel ('Just "txInputs") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [TxInput]) :*: S1 ('MetaSel ('Just "txReferenceInputs") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [TxInput])) :*: (S1 ('MetaSel ('Just "txCollateralInputs") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [TxInput]) :*: S1 ('MetaSel ('Just "txOutputs") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [TxOut]))) :*: ((S1 ('MetaSel ('Just "txReturnCollateral") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe TxOut)) :*: S1 ('MetaSel ('Just "txTotalCollateral") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Value))) :*: (S1 ('MetaSel ('Just "txMint") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Value) :*: S1 ('MetaSel ('Just "txFee") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Value)))) :*: (((S1 ('MetaSel ('Just "txValidRange") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 SlotRange) :*: S1 ('MetaSel ('Just "txMintingWitnesses") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 MintingWitnessesMap)) :*: (S1 ('MetaSel ('Just "txWithdrawals") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Withdrawal]) :*: S1 ('MetaSel ('Just "txCertificates") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Certificate]))) :*: ((S1 ('MetaSel ('Just "txSignatures") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Map PubKey Signature)) :*: S1 ('MetaSel ('Just "txScripts") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ScriptsMap)) :*: (S1 ('MetaSel ('Just "txData") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Map DatumHash Datum)) :*: S1 ('MetaSel ('Just "txMetadata") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe BuiltinByteString)))))))

newtype TxOut Source #

Validator, redeemer, and data scripts of a transaction input that spends a "pay to script" output. inScripts :: Tx -> TxInput -> Maybe (LedgerPlutusVersion, Validator, Redeemer, Datum) inScripts tx i@TxInput{txInputType=TxConsumeScriptAddress pv _ _ _} = case txInType $ fillTxInputWitnesses tx i of Just (ConsumeScriptAddress v r d) -> Just (pv, v, r, d) _ -> Nothing inScripts _ _ = Nothing

Constructors

TxOut 

Instances

Instances details
Eq TxOut Source # 
Instance details

Defined in Ledger.Tx.Internal

Methods

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

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

Show TxOut Source # 
Instance details

Defined in Ledger.Tx.Internal

Generic TxOut Source # 
Instance details

Defined in Ledger.Tx.Internal

Associated Types

type Rep TxOut :: Type -> Type Source #

Methods

from :: TxOut -> Rep TxOut x Source #

to :: Rep TxOut x -> TxOut Source #

NFData TxOut Source # 
Instance details

Defined in Ledger.Tx.Internal

Methods

rnf :: TxOut -> () Source #

ToJSON TxOut Source # 
Instance details

Defined in Ledger.Tx.Internal

FromJSON TxOut Source # 
Instance details

Defined in Ledger.Tx.Internal

FromCBOR TxOut Source # 
Instance details

Defined in Ledger.Tx.Internal

ToCBOR TxOut Source # 
Instance details

Defined in Ledger.Tx.Internal

Methods

toCBOR :: TxOut -> Encoding Source #

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy TxOut -> Size Source #

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [TxOut] -> Size Source #

ToSchema TxOut Source # 
Instance details

Defined in Ledger.Tx.Internal

Pretty TxOut Source # 
Instance details

Defined in Ledger.Tx.Internal

Methods

pretty :: TxOut -> Doc ann Source #

prettyList :: [TxOut] -> Doc ann Source #

Serialise TxOut Source # 
Instance details

Defined in Ledger.Tx.Internal

type Rep TxOut Source # 
Instance details

Defined in Ledger.Tx.Internal

type Rep TxOut = D1 ('MetaData "TxOut" "Ledger.Tx.Internal" "plutus-ledger-1.1.0.0-JskZbcPMCdRJVHaAZ0to82" 'True) (C1 ('MetaCons "TxOut" 'PrefixI 'True) (S1 ('MetaSel ('Just "getTxOut") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (TxOut CtxTx BabbageEra))))

data Certificate Source #

Constructors

Certificate 

Fields

Instances

Instances details
Eq Certificate Source # 
Instance details

Defined in Ledger.Tx.Internal

Show Certificate Source # 
Instance details

Defined in Ledger.Tx.Internal

Generic Certificate Source # 
Instance details

Defined in Ledger.Tx.Internal

Associated Types

type Rep Certificate :: Type -> Type Source #

NFData Certificate Source # 
Instance details

Defined in Ledger.Tx.Internal

Methods

rnf :: Certificate -> () Source #

ToJSON Certificate Source # 
Instance details

Defined in Ledger.Tx.Internal

FromJSON Certificate Source # 
Instance details

Defined in Ledger.Tx.Internal

ToSchema Certificate Source # 
Instance details

Defined in Ledger.Tx.Internal

Pretty Certificate Source # 
Instance details

Defined in Ledger.Tx.Internal

Serialise Certificate Source # 
Instance details

Defined in Ledger.Tx.Internal

type Rep Certificate Source # 
Instance details

Defined in Ledger.Tx.Internal

type Rep Certificate = D1 ('MetaData "Certificate" "Ledger.Tx.Internal" "plutus-ledger-1.1.0.0-JskZbcPMCdRJVHaAZ0to82" 'False) (C1 ('MetaCons "Certificate" 'PrefixI 'True) (S1 ('MetaSel ('Just "certificateDcert") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DCert) :*: S1 ('MetaSel ('Just "certificateRedeemer") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Redeemer))))

data Withdrawal Source #

Stake withdrawal, if applicable the script should be included in txScripts.

Constructors

Withdrawal 

Fields

Instances

Instances details
Eq Withdrawal Source # 
Instance details

Defined in Ledger.Tx.Internal

Show Withdrawal Source # 
Instance details

Defined in Ledger.Tx.Internal

Generic Withdrawal Source # 
Instance details

Defined in Ledger.Tx.Internal

Associated Types

type Rep Withdrawal :: Type -> Type Source #

NFData Withdrawal Source # 
Instance details

Defined in Ledger.Tx.Internal

Methods

rnf :: Withdrawal -> () Source #

ToJSON Withdrawal Source # 
Instance details

Defined in Ledger.Tx.Internal

FromJSON Withdrawal Source # 
Instance details

Defined in Ledger.Tx.Internal

ToSchema Withdrawal Source # 
Instance details

Defined in Ledger.Tx.Internal

Pretty Withdrawal Source # 
Instance details

Defined in Ledger.Tx.Internal

Serialise Withdrawal Source # 
Instance details

Defined in Ledger.Tx.Internal

type Rep Withdrawal Source # 
Instance details

Defined in Ledger.Tx.Internal

type Rep Withdrawal = D1 ('MetaData "Withdrawal" "Ledger.Tx.Internal" "plutus-ledger-1.1.0.0-JskZbcPMCdRJVHaAZ0to82" 'False) (C1 ('MetaCons "Withdrawal" 'PrefixI 'True) (S1 ('MetaSel ('Just "withdrawalCredential") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Credential) :*: (S1 ('MetaSel ('Just "withdrawalAmount") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Integer) :*: S1 ('MetaSel ('Just "withdrawalRedeemer") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Redeemer)))))

data TxInput Source #

A transaction input, consisting of a transaction output reference and an input type. Differs with TxIn by: TxIn *maybe* contains *full* data witnesses, TxInput always contains redeemer witness, but datum/validator hashes.

Constructors

TxInput 

Instances

Instances details
Eq TxInput Source # 
Instance details

Defined in Ledger.Tx.Internal

Ord TxInput Source # 
Instance details

Defined in Ledger.Tx.Internal

Show TxInput Source # 
Instance details

Defined in Ledger.Tx.Internal

Generic TxInput Source # 
Instance details

Defined in Ledger.Tx.Internal

Associated Types

type Rep TxInput :: Type -> Type Source #

NFData TxInput Source # 
Instance details

Defined in Ledger.Tx.Internal

Methods

rnf :: TxInput -> () Source #

ToJSON TxInput Source # 
Instance details

Defined in Ledger.Tx.Internal

FromJSON TxInput Source # 
Instance details

Defined in Ledger.Tx.Internal

ToSchema TxInput Source # 
Instance details

Defined in Ledger.Tx.Internal

Pretty TxInput Source # 
Instance details

Defined in Ledger.Tx.Internal

Methods

pretty :: TxInput -> Doc ann Source #

prettyList :: [TxInput] -> Doc ann Source #

Serialise TxInput Source # 
Instance details

Defined in Ledger.Tx.Internal

type Rep TxInput Source # 
Instance details

Defined in Ledger.Tx.Internal

type Rep TxInput = D1 ('MetaData "TxInput" "Ledger.Tx.Internal" "plutus-ledger-1.1.0.0-JskZbcPMCdRJVHaAZ0to82" 'False) (C1 ('MetaCons "TxInput" 'PrefixI 'True) (S1 ('MetaSel ('Just "txInputRef") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 TxOutRef) :*: S1 ('MetaSel ('Just "txInputType") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 TxInputType)))

data TxInputType Source #

The type of a transaction input with hashes.

Constructors

TxScriptAddress !Redeemer !(Either ValidatorHash (Versioned TxOutRef)) !(Maybe DatumHash)

A transaction input that consumes (with a validator hash) or references (with a txOutRef) a script address with the given the redeemer and datum hash.

TxConsumePublicKeyAddress

A transaction input that consumes a public key address.

TxConsumeSimpleScriptAddress

Consume a simple script

Instances

Instances details
Eq TxInputType Source # 
Instance details

Defined in Ledger.Tx.Internal

Ord TxInputType Source # 
Instance details

Defined in Ledger.Tx.Internal

Show TxInputType Source # 
Instance details

Defined in Ledger.Tx.Internal

Generic TxInputType Source # 
Instance details

Defined in Ledger.Tx.Internal

Associated Types

type Rep TxInputType :: Type -> Type Source #

NFData TxInputType Source # 
Instance details

Defined in Ledger.Tx.Internal

Methods

rnf :: TxInputType -> () Source #

ToJSON TxInputType Source # 
Instance details

Defined in Ledger.Tx.Internal

FromJSON TxInputType Source # 
Instance details

Defined in Ledger.Tx.Internal

ToSchema TxInputType Source # 
Instance details

Defined in Ledger.Tx.Internal

Serialise TxInputType Source # 
Instance details

Defined in Ledger.Tx.Internal

type Rep TxInputType Source # 
Instance details

Defined in Ledger.Tx.Internal

type Rep TxInputType = D1 ('MetaData "TxInputType" "Ledger.Tx.Internal" "plutus-ledger-1.1.0.0-JskZbcPMCdRJVHaAZ0to82" 'False) (C1 ('MetaCons "TxScriptAddress" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Redeemer) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Either ValidatorHash (Versioned TxOutRef))) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe DatumHash)))) :+: (C1 ('MetaCons "TxConsumePublicKeyAddress" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "TxConsumeSimpleScriptAddress" 'PrefixI 'False) (U1 :: Type -> Type)))

data TxIn Source #

A transaction input, consisting of a transaction output reference and an input type.

Constructors

TxIn 

Instances

Instances details
Eq TxIn Source # 
Instance details

Defined in Ledger.Tx.Internal

Methods

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

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

Ord TxIn Source # 
Instance details

Defined in Ledger.Tx.Internal

Show TxIn Source # 
Instance details

Defined in Ledger.Tx.Internal

Generic TxIn Source # 
Instance details

Defined in Ledger.Tx.Internal

Associated Types

type Rep TxIn :: Type -> Type Source #

Methods

from :: TxIn -> Rep TxIn x Source #

to :: Rep TxIn x -> TxIn Source #

NFData TxIn Source # 
Instance details

Defined in Ledger.Tx.Internal

Methods

rnf :: TxIn -> () Source #

ToJSON TxIn Source # 
Instance details

Defined in Ledger.Tx.Internal

FromJSON TxIn Source # 
Instance details

Defined in Ledger.Tx.Internal

ToSchema TxIn Source # 
Instance details

Defined in Ledger.Tx.Internal

Pretty TxIn Source # 
Instance details

Defined in Ledger.Tx.Internal

Methods

pretty :: TxIn -> Doc ann Source #

prettyList :: [TxIn] -> Doc ann Source #

Serialise TxIn Source # 
Instance details

Defined in Ledger.Tx.Internal

type Rep TxIn Source # 
Instance details

Defined in Ledger.Tx.Internal

type Rep TxIn = D1 ('MetaData "TxIn" "Ledger.Tx.Internal" "plutus-ledger-1.1.0.0-JskZbcPMCdRJVHaAZ0to82" 'False) (C1 ('MetaCons "TxIn" 'PrefixI 'True) (S1 ('MetaSel ('Just "txInRef") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 TxOutRef) :*: S1 ('MetaSel ('Just "txInType") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe TxInType))))

data TxInType Source #

The type of a transaction input.

Constructors

ScriptAddress !(Either (Versioned Validator) (Versioned TxOutRef)) !Redeemer !(Maybe Datum)

A transaction input that consumes (with a validator) or references (with a txOutRef) a script address with the given the redeemer and datum. Datum is optional if the input refers to a script output which contains an inline datum

ConsumePublicKeyAddress

A transaction input that consumes a public key address.

ConsumeSimpleScriptAddress

Consume a simple script

Instances

Instances details
Eq TxInType Source # 
Instance details

Defined in Ledger.Tx.Internal

Ord TxInType Source # 
Instance details

Defined in Ledger.Tx.Internal

Show TxInType Source # 
Instance details

Defined in Ledger.Tx.Internal

Generic TxInType Source # 
Instance details

Defined in Ledger.Tx.Internal

Associated Types

type Rep TxInType :: Type -> Type Source #

NFData TxInType Source # 
Instance details

Defined in Ledger.Tx.Internal

Methods

rnf :: TxInType -> () Source #

ToJSON TxInType Source # 
Instance details

Defined in Ledger.Tx.Internal

FromJSON TxInType Source # 
Instance details

Defined in Ledger.Tx.Internal

ToSchema TxInType Source # 
Instance details

Defined in Ledger.Tx.Internal

Serialise TxInType Source # 
Instance details

Defined in Ledger.Tx.Internal

type Rep TxInType Source # 
Instance details

Defined in Ledger.Tx.Internal

type Rep TxInType = D1 ('MetaData "TxInType" "Ledger.Tx.Internal" "plutus-ledger-1.1.0.0-JskZbcPMCdRJVHaAZ0to82" 'False) (C1 ('MetaCons "ScriptAddress" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Either (Versioned Validator) (Versioned TxOutRef))) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Redeemer) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe Datum)))) :+: (C1 ('MetaCons "ConsumePublicKeyAddress" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ConsumeSimpleScriptAddress" 'PrefixI 'False) (U1 :: Type -> Type)))

pubKeyTxIn :: TxOutRef -> TxIn Source #

A transaction input that spends a "pay to public key" output, given the witness.

scriptTxIn :: TxOutRef -> Versioned Validator -> Redeemer -> Maybe Datum -> TxIn Source #

A transaction input that spends a "pay to script" output, given witnesses. Datum is optional if the input refers to a script output which contains an inline datum

inputRef :: Lens' TxInput TxOutRef Source #

The TxOutRef spent by a transaction input.

inputType :: Lens' TxInput TxInputType Source #

The type of a transaction input.

inScripts :: TxIn -> Maybe (Versioned Validator, Redeemer, Maybe Datum) Source #

Validator, redeemer, and data scripts of a transaction input that spends a "pay to script" output.

inRef :: Lens' TxInput TxOutRef Source #

The TxOutRef spent by a transaction input.

inType :: Lens' TxInput TxInputType Source #

The type of a transaction input.

pubKeyTxInputs :: Fold [TxInput] TxInput Source #

Filter to get only the pubkey inputs.

scriptTxInputs :: Fold [TxInput] TxInput Source #

Filter to get only the scripts that consume or reference a script address

referenceScriptTxInputs :: Fold [TxInput] TxInput Source #

Filter to get only the scripts that reference a script address

inputs :: Lens' Tx [TxInput] Source #

The inputs of a transaction.

referenceInputs :: Lens' Tx [TxInput] Source #

The reference inputs of a transaction.

collateralInputs :: Lens' Tx [TxInput] Source #

The collateral inputs of a transaction for paying fees when validating the transaction fails.

outputs :: Lens' Tx [TxOut] Source #

The outputs of a transaction.

validRange :: Lens' Tx SlotRange Source #

The validity range of a transaction.

metadata :: Lens' Tx (Maybe BuiltinByteString) Source #

The inputs of a transaction.

validValuesTx :: Tx -> Bool Source #

Check that all values in a transaction are non-negative.

txOutDatumHash :: TxOut -> Maybe DatumHash Source #

Get a hash from the stored TxOutDatum (either dirctly or by hashing the inlined datum)

spentOutputs :: Tx -> [TxOutRef] Source #

The transaction output references consumed by a transaction.

referencedOutputs :: Tx -> [TxOutRef] Source #

The transaction output references referenced by a transaction.

fillTxInputWitnesses :: Tx -> TxInput -> TxIn Source #

Translate TxInput to old Plutus.V1.Ledger.Api TxIn taking script and datum witnesses from Tx.

addMintingPolicy :: Versioned MintingPolicy -> (Redeemer, Maybe (Versioned TxOutRef)) -> Tx -> Tx Source #

Add minting policy together with the redeemer into txMintingWitnesses and txScripts accordingly. Doesn't alter txMint.

addScriptTxInput :: TxOutRef -> Versioned Validator -> Redeemer -> Maybe Datum -> Tx -> Tx Source #

Add validator together with the redeemer and datum into txInputs, txData and txScripts accordingly. Datum is optional if the input refers to a script output which contains an inline datum

addReferenceTxInput :: TxOutRef -> Versioned TxOutRef -> Redeemer -> Maybe Datum -> Tx -> Tx Source #

Add script reference together with the redeemer and datum into txInputs and txData accordingly. Datum is optional if the input refers to a script output which contains an inline datum

data ValidationError Source #

A reason why a transaction is invalid.

Constructors

TxOutRefNotFound TxOutRef

The transaction output consumed by a transaction input could not be found (either because it was already spent, or because there was no transaction with the given hash on the blockchain).

ScriptFailure ScriptError

For pay-to-script outputs: evaluation of the validator script failed.

CardanoLedgerValidationError Text

An error from Cardano.Ledger validation

Instances

Instances details
Eq ValidationError Source # 
Instance details

Defined in Ledger.Index.Internal

Show ValidationError Source # 
Instance details

Defined in Ledger.Index.Internal

Generic ValidationError Source # 
Instance details

Defined in Ledger.Index.Internal

Associated Types

type Rep ValidationError :: Type -> Type Source #

ToJSON ValidationError Source # 
Instance details

Defined in Ledger.Index.Internal

FromJSON ValidationError Source # 
Instance details

Defined in Ledger.Index.Internal

Pretty ValidationError Source # 
Instance details

Defined in Ledger.Index.Internal

AsValidationError ValidationError Source # 
Instance details

Defined in Ledger.Index.Internal

type Rep ValidationError Source # 
Instance details

Defined in Ledger.Index.Internal

type Rep ValidationError = D1 ('MetaData "ValidationError" "Ledger.Index.Internal" "plutus-ledger-1.1.0.0-JskZbcPMCdRJVHaAZ0to82" 'False) (C1 ('MetaCons "TxOutRefNotFound" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 TxOutRef)) :+: (C1 ('MetaCons "ScriptFailure" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ScriptError)) :+: C1 ('MetaCons "CardanoLedgerValidationError" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text))))

newtype UtxoIndex Source #

The UTxOs of a blockchain indexed by their references.

Constructors

UtxoIndex 

Instances

Instances details
Eq UtxoIndex Source # 
Instance details

Defined in Ledger.Index.Internal

Show UtxoIndex Source # 
Instance details

Defined in Ledger.Index.Internal

Generic UtxoIndex Source # 
Instance details

Defined in Ledger.Index.Internal

Associated Types

type Rep UtxoIndex :: Type -> Type Source #

Semigroup UtxoIndex Source # 
Instance details

Defined in Ledger.Index.Internal

Monoid UtxoIndex Source # 
Instance details

Defined in Ledger.Index.Internal

NFData UtxoIndex Source # 
Instance details

Defined in Ledger.Index.Internal

Methods

rnf :: UtxoIndex -> () Source #

ToJSON UtxoIndex Source # 
Instance details

Defined in Ledger.Index.Internal

FromJSON UtxoIndex Source # 
Instance details

Defined in Ledger.Index.Internal

ToSchema UtxoIndex Source # 
Instance details

Defined in Ledger.Index.Internal

Serialise UtxoIndex Source # 
Instance details

Defined in Ledger.Index.Internal

type Rep UtxoIndex Source # 
Instance details

Defined in Ledger.Index.Internal

type Rep UtxoIndex = D1 ('MetaData "UtxoIndex" "Ledger.Index.Internal" "plutus-ledger-1.1.0.0-JskZbcPMCdRJVHaAZ0to82" 'True) (C1 ('MetaCons "UtxoIndex" 'PrefixI 'True) (S1 ('MetaSel ('Just "getIndex") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Map TxOutRef TxOut))))

data ValidationPhase Source #

Constructors

Phase1 
Phase2 

Instances

Instances details
Eq ValidationPhase Source # 
Instance details

Defined in Ledger.Index.Internal

Show ValidationPhase Source # 
Instance details

Defined in Ledger.Index.Internal

Generic ValidationPhase Source # 
Instance details

Defined in Ledger.Index.Internal

Associated Types

type Rep ValidationPhase :: Type -> Type Source #

ToJSON ValidationPhase Source # 
Instance details

Defined in Ledger.Index.Internal

FromJSON ValidationPhase Source # 
Instance details

Defined in Ledger.Index.Internal

Pretty ValidationPhase Source # 
Instance details

Defined in Ledger.Index.Internal

type Rep ValidationPhase Source # 
Instance details

Defined in Ledger.Index.Internal

type Rep ValidationPhase = D1 ('MetaData "ValidationPhase" "Ledger.Index.Internal" "plutus-ledger-1.1.0.0-JskZbcPMCdRJVHaAZ0to82" 'False) (C1 ('MetaCons "Phase1" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Phase2" 'PrefixI 'False) (U1 :: Type -> Type))

data DatumFromQuery Source #

A datum in a transaction output that comes from a chain index query.

Instances

Instances details
Eq DatumFromQuery Source # 
Instance details

Defined in Ledger.Tx

Show DatumFromQuery Source # 
Instance details

Defined in Ledger.Tx

Generic DatumFromQuery Source # 
Instance details

Defined in Ledger.Tx

Associated Types

type Rep DatumFromQuery :: Type -> Type Source #

NFData DatumFromQuery Source # 
Instance details

Defined in Ledger.Tx

Methods

rnf :: DatumFromQuery -> () Source #

ToJSON DatumFromQuery Source # 
Instance details

Defined in Ledger.Tx

FromJSON DatumFromQuery Source # 
Instance details

Defined in Ledger.Tx

ToSchema DatumFromQuery Source # 
Instance details

Defined in Ledger.Tx

Serialise DatumFromQuery Source # 
Instance details

Defined in Ledger.Tx

type Rep DatumFromQuery Source # 
Instance details

Defined in Ledger.Tx

type Rep DatumFromQuery = D1 ('MetaData "DatumFromQuery" "Ledger.Tx" "plutus-ledger-1.1.0.0-JskZbcPMCdRJVHaAZ0to82" 'False) (C1 ('MetaCons "DatumUnknown" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "DatumInline" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Datum)) :+: C1 ('MetaCons "DatumInBody" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Datum))))

data DecoratedTxOut Source #

Offchain view of a transaction output.

Constructors

PublicKeyDecoratedTxOut 

Fields

ScriptDecoratedTxOut 

Fields

Instances

Instances details
Eq DecoratedTxOut Source # 
Instance details

Defined in Ledger.Tx

Show DecoratedTxOut Source # 
Instance details

Defined in Ledger.Tx

Generic DecoratedTxOut Source # 
Instance details

Defined in Ledger.Tx

Associated Types

type Rep DecoratedTxOut :: Type -> Type Source #

NFData DecoratedTxOut Source # 
Instance details

Defined in Ledger.Tx

Methods

rnf :: DecoratedTxOut -> () Source #

ToJSON DecoratedTxOut Source # 
Instance details

Defined in Ledger.Tx

FromJSON DecoratedTxOut Source # 
Instance details

Defined in Ledger.Tx

ToSchema DecoratedTxOut Source # 
Instance details

Defined in Ledger.Tx

Pretty DecoratedTxOut Source # 
Instance details

Defined in Ledger.Tx

Serialise DecoratedTxOut Source # 
Instance details

Defined in Ledger.Tx

type Rep DecoratedTxOut Source # 
Instance details

Defined in Ledger.Tx

type Rep DecoratedTxOut = D1 ('MetaData "DecoratedTxOut" "Ledger.Tx" "plutus-ledger-1.1.0.0-JskZbcPMCdRJVHaAZ0to82" 'False) (C1 ('MetaCons "PublicKeyDecoratedTxOut" 'PrefixI 'True) ((S1 ('MetaSel ('Just "_decoratedTxOutPubKeyHash") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 PubKeyHash) :*: S1 ('MetaSel ('Just "_decoratedTxOutStakingCredential") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe StakingCredential))) :*: (S1 ('MetaSel ('Just "_decoratedTxOutValue") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Value) :*: (S1 ('MetaSel ('Just "_decoratedTxOutPubKeyDatum") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (DatumHash, DatumFromQuery))) :*: S1 ('MetaSel ('Just "_decoratedTxOutReferenceScript") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (Versioned Script)))))) :+: C1 ('MetaCons "ScriptDecoratedTxOut" 'PrefixI 'True) ((S1 ('MetaSel ('Just "_decoratedTxOutValidatorHash") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ValidatorHash) :*: (S1 ('MetaSel ('Just "_decoratedTxOutStakingCredential") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe StakingCredential)) :*: S1 ('MetaSel ('Just "_decoratedTxOutValue") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Value))) :*: (S1 ('MetaSel ('Just "_decoratedTxOutScriptDatum") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (DatumHash, DatumFromQuery)) :*: (S1 ('MetaSel ('Just "_decoratedTxOutReferenceScript") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (Versioned Script))) :*: S1 ('MetaSel ('Just "_decoratedTxOutValidator") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (Versioned Validator)))))))

data CardanoTx Source #

Instances

Instances details
Eq CardanoTx Source # 
Instance details

Defined in Ledger.Tx

Show CardanoTx Source # 
Instance details

Defined in Ledger.Tx

Generic CardanoTx Source # 
Instance details

Defined in Ledger.Tx

Associated Types

type Rep CardanoTx :: Type -> Type Source #

ToJSON CardanoTx Source # 
Instance details

Defined in Ledger.Tx

FromJSON CardanoTx Source # 
Instance details

Defined in Ledger.Tx

ToSchema CardanoTx Source # 
Instance details

Defined in Ledger.Tx

Pretty CardanoTx Source # 
Instance details

Defined in Ledger.Tx

Methods

pretty :: CardanoTx -> Doc ann Source #

prettyList :: [CardanoTx] -> Doc ann Source #

Serialise CardanoTx Source # 
Instance details

Defined in Ledger.Tx

type Rep CardanoTx Source # 
Instance details

Defined in Ledger.Tx

type Rep CardanoTx = D1 ('MetaData "CardanoTx" "Ledger.Tx" "plutus-ledger-1.1.0.0-JskZbcPMCdRJVHaAZ0to82" 'False) (C1 ('MetaCons "EmulatorTx" 'PrefixI 'True) (S1 ('MetaSel ('Just "_emulatorTx") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Tx)) :+: C1 ('MetaCons "CardanoApiTx" 'PrefixI 'True) (S1 ('MetaSel ('Just "_cardanoApiTx") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SomeCardanoApiTx)))

toTxInfoTxOut :: DecoratedTxOut -> TxOut Source #

Converts a transaction output from the chain index to the plutus-ledger-api transaction output.

Note that DecoratedTxOut supports features such inline datums and reference scripts which are not supported by V1 TxOut. Converting from DecoratedTxOut to TxOut and back is therefore lossy.

onCardanoTx :: (Tx -> r) -> (SomeCardanoApiTx -> r) -> CardanoTx -> r Source #

txId :: Tx -> TxId Source #

Compute the id of a transaction.

updateUtxo :: CardanoTx -> Map TxOutRef TxOut -> Map TxOutRef TxOut Source #

Update a map of unspent transaction outputs and signatures based on the inputs and outputs of a transaction.

updateUtxoCollateral :: CardanoTx -> Map TxOutRef TxOut -> Map TxOutRef TxOut Source #

Update a map of unspent transaction outputs and signatures based on the collateral inputs of a transaction (for when it is invalid).

txOutRefs :: Tx -> [(TxOut, TxOutRef)] Source #

A list of a transaction's outputs paired with a TxOutRefs referring to them.

unspentOutputsTx :: Tx -> Map TxOutRef TxOut Source #

The unspent outputs of a transaction.

pubKeyTxOut :: Value -> PaymentPubKey -> Maybe StakingCredential -> Either ToCardanoError TxOut Source #

Create a transaction output locked by a public payment key and optionnaly a public stake key.

addSignature :: PrivateKey -> Passphrase -> Tx -> Tx Source #

Sign the transaction with a PrivateKey and passphrase (ByteString) and add the signature to the transaction's list of signatures.

addSignature' :: PrivateKey -> Tx -> Tx Source #

Sign the transaction with a PrivateKey that has no passphrase and add the signature to the transaction's list of signatures

type Blockchain = [Block] Source #

A blockchain, which is just a list of blocks, starting with the newest.

type Block = [OnChainTx] Source #

A block on the blockchain. This is just a list of transactions following on from the chain so far.

data OnChainTx Source #

A transaction on the blockchain. Invalid transactions are still put on the chain to be able to collect fees.

Instances

Instances details
Eq OnChainTx Source # 
Instance details

Defined in Ledger.Blockchain

Show OnChainTx Source # 
Instance details

Defined in Ledger.Blockchain

Generic OnChainTx Source # 
Instance details

Defined in Ledger.Blockchain

Associated Types

type Rep OnChainTx :: Type -> Type Source #

ToJSON OnChainTx Source # 
Instance details

Defined in Ledger.Blockchain

FromJSON OnChainTx Source # 
Instance details

Defined in Ledger.Blockchain

Pretty OnChainTx Source # 
Instance details

Defined in Ledger.Blockchain

Methods

pretty :: OnChainTx -> Doc ann Source #

prettyList :: [OnChainTx] -> Doc ann Source #

Serialise OnChainTx Source # 
Instance details

Defined in Ledger.Blockchain

type Rep OnChainTx Source # 
Instance details

Defined in Ledger.Blockchain

type Rep OnChainTx = D1 ('MetaData "OnChainTx" "Ledger.Blockchain" "plutus-ledger-1.1.0.0-JskZbcPMCdRJVHaAZ0to82" 'False) (C1 ('MetaCons "Invalid" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 CardanoTx)) :+: C1 ('MetaCons "Valid" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 CardanoTx)))

newtype BlockId Source #

Block identifier (usually a hash)

Constructors

BlockId 

Instances

Instances details
Eq BlockId Source # 
Instance details

Defined in Ledger.Blockchain

Ord BlockId Source # 
Instance details

Defined in Ledger.Blockchain

Show BlockId Source # 
Instance details

Defined in Ledger.Blockchain

Generic BlockId Source # 
Instance details

Defined in Ledger.Blockchain

Associated Types

type Rep BlockId :: Type -> Type Source #

ToJSON BlockId Source # 
Instance details

Defined in Ledger.Blockchain

FromJSON BlockId Source # 
Instance details

Defined in Ledger.Blockchain

ToSchema BlockId Source # 
Instance details

Defined in Ledger.Blockchain

Pretty BlockId Source # 
Instance details

Defined in Ledger.Blockchain

Methods

pretty :: BlockId -> Doc ann Source #

prettyList :: [BlockId] -> Doc ann Source #

type Rep BlockId Source # 
Instance details

Defined in Ledger.Blockchain

type Rep BlockId = D1 ('MetaData "BlockId" "Ledger.Blockchain" "plutus-ledger-1.1.0.0-JskZbcPMCdRJVHaAZ0to82" 'True) (C1 ('MetaCons "BlockId" 'PrefixI 'True) (S1 ('MetaSel ('Just "getBlockId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ByteString)))

eitherTx :: (CardanoTx -> r) -> (CardanoTx -> r) -> OnChainTx -> r Source #

consumableInputs :: OnChainTx -> [TxIn] Source #

Outputs consumed from the UTXO set by the OnChainTx

outputsProduced :: OnChainTx -> Map TxOutRef TxOut Source #

Outputs added to the UTXO set by the OnChainTx

transaction :: Blockchain -> TxId -> Maybe OnChainTx Source #

Lookup a transaction in a Blockchain by its id.

out :: Blockchain -> TxOutRef -> Maybe TxOut Source #

Determine the unspent output that an input refers to

value :: Blockchain -> TxOutRef -> Maybe Value Source #

Determine the unspent value that a transaction output refers to.

datumTxo :: Blockchain -> TxOutRef -> Maybe DatumHash Source #

Determine the data script that a transaction output refers to.

pubKeyTxo :: Blockchain -> TxOutRef -> Maybe PubKeyHash Source #

Determine the public key that locks a transaction output, if there is one.

unspentOutputs :: Blockchain -> Map TxOutRef TxOut Source #

The unspent transaction outputs of the ledger as a whole.

initialise :: Blockchain -> UtxoIndex Source #

Create an index of all UTxOs on the chain.

insert :: CardanoTx -> UtxoIndex -> UtxoIndex Source #

Update the index for the addition of a transaction.

insertCollateral :: CardanoTx -> UtxoIndex -> UtxoIndex Source #

Update the index for the addition of only the collateral inputs of a failed transaction.

insertBlock :: Block -> UtxoIndex -> UtxoIndex Source #

Update the index for the addition of a block.

lookup :: MonadError ValidationError m => TxOutRef -> UtxoIndex -> m TxOut Source #

Find an unspent transaction output by the TxOutRef that spends it.

scriptTxIns :: Fold [TxIn] TxIn Source #

Filter to get only the script inputs.

pubKeyTxIns :: Fold [TxIn] TxIn Source #

Filter to get only the pubkey inputs.

adjustTxOut :: PParams (BabbageEra StandardCrypto) -> TxOut -> Either ToCardanoError ([Ada], TxOut) Source #

Adjust a single transaction output so it contains at least the minimum amount of Ada and return the adjustment (if any) and the updated TxOut.

minAdaTxOut :: PParams (BabbageEra StandardCrypto) -> TxOut -> Ada Source #

Exact computation of the mimimum Ada required for a given TxOut. TODO: Should be moved to cardano-api-extended once created

minAdaTxOutEstimated :: Ada Source #

Provide a reasonable estimate of the mimimum of Ada required for a TxOut.

An exact estimate of the the mimimum of Ada in a TxOut is determined by two things: - the PParams, more precisely its coinPerUTxOWord parameter. - the size of the TxOut. In many situations though, we need to determine a plausible value for the minimum of Ada needed for a TxOut without knowing much of the TxOut. This function provides a value big enough to balance UTxOs without a large inlined data (larger than a hash) nor a complex val with a lot of minted values. It's superior to the lowest minimum needed for an UTxO, as the lowest value require no datum. An estimate of the minimum required Ada for each tx output.

minFee :: Tx -> Value Source #

Minimum transaction fee.

maxFee :: Ada Source #

TODO Should be calculated based on the maximum script size permitted on the Cardano blockchain.

data AssetClass Source #

An asset class, identified by currency symbol and token name.

Instances

Instances details
Eq AssetClass 
Instance details

Defined in Plutus.V1.Ledger.Value

Data AssetClass 
Instance details

Defined in Plutus.V1.Ledger.Value

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> AssetClass -> c AssetClass Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c AssetClass Source #

toConstr :: AssetClass -> Constr Source #

dataTypeOf :: AssetClass -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c AssetClass) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c AssetClass) Source #

gmapT :: (forall b. Data b => b -> b) -> AssetClass -> AssetClass Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> AssetClass -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> AssetClass -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> AssetClass -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> AssetClass -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> AssetClass -> m AssetClass Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> AssetClass -> m AssetClass Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> AssetClass -> m AssetClass Source #

Ord AssetClass 
Instance details

Defined in Plutus.V1.Ledger.Value

Show AssetClass 
Instance details

Defined in Plutus.V1.Ledger.Value

Generic AssetClass 
Instance details

Defined in Plutus.V1.Ledger.Value

Associated Types

type Rep AssetClass :: Type -> Type Source #

NFData AssetClass 
Instance details

Defined in Plutus.V1.Ledger.Value

Methods

rnf :: AssetClass -> () Source #

Hashable AssetClass Source # 
Instance details

Defined in Ledger.Value.Orphans

ToJSON AssetClass Source # 
Instance details

Defined in Ledger.Value.Orphans

FromJSON AssetClass Source # 
Instance details

Defined in Ledger.Value.Orphans

ToSchema AssetClass Source # 
Instance details

Defined in Ledger.Orphans

Pretty AssetClass 
Instance details

Defined in Plutus.V1.Ledger.Value

Serialise AssetClass Source # 
Instance details

Defined in Ledger.Value.Orphans

UnsafeFromData AssetClass 
Instance details

Defined in Plutus.V1.Ledger.Value

FromData AssetClass 
Instance details

Defined in Plutus.V1.Ledger.Value

ToData AssetClass 
Instance details

Defined in Plutus.V1.Ledger.Value

Ord AssetClass 
Instance details

Defined in Plutus.V1.Ledger.Value

Eq AssetClass 
Instance details

Defined in Plutus.V1.Ledger.Value

Lift DefaultUni AssetClass 
Instance details

Defined in Plutus.V1.Ledger.Value

Typeable DefaultUni AssetClass 
Instance details

Defined in Plutus.V1.Ledger.Value

type Rep AssetClass 
Instance details

Defined in Plutus.V1.Ledger.Value

type Rep AssetClass = D1 ('MetaData "AssetClass" "Plutus.V1.Ledger.Value" "plutus-ledger-api-1.0.0.1-EUjexvcAhXiGIaLon6olWb" 'True) (C1 ('MetaCons "AssetClass" 'PrefixI 'True) (S1 ('MetaSel ('Just "unAssetClass") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (CurrencySymbol, TokenName))))

data CurrencySymbol Source #

Instances

Instances details
Eq CurrencySymbol 
Instance details

Defined in Plutus.V1.Ledger.Value

Data CurrencySymbol 
Instance details

Defined in Plutus.V1.Ledger.Value

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> CurrencySymbol -> c CurrencySymbol Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c CurrencySymbol Source #

toConstr :: CurrencySymbol -> Constr Source #

dataTypeOf :: CurrencySymbol -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c CurrencySymbol) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c CurrencySymbol) Source #

gmapT :: (forall b. Data b => b -> b) -> CurrencySymbol -> CurrencySymbol Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> CurrencySymbol -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> CurrencySymbol -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> CurrencySymbol -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> CurrencySymbol -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> CurrencySymbol -> m CurrencySymbol Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> CurrencySymbol -> m CurrencySymbol Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> CurrencySymbol -> m CurrencySymbol Source #

Ord CurrencySymbol 
Instance details

Defined in Plutus.V1.Ledger.Value

Show CurrencySymbol 
Instance details

Defined in Plutus.V1.Ledger.Value

IsString CurrencySymbol 
Instance details

Defined in Plutus.V1.Ledger.Value

Generic CurrencySymbol 
Instance details

Defined in Plutus.V1.Ledger.Value

Associated Types

type Rep CurrencySymbol :: Type -> Type Source #

NFData CurrencySymbol 
Instance details

Defined in Plutus.V1.Ledger.Value

Methods

rnf :: CurrencySymbol -> () Source #

Hashable CurrencySymbol Source # 
Instance details

Defined in Ledger.Value.Orphans

ToJSON CurrencySymbol Source # 
Instance details

Defined in Ledger.Value.Orphans

FromJSON CurrencySymbol Source # 
Instance details

Defined in Ledger.Value.Orphans

ToSchema CurrencySymbol Source # 
Instance details

Defined in Ledger.Orphans

Pretty CurrencySymbol 
Instance details

Defined in Plutus.V1.Ledger.Value

Serialise CurrencySymbol Source # 
Instance details

Defined in Ledger.Value.Orphans

UnsafeFromData CurrencySymbol 
Instance details

Defined in Plutus.V1.Ledger.Value

FromData CurrencySymbol 
Instance details

Defined in Plutus.V1.Ledger.Value

ToData CurrencySymbol 
Instance details

Defined in Plutus.V1.Ledger.Value

Ord CurrencySymbol 
Instance details

Defined in Plutus.V1.Ledger.Value

Eq CurrencySymbol 
Instance details

Defined in Plutus.V1.Ledger.Value

Lift DefaultUni CurrencySymbol 
Instance details

Defined in Plutus.V1.Ledger.Value

Typeable DefaultUni CurrencySymbol 
Instance details

Defined in Plutus.V1.Ledger.Value

type Rep CurrencySymbol 
Instance details

Defined in Plutus.V1.Ledger.Value

type Rep CurrencySymbol = D1 ('MetaData "CurrencySymbol" "Plutus.V1.Ledger.Value" "plutus-ledger-api-1.0.0.1-EUjexvcAhXiGIaLon6olWb" 'True) (C1 ('MetaCons "CurrencySymbol" 'PrefixI 'True) (S1 ('MetaSel ('Just "unCurrencySymbol") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 BuiltinByteString)))

data TokenName Source #

ByteString of a name of a token, shown as UTF-8 string when possible

Instances

Instances details
Eq TokenName 
Instance details

Defined in Plutus.V1.Ledger.Value

Data TokenName 
Instance details

Defined in Plutus.V1.Ledger.Value

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> TokenName -> c TokenName Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c TokenName Source #

toConstr :: TokenName -> Constr Source #

dataTypeOf :: TokenName -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c TokenName) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TokenName) Source #

gmapT :: (forall b. Data b => b -> b) -> TokenName -> TokenName Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TokenName -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TokenName -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> TokenName -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> TokenName -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> TokenName -> m TokenName Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> TokenName -> m TokenName Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> TokenName -> m TokenName Source #

Ord TokenName 
Instance details

Defined in Plutus.V1.Ledger.Value

Show TokenName 
Instance details

Defined in Plutus.V1.Ledger.Value

IsString TokenName 
Instance details

Defined in Plutus.V1.Ledger.Value

Generic TokenName 
Instance details

Defined in Plutus.V1.Ledger.Value

Associated Types

type Rep TokenName :: Type -> Type Source #

NFData TokenName 
Instance details

Defined in Plutus.V1.Ledger.Value

Methods

rnf :: TokenName -> () Source #

Hashable TokenName Source # 
Instance details

Defined in Ledger.Value.Orphans

ToJSON TokenName Source # 
Instance details

Defined in Ledger.Value.Orphans

FromJSON TokenName Source # 
Instance details

Defined in Ledger.Value.Orphans

ToSchema TokenName Source # 
Instance details

Defined in Ledger.Orphans

Pretty TokenName 
Instance details

Defined in Plutus.V1.Ledger.Value

Methods

pretty :: TokenName -> Doc ann Source #

prettyList :: [TokenName] -> Doc ann Source #

Serialise TokenName Source # 
Instance details

Defined in Ledger.Value.Orphans

UnsafeFromData TokenName 
Instance details

Defined in Plutus.V1.Ledger.Value

FromData TokenName 
Instance details

Defined in Plutus.V1.Ledger.Value

ToData TokenName 
Instance details

Defined in Plutus.V1.Ledger.Value

Ord TokenName 
Instance details

Defined in Plutus.V1.Ledger.Value

Eq TokenName 
Instance details

Defined in Plutus.V1.Ledger.Value

Lift DefaultUni TokenName 
Instance details

Defined in Plutus.V1.Ledger.Value

Typeable DefaultUni TokenName 
Instance details

Defined in Plutus.V1.Ledger.Value

type Rep TokenName 
Instance details

Defined in Plutus.V1.Ledger.Value

type Rep TokenName = D1 ('MetaData "TokenName" "Plutus.V1.Ledger.Value" "plutus-ledger-api-1.0.0.1-EUjexvcAhXiGIaLon6olWb" 'True) (C1 ('MetaCons "TokenName" 'PrefixI 'True) (S1 ('MetaSel ('Just "unTokenName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 BuiltinByteString)))

data Value Source #

A cryptocurrency value. This is a map from CurrencySymbols to a quantity of that currency.

Operations on currencies are usually implemented pointwise. That is, we apply the operation to the quantities for each currency in turn. So when we add two Values the resulting Value has, for each currency, the sum of the quantities of that particular currency in the argument Value. The effect of this is that the currencies in the Value are "independent", and are operated on separately.

Whenever we need to get the quantity of a currency in a Value where there is no explicit quantity of that currency in the Value, then the quantity is taken to be zero.

See note [Currencies] for more details.

Instances

Instances details
Eq Value 
Instance details

Defined in Plutus.V1.Ledger.Value

Methods

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

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

Data Value 
Instance details

Defined in Plutus.V1.Ledger.Value

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Value -> c Value Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Value Source #

toConstr :: Value -> Constr Source #

dataTypeOf :: Value -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Value) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Value) Source #

gmapT :: (forall b. Data b => b -> b) -> Value -> Value Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Value -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Value -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> Value -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Value -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Value -> m Value Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Value -> m Value Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Value -> m Value Source #

Show Value 
Instance details

Defined in Plutus.V1.Ledger.Value

Generic Value 
Instance details

Defined in Plutus.V1.Ledger.Value

Associated Types

type Rep Value :: Type -> Type Source #

Methods

from :: Value -> Rep Value x Source #

to :: Rep Value x -> Value Source #

Semigroup Value 
Instance details

Defined in Plutus.V1.Ledger.Value

Monoid Value 
Instance details

Defined in Plutus.V1.Ledger.Value

NFData Value 
Instance details

Defined in Plutus.V1.Ledger.Value

Methods

rnf :: Value -> () Source #

Hashable Value Source # 
Instance details

Defined in Ledger.Value.Orphans

ToJSON Value Source # 
Instance details

Defined in Ledger.Value.Orphans

FromJSON Value Source # 
Instance details

Defined in Ledger.Value.Orphans

ToSchema Value Source # 
Instance details

Defined in Ledger.Orphans

Pretty Value 
Instance details

Defined in Plutus.V1.Ledger.Value

Methods

pretty :: Value -> Doc ann Source #

prettyList :: [Value] -> Doc ann Source #

Serialise Value Source # 
Instance details

Defined in Ledger.Value.Orphans

UnsafeFromData Value 
Instance details

Defined in Plutus.V1.Ledger.Value

FromData Value 
Instance details

Defined in Plutus.V1.Ledger.Value

ToData Value 
Instance details

Defined in Plutus.V1.Ledger.Value

JoinSemiLattice Value 
Instance details

Defined in Plutus.V1.Ledger.Value

Methods

(\/) :: Value -> Value -> Value Source #

MeetSemiLattice Value 
Instance details

Defined in Plutus.V1.Ledger.Value

Methods

(/\) :: Value -> Value -> Value Source #

AdditiveSemigroup Value 
Instance details

Defined in Plutus.V1.Ledger.Value

Methods

(+) :: Value -> Value -> Value Source #

AdditiveMonoid Value 
Instance details

Defined in Plutus.V1.Ledger.Value

Methods

zero :: Value Source #

AdditiveGroup Value 
Instance details

Defined in Plutus.V1.Ledger.Value

Methods

(-) :: Value -> Value -> Value Source #

Monoid Value 
Instance details

Defined in Plutus.V1.Ledger.Value

Methods

mempty :: Value Source #

Group Value 
Instance details

Defined in Plutus.V1.Ledger.Value

Methods

inv :: Value -> Value Source #

Semigroup Value 
Instance details

Defined in Plutus.V1.Ledger.Value

Methods

(<>) :: Value -> Value -> Value Source #

Eq Value 
Instance details

Defined in Plutus.V1.Ledger.Value

Methods

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

Module Integer Value 
Instance details

Defined in Plutus.V1.Ledger.Value

Methods

scale :: Integer -> Value -> Value Source #

Lift DefaultUni Value 
Instance details

Defined in Plutus.V1.Ledger.Value

Typeable DefaultUni Value 
Instance details

Defined in Plutus.V1.Ledger.Value

type Rep Value 
Instance details

Defined in Plutus.V1.Ledger.Value

type Rep Value = D1 ('MetaData "Value" "Plutus.V1.Ledger.Value" "plutus-ledger-api-1.0.0.1-EUjexvcAhXiGIaLon6olWb" 'True) (C1 ('MetaCons "Value" 'PrefixI 'True) (S1 ('MetaSel ('Just "getValue") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Map CurrencySymbol (Map TokenName Integer)))))

data Ada Source #

ADA, the special currency on the Cardano blockchain. The unit of Ada is Lovelace, and 1M Lovelace is one Ada. See note [Currencies] in TH.

Instances

Instances details
Enum Ada Source # 
Instance details

Defined in Ledger.Ada

Eq Ada Source # 
Instance details

Defined in Ledger.Ada

Methods

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

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

Integral Ada Source # 
Instance details

Defined in Ledger.Ada

Methods

quot :: Ada -> Ada -> Ada Source #

rem :: Ada -> Ada -> Ada Source #

div :: Ada -> Ada -> Ada Source #

mod :: Ada -> Ada -> Ada Source #

quotRem :: Ada -> Ada -> (Ada, Ada) Source #

divMod :: Ada -> Ada -> (Ada, Ada) Source #

toInteger :: Ada -> Integer Source #

Num Ada Source # 
Instance details

Defined in Ledger.Ada

Ord Ada Source # 
Instance details

Defined in Ledger.Ada

Methods

compare :: Ada -> Ada -> Ordering Source #

(<) :: Ada -> Ada -> Bool Source #

(<=) :: Ada -> Ada -> Bool Source #

(>) :: Ada -> Ada -> Bool Source #

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

max :: Ada -> Ada -> Ada Source #

min :: Ada -> Ada -> Ada Source #

Real Ada Source # 
Instance details

Defined in Ledger.Ada

Show Ada Source # 
Instance details

Defined in Ledger.Ada

Generic Ada Source # 
Instance details

Defined in Ledger.Ada

Associated Types

type Rep Ada :: Type -> Type Source #

Methods

from :: Ada -> Rep Ada x Source #

to :: Rep Ada x -> Ada Source #

Semigroup Ada Source # 
Instance details

Defined in Ledger.Ada

Methods

(<>) :: Ada -> Ada -> Ada Source #

sconcat :: NonEmpty Ada -> Ada Source #

stimes :: Integral b => b -> Ada -> Ada Source #

Monoid Ada Source # 
Instance details

Defined in Ledger.Ada

ToJSON Ada Source # 
Instance details

Defined in Ledger.Ada

FromJSON Ada Source # 
Instance details

Defined in Ledger.Ada

ToSchema Ada Source # 
Instance details

Defined in Ledger.Orphans

Pretty Ada Source # 
Instance details

Defined in Ledger.Ada

Methods

pretty :: Ada -> Doc ann Source #

prettyList :: [Ada] -> Doc ann Source #

Serialise Ada Source # 
Instance details

Defined in Ledger.Ada

UnsafeFromData Ada Source # 
Instance details

Defined in Ledger.Ada

FromData Ada Source # 
Instance details

Defined in Ledger.Ada

ToData Ada Source # 
Instance details

Defined in Ledger.Ada

AdditiveSemigroup Ada Source # 
Instance details

Defined in Ledger.Ada

Methods

(+) :: Ada -> Ada -> Ada Source #

AdditiveMonoid Ada Source # 
Instance details

Defined in Ledger.Ada

Methods

zero :: Ada Source #

AdditiveGroup Ada Source # 
Instance details

Defined in Ledger.Ada

Methods

(-) :: Ada -> Ada -> Ada Source #

MultiplicativeSemigroup Ada Source # 
Instance details

Defined in Ledger.Ada

Methods

(*) :: Ada -> Ada -> Ada Source #

MultiplicativeMonoid Ada Source # 
Instance details

Defined in Ledger.Ada

Methods

one :: Ada Source #

Monoid Ada Source # 
Instance details

Defined in Ledger.Ada

Methods

mempty :: Ada Source #

Semigroup Ada Source # 
Instance details

Defined in Ledger.Ada

Methods

(<>) :: Ada -> Ada -> Ada Source #

Ord Ada Source # 
Instance details

Defined in Ledger.Ada

Methods

compare :: Ada -> Ada -> Ordering Source #

(<) :: Ada -> Ada -> Bool Source #

(<=) :: Ada -> Ada -> Bool Source #

(>) :: Ada -> Ada -> Bool Source #

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

max :: Ada -> Ada -> Ada Source #

min :: Ada -> Ada -> Ada Source #

Eq Ada Source # 
Instance details

Defined in Ledger.Ada

Methods

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

Lift DefaultUni Ada Source # 
Instance details

Defined in Ledger.Ada

Typeable DefaultUni Ada Source # 
Instance details

Defined in Ledger.Ada

type Rep Ada Source # 
Instance details

Defined in Ledger.Ada

type Rep Ada = D1 ('MetaData "Ada" "Ledger.Ada" "plutus-ledger-1.1.0.0-JskZbcPMCdRJVHaAZ0to82" 'True) (C1 ('MetaCons "Lovelace" 'PrefixI 'True) (S1 ('MetaSel ('Just "getLovelace") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Integer)))

data DCert Source #

A representation of the ledger DCert. Some information is digested, and not included

Instances

Instances details
Eq DCert 
Instance details

Defined in Plutus.V1.Ledger.DCert

Methods

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

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

Ord DCert 
Instance details

Defined in Plutus.V1.Ledger.DCert

Show DCert 
Instance details

Defined in Plutus.V1.Ledger.DCert

Generic DCert 
Instance details

Defined in Plutus.V1.Ledger.DCert

Associated Types

type Rep DCert :: Type -> Type Source #

Methods

from :: DCert -> Rep DCert x Source #

to :: Rep DCert x -> DCert Source #

NFData DCert 
Instance details

Defined in Plutus.V1.Ledger.DCert

Methods

rnf :: DCert -> () Source #

ToJSON DCert Source # 
Instance details

Defined in Ledger.DCert.Orphans

FromJSON DCert Source # 
Instance details

Defined in Ledger.DCert.Orphans

ToSchema DCert Source # 
Instance details

Defined in Ledger.Orphans

Pretty DCert 
Instance details

Defined in Plutus.V1.Ledger.DCert

Methods

pretty :: DCert -> Doc ann Source #

prettyList :: [DCert] -> Doc ann Source #

Serialise DCert Source # 
Instance details

Defined in Ledger.DCert.Orphans

UnsafeFromData DCert 
Instance details

Defined in Plutus.V1.Ledger.DCert

FromData DCert 
Instance details

Defined in Plutus.V1.Ledger.DCert

ToData DCert 
Instance details

Defined in Plutus.V1.Ledger.DCert

Eq DCert 
Instance details

Defined in Plutus.V1.Ledger.DCert

Methods

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

Lift DefaultUni DCert 
Instance details

Defined in Plutus.V1.Ledger.DCert

Typeable DefaultUni DCert 
Instance details

Defined in Plutus.V1.Ledger.DCert

type Rep DCert 
Instance details

Defined in Plutus.V1.Ledger.DCert

data NetworkId Source #

Instances

Instances details
Eq NetworkId 
Instance details

Defined in Cardano.Api.NetworkId

Data NetworkId Source # 
Instance details

Defined in Ledger.Orphans

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> NetworkId -> c NetworkId Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c NetworkId Source #

toConstr :: NetworkId -> Constr Source #

dataTypeOf :: NetworkId -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c NetworkId) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c NetworkId) Source #

gmapT :: (forall b. Data b => b -> b) -> NetworkId -> NetworkId Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> NetworkId -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> NetworkId -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> NetworkId -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> NetworkId -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> NetworkId -> m NetworkId Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> NetworkId -> m NetworkId Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> NetworkId -> m NetworkId Source #

Show NetworkId 
Instance details

Defined in Cardano.Api.NetworkId

Generic NetworkId Source # 
Instance details

Defined in Ledger.Orphans

Associated Types

type Rep NetworkId :: Type -> Type Source #

type Rep NetworkId Source # 
Instance details

Defined in Ledger.Orphans

type Rep NetworkId = D1 ('MetaData "NetworkId" "Cardano.Api.NetworkId" "cardano-api-1.35.4-1Qeb0LwBSO04Jx7qro0yT5" 'False) (C1 ('MetaCons "Mainnet" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Testnet" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedUnpack) (Rec0 NetworkMagic)))

data Credential Source #

Credential required to unlock a transaction output

Instances

Instances details
Eq Credential 
Instance details

Defined in Plutus.V1.Ledger.Credential

Ord Credential 
Instance details

Defined in Plutus.V1.Ledger.Credential

Show Credential 
Instance details

Defined in Plutus.V1.Ledger.Credential

Generic Credential 
Instance details

Defined in Plutus.V1.Ledger.Credential

Associated Types

type Rep Credential :: Type -> Type Source #

NFData Credential 
Instance details

Defined in Plutus.V1.Ledger.Credential

Methods

rnf :: Credential -> () Source #

Hashable Credential Source # 
Instance details

Defined in Ledger.Credential.Orphans

ToJSON Credential Source # 
Instance details

Defined in Ledger.Credential.Orphans

FromJSON Credential Source # 
Instance details

Defined in Ledger.Credential.Orphans

ToSchema Credential Source # 
Instance details

Defined in Ledger.Credential.Orphans

Pretty Credential 
Instance details

Defined in Plutus.V1.Ledger.Credential

Serialise Credential Source # 
Instance details

Defined in Ledger.Credential.Orphans

UnsafeFromData Credential 
Instance details

Defined in Plutus.V1.Ledger.Credential

FromData Credential 
Instance details

Defined in Plutus.V1.Ledger.Credential

ToData Credential 
Instance details

Defined in Plutus.V1.Ledger.Credential

Eq Credential 
Instance details

Defined in Plutus.V1.Ledger.Credential

Lift DefaultUni Credential 
Instance details

Defined in Plutus.V1.Ledger.Credential

Typeable DefaultUni Credential 
Instance details

Defined in Plutus.V1.Ledger.Credential

type Rep Credential 
Instance details

Defined in Plutus.V1.Ledger.Credential

type Rep Credential = D1 ('MetaData "Credential" "Plutus.V1.Ledger.Credential" "plutus-ledger-api-1.0.0.1-EUjexvcAhXiGIaLon6olWb" 'False) (C1 ('MetaCons "PubKeyCredential" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 PubKeyHash)) :+: C1 ('MetaCons "ScriptCredential" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ValidatorHash)))

data StakingCredential Source #

Staking credential used to assign rewards

Instances

Instances details
Eq StakingCredential 
Instance details

Defined in Plutus.V1.Ledger.Credential

Ord StakingCredential 
Instance details

Defined in Plutus.V1.Ledger.Credential

Show StakingCredential 
Instance details

Defined in Plutus.V1.Ledger.Credential

Generic StakingCredential 
Instance details

Defined in Plutus.V1.Ledger.Credential

Associated Types

type Rep StakingCredential :: Type -> Type Source #

NFData StakingCredential 
Instance details

Defined in Plutus.V1.Ledger.Credential

Methods

rnf :: StakingCredential -> () Source #

Hashable StakingCredential Source # 
Instance details

Defined in Ledger.Credential.Orphans

ToJSON StakingCredential Source # 
Instance details

Defined in Ledger.Credential.Orphans

FromJSON StakingCredential Source # 
Instance details

Defined in Ledger.Credential.Orphans

ToSchema StakingCredential Source # 
Instance details

Defined in Ledger.Credential.Orphans

Pretty StakingCredential 
Instance details

Defined in Plutus.V1.Ledger.Credential

Serialise StakingCredential Source # 
Instance details

Defined in Ledger.Credential.Orphans

UnsafeFromData StakingCredential 
Instance details

Defined in Plutus.V1.Ledger.Credential

FromData StakingCredential 
Instance details

Defined in Plutus.V1.Ledger.Credential

ToData StakingCredential 
Instance details

Defined in Plutus.V1.Ledger.Credential

Eq StakingCredential 
Instance details

Defined in Plutus.V1.Ledger.Credential

Lift DefaultUni StakingCredential 
Instance details

Defined in Plutus.V1.Ledger.Credential

Typeable DefaultUni StakingCredential 
Instance details

Defined in Plutus.V1.Ledger.Credential

type Rep StakingCredential 
Instance details

Defined in Plutus.V1.Ledger.Credential