{-# OPTIONS_GHC -Wno-orphans #-}
module Plutarch.LedgerApi.V3.Tx (
PTxId (..),
PTxOutRef (..),
) where
import Data.ByteString (ByteString)
import GHC.Generics (Generic)
import Generics.SOP qualified as SOP
import Plutarch.Prelude
import PlutusLedgerApi.V3 qualified as Plutus
import PlutusTx.Builtins.Internal qualified as PlutusTx
newtype PTxId (s :: S) = PTxId (Term s PByteString)
deriving stock
(
(forall x. PTxId s -> Rep (PTxId s) x)
-> (forall x. Rep (PTxId s) x -> PTxId s) -> Generic (PTxId s)
forall x. Rep (PTxId s) x -> PTxId s
forall x. PTxId s -> Rep (PTxId s) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall (s :: S) x. Rep (PTxId s) x -> PTxId s
forall (s :: S) x. PTxId s -> Rep (PTxId s) x
$cfrom :: forall (s :: S) x. PTxId s -> Rep (PTxId s) x
from :: forall x. PTxId s -> Rep (PTxId s) x
$cto :: forall (s :: S) x. Rep (PTxId s) x -> PTxId s
to :: forall x. Rep (PTxId s) x -> PTxId s
Generic
)
deriving anyclass
(
All SListI (Code (PTxId s))
All SListI (Code (PTxId s)) =>
(PTxId s -> Rep (PTxId s))
-> (Rep (PTxId s) -> PTxId s) -> Generic (PTxId s)
Rep (PTxId s) -> PTxId s
PTxId s -> Rep (PTxId s)
forall a.
All SListI (Code a) =>
(a -> Rep a) -> (Rep a -> a) -> Generic a
forall (s :: S). All SListI (Code (PTxId s))
forall (s :: S). Rep (PTxId s) -> PTxId s
forall (s :: S). PTxId s -> Rep (PTxId s)
$cfrom :: forall (s :: S). PTxId s -> Rep (PTxId s)
from :: PTxId s -> Rep (PTxId s)
$cto :: forall (s :: S). Rep (PTxId s) -> PTxId s
to :: Rep (PTxId s) -> PTxId s
SOP.Generic
,
(forall (s :: S). Term s (PAsData PTxId) -> Term s PTxId)
-> (forall (s :: S). Term s PTxId -> Term s PData) -> PIsData PTxId
forall (s :: S). Term s (PAsData PTxId) -> Term s PTxId
forall (s :: S). Term s PTxId -> Term s PData
forall (a :: S -> Type).
(forall (s :: S). Term s (PAsData a) -> Term s a)
-> (forall (s :: S). Term s a -> Term s PData) -> PIsData a
$cpfromDataImpl :: forall (s :: S). Term s (PAsData PTxId) -> Term s PTxId
pfromDataImpl :: forall (s :: S). Term s (PAsData PTxId) -> Term s PTxId
$cpdataImpl :: forall (s :: S). Term s PTxId -> Term s PData
pdataImpl :: forall (s :: S). Term s PTxId -> Term s PData
PIsData
,
(forall (s :: S). Term s PTxId -> Term s PTxId -> Term s PBool)
-> PEq PTxId
forall (s :: S). Term s PTxId -> Term s PTxId -> Term s PBool
forall (t :: S -> Type).
(forall (s :: S). Term s t -> Term s t -> Term s PBool) -> PEq t
$c#== :: forall (s :: S). Term s PTxId -> Term s PTxId -> Term s PBool
#== :: forall (s :: S). Term s PTxId -> Term s PTxId -> Term s PBool
PEq
,
PEq PTxId
PEq PTxId =>
(forall (s :: S). Term s PTxId -> Term s PTxId -> Term s PBool)
-> (forall (s :: S). Term s PTxId -> Term s PTxId -> Term s PBool)
-> (forall (s :: S). Term s PTxId -> Term s PTxId -> Term s PTxId)
-> (forall (s :: S). Term s PTxId -> Term s PTxId -> Term s PTxId)
-> POrd PTxId
forall (s :: S). Term s PTxId -> Term s PTxId -> Term s PBool
forall (s :: S). Term s PTxId -> Term s PTxId -> Term s PTxId
forall (t :: S -> Type).
PEq t =>
(forall (s :: S). Term s t -> Term s t -> Term s PBool)
-> (forall (s :: S). Term s t -> Term s t -> Term s PBool)
-> (forall (s :: S). Term s t -> Term s t -> Term s t)
-> (forall (s :: S). Term s t -> Term s t -> Term s t)
-> POrd t
$c#<= :: forall (s :: S). Term s PTxId -> Term s PTxId -> Term s PBool
#<= :: forall (s :: S). Term s PTxId -> Term s PTxId -> Term s PBool
$c#< :: forall (s :: S). Term s PTxId -> Term s PTxId -> Term s PBool
#< :: forall (s :: S). Term s PTxId -> Term s PTxId -> Term s PBool
$cpmax :: forall (s :: S). Term s PTxId -> Term s PTxId -> Term s PTxId
pmax :: forall (s :: S). Term s PTxId -> Term s PTxId -> Term s PTxId
$cpmin :: forall (s :: S). Term s PTxId -> Term s PTxId -> Term s PTxId
pmin :: forall (s :: S). Term s PTxId -> Term s PTxId -> Term s PTxId
POrd
,
(forall (s :: S). Bool -> Term s PTxId -> Term s PString)
-> PShow PTxId
forall (s :: S). Bool -> Term s PTxId -> Term s PString
forall (t :: S -> Type).
(forall (s :: S). Bool -> Term s t -> Term s PString) -> PShow t
$cpshow' :: forall (s :: S). Bool -> Term s PTxId -> Term s PString
pshow' :: forall (s :: S). Bool -> Term s PTxId -> Term s PString
PShow
)
deriving
(
(forall (s :: S). PTxId s -> Term s (PInner PTxId))
-> (forall (s :: S) (b :: S -> Type).
Term s (PInner PTxId) -> (PTxId s -> Term s b) -> Term s b)
-> PlutusType PTxId
forall (s :: S). PTxId s -> Term s (PInner PTxId)
forall (s :: S) (b :: S -> Type).
Term s (PInner PTxId) -> (PTxId s -> Term s b) -> Term s b
forall (a :: S -> Type).
(forall (s :: S). a s -> Term s (PInner a))
-> (forall (s :: S) (b :: S -> Type).
Term s (PInner a) -> (a s -> Term s b) -> Term s b)
-> PlutusType a
$cpcon' :: forall (s :: S). PTxId s -> Term s (PInner PTxId)
pcon' :: forall (s :: S). PTxId s -> Term s (PInner PTxId)
$cpmatch' :: forall (s :: S) (b :: S -> Type).
Term s (PInner PTxId) -> (PTxId s -> Term s b) -> Term s b
pmatch' :: forall (s :: S) (b :: S -> Type).
Term s (PInner PTxId) -> (PTxId s -> Term s b) -> Term s b
PlutusType
)
via (DeriveNewtypePlutusType PTxId)
instance PLiftable PTxId where
type AsHaskell PTxId = Plutus.TxId
type PlutusRepr PTxId = ByteString
{-# INLINEABLE haskToRepr #-}
haskToRepr :: AsHaskell PTxId -> PlutusRepr PTxId
haskToRepr (Plutus.TxId (PlutusTx.BuiltinByteString ByteString
str)) = ByteString
PlutusRepr PTxId
str
{-# INLINEABLE reprToHask #-}
reprToHask :: PlutusRepr PTxId -> Either LiftError (AsHaskell PTxId)
reprToHask = TxId -> Either LiftError TxId
forall a b. b -> Either a b
Right (TxId -> Either LiftError TxId)
-> (ByteString -> TxId) -> ByteString -> Either LiftError TxId
forall b c a. (b -> c) -> (a -> b) -> a -> c
. BuiltinByteString -> TxId
Plutus.TxId (BuiltinByteString -> TxId)
-> (ByteString -> BuiltinByteString) -> ByteString -> TxId
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> BuiltinByteString
PlutusTx.BuiltinByteString
{-# INLINEABLE reprToPlut #-}
reprToPlut :: forall (s :: S). PlutusRepr PTxId -> PLifted s PTxId
reprToPlut = PlutusRepr PTxId -> PLifted s PTxId
forall (a :: S -> Type) (s :: S).
(PLiftable a, Includes DefaultUni (PlutusRepr a)) =>
PlutusRepr a -> PLifted s a
reprToPlutUni
{-# INLINEABLE plutToRepr #-}
plutToRepr :: (forall (s :: S). PLifted s PTxId)
-> Either LiftError (PlutusRepr PTxId)
plutToRepr = (forall (s :: S). PLifted s PTxId)
-> Either LiftError (PlutusRepr PTxId)
forall (a :: S -> Type).
(PLiftable a, Includes DefaultUni (PlutusRepr a)) =>
(forall (s :: S). PLifted s a) -> Either LiftError (PlutusRepr a)
plutToReprUni
data PTxOutRef (s :: S) = PTxOutRef
{ forall (s :: S). PTxOutRef s -> Term s (PAsData PTxId)
ptxOutRef'id :: Term s (PAsData PTxId)
, forall (s :: S). PTxOutRef s -> Term s (PAsData PInteger)
ptxOutRef'idx :: Term s (PAsData PInteger)
}
deriving stock
(
(forall x. PTxOutRef s -> Rep (PTxOutRef s) x)
-> (forall x. Rep (PTxOutRef s) x -> PTxOutRef s)
-> Generic (PTxOutRef s)
forall x. Rep (PTxOutRef s) x -> PTxOutRef s
forall x. PTxOutRef s -> Rep (PTxOutRef s) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall (s :: S) x. Rep (PTxOutRef s) x -> PTxOutRef s
forall (s :: S) x. PTxOutRef s -> Rep (PTxOutRef s) x
$cfrom :: forall (s :: S) x. PTxOutRef s -> Rep (PTxOutRef s) x
from :: forall x. PTxOutRef s -> Rep (PTxOutRef s) x
$cto :: forall (s :: S) x. Rep (PTxOutRef s) x -> PTxOutRef s
to :: forall x. Rep (PTxOutRef s) x -> PTxOutRef s
Generic
)
deriving anyclass
(
All SListI (Code (PTxOutRef s))
All SListI (Code (PTxOutRef s)) =>
(PTxOutRef s -> Rep (PTxOutRef s))
-> (Rep (PTxOutRef s) -> PTxOutRef s) -> Generic (PTxOutRef s)
Rep (PTxOutRef s) -> PTxOutRef s
PTxOutRef s -> Rep (PTxOutRef s)
forall a.
All SListI (Code a) =>
(a -> Rep a) -> (Rep a -> a) -> Generic a
forall (s :: S). All SListI (Code (PTxOutRef s))
forall (s :: S). Rep (PTxOutRef s) -> PTxOutRef s
forall (s :: S). PTxOutRef s -> Rep (PTxOutRef s)
$cfrom :: forall (s :: S). PTxOutRef s -> Rep (PTxOutRef s)
from :: PTxOutRef s -> Rep (PTxOutRef s)
$cto :: forall (s :: S). Rep (PTxOutRef s) -> PTxOutRef s
to :: Rep (PTxOutRef s) -> PTxOutRef s
SOP.Generic
,
(forall (s :: S). Term s (PAsData PTxOutRef) -> Term s PTxOutRef)
-> (forall (s :: S). Term s PTxOutRef -> Term s PData)
-> PIsData PTxOutRef
forall (s :: S). Term s (PAsData PTxOutRef) -> Term s PTxOutRef
forall (s :: S). Term s PTxOutRef -> Term s PData
forall (a :: S -> Type).
(forall (s :: S). Term s (PAsData a) -> Term s a)
-> (forall (s :: S). Term s a -> Term s PData) -> PIsData a
$cpfromDataImpl :: forall (s :: S). Term s (PAsData PTxOutRef) -> Term s PTxOutRef
pfromDataImpl :: forall (s :: S). Term s (PAsData PTxOutRef) -> Term s PTxOutRef
$cpdataImpl :: forall (s :: S). Term s PTxOutRef -> Term s PData
pdataImpl :: forall (s :: S). Term s PTxOutRef -> Term s PData
PIsData
,
(forall (s :: S).
Term s PTxOutRef -> Term s PTxOutRef -> Term s PBool)
-> PEq PTxOutRef
forall (s :: S).
Term s PTxOutRef -> Term s PTxOutRef -> Term s PBool
forall (t :: S -> Type).
(forall (s :: S). Term s t -> Term s t -> Term s PBool) -> PEq t
$c#== :: forall (s :: S).
Term s PTxOutRef -> Term s PTxOutRef -> Term s PBool
#== :: forall (s :: S).
Term s PTxOutRef -> Term s PTxOutRef -> Term s PBool
PEq
,
(forall (s :: S). Bool -> Term s PTxOutRef -> Term s PString)
-> PShow PTxOutRef
forall (s :: S). Bool -> Term s PTxOutRef -> Term s PString
forall (t :: S -> Type).
(forall (s :: S). Bool -> Term s t -> Term s PString) -> PShow t
$cpshow' :: forall (s :: S). Bool -> Term s PTxOutRef -> Term s PString
pshow' :: forall (s :: S). Bool -> Term s PTxOutRef -> Term s PString
PShow
)
deriving
(
(forall (s :: S). PTxOutRef s -> Term s (PInner PTxOutRef))
-> (forall (s :: S) (b :: S -> Type).
Term s (PInner PTxOutRef) -> (PTxOutRef s -> Term s b) -> Term s b)
-> PlutusType PTxOutRef
forall (s :: S). PTxOutRef s -> Term s (PInner PTxOutRef)
forall (s :: S) (b :: S -> Type).
Term s (PInner PTxOutRef) -> (PTxOutRef s -> Term s b) -> Term s b
forall (a :: S -> Type).
(forall (s :: S). a s -> Term s (PInner a))
-> (forall (s :: S) (b :: S -> Type).
Term s (PInner a) -> (a s -> Term s b) -> Term s b)
-> PlutusType a
$cpcon' :: forall (s :: S). PTxOutRef s -> Term s (PInner PTxOutRef)
pcon' :: forall (s :: S). PTxOutRef s -> Term s (PInner PTxOutRef)
$cpmatch' :: forall (s :: S) (b :: S -> Type).
Term s (PInner PTxOutRef) -> (PTxOutRef s -> Term s b) -> Term s b
pmatch' :: forall (s :: S) (b :: S -> Type).
Term s (PInner PTxOutRef) -> (PTxOutRef s -> Term s b) -> Term s b
PlutusType
)
via (DeriveAsDataStruct PTxOutRef)
deriving via
DeriveDataPLiftable PTxOutRef Plutus.TxOutRef
instance
PLiftable PTxOutRef