Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Plutarch.LedgerApi.V2
Synopsis
- data PScriptPurpose (s :: S)
- = PMinting (Term s (PAsData PCurrencySymbol))
- | PSpending (Term s PTxOutRef)
- | PRewarding (Term s PStakingCredential)
- | PCertifying (Term s PDCert)
- data PScriptContext (s :: S) = PScriptContext {
- pscriptContext'txInfo :: Term s PTxInfo
- pscriptContext'purpose :: Term s PScriptPurpose
- data PDCert (s :: S)
- = PDCertDelegRegKey (Term s PStakingCredential)
- | PDCertDelegDeRegKey (Term s PStakingCredential)
- | PDCertDelegDelegate (Term s PStakingCredential) (Term s (PAsData PPubKeyHash))
- | PDCertPoolRegister (Term s (PAsData PPubKeyHash)) (Term s (PAsData PPubKeyHash))
- | PDCertPoolRetire (Term s (PAsData PPubKeyHash)) (Term s (PAsData PInteger))
- | PDCertGenesis
- | PDCertMir
- data PCredential (s :: S)
- = PPubKeyCredential (Term s (PAsData PPubKeyHash))
- | PScriptCredential (Term s (PAsData PScriptHash))
- data PStakingCredential (s :: S)
- = PStakingHash (Term s PCredential)
- | PStakingPtr (Term s (PAsData PInteger)) (Term s (PAsData PInteger)) (Term s (PAsData PInteger))
- newtype PValue (keys :: KeyGuarantees) (amounts :: AmountGuarantees) (s :: S) = PValue (Term s (PMap keys PCurrencySymbol (PMap keys PTokenName PInteger)))
- data AmountGuarantees
- newtype PLovelace (s :: S) = PLovelace (Term s PInteger)
- newtype PTokenName (s :: S) = PTokenName (Term s PByteString)
- newtype PCurrencySymbol (s :: S) = PCurrencySymbol (Term s PByteString)
- newtype PPosixTime (s :: S) = PPosixTime (Term s PInteger)
- pposixTime :: forall (s :: S). Term s PInteger -> Term s PPosixTime
- unPPosixTime :: forall (s :: S). Term s PPosixTime -> Term s PInteger
- data PExtended (a :: S -> Type) (s :: S)
- data PLowerBound (a :: S -> Type) (s :: S) = PLowerBound (Term s (PExtended a)) (Term s (PAsData PBool))
- data PUpperBound (a :: S -> Type) (s :: S) = PUpperBound (Term s (PExtended a)) (Term s (PAsData PBool))
- data PInterval (a :: S -> Type) (s :: S) = PInterval {
- pinteral'from :: Term s (PLowerBound a)
- pinteral'to :: Term s (PUpperBound a)
- newtype PDatum (s :: S) = PDatum (Term s PData)
- newtype PRedeemer (s :: S) = PRedeemer (Term s PData)
- newtype PDatumHash (s :: S) = PDatumHash (Term s PByteString)
- newtype PRedeemerHash (s :: S) = PRedeemerHash (Term s PByteString)
- newtype PScriptHash (s :: S) = PScriptHash (Term s PByteString)
- data PAddress (s :: S) = PAddress {
- paddress'credential :: Term s PCredential
- paddress'stakingCredential :: Term s (PMaybeData PStakingCredential)
- newtype PPubKeyHash (s :: S) = PPubKeyHash (Term s PByteString)
- newtype PTxId (s :: S) = PTxId (Term s (PAsData PByteString))
- data PTxInfo (s :: S) = PTxInfo {
- ptxInfo'inputs :: Term s (PAsData (PBuiltinList (PAsData PTxInInfo)))
- ptxInfo'referenceInputs :: Term s (PAsData (PBuiltinList (PAsData PTxInInfo)))
- ptxInfo'outputs :: Term s (PAsData (PBuiltinList (PAsData PTxOut)))
- ptxInfo'fee :: Term s (PAsData (PValue 'Sorted 'Positive))
- ptxInfo'mint :: Term s (PAsData (PValue 'Sorted 'NoGuarantees))
- ptxInfo'dcert :: Term s (PAsData (PBuiltinList (PAsData PDCert)))
- ptxInfo'wdrl :: Term s (PAsData (PMap 'Unsorted PStakingCredential PInteger))
- ptxInfo'validRange :: Term s (PInterval PPosixTime)
- ptxInfo'signatories :: Term s (PAsData (PBuiltinList (PAsData PPubKeyHash)))
- ptxInfo'redeemers :: Term s (PAsData (PMap 'Unsorted PScriptPurpose PRedeemer))
- ptxInfo'data :: Term s (PAsData (PMap 'Unsorted PDatumHash PDatum))
- ptxInfo'id :: Term s PTxId
- data PTxOut (s :: S) = PTxOut {
- ptxOut'address :: Term s PAddress
- ptxOut'value :: Term s (PAsData (PValue 'Sorted 'Positive))
- ptxOut'datum :: Term s POutputDatum
- ptxOut'referenceScript :: Term s (PMaybeData PScriptHash)
- data PTxOutRef (s :: S) = PTxOutRef {
- ptxOutRef'id :: Term s PTxId
- ptxOutRef'idx :: Term s (PAsData PInteger)
- data PTxInInfo (s :: S) = PTxInInfo {
- ptxInInfo'outRef :: Term s PTxOutRef
- ptxInInfo'resolved :: Term s PTxOut
- data POutputDatum (s :: S)
- = PNoOutputDatum
- | POutputDatumHash {
- poutputDatum'datumHash :: Term s (PAsData PDatumHash)
- | POutputDatum {
- poutputDatum'outputDatum :: Term s PDatum
- newtype PMap (keysort :: KeyGuarantees) (k :: S -> Type) (v :: S -> Type) (s :: S) = PMap (Term s (PBuiltinList (PBuiltinPair (PAsData k) (PAsData v))))
- data KeyGuarantees
- data Commutativity
- data PMaybeData (a :: S -> Type) (s :: S)
- data PRationalData s = PRationalData {
- prationalData'numerator :: Term s (PAsData PInteger)
- prationalData'denominator :: Term s (PAsData PPositive)
- pfromDJust :: forall (a :: S -> Type) (s :: S). PIsData a => Term s (PMaybeData a :--> a)
- pisDJust :: forall (a :: S -> Type) (s :: S). Term s (PMaybeData a :--> PBool)
- pmaybeData :: forall (a :: S -> Type) (b :: S -> Type) (s :: S). PIsData a => Term s (b :--> ((a :--> b) :--> (PMaybeData a :--> b)))
- pdjust :: forall (a :: S -> Type) (s :: S). PIsData a => Term s (a :--> PMaybeData a)
- pdnothing :: forall (a :: S -> Type) (s :: S). Term s (PMaybeData a)
- pmaybeToMaybeData :: forall (a :: S -> Type) (s :: S). PIsData a => Term s (PMaybe a :--> PMaybeData a)
- passertPDJust :: forall (a :: S -> Type) (s :: S). PIsData a => Term s (PString :--> (PMaybeData a :--> a))
- prationalFromData :: ClosedTerm (PRationalData :--> PRational)
Contexts
data PScriptPurpose (s :: S) Source #
Since: 3.1.1
Constructors
PMinting (Term s (PAsData PCurrencySymbol)) | |
PSpending (Term s PTxOutRef) | |
PRewarding (Term s PStakingCredential) | |
PCertifying (Term s PDCert) |
Instances
data PScriptContext (s :: S) Source #
Since: 3.1.1
Constructors
PScriptContext | |
Fields
|
Instances
PEq PScriptContext Source # | Since: 3.1.1 |
Defined in Plutarch.LedgerApi.V2 Methods (#==) :: forall (s :: S). Term s PScriptContext -> Term s PScriptContext -> Term s PBool | |
PIsData PScriptContext Source # | Since: 3.1.1 |
Defined in Plutarch.LedgerApi.V2 Methods pfromDataImpl :: forall (s :: S). Term s (PAsData PScriptContext) -> Term s PScriptContext pdataImpl :: forall (s :: S). Term s PScriptContext -> Term s PData | |
PLiftable PScriptContext Source # | |
Defined in Plutarch.LedgerApi.V2 Methods haskToRepr :: AsHaskell PScriptContext -> PlutusRepr PScriptContext reprToHask :: PlutusRepr PScriptContext -> Either LiftError (AsHaskell PScriptContext) reprToPlut :: forall (s :: S). PlutusRepr PScriptContext -> PLifted s PScriptContext plutToRepr :: (forall (s :: S). PLifted s PScriptContext) -> Either LiftError (PlutusRepr PScriptContext) | |
PlutusType PScriptContext Source # | |
Defined in Plutarch.LedgerApi.V2 Associated Types type PInner PScriptContext :: PType type PCovariant' PScriptContext type PContravariant' PScriptContext type PVariant' PScriptContext Methods pcon' :: forall (s :: S). PScriptContext s -> Term s (PInner PScriptContext) pmatch' :: forall (s :: S) (b :: PType). Term s (PInner PScriptContext) -> (PScriptContext s -> Term s b) -> Term s b | |
PShow PScriptContext Source # | Since: 3.1.1 |
Defined in Plutarch.LedgerApi.V2 Methods pshow' :: forall (s :: S). Bool -> Term s PScriptContext -> Term s PString | |
Generic (PScriptContext s) Source # | |
Defined in Plutarch.LedgerApi.V2 Methods from :: PScriptContext s -> Rep (PScriptContext s) x Source # to :: Rep (PScriptContext s) x -> PScriptContext s Source # | |
Generic (PScriptContext s) Source # | |
Defined in Plutarch.LedgerApi.V2 Associated Types type Code (PScriptContext s) :: [[Type]] Methods from :: PScriptContext s -> Rep (PScriptContext s) to :: Rep (PScriptContext s) -> PScriptContext s | |
type AsHaskell PScriptContext Source # | Since: 3.3.0 |
Defined in Plutarch.LedgerApi.V2 | |
type PlutusRepr PScriptContext Source # | |
Defined in Plutarch.LedgerApi.V2 | |
type PContravariant' PScriptContext Source # | |
Defined in Plutarch.LedgerApi.V2 | |
type PCovariant' PScriptContext Source # | |
Defined in Plutarch.LedgerApi.V2 | |
type PInner PScriptContext Source # | Since: 3.3.0 |
Defined in Plutarch.LedgerApi.V2 | |
type PVariant' PScriptContext Source # | |
Defined in Plutarch.LedgerApi.V2 | |
type Rep (PScriptContext s) Source # | Since: 3.1.1 |
Defined in Plutarch.LedgerApi.V2 type Rep (PScriptContext s) = D1 ('MetaData "PScriptContext" "Plutarch.LedgerApi.V2" "plutarch-ledger-api-3.3.0-9uebfPQOA90BujqVBUbxih" 'False) (C1 ('MetaCons "PScriptContext" 'PrefixI 'True) (S1 ('MetaSel ('Just "pscriptContext'txInfo") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Term s PTxInfo)) :*: S1 ('MetaSel ('Just "pscriptContext'purpose") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Term s PScriptPurpose)))) | |
type Code (PScriptContext s) Source # | Since: 3.3.0 |
Defined in Plutarch.LedgerApi.V2 |
Certificates
Since: 3.1.1
Constructors
PDCertDelegRegKey (Term s PStakingCredential) | |
PDCertDelegDeRegKey (Term s PStakingCredential) | |
PDCertDelegDelegate (Term s PStakingCredential) (Term s (PAsData PPubKeyHash)) | |
PDCertPoolRegister (Term s (PAsData PPubKeyHash)) (Term s (PAsData PPubKeyHash)) | |
PDCertPoolRetire (Term s (PAsData PPubKeyHash)) (Term s (PAsData PInteger)) | |
PDCertGenesis | |
PDCertMir |
Instances
Credentials
data PCredential (s :: S) Source #
Since: 2.0.0
Constructors
PPubKeyCredential (Term s (PAsData PPubKeyHash)) | |
PScriptCredential (Term s (PAsData PScriptHash)) |
Instances
PEq PCredential Source # | Since: 2.0.0 |
Defined in Plutarch.LedgerApi.V1.Credential Methods (#==) :: forall (s :: S). Term s PCredential -> Term s PCredential -> Term s PBool | |
PIsData PCredential Source # | Since: 2.0.0 |
Defined in Plutarch.LedgerApi.V1.Credential Methods pfromDataImpl :: forall (s :: S). Term s (PAsData PCredential) -> Term s PCredential pdataImpl :: forall (s :: S). Term s PCredential -> Term s PData | |
PLiftable PCredential Source # | |
Defined in Plutarch.LedgerApi.V1.Credential Methods haskToRepr :: AsHaskell PCredential -> PlutusRepr PCredential reprToHask :: PlutusRepr PCredential -> Either LiftError (AsHaskell PCredential) reprToPlut :: forall (s :: S). PlutusRepr PCredential -> PLifted s PCredential plutToRepr :: (forall (s :: S). PLifted s PCredential) -> Either LiftError (PlutusRepr PCredential) | |
PlutusType PCredential Source # | |
Defined in Plutarch.LedgerApi.V1.Credential Associated Types type PInner PCredential :: PType type PCovariant' PCredential type PContravariant' PCredential type PVariant' PCredential Methods pcon' :: forall (s :: S). PCredential s -> Term s (PInner PCredential) pmatch' :: forall (s :: S) (b :: PType). Term s (PInner PCredential) -> (PCredential s -> Term s b) -> Term s b | |
PShow PCredential Source # | Since: 2.0.0 |
Defined in Plutarch.LedgerApi.V1.Credential Methods pshow' :: forall (s :: S). Bool -> Term s PCredential -> Term s PString | |
Generic (PCredential s) Source # | |
Defined in Plutarch.LedgerApi.V1.Credential Methods from :: PCredential s -> Rep (PCredential s) x Source # to :: Rep (PCredential s) x -> PCredential s Source # | |
Generic (PCredential s) Source # | |
Defined in Plutarch.LedgerApi.V1.Credential Associated Types type Code (PCredential s) :: [[Type]] | |
type AsHaskell PCredential Source # | Since: 3.3.0 |
Defined in Plutarch.LedgerApi.V1.Credential | |
type PlutusRepr PCredential Source # | |
Defined in Plutarch.LedgerApi.V1.Credential | |
type PContravariant' PCredential Source # | |
Defined in Plutarch.LedgerApi.V1.Credential | |
type PCovariant' PCredential Source # | |
Defined in Plutarch.LedgerApi.V1.Credential | |
type PInner PCredential Source # | Since: 3.3.0 |
Defined in Plutarch.LedgerApi.V1.Credential | |
type PVariant' PCredential Source # | |
Defined in Plutarch.LedgerApi.V1.Credential | |
type Rep (PCredential s) Source # | Since: 2.0.0 |
Defined in Plutarch.LedgerApi.V1.Credential type Rep (PCredential s) = D1 ('MetaData "PCredential" "Plutarch.LedgerApi.V1.Credential" "plutarch-ledger-api-3.3.0-9uebfPQOA90BujqVBUbxih" 'False) (C1 ('MetaCons "PPubKeyCredential" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Term s (PAsData PPubKeyHash)))) :+: C1 ('MetaCons "PScriptCredential" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Term s (PAsData PScriptHash))))) | |
type Code (PCredential s) Source # | Since: 3.3.0 |
Defined in Plutarch.LedgerApi.V1.Credential |
data PStakingCredential (s :: S) Source #
Since: 2.0.0
Constructors
PStakingHash (Term s PCredential) | |
PStakingPtr (Term s (PAsData PInteger)) (Term s (PAsData PInteger)) (Term s (PAsData PInteger)) |
Instances
Value
newtype PValue (keys :: KeyGuarantees) (amounts :: AmountGuarantees) (s :: S) Source #
Since: 2.0.0
Constructors
PValue (Term s (PMap keys PCurrencySymbol (PMap keys PTokenName PInteger))) |
Instances
Semigroup (Term s (PValue 'Sorted normalization)) => Monoid (Term s (PValue 'Sorted normalization)) Source # | Since: 2.0.0 |
Defined in Plutarch.LedgerApi.Value Methods mempty :: Term s (PValue 'Sorted normalization) Source # mappend :: Term s (PValue 'Sorted normalization) -> Term s (PValue 'Sorted normalization) -> Term s (PValue 'Sorted normalization) Source # mconcat :: [Term s (PValue 'Sorted normalization)] -> Term s (PValue 'Sorted normalization) Source # | |
Semigroup (Term s (PValue 'Sorted 'NoGuarantees)) Source # | Since: 2.0.0 |
Defined in Plutarch.LedgerApi.Value Methods (<>) :: Term s (PValue 'Sorted 'NoGuarantees) -> Term s (PValue 'Sorted 'NoGuarantees) -> Term s (PValue 'Sorted 'NoGuarantees) Source # sconcat :: NonEmpty (Term s (PValue 'Sorted 'NoGuarantees)) -> Term s (PValue 'Sorted 'NoGuarantees) Source # stimes :: Integral b => b -> Term s (PValue 'Sorted 'NoGuarantees) -> Term s (PValue 'Sorted 'NoGuarantees) Source # | |
Semigroup (Term s (PValue 'Sorted 'NonZero)) Source # | Since: 2.0.0 |
Defined in Plutarch.LedgerApi.Value Methods (<>) :: Term s (PValue 'Sorted 'NonZero) -> Term s (PValue 'Sorted 'NonZero) -> Term s (PValue 'Sorted 'NonZero) Source # sconcat :: NonEmpty (Term s (PValue 'Sorted 'NonZero)) -> Term s (PValue 'Sorted 'NonZero) Source # stimes :: Integral b => b -> Term s (PValue 'Sorted 'NonZero) -> Term s (PValue 'Sorted 'NonZero) Source # | |
Semigroup (Term s (PValue 'Sorted 'Positive)) Source # | Since: 2.0.0 |
Defined in Plutarch.LedgerApi.Value Methods (<>) :: Term s (PValue 'Sorted 'Positive) -> Term s (PValue 'Sorted 'Positive) -> Term s (PValue 'Sorted 'Positive) Source # sconcat :: NonEmpty (Term s (PValue 'Sorted 'Positive)) -> Term s (PValue 'Sorted 'Positive) Source # stimes :: Integral b => b -> Term s (PValue 'Sorted 'Positive) -> Term s (PValue 'Sorted 'Positive) Source # | |
PEq (PValue 'Sorted 'NoGuarantees) Source # | Since: 2.0.0 |
Defined in Plutarch.LedgerApi.Value Methods (#==) :: forall (s :: S). Term s (PValue 'Sorted 'NoGuarantees) -> Term s (PValue 'Sorted 'NoGuarantees) -> Term s PBool | |
PEq (PValue 'Sorted 'NonZero) Source # | Since: 2.0.0 |
PEq (PValue 'Sorted 'Positive) Source # | Since: 2.0.0 |
PIsData (PValue keys amounts) Source # | Since: 2.0.0 |
Defined in Plutarch.LedgerApi.Value Methods pfromDataImpl :: forall (s :: S). Term s (PAsData (PValue keys amounts)) -> Term s (PValue keys amounts) pdataImpl :: forall (s :: S). Term s (PValue keys amounts) -> Term s PData | |
PLiftable (PValue 'Unsorted 'NoGuarantees) Source # | |
Defined in Plutarch.LedgerApi.Value Associated Types type AsHaskell (PValue 'Unsorted 'NoGuarantees) type PlutusRepr (PValue 'Unsorted 'NoGuarantees) Methods haskToRepr :: AsHaskell (PValue 'Unsorted 'NoGuarantees) -> PlutusRepr (PValue 'Unsorted 'NoGuarantees) reprToHask :: PlutusRepr (PValue 'Unsorted 'NoGuarantees) -> Either LiftError (AsHaskell (PValue 'Unsorted 'NoGuarantees)) reprToPlut :: forall (s :: S). PlutusRepr (PValue 'Unsorted 'NoGuarantees) -> PLifted s (PValue 'Unsorted 'NoGuarantees) plutToRepr :: (forall (s :: S). PLifted s (PValue 'Unsorted 'NoGuarantees)) -> Either LiftError (PlutusRepr (PValue 'Unsorted 'NoGuarantees)) | |
PlutusType (PValue keys amounts) Source # | |
Defined in Plutarch.LedgerApi.Value | |
PSemigroup (PValue 'Sorted normalization) => PMonoid (PValue 'Sorted normalization) Source # | Since: 3.3.0 |
PSemigroup (PValue 'Sorted 'NoGuarantees) Source # | Since: 3.3.0 |
Defined in Plutarch.LedgerApi.Value Methods (#<>) :: forall (s :: S). Term s (PValue 'Sorted 'NoGuarantees) -> Term s (PValue 'Sorted 'NoGuarantees) -> Term s (PValue 'Sorted 'NoGuarantees) pstimes :: forall (s :: S). Term s PPositive -> Term s (PValue 'Sorted 'NoGuarantees) -> Term s (PValue 'Sorted 'NoGuarantees) | |
PSemigroup (PValue 'Sorted 'NonZero) Source # | Since: 3.3.0 |
PSemigroup (PValue 'Sorted 'Positive) Source # | Since: 3.3.0 |
PShow (PValue keys amounts) Source # | Since: 2.0.0 |
Defined in Plutarch.LedgerApi.Value | |
Semigroup (Term s (PValue 'Sorted 'NoGuarantees)) => Group (Term s (PValue 'Sorted 'NoGuarantees)) Source # | Since: 2.0.0 |
Defined in Plutarch.LedgerApi.Value Methods inv :: Term s (PValue 'Sorted 'NoGuarantees) -> Term s (PValue 'Sorted 'NoGuarantees) | |
Semigroup (Term s (PValue 'Sorted 'NonZero)) => Group (Term s (PValue 'Sorted 'NonZero)) Source # | Since: 2.0.0 |
Semigroup (Term s (PValue 'Sorted normalization)) => Monoid (Term s (PValue 'Sorted normalization)) Source # | Since: 2.0.0 |
Defined in Plutarch.LedgerApi.Value | |
Semigroup (Term s (PValue 'Sorted 'NoGuarantees)) Source # | Since: 2.0.0 |
Defined in Plutarch.LedgerApi.Value Methods (<>) :: Term s (PValue 'Sorted 'NoGuarantees) -> Term s (PValue 'Sorted 'NoGuarantees) -> Term s (PValue 'Sorted 'NoGuarantees) | |
Semigroup (Term s (PValue 'Sorted 'NonZero)) Source # | Since: 2.0.0 |
Semigroup (Term s (PValue 'Sorted 'Positive)) Source # | Since: 2.0.0 |
Generic (PValue keys amounts s) Source # | |
Generic (PValue keys amounts s) Source # | |
type AsHaskell (PValue 'Unsorted 'NoGuarantees) Source # | Since: 3.3.0 |
Defined in Plutarch.LedgerApi.Value type AsHaskell (PValue 'Unsorted 'NoGuarantees) = AsHaskell (DeriveNewtypePLiftable (PValue 'Unsorted 'NoGuarantees) Value) | |
type PlutusRepr (PValue 'Unsorted 'NoGuarantees) Source # | |
Defined in Plutarch.LedgerApi.Value type PlutusRepr (PValue 'Unsorted 'NoGuarantees) = PlutusRepr (DeriveNewtypePLiftable (PValue 'Unsorted 'NoGuarantees) Value) | |
type PContravariant' (PValue keys amounts) Source # | |
Defined in Plutarch.LedgerApi.Value | |
type PCovariant' (PValue keys amounts) Source # | |
Defined in Plutarch.LedgerApi.Value | |
type PInner (PValue keys amounts) Source # | Since: 3.3.0 |
Defined in Plutarch.LedgerApi.Value | |
type PVariant' (PValue keys amounts) Source # | |
Defined in Plutarch.LedgerApi.Value | |
type Rep (PValue keys amounts s) Source # | Since: 2.0.0 |
Defined in Plutarch.LedgerApi.Value type Rep (PValue keys amounts s) = D1 ('MetaData "PValue" "Plutarch.LedgerApi.Value" "plutarch-ledger-api-3.3.0-9uebfPQOA90BujqVBUbxih" 'True) (C1 ('MetaCons "PValue" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Term s (PMap keys PCurrencySymbol (PMap keys PTokenName PInteger)))))) | |
type Code (PValue keys amounts s) Source # | Since: 3.3.0 |
Defined in Plutarch.LedgerApi.Value |
newtype PLovelace (s :: S) Source #
Since: 2.2.0
Constructors
PLovelace (Term s PInteger) |
Instances
PEq PLovelace Source # | Since: 2.2.0 |
Defined in Plutarch.LedgerApi.Value | |
PIsData PLovelace Source # | Since: 2.2.0 |
Defined in Plutarch.LedgerApi.Value Methods pfromDataImpl :: forall (s :: S). Term s (PAsData PLovelace) -> Term s PLovelace pdataImpl :: forall (s :: S). Term s PLovelace -> Term s PData | |
PLiftable PLovelace Source # | |
Defined in Plutarch.LedgerApi.Value Methods haskToRepr :: AsHaskell PLovelace -> PlutusRepr PLovelace reprToHask :: PlutusRepr PLovelace -> Either LiftError (AsHaskell PLovelace) reprToPlut :: forall (s :: S). PlutusRepr PLovelace -> PLifted s PLovelace plutToRepr :: (forall (s :: S). PLifted s PLovelace) -> Either LiftError (PlutusRepr PLovelace) | |
POrd PLovelace Source # | Since: 3.3.0 |
Defined in Plutarch.LedgerApi.Value Methods (#<=) :: forall (s :: S). Term s PLovelace -> Term s PLovelace -> Term s PBool (#<) :: forall (s :: S). Term s PLovelace -> Term s PLovelace -> Term s PBool pmax :: forall (s :: S). Term s PLovelace -> Term s PLovelace -> Term s PLovelace pmin :: forall (s :: S). Term s PLovelace -> Term s PLovelace -> Term s PLovelace | |
PlutusType PLovelace Source # | |
Defined in Plutarch.LedgerApi.Value | |
PShow PLovelace Source # | Since: 2.2.0 |
Defined in Plutarch.LedgerApi.Value | |
Generic (PLovelace s) Source # | |
Generic (PLovelace s) Source # | |
type AsHaskell PLovelace Source # | Since: 3.3.0 |
Defined in Plutarch.LedgerApi.Value | |
type PlutusRepr PLovelace Source # | |
Defined in Plutarch.LedgerApi.Value | |
type PContravariant' PLovelace Source # | |
Defined in Plutarch.LedgerApi.Value | |
type PCovariant' PLovelace Source # | |
Defined in Plutarch.LedgerApi.Value | |
type PInner PLovelace Source # | Since: 3.3.0 |
Defined in Plutarch.LedgerApi.Value | |
type PVariant' PLovelace Source # | |
Defined in Plutarch.LedgerApi.Value | |
type Rep (PLovelace s) Source # | Since: 2.2.0 |
Defined in Plutarch.LedgerApi.Value type Rep (PLovelace s) = D1 ('MetaData "PLovelace" "Plutarch.LedgerApi.Value" "plutarch-ledger-api-3.3.0-9uebfPQOA90BujqVBUbxih" 'True) (C1 ('MetaCons "PLovelace" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Term s PInteger)))) | |
type Code (PLovelace s) Source # | Since: 3.3.0 |
Defined in Plutarch.LedgerApi.Value |
newtype PTokenName (s :: S) Source #
Since: 2.0.0
Constructors
PTokenName (Term s PByteString) |
Instances
PEq PTokenName Source # | Since: 2.0.0 |
Defined in Plutarch.LedgerApi.Value Methods (#==) :: forall (s :: S). Term s PTokenName -> Term s PTokenName -> Term s PBool | |
PIsData PTokenName Source # | Since: 2.0.0 |
Defined in Plutarch.LedgerApi.Value Methods pfromDataImpl :: forall (s :: S). Term s (PAsData PTokenName) -> Term s PTokenName pdataImpl :: forall (s :: S). Term s PTokenName -> Term s PData | |
PLiftable PTokenName Source # | Since: 3.3.0 |
Defined in Plutarch.LedgerApi.Value Methods haskToRepr :: AsHaskell PTokenName -> PlutusRepr PTokenName reprToHask :: PlutusRepr PTokenName -> Either LiftError (AsHaskell PTokenName) reprToPlut :: forall (s :: S). PlutusRepr PTokenName -> PLifted s PTokenName plutToRepr :: (forall (s :: S). PLifted s PTokenName) -> Either LiftError (PlutusRepr PTokenName) | |
POrd PTokenName Source # | Since: 2.0.0 |
Defined in Plutarch.LedgerApi.Value Methods (#<=) :: forall (s :: S). Term s PTokenName -> Term s PTokenName -> Term s PBool (#<) :: forall (s :: S). Term s PTokenName -> Term s PTokenName -> Term s PBool pmax :: forall (s :: S). Term s PTokenName -> Term s PTokenName -> Term s PTokenName pmin :: forall (s :: S). Term s PTokenName -> Term s PTokenName -> Term s PTokenName | |
PlutusType PTokenName Source # | |
Defined in Plutarch.LedgerApi.Value Associated Types type PInner PTokenName :: PType type PCovariant' PTokenName type PContravariant' PTokenName type PVariant' PTokenName Methods pcon' :: forall (s :: S). PTokenName s -> Term s (PInner PTokenName) pmatch' :: forall (s :: S) (b :: PType). Term s (PInner PTokenName) -> (PTokenName s -> Term s b) -> Term s b | |
PShow PTokenName Source # | Since: 2.0.0 |
Defined in Plutarch.LedgerApi.Value Methods pshow' :: forall (s :: S). Bool -> Term s PTokenName -> Term s PString | |
Generic (PTokenName s) Source # | |
Defined in Plutarch.LedgerApi.Value Methods from :: PTokenName s -> Rep (PTokenName s) x Source # to :: Rep (PTokenName s) x -> PTokenName s Source # | |
Generic (PTokenName s) Source # | |
Defined in Plutarch.LedgerApi.Value Associated Types type Code (PTokenName s) :: [[Type]] | |
type AsHaskell PTokenName Source # | |
Defined in Plutarch.LedgerApi.Value type AsHaskell PTokenName = TokenName | |
type PlutusRepr PTokenName Source # | |
Defined in Plutarch.LedgerApi.Value | |
type PContravariant' PTokenName Source # | |
Defined in Plutarch.LedgerApi.Value | |
type PCovariant' PTokenName Source # | |
Defined in Plutarch.LedgerApi.Value | |
type PInner PTokenName Source # | Since: 3.3.0 |
Defined in Plutarch.LedgerApi.Value | |
type PVariant' PTokenName Source # | |
Defined in Plutarch.LedgerApi.Value | |
type Rep (PTokenName s) Source # | Since: 2.0.0 |
Defined in Plutarch.LedgerApi.Value type Rep (PTokenName s) = D1 ('MetaData "PTokenName" "Plutarch.LedgerApi.Value" "plutarch-ledger-api-3.3.0-9uebfPQOA90BujqVBUbxih" 'True) (C1 ('MetaCons "PTokenName" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Term s PByteString)))) | |
type Code (PTokenName s) Source # | Since: 3.3.0 |
Defined in Plutarch.LedgerApi.Value |
newtype PCurrencySymbol (s :: S) Source #
Since: 2.0.0
Constructors
PCurrencySymbol (Term s PByteString) |
Instances
PEq PCurrencySymbol Source # | Since: 2.0.0 |
Defined in Plutarch.LedgerApi.Value Methods (#==) :: forall (s :: S). Term s PCurrencySymbol -> Term s PCurrencySymbol -> Term s PBool | |
PIsData PCurrencySymbol Source # | Since: 2.0.0 |
Defined in Plutarch.LedgerApi.Value Methods pfromDataImpl :: forall (s :: S). Term s (PAsData PCurrencySymbol) -> Term s PCurrencySymbol pdataImpl :: forall (s :: S). Term s PCurrencySymbol -> Term s PData | |
PLiftable PCurrencySymbol Source # | Since: 3.3.0 |
Defined in Plutarch.LedgerApi.Value Methods haskToRepr :: AsHaskell PCurrencySymbol -> PlutusRepr PCurrencySymbol reprToHask :: PlutusRepr PCurrencySymbol -> Either LiftError (AsHaskell PCurrencySymbol) reprToPlut :: forall (s :: S). PlutusRepr PCurrencySymbol -> PLifted s PCurrencySymbol plutToRepr :: (forall (s :: S). PLifted s PCurrencySymbol) -> Either LiftError (PlutusRepr PCurrencySymbol) | |
POrd PCurrencySymbol Source # | Since: 2.0.0 |
Defined in Plutarch.LedgerApi.Value Methods (#<=) :: forall (s :: S). Term s PCurrencySymbol -> Term s PCurrencySymbol -> Term s PBool (#<) :: forall (s :: S). Term s PCurrencySymbol -> Term s PCurrencySymbol -> Term s PBool pmax :: forall (s :: S). Term s PCurrencySymbol -> Term s PCurrencySymbol -> Term s PCurrencySymbol pmin :: forall (s :: S). Term s PCurrencySymbol -> Term s PCurrencySymbol -> Term s PCurrencySymbol | |
PlutusType PCurrencySymbol Source # | |
Defined in Plutarch.LedgerApi.Value Associated Types type PInner PCurrencySymbol :: PType type PCovariant' PCurrencySymbol type PContravariant' PCurrencySymbol type PVariant' PCurrencySymbol Methods pcon' :: forall (s :: S). PCurrencySymbol s -> Term s (PInner PCurrencySymbol) pmatch' :: forall (s :: S) (b :: PType). Term s (PInner PCurrencySymbol) -> (PCurrencySymbol s -> Term s b) -> Term s b | |
PShow PCurrencySymbol Source # | Since: 2.0.0 |
Defined in Plutarch.LedgerApi.Value Methods pshow' :: forall (s :: S). Bool -> Term s PCurrencySymbol -> Term s PString | |
Generic (PCurrencySymbol s) Source # | |
Defined in Plutarch.LedgerApi.Value Methods from :: PCurrencySymbol s -> Rep (PCurrencySymbol s) x Source # to :: Rep (PCurrencySymbol s) x -> PCurrencySymbol s Source # | |
Generic (PCurrencySymbol s) Source # | |
Defined in Plutarch.LedgerApi.Value Associated Types type Code (PCurrencySymbol s) :: [[Type]] Methods from :: PCurrencySymbol s -> Rep (PCurrencySymbol s) to :: Rep (PCurrencySymbol s) -> PCurrencySymbol s | |
type AsHaskell PCurrencySymbol Source # | |
Defined in Plutarch.LedgerApi.Value type AsHaskell PCurrencySymbol = CurrencySymbol | |
type PlutusRepr PCurrencySymbol Source # | |
Defined in Plutarch.LedgerApi.Value | |
type PContravariant' PCurrencySymbol Source # | |
Defined in Plutarch.LedgerApi.Value | |
type PCovariant' PCurrencySymbol Source # | |
Defined in Plutarch.LedgerApi.Value | |
type PInner PCurrencySymbol Source # | Since: 3.3.0 |
Defined in Plutarch.LedgerApi.Value | |
type PVariant' PCurrencySymbol Source # | |
Defined in Plutarch.LedgerApi.Value | |
type Rep (PCurrencySymbol s) Source # | Since: 2.0.0 |
Defined in Plutarch.LedgerApi.Value type Rep (PCurrencySymbol s) = D1 ('MetaData "PCurrencySymbol" "Plutarch.LedgerApi.Value" "plutarch-ledger-api-3.3.0-9uebfPQOA90BujqVBUbxih" 'True) (C1 ('MetaCons "PCurrencySymbol" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Term s PByteString)))) | |
type Code (PCurrencySymbol s) Source # | Since: 3.3.0 |
Defined in Plutarch.LedgerApi.Value |
Time
newtype PPosixTime (s :: S) Source #
Since: 2.0.0
Constructors
PPosixTime (Term s PInteger) |
Instances
PCountable PPosixTime Source # | Since: 3.3.0 |
Defined in Plutarch.LedgerApi.V1.Time Methods psuccessor :: forall (s :: S). Term s (PPosixTime :--> PPosixTime) psuccessorN :: forall (s :: S). Term s (PPositive :--> (PPosixTime :--> PPosixTime)) | |
PEnumerable PPosixTime Source # | Since: 3.3.0 |
Defined in Plutarch.LedgerApi.V1.Time Methods ppredecessor :: forall (s :: S). Term s (PPosixTime :--> PPosixTime) ppredecessorN :: forall (s :: S). Term s (PPositive :--> (PPosixTime :--> PPosixTime)) | |
PEq PPosixTime Source # | Since: 2.0.0 |
Defined in Plutarch.LedgerApi.V1.Time Methods (#==) :: forall (s :: S). Term s PPosixTime -> Term s PPosixTime -> Term s PBool | |
PIsData PPosixTime Source # | Since: 2.0.0 |
Defined in Plutarch.LedgerApi.V1.Time Methods pfromDataImpl :: forall (s :: S). Term s (PAsData PPosixTime) -> Term s PPosixTime pdataImpl :: forall (s :: S). Term s PPosixTime -> Term s PData | |
PLiftable PPosixTime Source # | |
Defined in Plutarch.LedgerApi.V1.Time Methods haskToRepr :: AsHaskell PPosixTime -> PlutusRepr PPosixTime reprToHask :: PlutusRepr PPosixTime -> Either LiftError (AsHaskell PPosixTime) reprToPlut :: forall (s :: S). PlutusRepr PPosixTime -> PLifted s PPosixTime plutToRepr :: (forall (s :: S). PLifted s PPosixTime) -> Either LiftError (PlutusRepr PPosixTime) | |
PAdditiveGroup PPosixTime Source # | Since: 3.3.0 |
Defined in Plutarch.LedgerApi.V1.Time Methods pnegate :: forall (s :: S). Term s (PPosixTime :--> PPosixTime) (#-) :: forall (s :: S). Term s PPosixTime -> Term s PPosixTime -> Term s PPosixTime pscaleInteger :: forall (s :: S). Term s PPosixTime -> Term s PInteger -> Term s PPosixTime | |
PAdditiveMonoid PPosixTime Source # | Since: 3.3.0 |
Defined in Plutarch.LedgerApi.V1.Time Methods pzero :: forall (s :: S). Term s PPosixTime pscaleNatural :: forall (s :: S). Term s PPosixTime -> Term s PNatural -> Term s PPosixTime | |
PAdditiveSemigroup PPosixTime Source # | Since: 3.3.0 |
Defined in Plutarch.LedgerApi.V1.Time Methods (#+) :: forall (s :: S). Term s PPosixTime -> Term s PPosixTime -> Term s PPosixTime pscalePositive :: forall (s :: S). Term s PPosixTime -> Term s PPositive -> Term s PPosixTime | |
POrd PPosixTime Source # | Since: 2.0.0 |
Defined in Plutarch.LedgerApi.V1.Time Methods (#<=) :: forall (s :: S). Term s PPosixTime -> Term s PPosixTime -> Term s PBool (#<) :: forall (s :: S). Term s PPosixTime -> Term s PPosixTime -> Term s PBool pmax :: forall (s :: S). Term s PPosixTime -> Term s PPosixTime -> Term s PPosixTime pmin :: forall (s :: S). Term s PPosixTime -> Term s PPosixTime -> Term s PPosixTime | |
PlutusType PPosixTime Source # | |
Defined in Plutarch.LedgerApi.V1.Time Associated Types type PInner PPosixTime :: PType type PCovariant' PPosixTime type PContravariant' PPosixTime type PVariant' PPosixTime Methods pcon' :: forall (s :: S). PPosixTime s -> Term s (PInner PPosixTime) pmatch' :: forall (s :: S) (b :: PType). Term s (PInner PPosixTime) -> (PPosixTime s -> Term s b) -> Term s b | |
PShow PPosixTime Source # | Since: 2.0.0 |
Defined in Plutarch.LedgerApi.V1.Time Methods pshow' :: forall (s :: S). Bool -> Term s PPosixTime -> Term s PString | |
Generic (PPosixTime s) Source # | |
Defined in Plutarch.LedgerApi.V1.Time Methods from :: PPosixTime s -> Rep (PPosixTime s) x Source # to :: Rep (PPosixTime s) x -> PPosixTime s Source # | |
Generic (PPosixTime s) Source # | |
Defined in Plutarch.LedgerApi.V1.Time Associated Types type Code (PPosixTime s) :: [[Type]] | |
type AsHaskell PPosixTime Source # | Since: 3.3.0 |
Defined in Plutarch.LedgerApi.V1.Time | |
type PlutusRepr PPosixTime Source # | |
Defined in Plutarch.LedgerApi.V1.Time | |
type PContravariant' PPosixTime Source # | |
Defined in Plutarch.LedgerApi.V1.Time | |
type PCovariant' PPosixTime Source # | |
Defined in Plutarch.LedgerApi.V1.Time | |
type PInner PPosixTime Source # | Since: 3.3.0 |
Defined in Plutarch.LedgerApi.V1.Time | |
type PVariant' PPosixTime Source # | |
Defined in Plutarch.LedgerApi.V1.Time | |
type Rep (PPosixTime s) Source # | Since: 2.0.0 |
Defined in Plutarch.LedgerApi.V1.Time type Rep (PPosixTime s) = D1 ('MetaData "PPosixTime" "Plutarch.LedgerApi.V1.Time" "plutarch-ledger-api-3.3.0-9uebfPQOA90BujqVBUbxih" 'True) (C1 ('MetaCons "PPosixTime" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Term s PInteger)))) | |
type Code (PPosixTime s) Source # | Since: 3.3.0 |
Defined in Plutarch.LedgerApi.V1.Time |
pposixTime :: forall (s :: S). Term s PInteger -> Term s PPosixTime Source #
Construct a PPosixTime
from a PInteger
. Same as using the constructor,
but a lot shorter.
Since: 3.3.0
unPPosixTime :: forall (s :: S). Term s PPosixTime -> Term s PInteger Source #
Unwrap a PPosixTime
to get a PInteger
. Same as using pmatch
, but a
lot shorter. Also unwraps the Data
encoding.
Since: 3.3.0
Intervals
data PExtended (a :: S -> Type) (s :: S) Source #
Since: 2.0.0
Instances
PEq (PExtended a) Source # | Since: 2.0.0 |
Defined in Plutarch.LedgerApi.Interval | |
PIsData (PExtended a) Source # | Since: 2.0.0 |
Defined in Plutarch.LedgerApi.Interval Methods pfromDataImpl :: forall (s :: S). Term s (PAsData (PExtended a)) -> Term s (PExtended a) pdataImpl :: forall (s :: S). Term s (PExtended a) -> Term s PData | |
(FromData (AsHaskell a), ToData (AsHaskell a)) => PLiftable (PExtended a) Source # | |
Defined in Plutarch.LedgerApi.Interval Methods haskToRepr :: AsHaskell (PExtended a) -> PlutusRepr (PExtended a) reprToHask :: PlutusRepr (PExtended a) -> Either LiftError (AsHaskell (PExtended a)) reprToPlut :: forall (s :: S). PlutusRepr (PExtended a) -> PLifted s (PExtended a) plutToRepr :: (forall (s :: S). PLifted s (PExtended a)) -> Either LiftError (PlutusRepr (PExtended a)) | |
(POrd a, PIsData a) => POrd (PExtended a) Source # | |
Defined in Plutarch.LedgerApi.Interval Methods (#<=) :: forall (s :: S). Term s (PExtended a) -> Term s (PExtended a) -> Term s PBool (#<) :: forall (s :: S). Term s (PExtended a) -> Term s (PExtended a) -> Term s PBool pmax :: forall (s :: S). Term s (PExtended a) -> Term s (PExtended a) -> Term s (PExtended a) pmin :: forall (s :: S). Term s (PExtended a) -> Term s (PExtended a) -> Term s (PExtended a) | |
PlutusType (PExtended a) Source # | |
Defined in Plutarch.LedgerApi.Interval | |
(PIsData a, PShow a) => PShow (PExtended a) Source # | Since: 2.0.0 |
Defined in Plutarch.LedgerApi.Interval | |
Generic (PExtended a s) Source # | |
Generic (PExtended a s) Source # | |
type AsHaskell (PExtended a) Source # | |
Defined in Plutarch.LedgerApi.Interval | |
type PlutusRepr (PExtended a) Source # | |
Defined in Plutarch.LedgerApi.Interval | |
type PContravariant' (PExtended a) Source # | |
Defined in Plutarch.LedgerApi.Interval | |
type PCovariant' (PExtended a) Source # | |
Defined in Plutarch.LedgerApi.Interval | |
type PInner (PExtended a) Source # | Since: 3.3.0 |
Defined in Plutarch.LedgerApi.Interval | |
type PVariant' (PExtended a) Source # | |
Defined in Plutarch.LedgerApi.Interval | |
type Rep (PExtended a s) Source # | Since: 2.0.0 |
Defined in Plutarch.LedgerApi.Interval type Rep (PExtended a s) = D1 ('MetaData "PExtended" "Plutarch.LedgerApi.Interval" "plutarch-ledger-api-3.3.0-9uebfPQOA90BujqVBUbxih" 'False) (C1 ('MetaCons "PNegInf" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "PFinite" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Term s (PAsData a)))) :+: C1 ('MetaCons "PPosInf" 'PrefixI 'False) (U1 :: Type -> Type))) | |
type Code (PExtended a s) Source # | Since: 2.0.0 |
Defined in Plutarch.LedgerApi.Interval |
data PLowerBound (a :: S -> Type) (s :: S) Source #
Since: 2.0.0
Constructors
PLowerBound (Term s (PExtended a)) (Term s (PAsData PBool)) |
Instances
(PIsData a, PCountable a) => PEq (PLowerBound a) Source # | Since: 3.3.0 |
Defined in Plutarch.LedgerApi.Interval Methods (#==) :: forall (s :: S). Term s (PLowerBound a) -> Term s (PLowerBound a) -> Term s PBool | |
PIsData (PLowerBound a) Source # | Since: 2.0.0 |
Defined in Plutarch.LedgerApi.Interval Methods pfromDataImpl :: forall (s :: S). Term s (PAsData (PLowerBound a)) -> Term s (PLowerBound a) pdataImpl :: forall (s :: S). Term s (PLowerBound a) -> Term s PData | |
(FromData (AsHaskell a), ToData (AsHaskell a)) => PLiftable (PLowerBound a) Source # | |
Defined in Plutarch.LedgerApi.Interval Methods haskToRepr :: AsHaskell (PLowerBound a) -> PlutusRepr (PLowerBound a) reprToHask :: PlutusRepr (PLowerBound a) -> Either LiftError (AsHaskell (PLowerBound a)) reprToPlut :: forall (s :: S). PlutusRepr (PLowerBound a) -> PLifted s (PLowerBound a) plutToRepr :: (forall (s :: S). PLifted s (PLowerBound a)) -> Either LiftError (PlutusRepr (PLowerBound a)) | |
(PIsData a, PCountable a) => POrd (PLowerBound a) Source # | Since: 3.3.0 |
Defined in Plutarch.LedgerApi.Interval Methods (#<=) :: forall (s :: S). Term s (PLowerBound a) -> Term s (PLowerBound a) -> Term s PBool (#<) :: forall (s :: S). Term s (PLowerBound a) -> Term s (PLowerBound a) -> Term s PBool pmax :: forall (s :: S). Term s (PLowerBound a) -> Term s (PLowerBound a) -> Term s (PLowerBound a) pmin :: forall (s :: S). Term s (PLowerBound a) -> Term s (PLowerBound a) -> Term s (PLowerBound a) | |
PlutusType (PLowerBound a) Source # | |
Defined in Plutarch.LedgerApi.Interval Associated Types type PInner (PLowerBound a) :: PType type PCovariant' (PLowerBound a) type PContravariant' (PLowerBound a) type PVariant' (PLowerBound a) Methods pcon' :: forall (s :: S). PLowerBound a s -> Term s (PInner (PLowerBound a)) pmatch' :: forall (s :: S) (b :: PType). Term s (PInner (PLowerBound a)) -> (PLowerBound a s -> Term s b) -> Term s b | |
(PIsData a, PShow a) => PShow (PLowerBound a) Source # | Since: 2.0.0 |
Defined in Plutarch.LedgerApi.Interval Methods pshow' :: forall (s :: S). Bool -> Term s (PLowerBound a) -> Term s PString | |
Generic (PLowerBound a s) Source # | |
Defined in Plutarch.LedgerApi.Interval Methods from :: PLowerBound a s -> Rep (PLowerBound a s) x Source # to :: Rep (PLowerBound a s) x -> PLowerBound a s Source # | |
Generic (PLowerBound a s) Source # | |
Defined in Plutarch.LedgerApi.Interval Associated Types type Code (PLowerBound a s) :: [[Type]] Methods from :: PLowerBound a s -> Rep (PLowerBound a s) to :: Rep (PLowerBound a s) -> PLowerBound a s | |
type AsHaskell (PLowerBound a) Source # | |
Defined in Plutarch.LedgerApi.Interval type AsHaskell (PLowerBound a) = AsHaskell (DeriveDataPLiftable (PLowerBound a) (LowerBound (AsHaskell a))) | |
type PlutusRepr (PLowerBound a) Source # | |
Defined in Plutarch.LedgerApi.Interval type PlutusRepr (PLowerBound a) = PlutusRepr (DeriveDataPLiftable (PLowerBound a) (LowerBound (AsHaskell a))) | |
type PContravariant' (PLowerBound a) Source # | |
Defined in Plutarch.LedgerApi.Interval | |
type PCovariant' (PLowerBound a) Source # | |
Defined in Plutarch.LedgerApi.Interval | |
type PInner (PLowerBound a) Source # | Since: 3.3.0 |
Defined in Plutarch.LedgerApi.Interval | |
type PVariant' (PLowerBound a) Source # | |
Defined in Plutarch.LedgerApi.Interval | |
type Rep (PLowerBound a s) Source # | Since: 2.0.0 |
Defined in Plutarch.LedgerApi.Interval type Rep (PLowerBound a s) = D1 ('MetaData "PLowerBound" "Plutarch.LedgerApi.Interval" "plutarch-ledger-api-3.3.0-9uebfPQOA90BujqVBUbxih" 'False) (C1 ('MetaCons "PLowerBound" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Term s (PExtended a))) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Term s (PAsData PBool))))) | |
type Code (PLowerBound a s) Source # | Since: 2.0.0 |
Defined in Plutarch.LedgerApi.Interval |
data PUpperBound (a :: S -> Type) (s :: S) Source #
Since: 2.0.0
Constructors
PUpperBound (Term s (PExtended a)) (Term s (PAsData PBool)) |
Instances
(PIsData a, PEnumerable a) => PEq (PUpperBound a) Source # | Since: 3.3.0 |
Defined in Plutarch.LedgerApi.Interval Methods (#==) :: forall (s :: S). Term s (PUpperBound a) -> Term s (PUpperBound a) -> Term s PBool | |
PIsData (PUpperBound a) Source # | Since: 2.0.0 |
Defined in Plutarch.LedgerApi.Interval Methods pfromDataImpl :: forall (s :: S). Term s (PAsData (PUpperBound a)) -> Term s (PUpperBound a) pdataImpl :: forall (s :: S). Term s (PUpperBound a) -> Term s PData | |
(FromData (AsHaskell a), ToData (AsHaskell a)) => PLiftable (PUpperBound a) Source # | |
Defined in Plutarch.LedgerApi.Interval Methods haskToRepr :: AsHaskell (PUpperBound a) -> PlutusRepr (PUpperBound a) reprToHask :: PlutusRepr (PUpperBound a) -> Either LiftError (AsHaskell (PUpperBound a)) reprToPlut :: forall (s :: S). PlutusRepr (PUpperBound a) -> PLifted s (PUpperBound a) plutToRepr :: (forall (s :: S). PLifted s (PUpperBound a)) -> Either LiftError (PlutusRepr (PUpperBound a)) | |
(PIsData a, PEnumerable a) => POrd (PUpperBound a) Source # | Since: 3.3.0 |
Defined in Plutarch.LedgerApi.Interval Methods (#<=) :: forall (s :: S). Term s (PUpperBound a) -> Term s (PUpperBound a) -> Term s PBool (#<) :: forall (s :: S). Term s (PUpperBound a) -> Term s (PUpperBound a) -> Term s PBool pmax :: forall (s :: S). Term s (PUpperBound a) -> Term s (PUpperBound a) -> Term s (PUpperBound a) pmin :: forall (s :: S). Term s (PUpperBound a) -> Term s (PUpperBound a) -> Term s (PUpperBound a) | |
PlutusType (PUpperBound a) Source # | |
Defined in Plutarch.LedgerApi.Interval Associated Types type PInner (PUpperBound a) :: PType type PCovariant' (PUpperBound a) type PContravariant' (PUpperBound a) type PVariant' (PUpperBound a) Methods pcon' :: forall (s :: S). PUpperBound a s -> Term s (PInner (PUpperBound a)) pmatch' :: forall (s :: S) (b :: PType). Term s (PInner (PUpperBound a)) -> (PUpperBound a s -> Term s b) -> Term s b | |
(PIsData a, PShow a) => PShow (PUpperBound a) Source # | Since: 2.0.0 |
Defined in Plutarch.LedgerApi.Interval Methods pshow' :: forall (s :: S). Bool -> Term s (PUpperBound a) -> Term s PString | |
Generic (PUpperBound a s) Source # | |
Defined in Plutarch.LedgerApi.Interval Methods from :: PUpperBound a s -> Rep (PUpperBound a s) x Source # to :: Rep (PUpperBound a s) x -> PUpperBound a s Source # | |
Generic (PUpperBound a s) Source # | |
Defined in Plutarch.LedgerApi.Interval Associated Types type Code (PUpperBound a s) :: [[Type]] Methods from :: PUpperBound a s -> Rep (PUpperBound a s) to :: Rep (PUpperBound a s) -> PUpperBound a s | |
type AsHaskell (PUpperBound a) Source # | |
Defined in Plutarch.LedgerApi.Interval type AsHaskell (PUpperBound a) = AsHaskell (DeriveDataPLiftable (PUpperBound a) (UpperBound (AsHaskell a))) | |
type PlutusRepr (PUpperBound a) Source # | |
Defined in Plutarch.LedgerApi.Interval type PlutusRepr (PUpperBound a) = PlutusRepr (DeriveDataPLiftable (PUpperBound a) (UpperBound (AsHaskell a))) | |
type PContravariant' (PUpperBound a) Source # | |
Defined in Plutarch.LedgerApi.Interval | |
type PCovariant' (PUpperBound a) Source # | |
Defined in Plutarch.LedgerApi.Interval | |
type PInner (PUpperBound a) Source # | Since: 3.3.0 |
Defined in Plutarch.LedgerApi.Interval | |
type PVariant' (PUpperBound a) Source # | |
Defined in Plutarch.LedgerApi.Interval | |
type Rep (PUpperBound a s) Source # | Since: 2.0.0 |
Defined in Plutarch.LedgerApi.Interval type Rep (PUpperBound a s) = D1 ('MetaData "PUpperBound" "Plutarch.LedgerApi.Interval" "plutarch-ledger-api-3.3.0-9uebfPQOA90BujqVBUbxih" 'False) (C1 ('MetaCons "PUpperBound" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Term s (PExtended a))) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Term s (PAsData PBool))))) | |
type Code (PUpperBound a s) Source # | Since: 2.0.0 |
Defined in Plutarch.LedgerApi.Interval |
data PInterval (a :: S -> Type) (s :: S) Source #
Since: 2.0.0
Constructors
PInterval | |
Fields
|
Instances
(PIsData a, PEnumerable a) => PEq (PInterval a) Source # | Since: 2.0.0 |
Defined in Plutarch.LedgerApi.Interval | |
PIsData (PInterval a) Source # | Since: 2.0.0 |
Defined in Plutarch.LedgerApi.Interval Methods pfromDataImpl :: forall (s :: S). Term s (PAsData (PInterval a)) -> Term s (PInterval a) pdataImpl :: forall (s :: S). Term s (PInterval a) -> Term s PData | |
(FromData (AsHaskell a), ToData (AsHaskell a)) => PLiftable (PInterval a) Source # | |
Defined in Plutarch.LedgerApi.Interval Methods haskToRepr :: AsHaskell (PInterval a) -> PlutusRepr (PInterval a) reprToHask :: PlutusRepr (PInterval a) -> Either LiftError (AsHaskell (PInterval a)) reprToPlut :: forall (s :: S). PlutusRepr (PInterval a) -> PLifted s (PInterval a) plutToRepr :: (forall (s :: S). PLifted s (PInterval a)) -> Either LiftError (PlutusRepr (PInterval a)) | |
PlutusType (PInterval a) Source # | |
Defined in Plutarch.LedgerApi.Interval | |
(PIsData a, PShow a) => PShow (PInterval a) Source # | Since: 2.0.0 |
Defined in Plutarch.LedgerApi.Interval | |
Generic (PInterval a s) Source # | |
Generic (PInterval a s) Source # | |
type AsHaskell (PInterval a) Source # | Since: 3.3.0 |
Defined in Plutarch.LedgerApi.Interval | |
type PlutusRepr (PInterval a) Source # | |
Defined in Plutarch.LedgerApi.Interval | |
type PContravariant' (PInterval a) Source # | |
Defined in Plutarch.LedgerApi.Interval | |
type PCovariant' (PInterval a) Source # | |
Defined in Plutarch.LedgerApi.Interval | |
type PInner (PInterval a) Source # | Since: 3.3.0 |
Defined in Plutarch.LedgerApi.Interval | |
type PVariant' (PInterval a) Source # | |
Defined in Plutarch.LedgerApi.Interval | |
type Rep (PInterval a s) Source # | Since: 2.0.0 |
Defined in Plutarch.LedgerApi.Interval type Rep (PInterval a s) = D1 ('MetaData "PInterval" "Plutarch.LedgerApi.Interval" "plutarch-ledger-api-3.3.0-9uebfPQOA90BujqVBUbxih" 'False) (C1 ('MetaCons "PInterval" 'PrefixI 'True) (S1 ('MetaSel ('Just "pinteral'from") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Term s (PLowerBound a))) :*: S1 ('MetaSel ('Just "pinteral'to") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Term s (PUpperBound a))))) | |
type Code (PInterval a s) Source # | Since: 2.0.0 |
Defined in Plutarch.LedgerApi.Interval |
Script stuff
newtype PDatum (s :: S) Source #
Since: 2.0.0
Constructors
PDatum (Term s PData) |
Instances
newtype PRedeemer (s :: S) Source #
Since: 2.0.0
Constructors
PRedeemer (Term s PData) |
Instances
newtype PDatumHash (s :: S) Source #
Since: 2.0.0
Constructors
PDatumHash (Term s PByteString) |
Instances
PEq PDatumHash Source # | Since: 2.0.0 |
Defined in Plutarch.LedgerApi.V1.Scripts Methods (#==) :: forall (s :: S). Term s PDatumHash -> Term s PDatumHash -> Term s PBool | |
PIsData PDatumHash Source # | Since: 2.0.0 |
Defined in Plutarch.LedgerApi.V1.Scripts Methods pfromDataImpl :: forall (s :: S). Term s (PAsData PDatumHash) -> Term s PDatumHash pdataImpl :: forall (s :: S). Term s PDatumHash -> Term s PData | |
PLiftable PDatumHash Source # | Since: 3.3.0 |
Defined in Plutarch.LedgerApi.V1.Scripts Methods haskToRepr :: AsHaskell PDatumHash -> PlutusRepr PDatumHash reprToHask :: PlutusRepr PDatumHash -> Either LiftError (AsHaskell PDatumHash) reprToPlut :: forall (s :: S). PlutusRepr PDatumHash -> PLifted s PDatumHash plutToRepr :: (forall (s :: S). PLifted s PDatumHash) -> Either LiftError (PlutusRepr PDatumHash) | |
POrd PDatumHash Source # | Since: 2.0.0 |
Defined in Plutarch.LedgerApi.V1.Scripts Methods (#<=) :: forall (s :: S). Term s PDatumHash -> Term s PDatumHash -> Term s PBool (#<) :: forall (s :: S). Term s PDatumHash -> Term s PDatumHash -> Term s PBool pmax :: forall (s :: S). Term s PDatumHash -> Term s PDatumHash -> Term s PDatumHash pmin :: forall (s :: S). Term s PDatumHash -> Term s PDatumHash -> Term s PDatumHash | |
PlutusType PDatumHash Source # | |
Defined in Plutarch.LedgerApi.V1.Scripts Associated Types type PInner PDatumHash :: PType type PCovariant' PDatumHash type PContravariant' PDatumHash type PVariant' PDatumHash Methods pcon' :: forall (s :: S). PDatumHash s -> Term s (PInner PDatumHash) pmatch' :: forall (s :: S) (b :: PType). Term s (PInner PDatumHash) -> (PDatumHash s -> Term s b) -> Term s b | |
PShow PDatumHash Source # | Since: 2.0.0 |
Defined in Plutarch.LedgerApi.V1.Scripts Methods pshow' :: forall (s :: S). Bool -> Term s PDatumHash -> Term s PString | |
Generic (PDatumHash s) Source # | |
Defined in Plutarch.LedgerApi.V1.Scripts Methods from :: PDatumHash s -> Rep (PDatumHash s) x Source # to :: Rep (PDatumHash s) x -> PDatumHash s Source # | |
Generic (PDatumHash s) Source # | |
Defined in Plutarch.LedgerApi.V1.Scripts Associated Types type Code (PDatumHash s) :: [[Type]] | |
type AsHaskell PDatumHash Source # | |
Defined in Plutarch.LedgerApi.V1.Scripts type AsHaskell PDatumHash = DatumHash | |
type PlutusRepr PDatumHash Source # | |
Defined in Plutarch.LedgerApi.V1.Scripts | |
type PContravariant' PDatumHash Source # | |
Defined in Plutarch.LedgerApi.V1.Scripts | |
type PCovariant' PDatumHash Source # | |
Defined in Plutarch.LedgerApi.V1.Scripts | |
type PInner PDatumHash Source # | Since: 3.3.0 |
Defined in Plutarch.LedgerApi.V1.Scripts | |
type PVariant' PDatumHash Source # | |
Defined in Plutarch.LedgerApi.V1.Scripts | |
type Rep (PDatumHash s) Source # | Since: 2.0.0 |
Defined in Plutarch.LedgerApi.V1.Scripts type Rep (PDatumHash s) = D1 ('MetaData "PDatumHash" "Plutarch.LedgerApi.V1.Scripts" "plutarch-ledger-api-3.3.0-9uebfPQOA90BujqVBUbxih" 'True) (C1 ('MetaCons "PDatumHash" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Term s PByteString)))) | |
type Code (PDatumHash s) Source # | Since: 3.3.0 |
Defined in Plutarch.LedgerApi.V1.Scripts |
newtype PRedeemerHash (s :: S) Source #
Since: 2.0.0
Constructors
PRedeemerHash (Term s PByteString) |
Instances
PEq PRedeemerHash Source # | Since: 3.1.0 |
Defined in Plutarch.LedgerApi.V1.Scripts Methods (#==) :: forall (s :: S). Term s PRedeemerHash -> Term s PRedeemerHash -> Term s PBool | |
PIsData PRedeemerHash Source # | Since: 3.1.0 |
Defined in Plutarch.LedgerApi.V1.Scripts Methods pfromDataImpl :: forall (s :: S). Term s (PAsData PRedeemerHash) -> Term s PRedeemerHash pdataImpl :: forall (s :: S). Term s PRedeemerHash -> Term s PData | |
PLiftable PRedeemerHash Source # | Since: 3.3.0 |
Defined in Plutarch.LedgerApi.V1.Scripts Methods haskToRepr :: AsHaskell PRedeemerHash -> PlutusRepr PRedeemerHash reprToHask :: PlutusRepr PRedeemerHash -> Either LiftError (AsHaskell PRedeemerHash) reprToPlut :: forall (s :: S). PlutusRepr PRedeemerHash -> PLifted s PRedeemerHash plutToRepr :: (forall (s :: S). PLifted s PRedeemerHash) -> Either LiftError (PlutusRepr PRedeemerHash) | |
POrd PRedeemerHash Source # | Since: 3.1.0 |
Defined in Plutarch.LedgerApi.V1.Scripts Methods (#<=) :: forall (s :: S). Term s PRedeemerHash -> Term s PRedeemerHash -> Term s PBool (#<) :: forall (s :: S). Term s PRedeemerHash -> Term s PRedeemerHash -> Term s PBool pmax :: forall (s :: S). Term s PRedeemerHash -> Term s PRedeemerHash -> Term s PRedeemerHash pmin :: forall (s :: S). Term s PRedeemerHash -> Term s PRedeemerHash -> Term s PRedeemerHash | |
PlutusType PRedeemerHash Source # | |
Defined in Plutarch.LedgerApi.V1.Scripts Associated Types type PInner PRedeemerHash :: PType type PCovariant' PRedeemerHash type PContravariant' PRedeemerHash type PVariant' PRedeemerHash Methods pcon' :: forall (s :: S). PRedeemerHash s -> Term s (PInner PRedeemerHash) pmatch' :: forall (s :: S) (b :: PType). Term s (PInner PRedeemerHash) -> (PRedeemerHash s -> Term s b) -> Term s b | |
PShow PRedeemerHash Source # | Since: 3.1.0 |
Defined in Plutarch.LedgerApi.V1.Scripts Methods pshow' :: forall (s :: S). Bool -> Term s PRedeemerHash -> Term s PString | |
Generic (PRedeemerHash s) Source # | |
Defined in Plutarch.LedgerApi.V1.Scripts Methods from :: PRedeemerHash s -> Rep (PRedeemerHash s) x Source # to :: Rep (PRedeemerHash s) x -> PRedeemerHash s Source # | |
Generic (PRedeemerHash s) Source # | |
Defined in Plutarch.LedgerApi.V1.Scripts Associated Types type Code (PRedeemerHash s) :: [[Type]] Methods from :: PRedeemerHash s -> Rep (PRedeemerHash s) to :: Rep (PRedeemerHash s) -> PRedeemerHash s | |
type AsHaskell PRedeemerHash Source # | |
Defined in Plutarch.LedgerApi.V1.Scripts type AsHaskell PRedeemerHash = RedeemerHash | |
type PlutusRepr PRedeemerHash Source # | |
Defined in Plutarch.LedgerApi.V1.Scripts | |
type PContravariant' PRedeemerHash Source # | |
Defined in Plutarch.LedgerApi.V1.Scripts | |
type PCovariant' PRedeemerHash Source # | |
Defined in Plutarch.LedgerApi.V1.Scripts | |
type PInner PRedeemerHash Source # | Since: 3.3.0 |
Defined in Plutarch.LedgerApi.V1.Scripts | |
type PVariant' PRedeemerHash Source # | |
Defined in Plutarch.LedgerApi.V1.Scripts | |
type Rep (PRedeemerHash s) Source # | Since: 3.1.0 |
Defined in Plutarch.LedgerApi.V1.Scripts type Rep (PRedeemerHash s) = D1 ('MetaData "PRedeemerHash" "Plutarch.LedgerApi.V1.Scripts" "plutarch-ledger-api-3.3.0-9uebfPQOA90BujqVBUbxih" 'True) (C1 ('MetaCons "PRedeemerHash" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Term s PByteString)))) | |
type Code (PRedeemerHash s) Source # | Since: 3.3.0 |
Defined in Plutarch.LedgerApi.V1.Scripts |
newtype PScriptHash (s :: S) Source #
Since: 2.0.0
Constructors
PScriptHash (Term s PByteString) |
Instances
PEq PScriptHash Source # | Since: 2.0.0 |
Defined in Plutarch.LedgerApi.V1.Scripts Methods (#==) :: forall (s :: S). Term s PScriptHash -> Term s PScriptHash -> Term s PBool | |
PIsData PScriptHash Source # | Since: 2.0.0 |
Defined in Plutarch.LedgerApi.V1.Scripts Methods pfromDataImpl :: forall (s :: S). Term s (PAsData PScriptHash) -> Term s PScriptHash pdataImpl :: forall (s :: S). Term s PScriptHash -> Term s PData | |
PLiftable PScriptHash Source # | Since: 3.3.0 |
Defined in Plutarch.LedgerApi.V1.Scripts Methods haskToRepr :: AsHaskell PScriptHash -> PlutusRepr PScriptHash reprToHask :: PlutusRepr PScriptHash -> Either LiftError (AsHaskell PScriptHash) reprToPlut :: forall (s :: S). PlutusRepr PScriptHash -> PLifted s PScriptHash plutToRepr :: (forall (s :: S). PLifted s PScriptHash) -> Either LiftError (PlutusRepr PScriptHash) | |
POrd PScriptHash Source # | Since: 2.0.0 |
Defined in Plutarch.LedgerApi.V1.Scripts Methods (#<=) :: forall (s :: S). Term s PScriptHash -> Term s PScriptHash -> Term s PBool (#<) :: forall (s :: S). Term s PScriptHash -> Term s PScriptHash -> Term s PBool pmax :: forall (s :: S). Term s PScriptHash -> Term s PScriptHash -> Term s PScriptHash pmin :: forall (s :: S). Term s PScriptHash -> Term s PScriptHash -> Term s PScriptHash | |
PlutusType PScriptHash Source # | |
Defined in Plutarch.LedgerApi.V1.Scripts Associated Types type PInner PScriptHash :: PType type PCovariant' PScriptHash type PContravariant' PScriptHash type PVariant' PScriptHash Methods pcon' :: forall (s :: S). PScriptHash s -> Term s (PInner PScriptHash) pmatch' :: forall (s :: S) (b :: PType). Term s (PInner PScriptHash) -> (PScriptHash s -> Term s b) -> Term s b | |
PShow PScriptHash Source # | Since: 2.0.0 |
Defined in Plutarch.LedgerApi.V1.Scripts Methods pshow' :: forall (s :: S). Bool -> Term s PScriptHash -> Term s PString | |
Generic (PScriptHash s) Source # | |
Defined in Plutarch.LedgerApi.V1.Scripts Methods from :: PScriptHash s -> Rep (PScriptHash s) x Source # to :: Rep (PScriptHash s) x -> PScriptHash s Source # | |
Generic (PScriptHash s) Source # | |
Defined in Plutarch.LedgerApi.V1.Scripts Associated Types type Code (PScriptHash s) :: [[Type]] | |
type AsHaskell PScriptHash Source # | |
Defined in Plutarch.LedgerApi.V1.Scripts type AsHaskell PScriptHash = ScriptHash | |
type PlutusRepr PScriptHash Source # | |
Defined in Plutarch.LedgerApi.V1.Scripts | |
type PContravariant' PScriptHash Source # | |
Defined in Plutarch.LedgerApi.V1.Scripts | |
type PCovariant' PScriptHash Source # | |
Defined in Plutarch.LedgerApi.V1.Scripts | |
type PInner PScriptHash Source # | Since: 3.3.0 |
Defined in Plutarch.LedgerApi.V1.Scripts | |
type PVariant' PScriptHash Source # | |
Defined in Plutarch.LedgerApi.V1.Scripts | |
type Rep (PScriptHash s) Source # | Since: 2.0.0 |
Defined in Plutarch.LedgerApi.V1.Scripts type Rep (PScriptHash s) = D1 ('MetaData "PScriptHash" "Plutarch.LedgerApi.V1.Scripts" "plutarch-ledger-api-3.3.0-9uebfPQOA90BujqVBUbxih" 'True) (C1 ('MetaCons "PScriptHash" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Term s PByteString)))) | |
type Code (PScriptHash s) Source # | Since: 3.3.0 |
Defined in Plutarch.LedgerApi.V1.Scripts |
Transactions
data PAddress (s :: S) Source #
Since: 2.0.0
Constructors
PAddress | |
Fields
|
Instances
newtype PPubKeyHash (s :: S) Source #
Since: 2.0.0
Constructors
PPubKeyHash (Term s PByteString) |
Instances
PEq PPubKeyHash Source # | Since: 2.0.0 |
Defined in Plutarch.LedgerApi.V1.Crypto Methods (#==) :: forall (s :: S). Term s PPubKeyHash -> Term s PPubKeyHash -> Term s PBool | |
PIsData PPubKeyHash Source # | Since: 2.0.0 |
Defined in Plutarch.LedgerApi.V1.Crypto Methods pfromDataImpl :: forall (s :: S). Term s (PAsData PPubKeyHash) -> Term s PPubKeyHash pdataImpl :: forall (s :: S). Term s PPubKeyHash -> Term s PData | |
PLiftable PPubKeyHash Source # | Since: 3.3.0 |
Defined in Plutarch.LedgerApi.V1.Crypto Methods haskToRepr :: AsHaskell PPubKeyHash -> PlutusRepr PPubKeyHash reprToHask :: PlutusRepr PPubKeyHash -> Either LiftError (AsHaskell PPubKeyHash) reprToPlut :: forall (s :: S). PlutusRepr PPubKeyHash -> PLifted s PPubKeyHash plutToRepr :: (forall (s :: S). PLifted s PPubKeyHash) -> Either LiftError (PlutusRepr PPubKeyHash) | |
POrd PPubKeyHash Source # | Since: 2.0.0 |
Defined in Plutarch.LedgerApi.V1.Crypto Methods (#<=) :: forall (s :: S). Term s PPubKeyHash -> Term s PPubKeyHash -> Term s PBool (#<) :: forall (s :: S). Term s PPubKeyHash -> Term s PPubKeyHash -> Term s PBool pmax :: forall (s :: S). Term s PPubKeyHash -> Term s PPubKeyHash -> Term s PPubKeyHash pmin :: forall (s :: S). Term s PPubKeyHash -> Term s PPubKeyHash -> Term s PPubKeyHash | |
PlutusType PPubKeyHash Source # | |
Defined in Plutarch.LedgerApi.V1.Crypto Associated Types type PInner PPubKeyHash :: PType type PCovariant' PPubKeyHash type PContravariant' PPubKeyHash type PVariant' PPubKeyHash Methods pcon' :: forall (s :: S). PPubKeyHash s -> Term s (PInner PPubKeyHash) pmatch' :: forall (s :: S) (b :: PType). Term s (PInner PPubKeyHash) -> (PPubKeyHash s -> Term s b) -> Term s b | |
PShow PPubKeyHash Source # | Since: 2.0.0 |
Defined in Plutarch.LedgerApi.V1.Crypto Methods pshow' :: forall (s :: S). Bool -> Term s PPubKeyHash -> Term s PString | |
Generic (PPubKeyHash s) Source # | |
Defined in Plutarch.LedgerApi.V1.Crypto Methods from :: PPubKeyHash s -> Rep (PPubKeyHash s) x Source # to :: Rep (PPubKeyHash s) x -> PPubKeyHash s Source # | |
Generic (PPubKeyHash s) Source # | |
Defined in Plutarch.LedgerApi.V1.Crypto Associated Types type Code (PPubKeyHash s) :: [[Type]] | |
type AsHaskell PPubKeyHash Source # | |
Defined in Plutarch.LedgerApi.V1.Crypto type AsHaskell PPubKeyHash = PubKeyHash | |
type PlutusRepr PPubKeyHash Source # | |
Defined in Plutarch.LedgerApi.V1.Crypto | |
type PContravariant' PPubKeyHash Source # | |
Defined in Plutarch.LedgerApi.V1.Crypto | |
type PCovariant' PPubKeyHash Source # | |
Defined in Plutarch.LedgerApi.V1.Crypto | |
type PInner PPubKeyHash Source # | Since: 3.3.0 |
Defined in Plutarch.LedgerApi.V1.Crypto | |
type PVariant' PPubKeyHash Source # | |
Defined in Plutarch.LedgerApi.V1.Crypto | |
type Rep (PPubKeyHash s) Source # | Since: 2.0.0 |
Defined in Plutarch.LedgerApi.V1.Crypto type Rep (PPubKeyHash s) = D1 ('MetaData "PPubKeyHash" "Plutarch.LedgerApi.V1.Crypto" "plutarch-ledger-api-3.3.0-9uebfPQOA90BujqVBUbxih" 'True) (C1 ('MetaCons "PPubKeyHash" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Term s PByteString)))) | |
type Code (PPubKeyHash s) Source # | Since: 3.3.0 |
Defined in Plutarch.LedgerApi.V1.Crypto |
newtype PTxId (s :: S) Source #
Hashed with BLAKE2b-256
.
Since: 3.1.0
Constructors
PTxId (Term s (PAsData PByteString)) |
Instances
PEq PTxId Source # | Since: 2.0.0 |
Defined in Plutarch.LedgerApi.V1.Tx | |
PIsData PTxId Source # | Since: 2.0.0 |
Defined in Plutarch.LedgerApi.V1.Tx Methods pfromDataImpl :: forall (s :: S). Term s (PAsData PTxId) -> Term s PTxId | |
PLiftable PTxId Source # | |
Defined in Plutarch.LedgerApi.V1.Tx Methods haskToRepr :: AsHaskell PTxId -> PlutusRepr PTxId reprToHask :: PlutusRepr PTxId -> Either LiftError (AsHaskell PTxId) reprToPlut :: forall (s :: S). PlutusRepr PTxId -> PLifted s PTxId plutToRepr :: (forall (s :: S). PLifted s PTxId) -> Either LiftError (PlutusRepr PTxId) | |
PlutusType PTxId Source # | |
Defined in Plutarch.LedgerApi.V1.Tx | |
PShow PTxId Source # | Since: 2.0.0 |
Defined in Plutarch.LedgerApi.V1.Tx | |
Generic (PTxId s) Source # | |
Generic (PTxId s) Source # | |
type AsHaskell PTxId Source # | Since: 3.3.0 |
Defined in Plutarch.LedgerApi.V1.Tx | |
type PlutusRepr PTxId Source # | |
Defined in Plutarch.LedgerApi.V1.Tx | |
type PContravariant' PTxId Source # | |
Defined in Plutarch.LedgerApi.V1.Tx | |
type PCovariant' PTxId Source # | |
Defined in Plutarch.LedgerApi.V1.Tx | |
type PInner PTxId Source # | Since: 3.3.0 |
Defined in Plutarch.LedgerApi.V1.Tx | |
type PVariant' PTxId Source # | |
Defined in Plutarch.LedgerApi.V1.Tx | |
type Rep (PTxId s) Source # | Since: 2.0.0 |
Defined in Plutarch.LedgerApi.V1.Tx type Rep (PTxId s) = D1 ('MetaData "PTxId" "Plutarch.LedgerApi.V1.Tx" "plutarch-ledger-api-3.3.0-9uebfPQOA90BujqVBUbxih" 'True) (C1 ('MetaCons "PTxId" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Term s (PAsData PByteString))))) | |
type Code (PTxId s) Source # | Since: 3.3.0 |
Defined in Plutarch.LedgerApi.V1.Tx |
data PTxInfo (s :: S) Source #
Since: 3.1.1
Constructors
PTxInfo | |
Fields
|
Instances
Since: 2.0.0
Constructors
PTxOut | |
Fields
|
Instances
PEq PTxOut Source # | Since: 2.0.0 |
Defined in Plutarch.LedgerApi.V2.Tx | |
PIsData PTxOut Source # | Since: 2.0.0 |
Defined in Plutarch.LedgerApi.V2.Tx Methods pfromDataImpl :: forall (s :: S). Term s (PAsData PTxOut) -> Term s PTxOut | |
PLiftable PTxOut Source # | |
Defined in Plutarch.LedgerApi.V2.Tx Methods haskToRepr :: AsHaskell PTxOut -> PlutusRepr PTxOut reprToHask :: PlutusRepr PTxOut -> Either LiftError (AsHaskell PTxOut) reprToPlut :: forall (s :: S). PlutusRepr PTxOut -> PLifted s PTxOut plutToRepr :: (forall (s :: S). PLifted s PTxOut) -> Either LiftError (PlutusRepr PTxOut) | |
PlutusType PTxOut Source # | |
Defined in Plutarch.LedgerApi.V2.Tx | |
PShow PTxOut Source # | Since: 2.0.0 |
Defined in Plutarch.LedgerApi.V2.Tx | |
Generic (PTxOut s) Source # | |
Generic (PTxOut s) Source # | |
type AsHaskell PTxOut Source # | Since: 3.3.0 |
Defined in Plutarch.LedgerApi.V2.Tx | |
type PlutusRepr PTxOut Source # | |
Defined in Plutarch.LedgerApi.V2.Tx | |
type PContravariant' PTxOut Source # | |
Defined in Plutarch.LedgerApi.V2.Tx | |
type PCovariant' PTxOut Source # | |
Defined in Plutarch.LedgerApi.V2.Tx | |
type PInner PTxOut Source # | Since: 3.3.0 |
Defined in Plutarch.LedgerApi.V2.Tx | |
type PVariant' PTxOut Source # | |
Defined in Plutarch.LedgerApi.V2.Tx | |
type Rep (PTxOut s) Source # | Since: 2.0.0 |
Defined in Plutarch.LedgerApi.V2.Tx type Rep (PTxOut s) = D1 ('MetaData "PTxOut" "Plutarch.LedgerApi.V2.Tx" "plutarch-ledger-api-3.3.0-9uebfPQOA90BujqVBUbxih" 'False) (C1 ('MetaCons "PTxOut" 'PrefixI 'True) ((S1 ('MetaSel ('Just "ptxOut'address") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Term s PAddress)) :*: S1 ('MetaSel ('Just "ptxOut'value") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Term s (PAsData (PValue 'Sorted 'Positive))))) :*: (S1 ('MetaSel ('Just "ptxOut'datum") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Term s POutputDatum)) :*: S1 ('MetaSel ('Just "ptxOut'referenceScript") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Term s (PMaybeData PScriptHash)))))) | |
type Code (PTxOut s) Source # | Since: 2.0.0 |
Defined in Plutarch.LedgerApi.V2.Tx |
data PTxOutRef (s :: S) Source #
Reference to a transaction output, with an index referencing which exact output we mean.
Since: 2.0.0
Constructors
PTxOutRef | |
Fields
|
Instances
PEq PTxOutRef Source # | Since: 2.0.0 |
Defined in Plutarch.LedgerApi.V1.Tx | |
PIsData PTxOutRef Source # | Since: 2.0.0 |
Defined in Plutarch.LedgerApi.V1.Tx Methods pfromDataImpl :: forall (s :: S). Term s (PAsData PTxOutRef) -> Term s PTxOutRef pdataImpl :: forall (s :: S). Term s PTxOutRef -> Term s PData | |
PLiftable PTxOutRef Source # | |
Defined in Plutarch.LedgerApi.V1.Tx Methods haskToRepr :: AsHaskell PTxOutRef -> PlutusRepr PTxOutRef reprToHask :: PlutusRepr PTxOutRef -> Either LiftError (AsHaskell PTxOutRef) reprToPlut :: forall (s :: S). PlutusRepr PTxOutRef -> PLifted s PTxOutRef plutToRepr :: (forall (s :: S). PLifted s PTxOutRef) -> Either LiftError (PlutusRepr PTxOutRef) | |
PlutusType PTxOutRef Source # | |
Defined in Plutarch.LedgerApi.V1.Tx | |
PShow PTxOutRef Source # | Since: 2.0.0 |
Defined in Plutarch.LedgerApi.V1.Tx | |
Generic (PTxOutRef s) Source # | |
Generic (PTxOutRef s) Source # | |
type AsHaskell PTxOutRef Source # | Since: 3.3.0 |
Defined in Plutarch.LedgerApi.V1.Tx | |
type PlutusRepr PTxOutRef Source # | |
Defined in Plutarch.LedgerApi.V1.Tx | |
type PContravariant' PTxOutRef Source # | |
Defined in Plutarch.LedgerApi.V1.Tx | |
type PCovariant' PTxOutRef Source # | |
Defined in Plutarch.LedgerApi.V1.Tx | |
type PInner PTxOutRef Source # | Since: 3.3.0 |
Defined in Plutarch.LedgerApi.V1.Tx | |
type PVariant' PTxOutRef Source # | |
Defined in Plutarch.LedgerApi.V1.Tx | |
type Rep (PTxOutRef s) Source # | Since: 2.0.0 |
Defined in Plutarch.LedgerApi.V1.Tx type Rep (PTxOutRef s) = D1 ('MetaData "PTxOutRef" "Plutarch.LedgerApi.V1.Tx" "plutarch-ledger-api-3.3.0-9uebfPQOA90BujqVBUbxih" 'False) (C1 ('MetaCons "PTxOutRef" 'PrefixI 'True) (S1 ('MetaSel ('Just "ptxOutRef'id") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Term s PTxId)) :*: S1 ('MetaSel ('Just "ptxOutRef'idx") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Term s (PAsData PInteger))))) | |
type Code (PTxOutRef s) Source # | Since: 3.3.0 |
Defined in Plutarch.LedgerApi.V1.Tx |
data PTxInInfo (s :: S) Source #
Since: 3.1.1
Constructors
PTxInInfo | |
Fields
|
Instances
PEq PTxInInfo Source # | Since: 3.1.1 |
Defined in Plutarch.LedgerApi.V2 | |
PIsData PTxInInfo Source # | Since: 3.1.1 |
Defined in Plutarch.LedgerApi.V2 Methods pfromDataImpl :: forall (s :: S). Term s (PAsData PTxInInfo) -> Term s PTxInInfo pdataImpl :: forall (s :: S). Term s PTxInInfo -> Term s PData | |
PLiftable PTxInInfo Source # | |
Defined in Plutarch.LedgerApi.V2 Methods haskToRepr :: AsHaskell PTxInInfo -> PlutusRepr PTxInInfo reprToHask :: PlutusRepr PTxInInfo -> Either LiftError (AsHaskell PTxInInfo) reprToPlut :: forall (s :: S). PlutusRepr PTxInInfo -> PLifted s PTxInInfo plutToRepr :: (forall (s :: S). PLifted s PTxInInfo) -> Either LiftError (PlutusRepr PTxInInfo) | |
PlutusType PTxInInfo Source # | |
Defined in Plutarch.LedgerApi.V2 | |
PShow PTxInInfo Source # | Since: 3.1.1 |
Defined in Plutarch.LedgerApi.V2 | |
Generic (PTxInInfo s) Source # | |
Generic (PTxInInfo s) Source # | |
type AsHaskell PTxInInfo Source # | Since: 3.3.0 |
Defined in Plutarch.LedgerApi.V2 | |
type PlutusRepr PTxInInfo Source # | |
Defined in Plutarch.LedgerApi.V2 | |
type PContravariant' PTxInInfo Source # | |
Defined in Plutarch.LedgerApi.V2 | |
type PCovariant' PTxInInfo Source # | |
Defined in Plutarch.LedgerApi.V2 | |
type PInner PTxInInfo Source # | Since: 3.3.0 |
Defined in Plutarch.LedgerApi.V2 | |
type PVariant' PTxInInfo Source # | |
Defined in Plutarch.LedgerApi.V2 | |
type Rep (PTxInInfo s) Source # | Since: 3.1.1 |
Defined in Plutarch.LedgerApi.V2 type Rep (PTxInInfo s) = D1 ('MetaData "PTxInInfo" "Plutarch.LedgerApi.V2" "plutarch-ledger-api-3.3.0-9uebfPQOA90BujqVBUbxih" 'False) (C1 ('MetaCons "PTxInInfo" 'PrefixI 'True) (S1 ('MetaSel ('Just "ptxInInfo'outRef") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Term s PTxOutRef)) :*: S1 ('MetaSel ('Just "ptxInInfo'resolved") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Term s PTxOut)))) | |
type Code (PTxInInfo s) Source # | Since: 3.3.0 |
Defined in Plutarch.LedgerApi.V2 |
data POutputDatum (s :: S) Source #
Since: 2.0.0
Constructors
PNoOutputDatum | |
POutputDatumHash | |
Fields
| |
POutputDatum | Inline datum as per CIP-0032 |
Fields
|
Instances
PEq POutputDatum Source # | Since: 2.0.0 |
Defined in Plutarch.LedgerApi.V2.Tx Methods (#==) :: forall (s :: S). Term s POutputDatum -> Term s POutputDatum -> Term s PBool | |
PIsData POutputDatum Source # | Since: 2.0.0 |
Defined in Plutarch.LedgerApi.V2.Tx Methods pfromDataImpl :: forall (s :: S). Term s (PAsData POutputDatum) -> Term s POutputDatum pdataImpl :: forall (s :: S). Term s POutputDatum -> Term s PData | |
PLiftable POutputDatum Source # | |
Defined in Plutarch.LedgerApi.V2.Tx Methods haskToRepr :: AsHaskell POutputDatum -> PlutusRepr POutputDatum reprToHask :: PlutusRepr POutputDatum -> Either LiftError (AsHaskell POutputDatum) reprToPlut :: forall (s :: S). PlutusRepr POutputDatum -> PLifted s POutputDatum plutToRepr :: (forall (s :: S). PLifted s POutputDatum) -> Either LiftError (PlutusRepr POutputDatum) | |
PlutusType POutputDatum Source # | |
Defined in Plutarch.LedgerApi.V2.Tx Associated Types type PInner POutputDatum :: PType type PCovariant' POutputDatum type PContravariant' POutputDatum type PVariant' POutputDatum Methods pcon' :: forall (s :: S). POutputDatum s -> Term s (PInner POutputDatum) pmatch' :: forall (s :: S) (b :: PType). Term s (PInner POutputDatum) -> (POutputDatum s -> Term s b) -> Term s b | |
PShow POutputDatum Source # | Since: 2.0.0 |
Defined in Plutarch.LedgerApi.V2.Tx Methods pshow' :: forall (s :: S). Bool -> Term s POutputDatum -> Term s PString | |
Generic (POutputDatum s) Source # | |
Defined in Plutarch.LedgerApi.V2.Tx Methods from :: POutputDatum s -> Rep (POutputDatum s) x Source # to :: Rep (POutputDatum s) x -> POutputDatum s Source # | |
Generic (POutputDatum s) Source # | |
Defined in Plutarch.LedgerApi.V2.Tx Associated Types type Code (POutputDatum s) :: [[Type]] | |
type AsHaskell POutputDatum Source # | Since: 3.3.0 |
Defined in Plutarch.LedgerApi.V2.Tx | |
type PlutusRepr POutputDatum Source # | |
Defined in Plutarch.LedgerApi.V2.Tx | |
type PContravariant' POutputDatum Source # | |
Defined in Plutarch.LedgerApi.V2.Tx | |
type PCovariant' POutputDatum Source # | |
Defined in Plutarch.LedgerApi.V2.Tx | |
type PInner POutputDatum Source # | Since: 3.3.0 |
Defined in Plutarch.LedgerApi.V2.Tx | |
type PVariant' POutputDatum Source # | |
Defined in Plutarch.LedgerApi.V2.Tx | |
type Rep (POutputDatum s) Source # | Since: 2.0.0 |
Defined in Plutarch.LedgerApi.V2.Tx type Rep (POutputDatum s) = D1 ('MetaData "POutputDatum" "Plutarch.LedgerApi.V2.Tx" "plutarch-ledger-api-3.3.0-9uebfPQOA90BujqVBUbxih" 'False) (C1 ('MetaCons "PNoOutputDatum" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "POutputDatumHash" 'PrefixI 'True) (S1 ('MetaSel ('Just "poutputDatum'datumHash") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Term s (PAsData PDatumHash)))) :+: C1 ('MetaCons "POutputDatum" 'PrefixI 'True) (S1 ('MetaSel ('Just "poutputDatum'outputDatum") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Term s PDatum))))) | |
type Code (POutputDatum s) Source # | Since: 2.0.0 |
Defined in Plutarch.LedgerApi.V2.Tx |
Helpers
newtype PMap (keysort :: KeyGuarantees) (k :: S -> Type) (v :: S -> Type) (s :: S) Source #
Since: 2.0.0
Constructors
PMap (Term s (PBuiltinList (PBuiltinPair (PAsData k) (PAsData v)))) |
Instances
PEq (PMap 'Sorted k v) Source # | Since: 2.0.0 |
PIsData (PMap keysort k v) Source # | Since: 2.0.0 |
Defined in Plutarch.LedgerApi.AssocMap Methods pfromDataImpl :: forall (s :: S). Term s (PAsData (PMap keysort k v)) -> Term s (PMap keysort k v) pdataImpl :: forall (s :: S). Term s (PMap keysort k v) -> Term s PData | |
(ToData (AsHaskell k), ToData (AsHaskell v), FromData (AsHaskell k), FromData (AsHaskell v)) => PLiftable (PMap 'Unsorted k v) Source # | Since: 3.3.0 |
Defined in Plutarch.LedgerApi.AssocMap Methods haskToRepr :: AsHaskell (PMap 'Unsorted k v) -> PlutusRepr (PMap 'Unsorted k v) reprToHask :: PlutusRepr (PMap 'Unsorted k v) -> Either LiftError (AsHaskell (PMap 'Unsorted k v)) reprToPlut :: forall (s :: S). PlutusRepr (PMap 'Unsorted k v) -> PLifted s (PMap 'Unsorted k v) plutToRepr :: (forall (s :: S). PLifted s (PMap 'Unsorted k v)) -> Either LiftError (PlutusRepr (PMap 'Unsorted k v)) | |
PlutusType (PMap keysort k v) Source # | |
Defined in Plutarch.LedgerApi.AssocMap | |
(PIsData k, PIsData v, PShow k, PShow v) => PShow (PMap keysort k v) Source # | Since: 2.0.0 |
Defined in Plutarch.LedgerApi.AssocMap | |
Generic (PMap keysort k v s) Source # | |
Generic (PMap keysort k v s) Source # | |
type AsHaskell (PMap 'Unsorted k v) Source # | |
Defined in Plutarch.LedgerApi.AssocMap | |
type PlutusRepr (PMap 'Unsorted k v) Source # | |
Defined in Plutarch.LedgerApi.AssocMap | |
type PContravariant' (PMap keysort k v) Source # | |
Defined in Plutarch.LedgerApi.AssocMap | |
type PCovariant' (PMap keysort k v) Source # | |
Defined in Plutarch.LedgerApi.AssocMap | |
type PInner (PMap keysort k v) Source # | Since: 3.3.0 |
Defined in Plutarch.LedgerApi.AssocMap | |
type PVariant' (PMap keysort k v) Source # | |
Defined in Plutarch.LedgerApi.AssocMap | |
type Rep (PMap keysort k v s) Source # | Since: 2.0.0 |
Defined in Plutarch.LedgerApi.AssocMap type Rep (PMap keysort k v s) = D1 ('MetaData "PMap" "Plutarch.LedgerApi.AssocMap" "plutarch-ledger-api-3.3.0-9uebfPQOA90BujqVBUbxih" 'True) (C1 ('MetaCons "PMap" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Term s (PBuiltinList (PBuiltinPair (PAsData k) (PAsData v))))))) | |
type Code (PMap keysort k v s) Source # | Since: 2.0.0 |
Defined in Plutarch.LedgerApi.AssocMap |
data Commutativity Source #
Since: 2.0.0
Constructors
Commutative | |
NonCommutative |
Instances
Show Commutativity Source # | Since: 2.0.0 |
Defined in Plutarch.LedgerApi.AssocMap | |
Eq Commutativity Source # | Since: 2.0.0 |
Defined in Plutarch.LedgerApi.AssocMap Methods (==) :: Commutativity -> Commutativity -> Bool Source # (/=) :: Commutativity -> Commutativity -> Bool Source # | |
Ord Commutativity Source # | Since: 2.0.0 |
Defined in Plutarch.LedgerApi.AssocMap Methods compare :: Commutativity -> Commutativity -> Ordering Source # (<) :: Commutativity -> Commutativity -> Bool Source # (<=) :: Commutativity -> Commutativity -> Bool Source # (>) :: Commutativity -> Commutativity -> Bool Source # (>=) :: Commutativity -> Commutativity -> Bool Source # max :: Commutativity -> Commutativity -> Commutativity Source # min :: Commutativity -> Commutativity -> Commutativity Source # |
Utilities
Types
data PMaybeData (a :: S -> Type) (s :: S) Source #
Since: 3.3.0
Instances
PEq (PMaybeData a) Source # | Since: 2.0.0 |
Defined in Plutarch.LedgerApi.Utils Methods (#==) :: forall (s :: S). Term s (PMaybeData a) -> Term s (PMaybeData a) -> Term s PBool | |
PIsData (PMaybeData a) Source # | Since: 3.3.0 |
Defined in Plutarch.LedgerApi.Utils Methods pfromDataImpl :: forall (s :: S). Term s (PAsData (PMaybeData a)) -> Term s (PMaybeData a) pdataImpl :: forall (s :: S). Term s (PMaybeData a) -> Term s PData | |
(ToData (AsHaskell a), FromData (AsHaskell a)) => PLiftable (PMaybeData a) Source # | |
Defined in Plutarch.LedgerApi.Utils Methods haskToRepr :: AsHaskell (PMaybeData a) -> PlutusRepr (PMaybeData a) reprToHask :: PlutusRepr (PMaybeData a) -> Either LiftError (AsHaskell (PMaybeData a)) reprToPlut :: forall (s :: S). PlutusRepr (PMaybeData a) -> PLifted s (PMaybeData a) plutToRepr :: (forall (s :: S). PLifted s (PMaybeData a)) -> Either LiftError (PlutusRepr (PMaybeData a)) | |
(PIsData a, POrd a) => POrd (PMaybeData a) Source # | Since: 2.0.0 |
Defined in Plutarch.LedgerApi.Utils Methods (#<=) :: forall (s :: S). Term s (PMaybeData a) -> Term s (PMaybeData a) -> Term s PBool (#<) :: forall (s :: S). Term s (PMaybeData a) -> Term s (PMaybeData a) -> Term s PBool pmax :: forall (s :: S). Term s (PMaybeData a) -> Term s (PMaybeData a) -> Term s (PMaybeData a) pmin :: forall (s :: S). Term s (PMaybeData a) -> Term s (PMaybeData a) -> Term s (PMaybeData a) | |
PlutusType (PMaybeData a) Source # | |
Defined in Plutarch.LedgerApi.Utils Associated Types type PInner (PMaybeData a) :: PType type PCovariant' (PMaybeData a) type PContravariant' (PMaybeData a) type PVariant' (PMaybeData a) Methods pcon' :: forall (s :: S). PMaybeData a s -> Term s (PInner (PMaybeData a)) pmatch' :: forall (s :: S) (b :: PType). Term s (PInner (PMaybeData a)) -> (PMaybeData a s -> Term s b) -> Term s b | |
(PIsData a, PShow a) => PShow (PMaybeData a) Source # | Since: 2.0.0 |
Defined in Plutarch.LedgerApi.Utils Methods pshow' :: forall (s :: S). Bool -> Term s (PMaybeData a) -> Term s PString | |
Generic (PMaybeData a s) Source # | |
Defined in Plutarch.LedgerApi.Utils Methods from :: PMaybeData a s -> Rep (PMaybeData a s) x Source # to :: Rep (PMaybeData a s) x -> PMaybeData a s Source # | |
Generic (PMaybeData a s) Source # | |
Defined in Plutarch.LedgerApi.Utils Associated Types type Code (PMaybeData a s) :: [[Type]] | |
type AsHaskell (PMaybeData a) Source # | Since: 3.3.0 |
Defined in Plutarch.LedgerApi.Utils type AsHaskell (PMaybeData a) = AsHaskell (DeriveDataPLiftable (PMaybeData a) (Maybe (AsHaskell a))) | |
type PlutusRepr (PMaybeData a) Source # | |
Defined in Plutarch.LedgerApi.Utils type PlutusRepr (PMaybeData a) = PlutusRepr (DeriveDataPLiftable (PMaybeData a) (Maybe (AsHaskell a))) | |
type PContravariant' (PMaybeData a) Source # | |
Defined in Plutarch.LedgerApi.Utils | |
type PCovariant' (PMaybeData a) Source # | |
Defined in Plutarch.LedgerApi.Utils | |
type PInner (PMaybeData a) Source # | Since: 3.3.0 |
Defined in Plutarch.LedgerApi.Utils | |
type PVariant' (PMaybeData a) Source # | |
Defined in Plutarch.LedgerApi.Utils | |
type Rep (PMaybeData a s) Source # | Since: 2.0.0 |
Defined in Plutarch.LedgerApi.Utils type Rep (PMaybeData a s) = D1 ('MetaData "PMaybeData" "Plutarch.LedgerApi.Utils" "plutarch-ledger-api-3.3.0-9uebfPQOA90BujqVBUbxih" 'False) (C1 ('MetaCons "PDJust" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Term s (PAsData a)))) :+: C1 ('MetaCons "PDNothing" 'PrefixI 'False) (U1 :: Type -> Type)) | |
type Code (PMaybeData a s) Source # | Since: 3.3.0 |
Defined in Plutarch.LedgerApi.Utils |
data PRationalData s Source #
A Rational type that corresponds to the data encoding used by Rational
.
Since: 3.1.0
Constructors
PRationalData | |
Fields
|
Instances
PEq PRationalData Source # | Since: 3.1.0 |
Defined in Plutarch.LedgerApi.Utils Methods (#==) :: forall (s :: S). Term s PRationalData -> Term s PRationalData -> Term s PBool | |
PIsData PRationalData Source # | Since: 3.1.0 |
Defined in Plutarch.LedgerApi.Utils Methods pfromDataImpl :: forall (s :: S). Term s (PAsData PRationalData) -> Term s PRationalData pdataImpl :: forall (s :: S). Term s PRationalData -> Term s PData | |
PLiftable PRationalData Source # | |
Defined in Plutarch.LedgerApi.Utils Methods haskToRepr :: AsHaskell PRationalData -> PlutusRepr PRationalData reprToHask :: PlutusRepr PRationalData -> Either LiftError (AsHaskell PRationalData) reprToPlut :: forall (s :: S). PlutusRepr PRationalData -> PLifted s PRationalData plutToRepr :: (forall (s :: S). PLifted s PRationalData) -> Either LiftError (PlutusRepr PRationalData) | |
POrd PRationalData Source # | Since: 3.1.0 |
Defined in Plutarch.LedgerApi.Utils Methods (#<=) :: forall (s :: S). Term s PRationalData -> Term s PRationalData -> Term s PBool (#<) :: forall (s :: S). Term s PRationalData -> Term s PRationalData -> Term s PBool pmax :: forall (s :: S). Term s PRationalData -> Term s PRationalData -> Term s PRationalData pmin :: forall (s :: S). Term s PRationalData -> Term s PRationalData -> Term s PRationalData | |
PlutusType PRationalData Source # | |
Defined in Plutarch.LedgerApi.Utils Associated Types type PInner PRationalData :: PType type PCovariant' PRationalData type PContravariant' PRationalData type PVariant' PRationalData Methods pcon' :: forall (s :: S). PRationalData s -> Term s (PInner PRationalData) pmatch' :: forall (s :: S) (b :: PType). Term s (PInner PRationalData) -> (PRationalData s -> Term s b) -> Term s b | |
PShow PRationalData Source # | Since: 3.1.0 |
Defined in Plutarch.LedgerApi.Utils Methods pshow' :: forall (s :: S). Bool -> Term s PRationalData -> Term s PString | |
Generic (PRationalData s) Source # | |
Defined in Plutarch.LedgerApi.Utils Methods from :: PRationalData s -> Rep (PRationalData s) x Source # to :: Rep (PRationalData s) x -> PRationalData s Source # | |
Generic (PRationalData s) Source # | |
Defined in Plutarch.LedgerApi.Utils Associated Types type Code (PRationalData s) :: [[Type]] Methods from :: PRationalData s -> Rep (PRationalData s) to :: Rep (PRationalData s) -> PRationalData s | |
type AsHaskell PRationalData Source # | Since: 3.3.0 |
Defined in Plutarch.LedgerApi.Utils | |
type PlutusRepr PRationalData Source # | |
Defined in Plutarch.LedgerApi.Utils | |
type PContravariant' PRationalData Source # | |
Defined in Plutarch.LedgerApi.Utils | |
type PCovariant' PRationalData Source # | |
Defined in Plutarch.LedgerApi.Utils | |
type PInner PRationalData Source # | Since: 3.3.0 |
Defined in Plutarch.LedgerApi.Utils | |
type PVariant' PRationalData Source # | |
Defined in Plutarch.LedgerApi.Utils | |
type Rep (PRationalData s) Source # | Since: 3.1.0 |
Defined in Plutarch.LedgerApi.Utils type Rep (PRationalData s) = D1 ('MetaData "PRationalData" "Plutarch.LedgerApi.Utils" "plutarch-ledger-api-3.3.0-9uebfPQOA90BujqVBUbxih" 'False) (C1 ('MetaCons "PRationalData" 'PrefixI 'True) (S1 ('MetaSel ('Just "prationalData'numerator") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Term s (PAsData PInteger))) :*: S1 ('MetaSel ('Just "prationalData'denominator") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Term s (PAsData PPositive))))) | |
type Code (PRationalData s) Source # | Since: 3.3.0 |
Defined in Plutarch.LedgerApi.Utils |
Utilities
pfromDJust :: forall (a :: S -> Type) (s :: S). PIsData a => Term s (PMaybeData a :--> a) Source #
pisDJust :: forall (a :: S -> Type) (s :: S). Term s (PMaybeData a :--> PBool) Source #
Yield PTrue
if a given PMaybeData
is of the form
.PDJust
_
Since: 2.1.1
pmaybeData :: forall (a :: S -> Type) (b :: S -> Type) (s :: S). PIsData a => Term s (b :--> ((a :--> b) :--> (PMaybeData a :--> b))) Source #
Special version of pmaybe
that works with PMaybeData
.
Since: 2.1.1
pdjust :: forall (a :: S -> Type) (s :: S). PIsData a => Term s (a :--> PMaybeData a) Source #
Construct a PDJust
value.
Since: 2.1.1
pdnothing :: forall (a :: S -> Type) (s :: S). Term s (PMaybeData a) Source #
Construct a PDNothing
value.
Since: 2.1.1
pmaybeToMaybeData :: forall (a :: S -> Type) (s :: S). PIsData a => Term s (PMaybe a :--> PMaybeData a) Source #
Construct a PMaybeData
given a PMaybe
. Could be useful if you want to
"lift" from PMaybe
to Maybe
.
Since: 2.1.1
passertPDJust :: forall (a :: S -> Type) (s :: S). PIsData a => Term s (PString :--> (PMaybeData a :--> a)) Source #
Extract the value stored in a PMaybeData
container. If there's no value,
throw an error with the given message.
Since: 2.1.1
prationalFromData :: ClosedTerm (PRationalData :--> PRational) Source #
Since: 3.1.0