{-# LANGUAGE GADTs #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE TupleSections #-}
{-# LANGUAGE TypeApplications #-}
module Convex.PlutusLedger(
transScriptHash,
unTransScriptHash,
unTransScriptDataHash,
unTransTxOutDatumHash,
transPubKeyHash,
unTransPubKeyHash,
transStakeKeyHash,
unTransStakeKeyHash,
transAssetName,
toMaryAssetName,
unTransAssetName,
transPolicyId,
unTransPolicyId,
transAssetId,
unTransAssetId,
transCredential,
unTransCredential,
transStakeCredential,
unTransStakeCredential,
transStakeAddressReference,
unTransStakeAddressReference,
unTransAddressInEra,
transAddressInEra,
unTransTxOutRef,
transTxOutRef,
unTransPOSIXTime,
transPOSIXTime,
unTransTxOutValue,
transValue,
unTransValue,
unTransPlutusScript,
_Interval,
_UpperBound,
_LowerBound,
_NegInf,
_PosInf,
_Finite,
_FiniteInterval
) where
import qualified Cardano.Api.Shelley as C
import Cardano.Ledger.BaseTypes (CertIx (..), TxIx (..))
import Cardano.Ledger.Credential (Ptr (..))
import qualified Cardano.Ledger.Mary.Value as Mary (AssetName (..))
import qualified Codec.Serialise as Codec
import Control.Lens (Iso', Prism', iso, prism')
import qualified Data.ByteString.Lazy as BSL
import Data.ByteString.Short (fromShort)
import qualified Data.ByteString.Short as Short
import Data.Functor ((<&>))
import Data.Time.Clock.POSIX (POSIXTime)
import PlutusLedgerApi.Common (SerialisedScript)
import qualified PlutusLedgerApi.V1 as PV1
import PlutusLedgerApi.V1.Interval (Closure, Extended (..),
Interval (..), LowerBound (..),
UpperBound (..))
import qualified PlutusLedgerApi.V1.Scripts as P
import qualified PlutusLedgerApi.V1.Value as Value
import qualified PlutusTx.AssocMap as Map
import qualified PlutusTx.Prelude as PlutusTx
transScriptHash :: C.ScriptHash -> PV1.ScriptHash
transScriptHash :: ScriptHash -> ScriptHash
transScriptHash ScriptHash
h = BuiltinByteString -> ScriptHash
PV1.ScriptHash (forall a arep. ToBuiltin a arep => a -> arep
PV1.toBuiltin (forall a. SerialiseAsRawBytes a => a -> ByteString
C.serialiseToRawBytes ScriptHash
h))
unTransScriptHash :: PV1.ScriptHash -> Either C.SerialiseAsRawBytesError C.ScriptHash
unTransScriptHash :: ScriptHash -> Either SerialiseAsRawBytesError ScriptHash
unTransScriptHash (PV1.ScriptHash BuiltinByteString
vh) =
forall a.
SerialiseAsRawBytes a =>
AsType a -> ByteString -> Either SerialiseAsRawBytesError a
C.deserialiseFromRawBytes AsType ScriptHash
C.AsScriptHash forall a b. (a -> b) -> a -> b
$ forall arep a. FromBuiltin arep a => arep -> a
PlutusTx.fromBuiltin BuiltinByteString
vh
transAssetName :: Mary.AssetName -> PV1.TokenName
transAssetName :: AssetName -> TokenName
transAssetName (Mary.AssetName ShortByteString
bs) = BuiltinByteString -> TokenName
PV1.TokenName (forall a arep. ToBuiltin a arep => a -> arep
PV1.toBuiltin (ShortByteString -> ByteString
fromShort ShortByteString
bs))
unTransAssetName :: PV1.TokenName -> C.AssetName
unTransAssetName :: TokenName -> AssetName
unTransAssetName (PV1.TokenName BuiltinByteString
bs) = ByteString -> AssetName
C.AssetName forall a b. (a -> b) -> a -> b
$ forall arep a. FromBuiltin arep a => arep -> a
PV1.fromBuiltin BuiltinByteString
bs
transPolicyId :: C.PolicyId -> PV1.CurrencySymbol
transPolicyId :: PolicyId -> CurrencySymbol
transPolicyId (C.PolicyId ScriptHash
scriptHash) = BuiltinByteString -> CurrencySymbol
PV1.CurrencySymbol forall a b. (a -> b) -> a -> b
$ forall a arep. ToBuiltin a arep => a -> arep
PlutusTx.toBuiltin (forall a. SerialiseAsRawBytes a => a -> ByteString
C.serialiseToRawBytes ScriptHash
scriptHash)
unTransPolicyId :: PV1.CurrencySymbol -> Either C.SerialiseAsRawBytesError C.PolicyId
unTransPolicyId :: CurrencySymbol -> Either SerialiseAsRawBytesError PolicyId
unTransPolicyId (PV1.CurrencySymbol BuiltinByteString
bs) =
forall a.
SerialiseAsRawBytes a =>
AsType a -> ByteString -> Either SerialiseAsRawBytesError a
C.deserialiseFromRawBytes AsType PolicyId
C.AsPolicyId (forall arep a. FromBuiltin arep a => arep -> a
PlutusTx.fromBuiltin BuiltinByteString
bs)
transAssetId :: C.AssetId -> Value.AssetClass
transAssetId :: AssetId -> AssetClass
transAssetId AssetId
C.AdaAssetId = CurrencySymbol -> TokenName -> AssetClass
Value.assetClass CurrencySymbol
PV1.adaSymbol TokenName
PV1.adaToken
transAssetId (C.AssetId PolicyId
policyId AssetName
assetName) =
CurrencySymbol -> TokenName -> AssetClass
Value.assetClass
(PolicyId -> CurrencySymbol
transPolicyId forall a b. (a -> b) -> a -> b
$ PolicyId
policyId)
(AssetName -> TokenName
transAssetName forall a b. (a -> b) -> a -> b
$ AssetName -> AssetName
toMaryAssetName AssetName
assetName)
toMaryAssetName :: C.AssetName -> Mary.AssetName
toMaryAssetName :: AssetName -> AssetName
toMaryAssetName (C.AssetName ByteString
n) = ShortByteString -> AssetName
Mary.AssetName forall a b. (a -> b) -> a -> b
$ ByteString -> ShortByteString
Short.toShort ByteString
n
unTransAssetId :: Value.AssetClass -> Either C.SerialiseAsRawBytesError C.AssetId
unTransAssetId :: AssetClass -> Either SerialiseAsRawBytesError AssetId
unTransAssetId (Value.AssetClass (CurrencySymbol
currencySymbol, TokenName
tokenName))
| CurrencySymbol
currencySymbol forall a. Eq a => a -> a -> Bool
== CurrencySymbol
PV1.adaSymbol Bool -> Bool -> Bool
&& TokenName
tokenName forall a. Eq a => a -> a -> Bool
== TokenName
PV1.adaToken =
forall (f :: * -> *) a. Applicative f => a -> f a
pure AssetId
C.AdaAssetId
| Bool
otherwise =
PolicyId -> AssetName -> AssetId
C.AssetId
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> CurrencySymbol -> Either SerialiseAsRawBytesError PolicyId
unTransPolicyId CurrencySymbol
currencySymbol
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall (f :: * -> *) a. Applicative f => a -> f a
pure (TokenName -> AssetName
unTransAssetName TokenName
tokenName)
unTransPubKeyHash :: PV1.PubKeyHash -> Either C.SerialiseAsRawBytesError (C.Hash C.PaymentKey)
unTransPubKeyHash :: PubKeyHash -> Either SerialiseAsRawBytesError (Hash PaymentKey)
unTransPubKeyHash (PV1.PubKeyHash BuiltinByteString
pkh) =
let bsx :: ByteString
bsx = forall arep a. FromBuiltin arep a => arep -> a
PlutusTx.fromBuiltin BuiltinByteString
pkh
in forall a.
SerialiseAsRawBytes a =>
AsType a -> ByteString -> Either SerialiseAsRawBytesError a
C.deserialiseFromRawBytes (forall a. AsType a -> AsType (Hash a)
C.AsHash AsType PaymentKey
C.AsPaymentKey) ByteString
bsx
transPubKeyHash :: C.Hash C.PaymentKey -> PV1.PubKeyHash
transPubKeyHash :: Hash PaymentKey -> PubKeyHash
transPubKeyHash = BuiltinByteString -> PubKeyHash
PV1.PubKeyHash forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a arep. ToBuiltin a arep => a -> arep
PlutusTx.toBuiltin forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. SerialiseAsRawBytes a => a -> ByteString
C.serialiseToRawBytes
transStakeKeyHash :: C.Hash C.StakeKey -> PV1.PubKeyHash
transStakeKeyHash :: Hash StakeKey -> PubKeyHash
transStakeKeyHash = BuiltinByteString -> PubKeyHash
PV1.PubKeyHash forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a arep. ToBuiltin a arep => a -> arep
PlutusTx.toBuiltin forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. SerialiseAsRawBytes a => a -> ByteString
C.serialiseToRawBytes
unTransStakeKeyHash :: PV1.PubKeyHash -> Either C.SerialiseAsRawBytesError (C.Hash C.StakeKey)
unTransStakeKeyHash :: PubKeyHash -> Either SerialiseAsRawBytesError (Hash StakeKey)
unTransStakeKeyHash (PV1.PubKeyHash BuiltinByteString
pkh) =
let bsx :: ByteString
bsx = forall arep a. FromBuiltin arep a => arep -> a
PlutusTx.fromBuiltin BuiltinByteString
pkh
in forall a.
SerialiseAsRawBytes a =>
AsType a -> ByteString -> Either SerialiseAsRawBytesError a
C.deserialiseFromRawBytes (forall a. AsType a -> AsType (Hash a)
C.AsHash AsType StakeKey
C.AsStakeKey) ByteString
bsx
unTransCredential :: PV1.Credential -> Either C.SerialiseAsRawBytesError C.PaymentCredential
unTransCredential :: Credential -> Either SerialiseAsRawBytesError PaymentCredential
unTransCredential = \case
PV1.PubKeyCredential PubKeyHash
c -> Hash PaymentKey -> PaymentCredential
C.PaymentCredentialByKey forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> PubKeyHash -> Either SerialiseAsRawBytesError (Hash PaymentKey)
unTransPubKeyHash PubKeyHash
c
PV1.ScriptCredential ScriptHash
c -> ScriptHash -> PaymentCredential
C.PaymentCredentialByScript forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ScriptHash -> Either SerialiseAsRawBytesError ScriptHash
unTransScriptHash ScriptHash
c
transCredential :: C.PaymentCredential -> PV1.Credential
transCredential :: PaymentCredential -> Credential
transCredential = \case
C.PaymentCredentialByKey Hash PaymentKey
k -> PubKeyHash -> Credential
PV1.PubKeyCredential (Hash PaymentKey -> PubKeyHash
transPubKeyHash Hash PaymentKey
k)
C.PaymentCredentialByScript ScriptHash
k -> ScriptHash -> Credential
PV1.ScriptCredential (ScriptHash -> ScriptHash
transScriptHash ScriptHash
k)
transStakeAddressReference :: C.StakeAddressReference -> Maybe PV1.StakingCredential
transStakeAddressReference :: StakeAddressReference -> Maybe StakingCredential
transStakeAddressReference = \case
C.StakeAddressByValue StakeCredential
x -> forall a. a -> Maybe a
Just (Credential -> StakingCredential
PV1.StakingHash forall a b. (a -> b) -> a -> b
$ StakeCredential -> Credential
transStakeCredential StakeCredential
x)
C.StakeAddressByPointer (C.StakeAddressPointer (Ptr (C.SlotNo Word64
slotNo) (TxIx Word64
txIx) (CertIx Word64
ptrIx))) -> forall a. a -> Maybe a
Just (Integer -> Integer -> Integer -> StakingCredential
PV1.StakingPtr (forall a b. (Integral a, Num b) => a -> b
fromIntegral Word64
slotNo) (forall a b. (Integral a, Num b) => a -> b
fromIntegral Word64
txIx) (forall a b. (Integral a, Num b) => a -> b
fromIntegral Word64
ptrIx))
StakeAddressReference
C.NoStakeAddress -> forall a. Maybe a
Nothing
transStakeCredential :: C.StakeCredential -> PV1.Credential
transStakeCredential :: StakeCredential -> Credential
transStakeCredential (C.StakeCredentialByKey Hash StakeKey
stakeKeyHash) = PubKeyHash -> Credential
PV1.PubKeyCredential (Hash StakeKey -> PubKeyHash
transStakeKeyHash Hash StakeKey
stakeKeyHash)
transStakeCredential (C.StakeCredentialByScript ScriptHash
scriptHash) = ScriptHash -> Credential
PV1.ScriptCredential (ScriptHash -> ScriptHash
transScriptHash ScriptHash
scriptHash)
unTransStakeCredential :: PV1.Credential -> Either C.SerialiseAsRawBytesError C.StakeCredential
unTransStakeCredential :: Credential -> Either SerialiseAsRawBytesError StakeCredential
unTransStakeCredential (PV1.PubKeyCredential PubKeyHash
pubKeyHash) = Hash StakeKey -> StakeCredential
C.StakeCredentialByKey forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> PubKeyHash -> Either SerialiseAsRawBytesError (Hash StakeKey)
unTransStakeKeyHash PubKeyHash
pubKeyHash
unTransStakeCredential (PV1.ScriptCredential ScriptHash
scriptHash) = ScriptHash -> StakeCredential
C.StakeCredentialByScript forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ScriptHash -> Either SerialiseAsRawBytesError ScriptHash
unTransScriptHash ScriptHash
scriptHash
unTransStakeAddressReference :: Maybe PV1.StakingCredential -> Either C.SerialiseAsRawBytesError C.StakeAddressReference
unTransStakeAddressReference :: Maybe StakingCredential
-> Either SerialiseAsRawBytesError StakeAddressReference
unTransStakeAddressReference Maybe StakingCredential
Nothing = forall a b. b -> Either a b
Right StakeAddressReference
C.NoStakeAddress
unTransStakeAddressReference (Just (PV1.StakingHash Credential
credential)) =
StakeCredential -> StakeAddressReference
C.StakeAddressByValue forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Credential -> Either SerialiseAsRawBytesError StakeCredential
unTransStakeCredential Credential
credential
unTransStakeAddressReference (Just (PV1.StakingPtr Integer
slotNo Integer
txIx Integer
ptrIx)) =
forall a b. b -> Either a b
Right (StakeAddressPointer -> StakeAddressReference
C.StakeAddressByPointer (Ptr -> StakeAddressPointer
C.StakeAddressPointer (SlotNo -> TxIx -> CertIx -> Ptr
Ptr (Word64 -> SlotNo
C.SlotNo forall a b. (a -> b) -> a -> b
$ forall a b. (Integral a, Num b) => a -> b
fromIntegral Integer
slotNo) (Word64 -> TxIx
TxIx forall a b. (a -> b) -> a -> b
$ forall a b. (Integral a, Num b) => a -> b
fromIntegral Integer
txIx) (Word64 -> CertIx
CertIx forall a b. (a -> b) -> a -> b
$ forall a b. (Integral a, Num b) => a -> b
fromIntegral Integer
ptrIx))))
unTransAddressInEra :: C.NetworkId -> PV1.Address -> Either C.SerialiseAsRawBytesError (C.AddressInEra C.BabbageEra)
unTransAddressInEra :: NetworkId
-> Address
-> Either SerialiseAsRawBytesError (AddressInEra BabbageEra)
unTransAddressInEra NetworkId
networkId (PV1.Address Credential
cred Maybe StakingCredential
staking) =
forall addrtype era.
AddressTypeInEra addrtype era
-> Address addrtype -> AddressInEra era
C.AddressInEra (forall era. ShelleyBasedEra era -> AddressTypeInEra ShelleyAddr era
C.ShelleyAddressInEra ShelleyBasedEra BabbageEra
C.ShelleyBasedEraBabbage) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>
(NetworkId
-> PaymentCredential
-> StakeAddressReference
-> Address ShelleyAddr
C.makeShelleyAddress NetworkId
networkId
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Credential -> Either SerialiseAsRawBytesError PaymentCredential
unTransCredential Credential
cred
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Maybe StakingCredential
-> Either SerialiseAsRawBytesError StakeAddressReference
unTransStakeAddressReference Maybe StakingCredential
staking
)
transAddressInEra :: C.AddressInEra C.BabbageEra -> Maybe PV1.Address
transAddressInEra :: AddressInEra BabbageEra -> Maybe Address
transAddressInEra = \case
C.AddressInEra (C.ShelleyAddressInEra ShelleyBasedEra BabbageEra
C.ShelleyBasedEraBabbage) (C.ShelleyAddress Network
_ PaymentCredential StandardCrypto
p StakeReference StandardCrypto
s) ->
forall a. a -> Maybe a
Just forall a b. (a -> b) -> a -> b
$ Credential -> Maybe StakingCredential -> Address
PV1.Address
(PaymentCredential -> Credential
transCredential forall a b. (a -> b) -> a -> b
$ PaymentCredential StandardCrypto -> PaymentCredential
C.fromShelleyPaymentCredential PaymentCredential StandardCrypto
p)
(StakeAddressReference -> Maybe StakingCredential
transStakeAddressReference forall a b. (a -> b) -> a -> b
$ StakeReference StandardCrypto -> StakeAddressReference
C.fromShelleyStakeReference StakeReference StandardCrypto
s)
C.AddressInEra AddressTypeInEra addrtype BabbageEra
C.ByronAddressInAnyEra Address addrtype
_ -> forall a. Maybe a
Nothing
unTransTxOutRef :: PV1.TxOutRef -> Either C.SerialiseAsRawBytesError C.TxIn
unTransTxOutRef :: TxOutRef -> Either SerialiseAsRawBytesError TxIn
unTransTxOutRef PV1.TxOutRef{txOutRefId :: TxOutRef -> TxId
PV1.txOutRefId=PV1.TxId BuiltinByteString
bs, Integer
txOutRefIdx :: TxOutRef -> Integer
txOutRefIdx :: Integer
PV1.txOutRefIdx} =
let i :: Either SerialiseAsRawBytesError TxId
i = forall a.
SerialiseAsRawBytes a =>
AsType a -> ByteString -> Either SerialiseAsRawBytesError a
C.deserialiseFromRawBytes AsType TxId
C.AsTxId forall a b. (a -> b) -> a -> b
$ forall arep a. FromBuiltin arep a => arep -> a
PlutusTx.fromBuiltin BuiltinByteString
bs
in TxId -> TxIx -> TxIn
C.TxIn forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Either SerialiseAsRawBytesError TxId
i forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall (f :: * -> *) a. Applicative f => a -> f a
pure (Word -> TxIx
C.TxIx forall a b. (a -> b) -> a -> b
$ forall a b. (Integral a, Num b) => a -> b
fromIntegral Integer
txOutRefIdx)
transTxOutRef :: C.TxIn -> PV1.TxOutRef
transTxOutRef :: TxIn -> TxOutRef
transTxOutRef (C.TxIn TxId
txId (C.TxIx Word
ix)) =
let i :: TxId
i = BuiltinByteString -> TxId
PV1.TxId forall a b. (a -> b) -> a -> b
$ forall a arep. ToBuiltin a arep => a -> arep
PlutusTx.toBuiltin forall a b. (a -> b) -> a -> b
$ forall a. SerialiseAsRawBytes a => a -> ByteString
C.serialiseToRawBytes TxId
txId
in TxId -> Integer -> TxOutRef
PV1.TxOutRef TxId
i (forall a b. (Integral a, Num b) => a -> b
fromIntegral Word
ix)
transPOSIXTime :: POSIXTime -> PV1.POSIXTime
transPOSIXTime :: POSIXTime -> POSIXTime
transPOSIXTime POSIXTime
posixTimeSeconds = Integer -> POSIXTime
PV1.POSIXTime (forall a b. (RealFrac a, Integral b) => a -> b
floor @Rational (Rational
1000 forall a. Num a => a -> a -> a
* forall a b. (Real a, Fractional b) => a -> b
realToFrac POSIXTime
posixTimeSeconds))
unTransPOSIXTime :: PV1.POSIXTime -> POSIXTime
unTransPOSIXTime :: POSIXTime -> POSIXTime
unTransPOSIXTime (PV1.POSIXTime Integer
pt) = forall a b. (Real a, Fractional b) => a -> b
realToFrac @Rational forall a b. (a -> b) -> a -> b
$ forall a b. (Integral a, Num b) => a -> b
fromIntegral Integer
pt forall a. Fractional a => a -> a -> a
/ Rational
1000
unTransTxOutValue :: PV1.Value -> Either C.SerialiseAsRawBytesError (C.TxOutValue C.BabbageEra)
unTransTxOutValue :: Value -> Either SerialiseAsRawBytesError (TxOutValue BabbageEra)
unTransTxOutValue Value
value = forall era. MultiAssetSupportedInEra era -> Value -> TxOutValue era
C.TxOutValue MultiAssetSupportedInEra BabbageEra
C.MultiAssetInBabbageEra forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Value -> Either SerialiseAsRawBytesError Value
unTransValue Value
value
unTransValue :: PV1.Value -> Either C.SerialiseAsRawBytesError C.Value
unTransValue :: Value -> Either SerialiseAsRawBytesError Value
unTransValue =
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap [(AssetId, Quantity)] -> Value
C.valueFromList forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse (CurrencySymbol, TokenName, Integer)
-> Either SerialiseAsRawBytesError (AssetId, Quantity)
toSingleton forall b c a. (b -> c) -> (a -> b) -> a -> c
. Value -> [(CurrencySymbol, TokenName, Integer)]
Value.flattenValue
where
toSingleton :: (CurrencySymbol, TokenName, Integer)
-> Either SerialiseAsRawBytesError (AssetId, Quantity)
toSingleton (CurrencySymbol
cs, TokenName
tn, Integer
q) =
AssetClass -> Either SerialiseAsRawBytesError AssetId
unTransAssetId (CurrencySymbol -> TokenName -> AssetClass
Value.assetClass CurrencySymbol
cs TokenName
tn) forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
<&> (, Integer -> Quantity
C.Quantity Integer
q)
transValue :: C.Value -> PV1.Value
transValue :: Value -> Value
transValue =
let t :: (AssetId, Quantity) -> (CurrencySymbol, Map TokenName Integer)
t (AssetId
assetId, C.Quantity Integer
quantity) =
let Value.AssetClass (CurrencySymbol
sym, TokenName
tn) = AssetId -> AssetClass
transAssetId AssetId
assetId
in (CurrencySymbol
sym, forall k v. k -> v -> Map k v
Map.singleton TokenName
tn Integer
quantity)
in Map CurrencySymbol (Map TokenName Integer) -> Value
PV1.Value forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall k v. [(k, v)] -> Map k v
Map.fromList forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (AssetId, Quantity) -> (CurrencySymbol, Map TokenName Integer)
t forall b c a. (b -> c) -> (a -> b) -> a -> c
. Value -> [(AssetId, Quantity)]
C.valueToList
unTransPlutusScript
:: C.SerialiseAsRawBytes plutusScript
=> C.AsType plutusScript
-> SerialisedScript
-> Either C.SerialiseAsRawBytesError plutusScript
unTransPlutusScript :: forall plutusScript.
SerialiseAsRawBytes plutusScript =>
AsType plutusScript
-> ShortByteString -> Either SerialiseAsRawBytesError plutusScript
unTransPlutusScript AsType plutusScript
asPlutusScriptType =
forall a.
SerialiseAsRawBytes a =>
AsType a -> ByteString -> Either SerialiseAsRawBytesError a
C.deserialiseFromRawBytes AsType plutusScript
asPlutusScriptType forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> ByteString
BSL.toStrict forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Serialise a => a -> ByteString
Codec.serialise
unTransScriptDataHash :: P.DatumHash -> Either C.SerialiseAsRawBytesError (C.Hash C.ScriptData)
unTransScriptDataHash :: DatumHash -> Either SerialiseAsRawBytesError (Hash ScriptData)
unTransScriptDataHash (P.DatumHash BuiltinByteString
bs) =
forall a.
SerialiseAsRawBytes a =>
AsType a -> ByteString -> Either SerialiseAsRawBytesError a
C.deserialiseFromRawBytes (forall a. AsType a -> AsType (Hash a)
C.AsHash AsType ScriptData
C.AsScriptData) (forall arep a. FromBuiltin arep a => arep -> a
PlutusTx.fromBuiltin BuiltinByteString
bs)
unTransTxOutDatumHash :: P.DatumHash -> Either C.SerialiseAsRawBytesError (C.TxOutDatum ctx C.BabbageEra)
unTransTxOutDatumHash :: forall ctx.
DatumHash
-> Either SerialiseAsRawBytesError (TxOutDatum ctx BabbageEra)
unTransTxOutDatumHash DatumHash
datumHash = forall era ctx.
ScriptDataSupportedInEra era
-> Hash ScriptData -> TxOutDatum ctx era
C.TxOutDatumHash ScriptDataSupportedInEra BabbageEra
C.ScriptDataInBabbageEra forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> DatumHash -> Either SerialiseAsRawBytesError (Hash ScriptData)
unTransScriptDataHash DatumHash
datumHash
_Interval :: Iso' (Interval a) (LowerBound a, UpperBound a)
_Interval :: forall a. Iso' (Interval a) (LowerBound a, UpperBound a)
_Interval = forall s a b t. (s -> a) -> (b -> t) -> Iso s t a b
iso forall {a}. Interval a -> (LowerBound a, UpperBound a)
from forall {a}. (LowerBound a, UpperBound a) -> Interval a
to where
from :: Interval a -> (LowerBound a, UpperBound a)
from Interval{LowerBound a
ivFrom :: forall a. Interval a -> LowerBound a
ivFrom :: LowerBound a
ivFrom, UpperBound a
ivTo :: forall a. Interval a -> UpperBound a
ivTo :: UpperBound a
ivTo} = (LowerBound a
ivFrom, UpperBound a
ivTo)
to :: (LowerBound a, UpperBound a) -> Interval a
to (LowerBound a
ivFrom, UpperBound a
ivTo) = Interval{LowerBound a
ivFrom :: LowerBound a
ivFrom :: LowerBound a
ivFrom, UpperBound a
ivTo :: UpperBound a
ivTo :: UpperBound a
ivTo}
_UpperBound :: Iso' (UpperBound a) (Extended a, Closure)
_UpperBound :: forall a. Iso' (UpperBound a) (Extended a, Bool)
_UpperBound = forall s a b t. (s -> a) -> (b -> t) -> Iso s t a b
iso forall {a}. UpperBound a -> (Extended a, Bool)
from forall {a}. (Extended a, Bool) -> UpperBound a
to where
from :: UpperBound a -> (Extended a, Bool)
from (UpperBound Extended a
a Bool
b) = (Extended a
a, Bool
b)
to :: (Extended a, Bool) -> UpperBound a
to = forall a b c. (a -> b -> c) -> (a, b) -> c
uncurry forall a. Extended a -> Bool -> UpperBound a
UpperBound
_LowerBound :: Iso' (LowerBound a) (Extended a, Closure)
_LowerBound :: forall a. Iso' (LowerBound a) (Extended a, Bool)
_LowerBound = forall s a b t. (s -> a) -> (b -> t) -> Iso s t a b
iso forall {a}. LowerBound a -> (Extended a, Bool)
from forall {a}. (Extended a, Bool) -> LowerBound a
to where
from :: LowerBound a -> (Extended a, Bool)
from (LowerBound Extended a
a Bool
b) = (Extended a
a, Bool
b)
to :: (Extended a, Bool) -> LowerBound a
to = forall a b c. (a -> b -> c) -> (a, b) -> c
uncurry forall a. Extended a -> Bool -> LowerBound a
LowerBound
_NegInf :: Prism' (Extended a) ()
_NegInf :: forall a. Prism' (Extended a) ()
_NegInf = forall b s a. (b -> s) -> (s -> Maybe a) -> Prism s s a b
prism' forall {a}. () -> Extended a
from forall {a}. Extended a -> Maybe ()
to where
from :: () -> Extended a
from () = forall a. Extended a
NegInf
to :: Extended a -> Maybe ()
to = \case
Extended a
NegInf -> forall a. a -> Maybe a
Just ()
Extended a
_ -> forall a. Maybe a
Nothing
_PosInf :: Prism' (Extended a) ()
_PosInf :: forall a. Prism' (Extended a) ()
_PosInf = forall b s a. (b -> s) -> (s -> Maybe a) -> Prism s s a b
prism' forall {a}. () -> Extended a
from forall {a}. Extended a -> Maybe ()
to where
from :: () -> Extended a
from () = forall a. Extended a
PosInf
to :: Extended a -> Maybe ()
to = \case
Extended a
PosInf -> forall a. a -> Maybe a
Just ()
Extended a
_ -> forall a. Maybe a
Nothing
_Finite :: Prism' (Extended a) a
_Finite :: forall a. Prism' (Extended a) a
_Finite = forall b s a. (b -> s) -> (s -> Maybe a) -> Prism s s a b
prism' forall {a}. a -> Extended a
from forall {a}. Extended a -> Maybe a
to where
from :: a -> Extended a
from = forall {a}. a -> Extended a
Finite
to :: Extended a -> Maybe a
to = \case
Finite a
a -> forall a. a -> Maybe a
Just a
a
Extended a
_ -> forall a. Maybe a
Nothing
_FiniteInterval :: Prism' (Interval a) ((a, a), (Closure, Closure))
_FiniteInterval :: forall a. Prism' (Interval a) ((a, a), (Bool, Bool))
_FiniteInterval = forall b s a. (b -> s) -> (s -> Maybe a) -> Prism s s a b
prism' forall {a}. ((a, a), (Bool, Bool)) -> Interval a
from forall {b}. Interval b -> Maybe ((b, b), (Bool, Bool))
to where
from :: ((a, a), (Bool, Bool)) -> Interval a
from ((a
l, a
u), (Bool
lc, Bool
uc)) = forall a. LowerBound a -> UpperBound a -> Interval a
Interval (forall a. Extended a -> Bool -> LowerBound a
LowerBound (forall {a}. a -> Extended a
Finite a
l) Bool
lc) (forall a. Extended a -> Bool -> UpperBound a
UpperBound (forall {a}. a -> Extended a
Finite a
u) Bool
uc)
to :: Interval b -> Maybe ((b, b), (Bool, Bool))
to (Interval (LowerBound (Finite b
l) Bool
lc) (UpperBound (Finite b
u) Bool
uc)) = forall a. a -> Maybe a
Just ((b
l, b
u), (Bool
lc, Bool
uc))
to Interval b
_ = forall a. Maybe a
Nothing