{-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE UndecidableInstances #-} {-# OPTIONS_GHC -Wno-orphans #-} module Plutarch.Api.V1.Address ( PCredential (PPubKeyCredential, PScriptCredential), PStakingCredential (PStakingHash, PStakingPtr), PAddress (PAddress), ) where import PlutusLedgerApi.V1 qualified as Plutus import Plutarch.Api.V1.Crypto (PPubKeyHash) import Plutarch.Api.V1.Maybe (PMaybeData) import Plutarch.Api.V1.Scripts (PScriptHash) import Plutarch.DataRepr ( DerivePConstantViaData (DerivePConstantViaData), PDataFields, ) import Plutarch.Lift ( PConstantDecl, PLifted, PUnsafeLiftDecl, ) import Plutarch.Prelude data PCredential (s :: S) = PPubKeyCredential (Term s (PDataRecord '["_0" ':= PPubKeyHash])) | PScriptCredential (Term s (PDataRecord '["_0" ':= PScriptHash])) deriving stock (forall a. (forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a forall (s :: S) x. Rep (PCredential s) x -> PCredential s forall (s :: S) x. PCredential s -> Rep (PCredential s) x $cto :: forall (s :: S) x. Rep (PCredential s) x -> PCredential s $cfrom :: forall (s :: S) x. PCredential s -> Rep (PCredential s) x Generic) deriving anyclass (forall (s :: S). PCredential s -> Term s (PInner PCredential) forall (s :: S) (b :: PType). Term s (PInner PCredential) -> (PCredential s -> Term s b) -> Term s b forall (a :: PType). (forall (s :: S). a s -> Term s (PInner a)) -> (forall (s :: S) (b :: PType). Term s (PInner a) -> (a s -> Term s b) -> Term s b) -> PlutusType a pmatch' :: forall (s :: S) (b :: PType). Term s (PInner PCredential) -> (PCredential s -> Term s b) -> Term s b $cpmatch' :: forall (s :: S) (b :: PType). Term s (PInner PCredential) -> (PCredential s -> Term s b) -> Term s b pcon' :: forall (s :: S). PCredential s -> Term s (PInner PCredential) $cpcon' :: forall (s :: S). PCredential s -> Term s (PInner PCredential) PlutusType, forall (s :: S). Term s (PAsData PCredential) -> Term s PCredential forall (s :: S). Term s PCredential -> Term s PData forall (a :: PType). (forall (s :: S). Term s (PAsData a) -> Term s a) -> (forall (s :: S). Term s a -> Term s PData) -> PIsData a pdataImpl :: forall (s :: S). Term s PCredential -> Term s PData $cpdataImpl :: forall (s :: S). Term s PCredential -> Term s PData pfromDataImpl :: forall (s :: S). Term s (PAsData PCredential) -> Term s PCredential $cpfromDataImpl :: forall (s :: S). Term s (PAsData PCredential) -> Term s PCredential PIsData, forall (s :: S). Term s PCredential -> Term s PCredential -> Term s PBool forall (t :: PType). (forall (s :: S). Term s t -> Term s t -> Term s PBool) -> PEq t #== :: forall (s :: S). Term s PCredential -> Term s PCredential -> Term s PBool $c#== :: forall (s :: S). Term s PCredential -> Term s PCredential -> Term s PBool PEq, PEq PCredential forall (s :: S). Term s PCredential -> Term s PCredential -> Term s PBool forall (t :: PType). 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) -> PPartialOrd t #< :: forall (s :: S). Term s PCredential -> Term s PCredential -> Term s PBool $c#< :: forall (s :: S). Term s PCredential -> Term s PCredential -> Term s PBool #<= :: forall (s :: S). Term s PCredential -> Term s PCredential -> Term s PBool $c#<= :: forall (s :: S). Term s PCredential -> Term s PCredential -> Term s PBool PPartialOrd, PPartialOrd PCredential forall (t :: PType). PPartialOrd t -> POrd t POrd, forall (s :: S). Bool -> Term s PCredential -> Term s PString forall (t :: PType). (forall (s :: S). Bool -> Term s t -> Term s PString) -> PShow t pshow' :: forall (s :: S). Bool -> Term s PCredential -> Term s PString $cpshow' :: forall (s :: S). Bool -> Term s PCredential -> Term s PString PShow, PTryFrom PData) instance DerivePlutusType PCredential where type DPTStrat _ = PlutusTypeData instance PUnsafeLiftDecl PCredential where type PLifted PCredential = Plutus.Credential deriving via (DerivePConstantViaData Plutus.Credential PCredential) instance PConstantDecl Plutus.Credential instance PTryFrom PData (PAsData PCredential) data PStakingCredential (s :: S) = PStakingHash (Term s (PDataRecord '["_0" ':= PCredential])) | PStakingPtr ( Term s ( PDataRecord '[ "_0" ':= PInteger , "_1" ':= PInteger , "_2" ':= PInteger ] ) ) deriving stock (forall a. (forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a forall (s :: S) x. Rep (PStakingCredential s) x -> PStakingCredential s forall (s :: S) x. PStakingCredential s -> Rep (PStakingCredential s) x $cto :: forall (s :: S) x. Rep (PStakingCredential s) x -> PStakingCredential s $cfrom :: forall (s :: S) x. PStakingCredential s -> Rep (PStakingCredential s) x Generic) deriving anyclass (forall (s :: S). PStakingCredential s -> Term s (PInner PStakingCredential) forall (s :: S) (b :: PType). Term s (PInner PStakingCredential) -> (PStakingCredential s -> Term s b) -> Term s b forall (a :: PType). (forall (s :: S). a s -> Term s (PInner a)) -> (forall (s :: S) (b :: PType). Term s (PInner a) -> (a s -> Term s b) -> Term s b) -> PlutusType a pmatch' :: forall (s :: S) (b :: PType). Term s (PInner PStakingCredential) -> (PStakingCredential s -> Term s b) -> Term s b $cpmatch' :: forall (s :: S) (b :: PType). Term s (PInner PStakingCredential) -> (PStakingCredential s -> Term s b) -> Term s b pcon' :: forall (s :: S). PStakingCredential s -> Term s (PInner PStakingCredential) $cpcon' :: forall (s :: S). PStakingCredential s -> Term s (PInner PStakingCredential) PlutusType, forall (s :: S). Term s (PAsData PStakingCredential) -> Term s PStakingCredential forall (s :: S). Term s PStakingCredential -> Term s PData forall (a :: PType). (forall (s :: S). Term s (PAsData a) -> Term s a) -> (forall (s :: S). Term s a -> Term s PData) -> PIsData a pdataImpl :: forall (s :: S). Term s PStakingCredential -> Term s PData $cpdataImpl :: forall (s :: S). Term s PStakingCredential -> Term s PData pfromDataImpl :: forall (s :: S). Term s (PAsData PStakingCredential) -> Term s PStakingCredential $cpfromDataImpl :: forall (s :: S). Term s (PAsData PStakingCredential) -> Term s PStakingCredential PIsData, forall (s :: S). Term s PStakingCredential -> Term s PStakingCredential -> Term s PBool forall (t :: PType). (forall (s :: S). Term s t -> Term s t -> Term s PBool) -> PEq t #== :: forall (s :: S). Term s PStakingCredential -> Term s PStakingCredential -> Term s PBool $c#== :: forall (s :: S). Term s PStakingCredential -> Term s PStakingCredential -> Term s PBool PEq, PEq PStakingCredential forall (s :: S). Term s PStakingCredential -> Term s PStakingCredential -> Term s PBool forall (t :: PType). 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) -> PPartialOrd t #< :: forall (s :: S). Term s PStakingCredential -> Term s PStakingCredential -> Term s PBool $c#< :: forall (s :: S). Term s PStakingCredential -> Term s PStakingCredential -> Term s PBool #<= :: forall (s :: S). Term s PStakingCredential -> Term s PStakingCredential -> Term s PBool $c#<= :: forall (s :: S). Term s PStakingCredential -> Term s PStakingCredential -> Term s PBool PPartialOrd, PPartialOrd PStakingCredential forall (t :: PType). PPartialOrd t -> POrd t POrd, forall (s :: S). Bool -> Term s PStakingCredential -> Term s PString forall (t :: PType). (forall (s :: S). Bool -> Term s t -> Term s PString) -> PShow t pshow' :: forall (s :: S). Bool -> Term s PStakingCredential -> Term s PString $cpshow' :: forall (s :: S). Bool -> Term s PStakingCredential -> Term s PString PShow, PTryFrom PData) instance DerivePlutusType PStakingCredential where type DPTStrat _ = PlutusTypeData instance PUnsafeLiftDecl PStakingCredential where type PLifted PStakingCredential = Plutus.StakingCredential deriving via (DerivePConstantViaData Plutus.StakingCredential PStakingCredential) instance PConstantDecl Plutus.StakingCredential instance PTryFrom PData (PAsData PStakingCredential) newtype PAddress (s :: S) = PAddress ( Term s ( PDataRecord '[ "credential" ':= PCredential , "stakingCredential" ':= PMaybeData PStakingCredential ] ) ) deriving stock (forall a. (forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a forall (s :: S) x. Rep (PAddress s) x -> PAddress s forall (s :: S) x. PAddress s -> Rep (PAddress s) x $cto :: forall (s :: S) x. Rep (PAddress s) x -> PAddress s $cfrom :: forall (s :: S) x. PAddress s -> Rep (PAddress s) x Generic) deriving anyclass (forall (s :: S). PAddress s -> Term s (PInner PAddress) forall (s :: S) (b :: PType). Term s (PInner PAddress) -> (PAddress s -> Term s b) -> Term s b forall (a :: PType). (forall (s :: S). a s -> Term s (PInner a)) -> (forall (s :: S) (b :: PType). Term s (PInner a) -> (a s -> Term s b) -> Term s b) -> PlutusType a pmatch' :: forall (s :: S) (b :: PType). Term s (PInner PAddress) -> (PAddress s -> Term s b) -> Term s b $cpmatch' :: forall (s :: S) (b :: PType). Term s (PInner PAddress) -> (PAddress s -> Term s b) -> Term s b pcon' :: forall (s :: S). PAddress s -> Term s (PInner PAddress) $cpcon' :: forall (s :: S). PAddress s -> Term s (PInner PAddress) PlutusType, forall (s :: S). Term s (PAsData PAddress) -> Term s PAddress forall (s :: S). Term s PAddress -> Term s PData forall (a :: PType). (forall (s :: S). Term s (PAsData a) -> Term s a) -> (forall (s :: S). Term s a -> Term s PData) -> PIsData a pdataImpl :: forall (s :: S). Term s PAddress -> Term s PData $cpdataImpl :: forall (s :: S). Term s PAddress -> Term s PData pfromDataImpl :: forall (s :: S). Term s (PAsData PAddress) -> Term s PAddress $cpfromDataImpl :: forall (s :: S). Term s (PAsData PAddress) -> Term s PAddress PIsData, forall (s :: S). Term s PAddress -> Term s (PDataRecord (PFields PAddress)) forall (a :: PType). (forall (s :: S). Term s a -> Term s (PDataRecord (PFields a))) -> PDataFields a ptoFields :: forall (s :: S). Term s PAddress -> Term s (PDataRecord (PFields PAddress)) $cptoFields :: forall (s :: S). Term s PAddress -> Term s (PDataRecord (PFields PAddress)) PDataFields, forall (s :: S). Term s PAddress -> Term s PAddress -> Term s PBool forall (t :: PType). (forall (s :: S). Term s t -> Term s t -> Term s PBool) -> PEq t #== :: forall (s :: S). Term s PAddress -> Term s PAddress -> Term s PBool $c#== :: forall (s :: S). Term s PAddress -> Term s PAddress -> Term s PBool PEq, PEq PAddress forall (s :: S). Term s PAddress -> Term s PAddress -> Term s PBool forall (t :: PType). 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) -> PPartialOrd t #< :: forall (s :: S). Term s PAddress -> Term s PAddress -> Term s PBool $c#< :: forall (s :: S). Term s PAddress -> Term s PAddress -> Term s PBool #<= :: forall (s :: S). Term s PAddress -> Term s PAddress -> Term s PBool $c#<= :: forall (s :: S). Term s PAddress -> Term s PAddress -> Term s PBool PPartialOrd, PPartialOrd PAddress forall (t :: PType). PPartialOrd t -> POrd t POrd, forall (s :: S). Bool -> Term s PAddress -> Term s PString forall (t :: PType). (forall (s :: S). Bool -> Term s t -> Term s PString) -> PShow t pshow' :: forall (s :: S). Bool -> Term s PAddress -> Term s PString $cpshow' :: forall (s :: S). Bool -> Term s PAddress -> Term s PString PShow, PTryFrom PData) instance DerivePlutusType PAddress where type DPTStrat _ = PlutusTypeData instance PUnsafeLiftDecl PAddress where type PLifted PAddress = Plutus.Address deriving via (DerivePConstantViaData Plutus.Address PAddress) instance PConstantDecl Plutus.Address instance PTryFrom PData (PAsData PAddress)