{-# LANGUAGE PatternSynonyms #-}
module PlutusLedgerApi.Data.V1 (
SerialisedScript,
ScriptForEvaluation,
serialisedScript,
deserialisedScript,
serialiseCompiledCode,
serialiseUPLC,
deserialiseScript,
uncheckedDeserialiseUPLC,
evaluateScriptRestricting,
evaluateScriptCounting,
MajorProtocolVersion (..),
VerboseMode (..),
LogOutput,
ExBudget (..),
ExCPU (..),
ExMemory (..),
SatInt (unSatInt),
fromSatInt,
EvaluationContext,
mkEvaluationContext,
ParamName (..),
CostModelApplyError (..),
CostModelParams,
assertWellFormedCostModelParams,
ScriptContext,
pattern ScriptContext,
scriptContextTxInfo,
scriptContextPurpose,
ScriptPurpose,
pattern Minting,
pattern Spending,
pattern Rewarding,
pattern Certifying,
BuiltinByteString,
toBuiltin,
fromBuiltin,
LedgerBytes (..),
fromBytes,
DCert,
pattern DCertDelegRegKey,
pattern DCertDelegDeRegKey,
pattern DCertDelegDelegate,
pattern DCertPoolRegister,
pattern DCertPoolRetire,
pattern DCertGenesis,
pattern DCertMir,
StakingCredential,
pattern StakingHash,
pattern StakingPtr,
Credential,
pattern PubKeyCredential,
pattern ScriptCredential,
Value (..),
CurrencySymbol (..),
TokenName (..),
singleton,
unionWith,
adaSymbol,
adaToken,
Lovelace (..),
POSIXTime (..),
POSIXTimeRange,
Address,
pattern Address,
addressCredential,
addressStakingCredential,
PubKeyHash (..),
TxId (..),
TxInfo,
pattern TxInfo,
txInfoInputs,
txInfoOutputs,
txInfoFee,
txInfoMint,
txInfoDCert,
txInfoWdrl,
txInfoValidRange,
txInfoSignatories,
txInfoData,
txInfoId,
TxOut,
pattern TxOut,
txOutAddress,
txOutValue,
txOutDatumHash,
TxOutRef,
pattern TxOutRef,
txOutRefId,
txOutRefIdx,
TxInInfo,
pattern TxInInfo,
txInInfoOutRef,
txInInfoResolved,
Interval,
pattern Interval,
ivFrom,
ivTo,
Extended,
pattern NegInf,
pattern PosInf,
pattern Finite,
Closure,
UpperBound,
pattern UpperBound,
LowerBound,
pattern LowerBound,
always,
from,
to,
lowerBound,
upperBound,
strictLowerBound,
strictUpperBound,
ScriptHash (..),
Redeemer (..),
RedeemerHash (..),
Datum (..),
DatumHash (..),
PLC.Data (..),
BuiltinData (..),
ToData (..),
FromData (..),
UnsafeFromData (..),
toData,
fromData,
dataToBuiltinData,
builtinDataToData,
EvaluationError (..),
ScriptDecodeError (..),
) where
import Data.SatInt
import PlutusCore.Data qualified as PLC
import PlutusCore.Evaluation.Machine.ExBudget as PLC
import PlutusLedgerApi.Common as Common hiding (deserialiseScript, evaluateScriptCounting,
evaluateScriptRestricting)
import PlutusLedgerApi.Common qualified as Common (deserialiseScript, evaluateScriptCounting,
evaluateScriptRestricting)
import PlutusLedgerApi.V1.Bytes
import PlutusLedgerApi.V1.Crypto
import PlutusLedgerApi.V1.Data.Address
import PlutusLedgerApi.V1.Data.Contexts
import PlutusLedgerApi.V1.Data.Credential
import PlutusLedgerApi.V1.Data.DCert
import PlutusLedgerApi.V1.Data.Interval hiding (singleton)
import PlutusLedgerApi.V1.Data.Time
import PlutusLedgerApi.V1.Data.Value
import PlutusLedgerApi.V1.EvaluationContext
import PlutusLedgerApi.V1.ParamName
import PlutusLedgerApi.V1.Scripts as Scripts
thisLedgerLanguage :: PlutusLedgerLanguage
thisLedgerLanguage :: PlutusLedgerLanguage
thisLedgerLanguage = PlutusLedgerLanguage
PlutusV1
deserialiseScript
:: forall m
. (MonadError ScriptDecodeError m)
=> MajorProtocolVersion
-> SerialisedScript
-> m ScriptForEvaluation
deserialiseScript :: forall (m :: * -> *).
MonadError ScriptDecodeError m =>
MajorProtocolVersion -> SerialisedScript -> m ScriptForEvaluation
deserialiseScript = PlutusLedgerLanguage
-> MajorProtocolVersion
-> SerialisedScript
-> m ScriptForEvaluation
forall (m :: * -> *).
MonadError ScriptDecodeError m =>
PlutusLedgerLanguage
-> MajorProtocolVersion
-> SerialisedScript
-> m ScriptForEvaluation
Common.deserialiseScript PlutusLedgerLanguage
thisLedgerLanguage
evaluateScriptCounting
:: MajorProtocolVersion
-> VerboseMode
-> EvaluationContext
-> ScriptForEvaluation
-> [PLC.Data]
-> (LogOutput, Either EvaluationError ExBudget)
evaluateScriptCounting :: MajorProtocolVersion
-> VerboseMode
-> EvaluationContext
-> ScriptForEvaluation
-> [Data]
-> (LogOutput, Either EvaluationError ExBudget)
evaluateScriptCounting = PlutusLedgerLanguage
-> MajorProtocolVersion
-> VerboseMode
-> EvaluationContext
-> ScriptForEvaluation
-> [Data]
-> (LogOutput, Either EvaluationError ExBudget)
Common.evaluateScriptCounting PlutusLedgerLanguage
thisLedgerLanguage
evaluateScriptRestricting
:: MajorProtocolVersion
-> VerboseMode
-> EvaluationContext
-> ExBudget
-> ScriptForEvaluation
-> [PLC.Data]
-> (LogOutput, Either EvaluationError ExBudget)
evaluateScriptRestricting :: MajorProtocolVersion
-> VerboseMode
-> EvaluationContext
-> ExBudget
-> ScriptForEvaluation
-> [Data]
-> (LogOutput, Either EvaluationError ExBudget)
evaluateScriptRestricting = PlutusLedgerLanguage
-> MajorProtocolVersion
-> VerboseMode
-> EvaluationContext
-> ExBudget
-> ScriptForEvaluation
-> [Data]
-> (LogOutput, Either EvaluationError ExBudget)
Common.evaluateScriptRestricting PlutusLedgerLanguage
thisLedgerLanguage