{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE UndecidableInstances #-}
{-# OPTIONS_GHC -Wno-orphans #-}
module Plutarch.Either (
PEither (PLeft, PRight),
PEitherData (PDLeft, PDRight),
pisLeft,
pfromLeft,
pfromRight,
pdleft,
pdright,
peitherData,
pdisLeft,
pdisRight,
pdfromLeft,
pdfromRight,
) where
import Data.Kind (Type)
import GHC.Generics (Generic)
import Generics.SOP qualified as SOP
import Plutarch.Builtin.Bool (
PBool (PFalse, PTrue),
pif,
pif',
)
import Plutarch.Builtin.Data (
PAsData,
PData,
pasConstr,
pconstrBuiltin,
pfstBuiltin,
psndBuiltin,
)
import Plutarch.Internal.Eq (PEq ((#==)))
import Plutarch.Internal.IsData (PIsData (pdataImpl, pfromDataImpl), pdata, pforgetData, pfromData)
import Plutarch.Internal.Lift (
DeriveDataPLiftable,
PLiftable (
AsHaskell,
PlutusRepr,
haskToRepr,
plutToRepr,
reprToHask,
reprToPlut
),
PLifted (PLifted),
PLiftedClosed,
getPLiftedClosed,
mkPLifted,
mkPLiftedClosed,
pconstant,
pliftedFromClosed,
pliftedToClosed,
)
import Plutarch.Internal.ListLike (pcons, phead, pnil)
import Plutarch.Internal.Ord (POrd (pmax, pmin, (#<), (#<=)))
import Plutarch.Internal.Other (pto)
import Plutarch.Internal.PLam (plam)
import Plutarch.Internal.PlutusType (
PlutusType (PInner, pcon', pmatch'),
pcon,
pmatch,
)
import Plutarch.Internal.Show (PShow)
import Plutarch.Internal.Term (
S,
Term,
phoistAcyclic,
plet,
(#),
(#$),
(:-->),
)
import Plutarch.Internal.TryFrom (PTryFrom)
import Plutarch.Repr.SOP (DeriveAsSOPStruct (DeriveAsSOPStruct))
import Plutarch.Trace (ptraceInfoError)
import Plutarch.Unsafe (punsafeCoerce)
import PlutusLedgerApi.V3 qualified as Plutus
data PEither (a :: S -> Type) (b :: S -> Type) (s :: S)
= PLeft (Term s a)
| PRight (Term s b)
deriving stock
(
(forall x. PEither a b s -> Rep (PEither a b s) x)
-> (forall x. Rep (PEither a b s) x -> PEither a b s)
-> Generic (PEither a b s)
forall x. Rep (PEither a b s) x -> PEither a b s
forall x. PEither a b s -> Rep (PEither a b s) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall (a :: S -> Type) (b :: S -> Type) (s :: S) x.
Rep (PEither a b s) x -> PEither a b s
forall (a :: S -> Type) (b :: S -> Type) (s :: S) x.
PEither a b s -> Rep (PEither a b s) x
$cfrom :: forall (a :: S -> Type) (b :: S -> Type) (s :: S) x.
PEither a b s -> Rep (PEither a b s) x
from :: forall x. PEither a b s -> Rep (PEither a b s) x
$cto :: forall (a :: S -> Type) (b :: S -> Type) (s :: S) x.
Rep (PEither a b s) x -> PEither a b s
to :: forall x. Rep (PEither a b s) x -> PEither a b s
Generic
)
deriving anyclass
(
All @[Type] (SListI @Type) (Code (PEither a b s))
All @[Type] (SListI @Type) (Code (PEither a b s)) =>
(PEither a b s -> Rep (PEither a b s))
-> (Rep (PEither a b s) -> PEither a b s)
-> Generic (PEither a b s)
Rep (PEither a b s) -> PEither a b s
PEither a b s -> Rep (PEither a b s)
forall a.
All @[Type] (SListI @Type) (Code a) =>
(a -> Rep a) -> (Rep a -> a) -> Generic a
forall (a :: S -> Type) (b :: S -> Type) (s :: S).
All @[Type] (SListI @Type) (Code (PEither a b s))
forall (a :: S -> Type) (b :: S -> Type) (s :: S).
Rep (PEither a b s) -> PEither a b s
forall (a :: S -> Type) (b :: S -> Type) (s :: S).
PEither a b s -> Rep (PEither a b s)
$cfrom :: forall (a :: S -> Type) (b :: S -> Type) (s :: S).
PEither a b s -> Rep (PEither a b s)
from :: PEither a b s -> Rep (PEither a b s)
$cto :: forall (a :: S -> Type) (b :: S -> Type) (s :: S).
Rep (PEither a b s) -> PEither a b s
to :: Rep (PEither a b s) -> PEither a b s
SOP.Generic
,
(forall (s :: S).
Term s (PEither a b) -> Term s (PEither a b) -> Term s PBool)
-> PEq (PEither a b)
forall (s :: S).
Term s (PEither a b) -> Term s (PEither a b) -> Term s PBool
forall (t :: S -> Type).
(forall (s :: S). Term s t -> Term s t -> Term s PBool) -> PEq t
forall (a :: S -> Type) (b :: S -> Type) (s :: S).
(PEq a, PEq b) =>
Term s (PEither a b) -> Term s (PEither a b) -> Term s PBool
$c#== :: forall (a :: S -> Type) (b :: S -> Type) (s :: S).
(PEq a, PEq b) =>
Term s (PEither a b) -> Term s (PEither a b) -> Term s PBool
#== :: forall (s :: S).
Term s (PEither a b) -> Term s (PEither a b) -> Term s PBool
PEq
,
(forall (s :: S). Bool -> Term s (PEither a b) -> Term s PString)
-> PShow (PEither a b)
forall (s :: S). Bool -> Term s (PEither a b) -> Term s PString
forall (t :: S -> Type).
(forall (s :: S). Bool -> Term s t -> Term s PString) -> PShow t
forall (a :: S -> Type) (b :: S -> Type) (s :: S).
(PShow a, PShow b) =>
Bool -> Term s (PEither a b) -> Term s PString
$cpshow' :: forall (a :: S -> Type) (b :: S -> Type) (s :: S).
(PShow a, PShow b) =>
Bool -> Term s (PEither a b) -> Term s PString
pshow' :: forall (s :: S). Bool -> Term s (PEither a b) -> Term s PString
PShow
)
deriving via
DeriveAsSOPStruct (PEither a b)
instance
PlutusType (PEither a b)
instance (PLiftable a, PLiftable b) => PLiftable (PEither a b) where
type AsHaskell (PEither a b) = Either (AsHaskell a) (AsHaskell b)
type PlutusRepr (PEither a b) = PLiftedClosed (PEither a b)
{-# INLINEABLE haskToRepr #-}
haskToRepr :: AsHaskell (PEither a b) -> PlutusRepr (PEither a b)
haskToRepr = \case
Left AsHaskell a
x -> (forall (s :: S). Term s (PEither a b))
-> PLiftedClosed (PEither a b)
forall (a :: S -> Type).
(forall (s :: S). Term s a) -> PLiftedClosed a
mkPLiftedClosed ((forall (s :: S). Term s (PEither a b))
-> PLiftedClosed (PEither a b))
-> (forall (s :: S). Term s (PEither a b))
-> PLiftedClosed (PEither a b)
forall a b. (a -> b) -> a -> b
$ PEither a b s -> Term s (PEither a b)
forall (a :: S -> Type) (s :: S). PlutusType a => a s -> Term s a
pcon (PEither a b s -> Term s (PEither a b))
-> PEither a b s -> Term s (PEither a b)
forall a b. (a -> b) -> a -> b
$ Term s a -> PEither a b s
forall (a :: S -> Type) (b :: S -> Type) (s :: S).
Term s a -> PEither a b s
PLeft (forall (a :: S -> Type) (s :: S).
PLiftable a =>
AsHaskell a -> Term s a
pconstant @a AsHaskell a
x)
Right AsHaskell b
x -> (forall (s :: S). Term s (PEither a b))
-> PLiftedClosed (PEither a b)
forall (a :: S -> Type).
(forall (s :: S). Term s a) -> PLiftedClosed a
mkPLiftedClosed ((forall (s :: S). Term s (PEither a b))
-> PLiftedClosed (PEither a b))
-> (forall (s :: S). Term s (PEither a b))
-> PLiftedClosed (PEither a b)
forall a b. (a -> b) -> a -> b
$ PEither a b s -> Term s (PEither a b)
forall (a :: S -> Type) (s :: S). PlutusType a => a s -> Term s a
pcon (PEither a b s -> Term s (PEither a b))
-> PEither a b s -> Term s (PEither a b)
forall a b. (a -> b) -> a -> b
$ Term s b -> PEither a b s
forall (a :: S -> Type) (b :: S -> Type) (s :: S).
Term s b -> PEither a b s
PRight (forall (a :: S -> Type) (s :: S).
PLiftable a =>
AsHaskell a -> Term s a
pconstant @b AsHaskell b
x)
{-# INLINEABLE reprToHask #-}
reprToHask :: PlutusRepr (PEither a b)
-> Either LiftError (AsHaskell (PEither a b))
reprToHask PlutusRepr (PEither a b)
x = do
Bool
isLeft :: Bool <- (forall (s :: S). PLifted s PBool)
-> Either LiftError (PlutusRepr PBool)
forall (a :: S -> Type).
PLiftable a =>
(forall (s :: S). PLifted s a) -> Either LiftError (PlutusRepr a)
plutToRepr ((forall (s :: S). PLifted s PBool)
-> Either LiftError (PlutusRepr PBool))
-> (forall (s :: S). PLifted s PBool)
-> Either LiftError (PlutusRepr PBool)
forall a b. (a -> b) -> a -> b
$ Term s PBool -> PLifted s PBool
forall (s :: S) (a :: S -> Type). Term s a -> PLifted s a
mkPLifted (Term s (PEither a b :--> PBool)
forall (a :: S -> Type) (b :: S -> Type) (s :: S).
Term s (PEither a b :--> PBool)
pisLeft Term s (PEither a b :--> PBool)
-> Term s (PEither a b) -> Term s PBool
forall (s :: S) (a :: S -> Type) (b :: S -> Type).
Term s (a :--> b) -> Term s a -> Term s b
# PLiftedClosed (PEither a b)
-> forall (s :: S). Term s (PEither a b)
forall (a :: S -> Type).
PLiftedClosed a -> forall (s :: S). Term s a
getPLiftedClosed PlutusRepr (PEither a b)
PLiftedClosed (PEither a b)
x)
if Bool
isLeft
then do
PlutusRepr a
lr :: PlutusRepr a <- (forall (s :: S). PLifted s a) -> Either LiftError (PlutusRepr a)
forall (a :: S -> Type).
PLiftable a =>
(forall (s :: S). PLifted s a) -> Either LiftError (PlutusRepr a)
plutToRepr ((forall (s :: S). PLifted s a) -> Either LiftError (PlutusRepr a))
-> (forall (s :: S). PLifted s a)
-> Either LiftError (PlutusRepr a)
forall a b. (a -> b) -> a -> b
$ Term s a -> PLifted s a
forall (s :: S) (a :: S -> Type). Term s a -> PLifted s a
mkPLifted (Term s (PEither a b :--> a)
forall (a :: S -> Type) (b :: S -> Type) (s :: S).
Term s (PEither a b :--> a)
pfromLeft Term s (PEither a b :--> a) -> Term s (PEither a b) -> Term s a
forall (s :: S) (a :: S -> Type) (b :: S -> Type).
Term s (a :--> b) -> Term s a -> Term s b
# PLiftedClosed (PEither a b)
-> forall (s :: S). Term s (PEither a b)
forall (a :: S -> Type).
PLiftedClosed a -> forall (s :: S). Term s a
getPLiftedClosed PlutusRepr (PEither a b)
PLiftedClosed (PEither a b)
x)
AsHaskell a
lh :: AsHaskell a <- forall (a :: S -> Type).
PLiftable a =>
PlutusRepr a -> Either LiftError (AsHaskell a)
reprToHask @a PlutusRepr a
lr
Either (AsHaskell a) (AsHaskell b)
-> Either LiftError (Either (AsHaskell a) (AsHaskell b))
forall a. a -> Either LiftError a
forall (f :: Type -> Type) a. Applicative f => a -> f a
pure (Either (AsHaskell a) (AsHaskell b)
-> Either LiftError (Either (AsHaskell a) (AsHaskell b)))
-> Either (AsHaskell a) (AsHaskell b)
-> Either LiftError (Either (AsHaskell a) (AsHaskell b))
forall a b. (a -> b) -> a -> b
$ AsHaskell a -> Either (AsHaskell a) (AsHaskell b)
forall a b. a -> Either a b
Left AsHaskell a
lh
else do
PlutusRepr b
rr :: PlutusRepr b <- (forall (s :: S). PLifted s b) -> Either LiftError (PlutusRepr b)
forall (a :: S -> Type).
PLiftable a =>
(forall (s :: S). PLifted s a) -> Either LiftError (PlutusRepr a)
plutToRepr ((forall (s :: S). PLifted s b) -> Either LiftError (PlutusRepr b))
-> (forall (s :: S). PLifted s b)
-> Either LiftError (PlutusRepr b)
forall a b. (a -> b) -> a -> b
$ Term s b -> PLifted s b
forall (s :: S) (a :: S -> Type). Term s a -> PLifted s a
mkPLifted (Term s (PEither a b :--> b)
forall (a :: S -> Type) (b :: S -> Type) (s :: S).
Term s (PEither a b :--> b)
pfromRight Term s (PEither a b :--> b) -> Term s (PEither a b) -> Term s b
forall (s :: S) (a :: S -> Type) (b :: S -> Type).
Term s (a :--> b) -> Term s a -> Term s b
# PLiftedClosed (PEither a b)
-> forall (s :: S). Term s (PEither a b)
forall (a :: S -> Type).
PLiftedClosed a -> forall (s :: S). Term s a
getPLiftedClosed PlutusRepr (PEither a b)
PLiftedClosed (PEither a b)
x)
AsHaskell b
rh :: AsHaskell b <- forall (a :: S -> Type).
PLiftable a =>
PlutusRepr a -> Either LiftError (AsHaskell a)
reprToHask @b PlutusRepr b
rr
Either (AsHaskell a) (AsHaskell b)
-> Either LiftError (Either (AsHaskell a) (AsHaskell b))
forall a. a -> Either LiftError a
forall (f :: Type -> Type) a. Applicative f => a -> f a
pure (Either (AsHaskell a) (AsHaskell b)
-> Either LiftError (Either (AsHaskell a) (AsHaskell b)))
-> Either (AsHaskell a) (AsHaskell b)
-> Either LiftError (Either (AsHaskell a) (AsHaskell b))
forall a b. (a -> b) -> a -> b
$ AsHaskell b -> Either (AsHaskell a) (AsHaskell b)
forall a b. b -> Either a b
Right AsHaskell b
rh
{-# INLINEABLE reprToPlut #-}
reprToPlut :: forall (s :: S).
PlutusRepr (PEither a b) -> PLifted s (PEither a b)
reprToPlut = PlutusRepr (PEither a b) -> PLifted s (PEither a b)
PLiftedClosed (PEither a b) -> PLifted s (PEither a b)
forall (a :: S -> Type) (s :: S). PLiftedClosed a -> PLifted s a
pliftedFromClosed
{-# INLINEABLE plutToRepr #-}
plutToRepr :: (forall (s :: S). PLifted s (PEither a b))
-> Either LiftError (PlutusRepr (PEither a b))
plutToRepr = PLiftedClosed (PEither a b)
-> Either LiftError (PLiftedClosed (PEither a b))
forall a b. b -> Either a b
Right (PLiftedClosed (PEither a b)
-> Either LiftError (PLiftedClosed (PEither a b)))
-> ((forall (s :: S). PLifted s (PEither a b))
-> PLiftedClosed (PEither a b))
-> (forall (s :: S). PLifted s (PEither a b))
-> Either LiftError (PLiftedClosed (PEither a b))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (forall (s :: S). PLifted s (PEither a b))
-> PLiftedClosed (PEither a b)
forall (a :: S -> Type).
(forall (s :: S). PLifted s a) -> PLiftedClosed a
pliftedToClosed
pisLeft ::
forall (a :: S -> Type) (b :: S -> Type) (s :: S).
Term s (PEither a b :--> PBool)
pisLeft :: forall (a :: S -> Type) (b :: S -> Type) (s :: S).
Term s (PEither a b :--> PBool)
pisLeft = ClosedTerm (PEither a b :--> PBool)
-> Term s (PEither a b :--> PBool)
forall (a :: S -> Type) (s :: S).
HasCallStack =>
ClosedTerm a -> Term s a
phoistAcyclic (ClosedTerm (PEither a b :--> PBool)
-> Term s (PEither a b :--> PBool))
-> ClosedTerm (PEither a b :--> PBool)
-> Term s (PEither a b :--> PBool)
forall a b. (a -> b) -> a -> b
$ (Term s (PEither a b) -> Term s PBool)
-> Term s (PEither a b :--> PBool)
forall a (b :: S -> Type) (s :: S) (c :: S -> Type).
(PLamN a b s, HasCallStack) =>
(Term s c -> a) -> Term s (c :--> b)
forall (c :: S -> Type).
HasCallStack =>
(Term s c -> Term s PBool) -> Term s (c :--> PBool)
plam ((Term s (PEither a b) -> Term s PBool)
-> Term s (PEither a b :--> PBool))
-> (Term s (PEither a b) -> Term s PBool)
-> Term s (PEither a b :--> PBool)
forall a b. (a -> b) -> a -> b
$ \Term s (PEither a b)
t -> Term s (PEither a b)
-> (PEither a b s -> Term s PBool) -> Term s PBool
forall (a :: S -> Type) (s :: S) (b :: S -> Type).
PlutusType a =>
Term s a -> (a s -> Term s b) -> Term s b
pmatch Term s (PEither a b)
t ((PEither a b s -> Term s PBool) -> Term s PBool)
-> (PEither a b s -> Term s PBool) -> Term s PBool
forall a b. (a -> b) -> a -> b
$ \case
PLeft Term s a
_ -> PBool s -> Term s PBool
forall (a :: S -> Type) (s :: S). PlutusType a => a s -> Term s a
pcon PBool s
forall (s :: S). PBool s
PTrue
PRight Term s b
_ -> PBool s -> Term s PBool
forall (a :: S -> Type) (s :: S). PlutusType a => a s -> Term s a
pcon PBool s
forall (s :: S). PBool s
PFalse
pfromLeft ::
forall (a :: S -> Type) (b :: S -> Type) (s :: S).
Term s (PEither a b :--> a)
pfromLeft :: forall (a :: S -> Type) (b :: S -> Type) (s :: S).
Term s (PEither a b :--> a)
pfromLeft = ClosedTerm (PEither a b :--> a) -> Term s (PEither a b :--> a)
forall (a :: S -> Type) (s :: S).
HasCallStack =>
ClosedTerm a -> Term s a
phoistAcyclic (ClosedTerm (PEither a b :--> a) -> Term s (PEither a b :--> a))
-> ClosedTerm (PEither a b :--> a) -> Term s (PEither a b :--> a)
forall a b. (a -> b) -> a -> b
$ (Term s (PEither a b) -> Term s a) -> Term s (PEither a b :--> a)
forall a (b :: S -> Type) (s :: S) (c :: S -> Type).
(PLamN a b s, HasCallStack) =>
(Term s c -> a) -> Term s (c :--> b)
forall (c :: S -> Type).
HasCallStack =>
(Term s c -> Term s a) -> Term s (c :--> a)
plam ((Term s (PEither a b) -> Term s a) -> Term s (PEither a b :--> a))
-> (Term s (PEither a b) -> Term s a)
-> Term s (PEither a b :--> a)
forall a b. (a -> b) -> a -> b
$ \Term s (PEither a b)
t -> Term s (PEither a b) -> (PEither a b s -> Term s a) -> Term s a
forall (a :: S -> Type) (s :: S) (b :: S -> Type).
PlutusType a =>
Term s a -> (a s -> Term s b) -> Term s b
pmatch Term s (PEither a b)
t ((PEither a b s -> Term s a) -> Term s a)
-> (PEither a b s -> Term s a) -> Term s a
forall a b. (a -> b) -> a -> b
$ \case
PLeft Term s a
x -> Term s a
x
PRight Term s b
_ -> Term s PString -> Term s a
forall (a :: S -> Type) (s :: S). Term s PString -> Term s a
ptraceInfoError Term s PString
"pfromLeft: used on a PRight"
pfromRight ::
forall (a :: S -> Type) (b :: S -> Type) (s :: S).
Term s (PEither a b :--> b)
pfromRight :: forall (a :: S -> Type) (b :: S -> Type) (s :: S).
Term s (PEither a b :--> b)
pfromRight = ClosedTerm (PEither a b :--> b) -> Term s (PEither a b :--> b)
forall (a :: S -> Type) (s :: S).
HasCallStack =>
ClosedTerm a -> Term s a
phoistAcyclic (ClosedTerm (PEither a b :--> b) -> Term s (PEither a b :--> b))
-> ClosedTerm (PEither a b :--> b) -> Term s (PEither a b :--> b)
forall a b. (a -> b) -> a -> b
$ (Term s (PEither a b) -> Term s b) -> Term s (PEither a b :--> b)
forall a (b :: S -> Type) (s :: S) (c :: S -> Type).
(PLamN a b s, HasCallStack) =>
(Term s c -> a) -> Term s (c :--> b)
forall (c :: S -> Type).
HasCallStack =>
(Term s c -> Term s b) -> Term s (c :--> b)
plam ((Term s (PEither a b) -> Term s b) -> Term s (PEither a b :--> b))
-> (Term s (PEither a b) -> Term s b)
-> Term s (PEither a b :--> b)
forall a b. (a -> b) -> a -> b
$ \Term s (PEither a b)
t -> Term s (PEither a b) -> (PEither a b s -> Term s b) -> Term s b
forall (a :: S -> Type) (s :: S) (b :: S -> Type).
PlutusType a =>
Term s a -> (a s -> Term s b) -> Term s b
pmatch Term s (PEither a b)
t ((PEither a b s -> Term s b) -> Term s b)
-> (PEither a b s -> Term s b) -> Term s b
forall a b. (a -> b) -> a -> b
$ \case
PLeft Term s a
_ -> Term s PString -> Term s b
forall (a :: S -> Type) (s :: S). Term s PString -> Term s a
ptraceInfoError Term s PString
"pfromRight: used on a PLeft"
PRight Term s b
x -> Term s b
x
data PEitherData (a :: S -> Type) (b :: S -> Type) (s :: S)
= PDLeft (Term s (PAsData a))
| PDRight (Term s (PAsData b))
deriving stock
(
(forall x. PEitherData a b s -> Rep (PEitherData a b s) x)
-> (forall x. Rep (PEitherData a b s) x -> PEitherData a b s)
-> Generic (PEitherData a b s)
forall x. Rep (PEitherData a b s) x -> PEitherData a b s
forall x. PEitherData a b s -> Rep (PEitherData a b s) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall (a :: S -> Type) (b :: S -> Type) (s :: S) x.
Rep (PEitherData a b s) x -> PEitherData a b s
forall (a :: S -> Type) (b :: S -> Type) (s :: S) x.
PEitherData a b s -> Rep (PEitherData a b s) x
$cfrom :: forall (a :: S -> Type) (b :: S -> Type) (s :: S) x.
PEitherData a b s -> Rep (PEitherData a b s) x
from :: forall x. PEitherData a b s -> Rep (PEitherData a b s) x
$cto :: forall (a :: S -> Type) (b :: S -> Type) (s :: S) x.
Rep (PEitherData a b s) x -> PEitherData a b s
to :: forall x. Rep (PEitherData a b s) x -> PEitherData a b s
Generic
)
deriving anyclass
(
(forall (s :: S).
Term s (PEitherData a b)
-> Term s (PEitherData a b) -> Term s PBool)
-> PEq (PEitherData a b)
forall (s :: S).
Term s (PEitherData a b)
-> Term s (PEitherData a b) -> Term s PBool
forall (t :: S -> Type).
(forall (s :: S). Term s t -> Term s t -> Term s PBool) -> PEq t
forall (a :: S -> Type) (b :: S -> Type) (s :: S).
Term s (PEitherData a b)
-> Term s (PEitherData a b) -> Term s PBool
$c#== :: forall (a :: S -> Type) (b :: S -> Type) (s :: S).
Term s (PEitherData a b)
-> Term s (PEitherData a b) -> Term s PBool
#== :: forall (s :: S).
Term s (PEitherData a b)
-> Term s (PEitherData a b) -> Term s PBool
PEq
,
(forall (s :: S).
Bool -> Term s (PEitherData a b) -> Term s PString)
-> PShow (PEitherData a b)
forall (s :: S). Bool -> Term s (PEitherData a b) -> Term s PString
forall (t :: S -> Type).
(forall (s :: S). Bool -> Term s t -> Term s PString) -> PShow t
forall (a :: S -> Type) (b :: S -> Type) (s :: S).
(PIsData a, PIsData b, PShow a, PShow b) =>
Bool -> Term s (PEitherData a b) -> Term s PString
$cpshow' :: forall (a :: S -> Type) (b :: S -> Type) (s :: S).
(PIsData a, PIsData b, PShow a, PShow b) =>
Bool -> Term s (PEitherData a b) -> Term s PString
pshow' :: forall (s :: S). Bool -> Term s (PEitherData a b) -> Term s PString
PShow
)
instance
(POrd a, POrd b, PIsData a, PIsData b) =>
POrd (PEitherData a b)
where
{-# INLINEABLE (#<=) #-}
Term s (PEitherData a b)
t1 #<= :: forall (s :: S).
Term s (PEitherData a b)
-> Term s (PEitherData a b) -> Term s PBool
#<= Term s (PEitherData a b)
t2 = Term s (PEitherData a b)
-> (PEitherData a b s -> Term s PBool) -> Term s PBool
forall (a :: S -> Type) (s :: S) (b :: S -> Type).
PlutusType a =>
Term s a -> (a s -> Term s b) -> Term s b
pmatch Term s (PEitherData a b)
t1 ((PEitherData a b s -> Term s PBool) -> Term s PBool)
-> (PEitherData a b s -> Term s PBool) -> Term s PBool
forall a b. (a -> b) -> a -> b
$ \case
PDLeft Term s (PAsData a)
t1' -> Term s (PEitherData a b)
-> (PEitherData a b s -> Term s PBool) -> Term s PBool
forall (a :: S -> Type) (s :: S) (b :: S -> Type).
PlutusType a =>
Term s a -> (a s -> Term s b) -> Term s b
pmatch Term s (PEitherData a b)
t2 ((PEitherData a b s -> Term s PBool) -> Term s PBool)
-> (PEitherData a b s -> Term s PBool) -> Term s PBool
forall a b. (a -> b) -> a -> b
$ \case
PDLeft Term s (PAsData a)
t2' -> Term s (PAsData a) -> Term s a
forall (a :: S -> Type) (s :: S).
PIsData a =>
Term s (PAsData a) -> Term s a
pfromData Term s (PAsData a)
t1' Term s a -> Term s a -> Term s PBool
forall (s :: S). Term s a -> Term s a -> Term s PBool
forall (t :: S -> Type) (s :: S).
POrd t =>
Term s t -> Term s t -> Term s PBool
#<= Term s (PAsData a) -> Term s a
forall (a :: S -> Type) (s :: S).
PIsData a =>
Term s (PAsData a) -> Term s a
pfromData Term s (PAsData a)
t2'
PDRight Term s (PAsData b)
_ -> PBool s -> Term s PBool
forall (a :: S -> Type) (s :: S). PlutusType a => a s -> Term s a
pcon PBool s
forall (s :: S). PBool s
PTrue
PDRight Term s (PAsData b)
t1' -> Term s (PEitherData a b)
-> (PEitherData a b s -> Term s PBool) -> Term s PBool
forall (a :: S -> Type) (s :: S) (b :: S -> Type).
PlutusType a =>
Term s a -> (a s -> Term s b) -> Term s b
pmatch Term s (PEitherData a b)
t2 ((PEitherData a b s -> Term s PBool) -> Term s PBool)
-> (PEitherData a b s -> Term s PBool) -> Term s PBool
forall a b. (a -> b) -> a -> b
$ \case
PDLeft Term s (PAsData a)
_ -> PBool s -> Term s PBool
forall (a :: S -> Type) (s :: S). PlutusType a => a s -> Term s a
pcon PBool s
forall (s :: S). PBool s
PFalse
PDRight Term s (PAsData b)
t2' -> Term s (PAsData b) -> Term s b
forall (a :: S -> Type) (s :: S).
PIsData a =>
Term s (PAsData a) -> Term s a
pfromData Term s (PAsData b)
t1' Term s b -> Term s b -> Term s PBool
forall (s :: S). Term s b -> Term s b -> Term s PBool
forall (t :: S -> Type) (s :: S).
POrd t =>
Term s t -> Term s t -> Term s PBool
#<= Term s (PAsData b) -> Term s b
forall (a :: S -> Type) (s :: S).
PIsData a =>
Term s (PAsData a) -> Term s a
pfromData Term s (PAsData b)
t2'
{-# INLINEABLE (#<) #-}
Term s (PEitherData a b)
t1 #< :: forall (s :: S).
Term s (PEitherData a b)
-> Term s (PEitherData a b) -> Term s PBool
#< Term s (PEitherData a b)
t2 = Term s (PEitherData a b)
-> (PEitherData a b s -> Term s PBool) -> Term s PBool
forall (a :: S -> Type) (s :: S) (b :: S -> Type).
PlutusType a =>
Term s a -> (a s -> Term s b) -> Term s b
pmatch Term s (PEitherData a b)
t1 ((PEitherData a b s -> Term s PBool) -> Term s PBool)
-> (PEitherData a b s -> Term s PBool) -> Term s PBool
forall a b. (a -> b) -> a -> b
$ \case
PDLeft Term s (PAsData a)
t1' -> Term s (PEitherData a b)
-> (PEitherData a b s -> Term s PBool) -> Term s PBool
forall (a :: S -> Type) (s :: S) (b :: S -> Type).
PlutusType a =>
Term s a -> (a s -> Term s b) -> Term s b
pmatch Term s (PEitherData a b)
t2 ((PEitherData a b s -> Term s PBool) -> Term s PBool)
-> (PEitherData a b s -> Term s PBool) -> Term s PBool
forall a b. (a -> b) -> a -> b
$ \case
PDLeft Term s (PAsData a)
t2' -> Term s (PAsData a) -> Term s a
forall (a :: S -> Type) (s :: S).
PIsData a =>
Term s (PAsData a) -> Term s a
pfromData Term s (PAsData a)
t1' Term s a -> Term s a -> Term s PBool
forall (s :: S). Term s a -> Term s a -> Term s PBool
forall (t :: S -> Type) (s :: S).
POrd t =>
Term s t -> Term s t -> Term s PBool
#< Term s (PAsData a) -> Term s a
forall (a :: S -> Type) (s :: S).
PIsData a =>
Term s (PAsData a) -> Term s a
pfromData Term s (PAsData a)
t2'
PDRight Term s (PAsData b)
_ -> PBool s -> Term s PBool
forall (a :: S -> Type) (s :: S). PlutusType a => a s -> Term s a
pcon PBool s
forall (s :: S). PBool s
PTrue
PDRight Term s (PAsData b)
t1' -> Term s (PEitherData a b)
-> (PEitherData a b s -> Term s PBool) -> Term s PBool
forall (a :: S -> Type) (s :: S) (b :: S -> Type).
PlutusType a =>
Term s a -> (a s -> Term s b) -> Term s b
pmatch Term s (PEitherData a b)
t2 ((PEitherData a b s -> Term s PBool) -> Term s PBool)
-> (PEitherData a b s -> Term s PBool) -> Term s PBool
forall a b. (a -> b) -> a -> b
$ \case
PDLeft Term s (PAsData a)
_ -> PBool s -> Term s PBool
forall (a :: S -> Type) (s :: S). PlutusType a => a s -> Term s a
pcon PBool s
forall (s :: S). PBool s
PFalse
PDRight Term s (PAsData b)
t2' -> Term s (PAsData b) -> Term s b
forall (a :: S -> Type) (s :: S).
PIsData a =>
Term s (PAsData a) -> Term s a
pfromData Term s (PAsData b)
t1' Term s b -> Term s b -> Term s PBool
forall (s :: S). Term s b -> Term s b -> Term s PBool
forall (t :: S -> Type) (s :: S).
POrd t =>
Term s t -> Term s t -> Term s PBool
#< Term s (PAsData b) -> Term s b
forall (a :: S -> Type) (s :: S).
PIsData a =>
Term s (PAsData a) -> Term s a
pfromData Term s (PAsData b)
t2'
{-# INLINEABLE pmax #-}
pmax :: forall (s :: S).
Term s (PEitherData a b)
-> Term s (PEitherData a b) -> Term s (PEitherData a b)
pmax Term s (PEitherData a b)
t1 Term s (PEitherData a b)
t2 = Term s (PEitherData a b)
-> (PEitherData a b s -> Term s (PEitherData a b))
-> Term s (PEitherData a b)
forall (a :: S -> Type) (s :: S) (b :: S -> Type).
PlutusType a =>
Term s a -> (a s -> Term s b) -> Term s b
pmatch Term s (PEitherData a b)
t1 ((PEitherData a b s -> Term s (PEitherData a b))
-> Term s (PEitherData a b))
-> (PEitherData a b s -> Term s (PEitherData a b))
-> Term s (PEitherData a b)
forall a b. (a -> b) -> a -> b
$ \case
PDLeft Term s (PAsData a)
t1' -> Term s (PEitherData a b)
-> (PEitherData a b s -> Term s (PEitherData a b))
-> Term s (PEitherData a b)
forall (a :: S -> Type) (s :: S) (b :: S -> Type).
PlutusType a =>
Term s a -> (a s -> Term s b) -> Term s b
pmatch Term s (PEitherData a b)
t2 ((PEitherData a b s -> Term s (PEitherData a b))
-> Term s (PEitherData a b))
-> (PEitherData a b s -> Term s (PEitherData a b))
-> Term s (PEitherData a b)
forall a b. (a -> b) -> a -> b
$ \case
PDLeft Term s (PAsData a)
t2' -> Term
s
(PBool
:--> (PEitherData a b :--> (PEitherData a b :--> PEitherData a b)))
forall (a :: S -> Type) (s :: S).
Term s (PBool :--> (a :--> (a :--> a)))
pif' Term
s
(PBool
:--> (PEitherData a b :--> (PEitherData a b :--> PEitherData a b)))
-> Term s PBool
-> Term
s (PEitherData a b :--> (PEitherData a b :--> PEitherData a b))
forall (s :: S) (a :: S -> Type) (b :: S -> Type).
Term s (a :--> b) -> Term s a -> Term s b
# (Term s (PAsData a) -> Term s a
forall (a :: S -> Type) (s :: S).
PIsData a =>
Term s (PAsData a) -> Term s a
pfromData Term s (PAsData a)
t1' Term s a -> Term s a -> Term s PBool
forall (s :: S). Term s a -> Term s a -> Term s PBool
forall (t :: S -> Type) (s :: S).
POrd t =>
Term s t -> Term s t -> Term s PBool
#< Term s (PAsData a) -> Term s a
forall (a :: S -> Type) (s :: S).
PIsData a =>
Term s (PAsData a) -> Term s a
pfromData Term s (PAsData a)
t2') Term
s (PEitherData a b :--> (PEitherData a b :--> PEitherData a b))
-> Term s (PEitherData a b)
-> Term s (PEitherData a b :--> PEitherData a b)
forall (s :: S) (a :: S -> Type) (b :: S -> Type).
Term s (a :--> b) -> Term s a -> Term s b
# Term s (PEitherData a b)
t2 Term s (PEitherData a b :--> PEitherData a b)
-> Term s (PEitherData a b) -> Term s (PEitherData a b)
forall (s :: S) (a :: S -> Type) (b :: S -> Type).
Term s (a :--> b) -> Term s a -> Term s b
# Term s (PEitherData a b)
t1
PDRight Term s (PAsData b)
_ -> Term s (PEitherData a b)
t2
PDRight Term s (PAsData b)
t1' -> Term s (PEitherData a b)
-> (PEitherData a b s -> Term s (PEitherData a b))
-> Term s (PEitherData a b)
forall (a :: S -> Type) (s :: S) (b :: S -> Type).
PlutusType a =>
Term s a -> (a s -> Term s b) -> Term s b
pmatch Term s (PEitherData a b)
t2 ((PEitherData a b s -> Term s (PEitherData a b))
-> Term s (PEitherData a b))
-> (PEitherData a b s -> Term s (PEitherData a b))
-> Term s (PEitherData a b)
forall a b. (a -> b) -> a -> b
$ \case
PDLeft Term s (PAsData a)
_ -> Term s (PEitherData a b)
t1
PDRight Term s (PAsData b)
t2' -> Term
s
(PBool
:--> (PEitherData a b :--> (PEitherData a b :--> PEitherData a b)))
forall (a :: S -> Type) (s :: S).
Term s (PBool :--> (a :--> (a :--> a)))
pif' Term
s
(PBool
:--> (PEitherData a b :--> (PEitherData a b :--> PEitherData a b)))
-> Term s PBool
-> Term
s (PEitherData a b :--> (PEitherData a b :--> PEitherData a b))
forall (s :: S) (a :: S -> Type) (b :: S -> Type).
Term s (a :--> b) -> Term s a -> Term s b
# (Term s (PAsData b) -> Term s b
forall (a :: S -> Type) (s :: S).
PIsData a =>
Term s (PAsData a) -> Term s a
pfromData Term s (PAsData b)
t1' Term s b -> Term s b -> Term s PBool
forall (s :: S). Term s b -> Term s b -> Term s PBool
forall (t :: S -> Type) (s :: S).
POrd t =>
Term s t -> Term s t -> Term s PBool
#< Term s (PAsData b) -> Term s b
forall (a :: S -> Type) (s :: S).
PIsData a =>
Term s (PAsData a) -> Term s a
pfromData Term s (PAsData b)
t2') Term
s (PEitherData a b :--> (PEitherData a b :--> PEitherData a b))
-> Term s (PEitherData a b)
-> Term s (PEitherData a b :--> PEitherData a b)
forall (s :: S) (a :: S -> Type) (b :: S -> Type).
Term s (a :--> b) -> Term s a -> Term s b
# Term s (PEitherData a b)
t2 Term s (PEitherData a b :--> PEitherData a b)
-> Term s (PEitherData a b) -> Term s (PEitherData a b)
forall (s :: S) (a :: S -> Type) (b :: S -> Type).
Term s (a :--> b) -> Term s a -> Term s b
# Term s (PEitherData a b)
t1
{-# INLINEABLE pmin #-}
pmin :: forall (s :: S).
Term s (PEitherData a b)
-> Term s (PEitherData a b) -> Term s (PEitherData a b)
pmin Term s (PEitherData a b)
t1 Term s (PEitherData a b)
t2 = Term s (PEitherData a b)
-> (PEitherData a b s -> Term s (PEitherData a b))
-> Term s (PEitherData a b)
forall (a :: S -> Type) (s :: S) (b :: S -> Type).
PlutusType a =>
Term s a -> (a s -> Term s b) -> Term s b
pmatch Term s (PEitherData a b)
t1 ((PEitherData a b s -> Term s (PEitherData a b))
-> Term s (PEitherData a b))
-> (PEitherData a b s -> Term s (PEitherData a b))
-> Term s (PEitherData a b)
forall a b. (a -> b) -> a -> b
$ \case
PDLeft Term s (PAsData a)
t1' -> Term s (PEitherData a b)
-> (PEitherData a b s -> Term s (PEitherData a b))
-> Term s (PEitherData a b)
forall (a :: S -> Type) (s :: S) (b :: S -> Type).
PlutusType a =>
Term s a -> (a s -> Term s b) -> Term s b
pmatch Term s (PEitherData a b)
t2 ((PEitherData a b s -> Term s (PEitherData a b))
-> Term s (PEitherData a b))
-> (PEitherData a b s -> Term s (PEitherData a b))
-> Term s (PEitherData a b)
forall a b. (a -> b) -> a -> b
$ \case
PDLeft Term s (PAsData a)
t2' -> Term
s
(PBool
:--> (PEitherData a b :--> (PEitherData a b :--> PEitherData a b)))
forall (a :: S -> Type) (s :: S).
Term s (PBool :--> (a :--> (a :--> a)))
pif' Term
s
(PBool
:--> (PEitherData a b :--> (PEitherData a b :--> PEitherData a b)))
-> Term s PBool
-> Term
s (PEitherData a b :--> (PEitherData a b :--> PEitherData a b))
forall (s :: S) (a :: S -> Type) (b :: S -> Type).
Term s (a :--> b) -> Term s a -> Term s b
# (Term s (PAsData a) -> Term s a
forall (a :: S -> Type) (s :: S).
PIsData a =>
Term s (PAsData a) -> Term s a
pfromData Term s (PAsData a)
t1' Term s a -> Term s a -> Term s PBool
forall (s :: S). Term s a -> Term s a -> Term s PBool
forall (t :: S -> Type) (s :: S).
POrd t =>
Term s t -> Term s t -> Term s PBool
#< Term s (PAsData a) -> Term s a
forall (a :: S -> Type) (s :: S).
PIsData a =>
Term s (PAsData a) -> Term s a
pfromData Term s (PAsData a)
t2') Term
s (PEitherData a b :--> (PEitherData a b :--> PEitherData a b))
-> Term s (PEitherData a b)
-> Term s (PEitherData a b :--> PEitherData a b)
forall (s :: S) (a :: S -> Type) (b :: S -> Type).
Term s (a :--> b) -> Term s a -> Term s b
# Term s (PEitherData a b)
t1 Term s (PEitherData a b :--> PEitherData a b)
-> Term s (PEitherData a b) -> Term s (PEitherData a b)
forall (s :: S) (a :: S -> Type) (b :: S -> Type).
Term s (a :--> b) -> Term s a -> Term s b
# Term s (PEitherData a b)
t2
PDRight Term s (PAsData b)
_ -> Term s (PEitherData a b)
t1
PDRight Term s (PAsData b)
t1' -> Term s (PEitherData a b)
-> (PEitherData a b s -> Term s (PEitherData a b))
-> Term s (PEitherData a b)
forall (a :: S -> Type) (s :: S) (b :: S -> Type).
PlutusType a =>
Term s a -> (a s -> Term s b) -> Term s b
pmatch Term s (PEitherData a b)
t2 ((PEitherData a b s -> Term s (PEitherData a b))
-> Term s (PEitherData a b))
-> (PEitherData a b s -> Term s (PEitherData a b))
-> Term s (PEitherData a b)
forall a b. (a -> b) -> a -> b
$ \case
PDLeft Term s (PAsData a)
_ -> Term s (PEitherData a b)
t2
PDRight Term s (PAsData b)
t2' -> Term
s
(PBool
:--> (PEitherData a b :--> (PEitherData a b :--> PEitherData a b)))
forall (a :: S -> Type) (s :: S).
Term s (PBool :--> (a :--> (a :--> a)))
pif' Term
s
(PBool
:--> (PEitherData a b :--> (PEitherData a b :--> PEitherData a b)))
-> Term s PBool
-> Term
s (PEitherData a b :--> (PEitherData a b :--> PEitherData a b))
forall (s :: S) (a :: S -> Type) (b :: S -> Type).
Term s (a :--> b) -> Term s a -> Term s b
# (Term s (PAsData b) -> Term s b
forall (a :: S -> Type) (s :: S).
PIsData a =>
Term s (PAsData a) -> Term s a
pfromData Term s (PAsData b)
t1' Term s b -> Term s b -> Term s PBool
forall (s :: S). Term s b -> Term s b -> Term s PBool
forall (t :: S -> Type) (s :: S).
POrd t =>
Term s t -> Term s t -> Term s PBool
#< Term s (PAsData b) -> Term s b
forall (a :: S -> Type) (s :: S).
PIsData a =>
Term s (PAsData a) -> Term s a
pfromData Term s (PAsData b)
t2') Term
s (PEitherData a b :--> (PEitherData a b :--> PEitherData a b))
-> Term s (PEitherData a b)
-> Term s (PEitherData a b :--> PEitherData a b)
forall (s :: S) (a :: S -> Type) (b :: S -> Type).
Term s (a :--> b) -> Term s a -> Term s b
# Term s (PEitherData a b)
t1 Term s (PEitherData a b :--> PEitherData a b)
-> Term s (PEitherData a b) -> Term s (PEitherData a b)
forall (s :: S) (a :: S -> Type) (b :: S -> Type).
Term s (a :--> b) -> Term s a -> Term s b
# Term s (PEitherData a b)
t2
instance PlutusType (PEitherData a b) where
type PInner (PEitherData a b) = PData
{-# INLINEABLE pcon' #-}
pcon' :: forall (s :: S).
PEitherData a b s -> Term s (PInner (PEitherData a b))
pcon' = \case
PDLeft Term s (PAsData a)
t ->
Term s (PAsData (PBuiltinPair PInteger (PBuiltinList PData)))
-> Term s PData
forall (s :: S) (a :: S -> Type).
Term s (PAsData a) -> Term s PData
pforgetData (Term s (PAsData (PBuiltinPair PInteger (PBuiltinList PData)))
-> Term s PData)
-> Term s (PAsData (PBuiltinPair PInteger (PBuiltinList PData)))
-> Term s PData
forall a b. (a -> b) -> a -> b
$ Term
s
(PInteger
:--> (PBuiltinList PData
:--> PAsData (PBuiltinPair PInteger (PBuiltinList PData))))
forall (s :: S).
Term
s
(PInteger
:--> (PBuiltinList PData
:--> PAsData (PBuiltinPair PInteger (PBuiltinList PData))))
pconstrBuiltin Term
s
(PInteger
:--> (PBuiltinList PData
:--> PAsData (PBuiltinPair PInteger (PBuiltinList PData))))
-> Term s PInteger
-> Term
s
(PBuiltinList PData
:--> PAsData (PBuiltinPair PInteger (PBuiltinList PData)))
forall (s :: S) (a :: S -> Type) (b :: S -> Type).
Term s (a :--> b) -> Term s a -> Term s b
# Term s PInteger
0 Term
s
(PBuiltinList PData
:--> PAsData (PBuiltinPair PInteger (PBuiltinList PData)))
-> Term s (PBuiltinList PData)
-> Term s (PAsData (PBuiltinPair PInteger (PBuiltinList PData)))
forall (s :: S) (a :: S -> Type) (b :: S -> Type).
Term s (a :--> b) -> Term s a -> Term s b
#$ Term s (PData :--> (PBuiltinList PData :--> PBuiltinList PData))
forall (a :: S -> Type) (s :: S).
PElemConstraint PBuiltinList a =>
Term s (a :--> (PBuiltinList a :--> PBuiltinList a))
forall (list :: (S -> Type) -> S -> Type) (a :: S -> Type)
(s :: S).
(PListLike list, PElemConstraint list a) =>
Term s (a :--> (list a :--> list a))
pcons Term s (PData :--> (PBuiltinList PData :--> PBuiltinList PData))
-> Term s PData
-> Term s (PBuiltinList PData :--> PBuiltinList PData)
forall (s :: S) (a :: S -> Type) (b :: S -> Type).
Term s (a :--> b) -> Term s a -> Term s b
# Term s (PAsData a) -> Term s PData
forall (s :: S) (a :: S -> Type).
Term s (PAsData a) -> Term s PData
pforgetData Term s (PAsData a)
t Term s (PBuiltinList PData :--> PBuiltinList PData)
-> Term s (PBuiltinList PData) -> Term s (PBuiltinList PData)
forall (s :: S) (a :: S -> Type) (b :: S -> Type).
Term s (a :--> b) -> Term s a -> Term s b
# Term s (PBuiltinList PData)
forall (a :: S -> Type) (s :: S).
PElemConstraint PBuiltinList a =>
Term s (PBuiltinList a)
forall (list :: (S -> Type) -> S -> Type) (a :: S -> Type)
(s :: S).
(PListLike list, PElemConstraint list a) =>
Term s (list a)
pnil
PDRight Term s (PAsData b)
t ->
Term s (PAsData (PBuiltinPair PInteger (PBuiltinList PData)))
-> Term s PData
forall (s :: S) (a :: S -> Type).
Term s (PAsData a) -> Term s PData
pforgetData (Term s (PAsData (PBuiltinPair PInteger (PBuiltinList PData)))
-> Term s PData)
-> Term s (PAsData (PBuiltinPair PInteger (PBuiltinList PData)))
-> Term s PData
forall a b. (a -> b) -> a -> b
$ Term
s
(PInteger
:--> (PBuiltinList PData
:--> PAsData (PBuiltinPair PInteger (PBuiltinList PData))))
forall (s :: S).
Term
s
(PInteger
:--> (PBuiltinList PData
:--> PAsData (PBuiltinPair PInteger (PBuiltinList PData))))
pconstrBuiltin Term
s
(PInteger
:--> (PBuiltinList PData
:--> PAsData (PBuiltinPair PInteger (PBuiltinList PData))))
-> Term s PInteger
-> Term
s
(PBuiltinList PData
:--> PAsData (PBuiltinPair PInteger (PBuiltinList PData)))
forall (s :: S) (a :: S -> Type) (b :: S -> Type).
Term s (a :--> b) -> Term s a -> Term s b
# Term s PInteger
1 Term
s
(PBuiltinList PData
:--> PAsData (PBuiltinPair PInteger (PBuiltinList PData)))
-> Term s (PBuiltinList PData)
-> Term s (PAsData (PBuiltinPair PInteger (PBuiltinList PData)))
forall (s :: S) (a :: S -> Type) (b :: S -> Type).
Term s (a :--> b) -> Term s a -> Term s b
#$ Term s (PData :--> (PBuiltinList PData :--> PBuiltinList PData))
forall (a :: S -> Type) (s :: S).
PElemConstraint PBuiltinList a =>
Term s (a :--> (PBuiltinList a :--> PBuiltinList a))
forall (list :: (S -> Type) -> S -> Type) (a :: S -> Type)
(s :: S).
(PListLike list, PElemConstraint list a) =>
Term s (a :--> (list a :--> list a))
pcons Term s (PData :--> (PBuiltinList PData :--> PBuiltinList PData))
-> Term s PData
-> Term s (PBuiltinList PData :--> PBuiltinList PData)
forall (s :: S) (a :: S -> Type) (b :: S -> Type).
Term s (a :--> b) -> Term s a -> Term s b
# Term s (PAsData b) -> Term s PData
forall (s :: S) (a :: S -> Type).
Term s (PAsData a) -> Term s PData
pforgetData Term s (PAsData b)
t Term s (PBuiltinList PData :--> PBuiltinList PData)
-> Term s (PBuiltinList PData) -> Term s (PBuiltinList PData)
forall (s :: S) (a :: S -> Type) (b :: S -> Type).
Term s (a :--> b) -> Term s a -> Term s b
# Term s (PBuiltinList PData)
forall (a :: S -> Type) (s :: S).
PElemConstraint PBuiltinList a =>
Term s (PBuiltinList a)
forall (list :: (S -> Type) -> S -> Type) (a :: S -> Type)
(s :: S).
(PListLike list, PElemConstraint list a) =>
Term s (list a)
pnil
{-# INLINEABLE pmatch' #-}
pmatch' :: forall (s :: S) (b :: S -> Type).
Term s (PInner (PEitherData a b))
-> (PEitherData a b s -> Term s b) -> Term s b
pmatch' Term s (PInner (PEitherData a b))
t PEitherData a b s -> Term s b
f = Term s (PBuiltinPair PInteger (PBuiltinList PData))
-> (Term s (PBuiltinPair PInteger (PBuiltinList PData))
-> Term s b)
-> Term s b
forall (s :: S) (a :: S -> Type) (b :: S -> Type).
Term s a -> (Term s a -> Term s b) -> Term s b
plet (Term s (PData :--> PBuiltinPair PInteger (PBuiltinList PData))
forall (s :: S).
Term s (PData :--> PBuiltinPair PInteger (PBuiltinList PData))
pasConstr Term s (PData :--> PBuiltinPair PInteger (PBuiltinList PData))
-> Term s PData
-> Term s (PBuiltinPair PInteger (PBuiltinList PData))
forall (s :: S) (a :: S -> Type) (b :: S -> Type).
Term s (a :--> b) -> Term s a -> Term s b
# Term s PData
Term s (PInner (PEitherData a b))
t) ((Term s (PBuiltinPair PInteger (PBuiltinList PData)) -> Term s b)
-> Term s b)
-> (Term s (PBuiltinPair PInteger (PBuiltinList PData))
-> Term s b)
-> Term s b
forall a b. (a -> b) -> a -> b
$ \Term s (PBuiltinPair PInteger (PBuiltinList PData))
asConstr ->
Term s PData -> (Term s PData -> Term s b) -> Term s b
forall (s :: S) (a :: S -> Type) (b :: S -> Type).
Term s a -> (Term s a -> Term s b) -> Term s b
plet (Term s (PBuiltinList PData :--> PData)
forall (a :: S -> Type) (s :: S).
PElemConstraint PBuiltinList a =>
Term s (PBuiltinList a :--> a)
forall (list :: (S -> Type) -> S -> Type) (a :: S -> Type)
(s :: S).
(PListLike list, PElemConstraint list a) =>
Term s (list a :--> a)
phead Term s (PBuiltinList PData :--> PData)
-> Term s (PBuiltinList PData) -> Term s PData
forall (s :: S) (a :: S -> Type) (b :: S -> Type).
Term s (a :--> b) -> Term s a -> Term s b
#$ Term
s
(PBuiltinPair PInteger (PBuiltinList PData)
:--> PBuiltinList PData)
forall (s :: S) (a :: S -> Type) (b :: S -> Type).
Term s (PBuiltinPair a b :--> b)
psndBuiltin Term
s
(PBuiltinPair PInteger (PBuiltinList PData)
:--> PBuiltinList PData)
-> Term s (PBuiltinPair PInteger (PBuiltinList PData))
-> Term s (PBuiltinList PData)
forall (s :: S) (a :: S -> Type) (b :: S -> Type).
Term s (a :--> b) -> Term s a -> Term s b
# Term s (PBuiltinPair PInteger (PBuiltinList PData))
asConstr) ((Term s PData -> Term s b) -> Term s b)
-> (Term s PData -> Term s b) -> Term s b
forall a b. (a -> b) -> a -> b
$ \Term s PData
arg ->
Term s PBool -> Term s b -> Term s b -> Term s b
forall (a :: S -> Type) (s :: S).
Term s PBool -> Term s a -> Term s a -> Term s a
pif
((Term s (PBuiltinPair PInteger (PBuiltinList PData) :--> PInteger)
forall (s :: S) (a :: S -> Type) (b :: S -> Type).
Term s (PBuiltinPair a b :--> a)
pfstBuiltin Term s (PBuiltinPair PInteger (PBuiltinList PData) :--> PInteger)
-> Term s (PBuiltinPair PInteger (PBuiltinList PData))
-> Term s PInteger
forall (s :: S) (a :: S -> Type) (b :: S -> Type).
Term s (a :--> b) -> Term s a -> Term s b
# Term s (PBuiltinPair PInteger (PBuiltinList PData))
asConstr) Term s PInteger -> Term s PInteger -> Term s PBool
forall (s :: S). Term s PInteger -> Term s PInteger -> Term s PBool
forall (t :: S -> Type) (s :: S).
PEq t =>
Term s t -> Term s t -> Term s PBool
#== Term s PInteger
0)
(PEitherData a b s -> Term s b
f (PEitherData a b s -> Term s b)
-> (Term s PData -> PEitherData a b s) -> Term s PData -> Term s b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Term s (PAsData a) -> PEitherData a b s
forall (a :: S -> Type) (b :: S -> Type) (s :: S).
Term s (PAsData a) -> PEitherData a b s
PDLeft (Term s (PAsData a) -> PEitherData a b s)
-> (Term s PData -> Term s (PAsData a))
-> Term s PData
-> PEitherData a b s
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Term s PData -> Term s (PAsData a)
forall (b :: S -> Type) (a :: S -> Type) (s :: S).
Term s a -> Term s b
punsafeCoerce (Term s PData -> Term s b) -> Term s PData -> Term s b
forall a b. (a -> b) -> a -> b
$ Term s PData
arg)
(PEitherData a b s -> Term s b
f (PEitherData a b s -> Term s b)
-> (Term s PData -> PEitherData a b s) -> Term s PData -> Term s b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Term s (PAsData b) -> PEitherData a b s
forall (a :: S -> Type) (b :: S -> Type) (s :: S).
Term s (PAsData b) -> PEitherData a b s
PDRight (Term s (PAsData b) -> PEitherData a b s)
-> (Term s PData -> Term s (PAsData b))
-> Term s PData
-> PEitherData a b s
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Term s PData -> Term s (PAsData b)
forall (b :: S -> Type) (a :: S -> Type) (s :: S).
Term s a -> Term s b
punsafeCoerce (Term s PData -> Term s b) -> Term s PData -> Term s b
forall a b. (a -> b) -> a -> b
$ Term s PData
arg)
deriving via
DeriveDataPLiftable (PEitherData a b) (Either (AsHaskell a) (AsHaskell b))
instance
( Plutus.ToData (AsHaskell a)
, Plutus.FromData (AsHaskell a)
, Plutus.ToData (AsHaskell b)
, Plutus.FromData (AsHaskell b)
) =>
PLiftable (PEitherData a b)
instance PIsData (PEitherData a b) where
{-# INLINEABLE pdataImpl #-}
pdataImpl :: forall (s :: S). Term s (PEitherData a b) -> Term s PData
pdataImpl = Term s (PEitherData a b) -> Term s PData
Term s (PEitherData a b) -> Term s (PInner (PEitherData a b))
forall (s :: S) (a :: S -> Type). Term s a -> Term s (PInner a)
pto
{-# INLINEABLE pfromDataImpl #-}
pfromDataImpl :: forall (s :: S).
Term s (PAsData (PEitherData a b)) -> Term s (PEitherData a b)
pfromDataImpl = Term s (PAsData (PEitherData a b)) -> Term s (PEitherData a b)
forall (b :: S -> Type) (a :: S -> Type) (s :: S).
Term s a -> Term s b
punsafeCoerce
instance (PTryFrom PData a, PTryFrom PData b) => PTryFrom PData (PEitherData a b)
instance (PTryFrom PData a, PTryFrom PData b) => PTryFrom PData (PAsData (PEitherData a b))
pdleft ::
forall (a :: S -> Type) (b :: S -> Type) (s :: S).
PIsData a =>
Term s (a :--> PEitherData a b)
pdleft :: forall (a :: S -> Type) (b :: S -> Type) (s :: S).
PIsData a =>
Term s (a :--> PEitherData a b)
pdleft = ClosedTerm (a :--> PEitherData a b)
-> Term s (a :--> PEitherData a b)
forall (a :: S -> Type) (s :: S).
HasCallStack =>
ClosedTerm a -> Term s a
phoistAcyclic (ClosedTerm (a :--> PEitherData a b)
-> Term s (a :--> PEitherData a b))
-> ClosedTerm (a :--> PEitherData a b)
-> Term s (a :--> PEitherData a b)
forall a b. (a -> b) -> a -> b
$ (Term s a -> Term s (PEitherData a b))
-> Term s (a :--> PEitherData a b)
forall a (b :: S -> Type) (s :: S) (c :: S -> Type).
(PLamN a b s, HasCallStack) =>
(Term s c -> a) -> Term s (c :--> b)
forall (c :: S -> Type).
HasCallStack =>
(Term s c -> Term s (PEitherData a b))
-> Term s (c :--> PEitherData a b)
plam ((Term s a -> Term s (PEitherData a b))
-> Term s (a :--> PEitherData a b))
-> (Term s a -> Term s (PEitherData a b))
-> Term s (a :--> PEitherData a b)
forall a b. (a -> b) -> a -> b
$ \Term s a
x ->
PEitherData a b s -> Term s (PEitherData a b)
forall (a :: S -> Type) (s :: S). PlutusType a => a s -> Term s a
pcon (PEitherData a b s -> Term s (PEitherData a b))
-> (Term s a -> PEitherData a b s)
-> Term s a
-> Term s (PEitherData a b)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Term s (PAsData a) -> PEitherData a b s
forall (a :: S -> Type) (b :: S -> Type) (s :: S).
Term s (PAsData a) -> PEitherData a b s
PDLeft (Term s (PAsData a) -> PEitherData a b s)
-> (Term s a -> Term s (PAsData a))
-> Term s a
-> PEitherData a b s
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Term s a -> Term s (PAsData a)
forall (a :: S -> Type) (s :: S).
PIsData a =>
Term s a -> Term s (PAsData a)
pdata (Term s a -> Term s (PEitherData a b))
-> Term s a -> Term s (PEitherData a b)
forall a b. (a -> b) -> a -> b
$ Term s a
x
pdright ::
forall (a :: S -> Type) (b :: S -> Type) (s :: S).
PIsData b =>
Term s (b :--> PEitherData a b)
pdright :: forall (a :: S -> Type) (b :: S -> Type) (s :: S).
PIsData b =>
Term s (b :--> PEitherData a b)
pdright = ClosedTerm (b :--> PEitherData a b)
-> Term s (b :--> PEitherData a b)
forall (a :: S -> Type) (s :: S).
HasCallStack =>
ClosedTerm a -> Term s a
phoistAcyclic (ClosedTerm (b :--> PEitherData a b)
-> Term s (b :--> PEitherData a b))
-> ClosedTerm (b :--> PEitherData a b)
-> Term s (b :--> PEitherData a b)
forall a b. (a -> b) -> a -> b
$ (Term s b -> Term s (PEitherData a b))
-> Term s (b :--> PEitherData a b)
forall a (b :: S -> Type) (s :: S) (c :: S -> Type).
(PLamN a b s, HasCallStack) =>
(Term s c -> a) -> Term s (c :--> b)
forall (c :: S -> Type).
HasCallStack =>
(Term s c -> Term s (PEitherData a b))
-> Term s (c :--> PEitherData a b)
plam ((Term s b -> Term s (PEitherData a b))
-> Term s (b :--> PEitherData a b))
-> (Term s b -> Term s (PEitherData a b))
-> Term s (b :--> PEitherData a b)
forall a b. (a -> b) -> a -> b
$ \Term s b
x ->
PEitherData a b s -> Term s (PEitherData a b)
forall (a :: S -> Type) (s :: S). PlutusType a => a s -> Term s a
pcon (PEitherData a b s -> Term s (PEitherData a b))
-> (Term s b -> PEitherData a b s)
-> Term s b
-> Term s (PEitherData a b)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Term s (PAsData b) -> PEitherData a b s
forall (a :: S -> Type) (b :: S -> Type) (s :: S).
Term s (PAsData b) -> PEitherData a b s
PDRight (Term s (PAsData b) -> PEitherData a b s)
-> (Term s b -> Term s (PAsData b))
-> Term s b
-> PEitherData a b s
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Term s b -> Term s (PAsData b)
forall (a :: S -> Type) (s :: S).
PIsData a =>
Term s a -> Term s (PAsData a)
pdata (Term s b -> Term s (PEitherData a b))
-> Term s b -> Term s (PEitherData a b)
forall a b. (a -> b) -> a -> b
$ Term s b
x
peitherData ::
forall (a :: S -> Type) (b :: S -> Type) (r :: S -> Type) (s :: S).
(PIsData a, PIsData b) =>
Term s ((a :--> r) :--> (b :--> r) :--> PEitherData a b :--> r)
peitherData :: forall (a :: S -> Type) (b :: S -> Type) (r :: S -> Type) (s :: S).
(PIsData a, PIsData b) =>
Term s ((a :--> r) :--> ((b :--> r) :--> (PEitherData a b :--> r)))
peitherData = ClosedTerm
((a :--> r) :--> ((b :--> r) :--> (PEitherData a b :--> r)))
-> Term
s ((a :--> r) :--> ((b :--> r) :--> (PEitherData a b :--> r)))
forall (a :: S -> Type) (s :: S).
HasCallStack =>
ClosedTerm a -> Term s a
phoistAcyclic (ClosedTerm
((a :--> r) :--> ((b :--> r) :--> (PEitherData a b :--> r)))
-> Term
s ((a :--> r) :--> ((b :--> r) :--> (PEitherData a b :--> r))))
-> ClosedTerm
((a :--> r) :--> ((b :--> r) :--> (PEitherData a b :--> r)))
-> Term
s ((a :--> r) :--> ((b :--> r) :--> (PEitherData a b :--> r)))
forall a b. (a -> b) -> a -> b
$ (Term s (a :--> r)
-> Term s (b :--> r) -> Term s (PEitherData a b) -> Term s r)
-> Term
s ((a :--> r) :--> ((b :--> r) :--> (PEitherData a b :--> r)))
forall a (b :: S -> Type) (s :: S) (c :: S -> Type).
(PLamN a b s, HasCallStack) =>
(Term s c -> a) -> Term s (c :--> b)
forall (c :: S -> Type).
HasCallStack =>
(Term s c
-> Term s (b :--> r) -> Term s (PEitherData a b) -> Term s r)
-> Term s (c :--> ((b :--> r) :--> (PEitherData a b :--> r)))
plam ((Term s (a :--> r)
-> Term s (b :--> r) -> Term s (PEitherData a b) -> Term s r)
-> Term
s ((a :--> r) :--> ((b :--> r) :--> (PEitherData a b :--> r))))
-> (Term s (a :--> r)
-> Term s (b :--> r) -> Term s (PEitherData a b) -> Term s r)
-> Term
s ((a :--> r) :--> ((b :--> r) :--> (PEitherData a b :--> r)))
forall a b. (a -> b) -> a -> b
$ \Term s (a :--> r)
whenLeft Term s (b :--> r)
whenRight Term s (PEitherData a b)
t ->
Term s (PEitherData a b)
-> (PEitherData a b s -> Term s r) -> Term s r
forall (a :: S -> Type) (s :: S) (b :: S -> Type).
PlutusType a =>
Term s a -> (a s -> Term s b) -> Term s b
pmatch Term s (PEitherData a b)
t ((PEitherData a b s -> Term s r) -> Term s r)
-> (PEitherData a b s -> Term s r) -> Term s r
forall a b. (a -> b) -> a -> b
$ \case
PDLeft Term s (PAsData a)
x -> Term s (a :--> r)
whenLeft Term s (a :--> r) -> Term s a -> Term s r
forall (s :: S) (a :: S -> Type) (b :: S -> Type).
Term s (a :--> b) -> Term s a -> Term s b
# Term s (PAsData a) -> Term s a
forall (a :: S -> Type) (s :: S).
PIsData a =>
Term s (PAsData a) -> Term s a
pfromData Term s (PAsData a)
x
PDRight Term s (PAsData b)
x -> Term s (b :--> r)
whenRight Term s (b :--> r) -> Term s b -> Term s r
forall (s :: S) (a :: S -> Type) (b :: S -> Type).
Term s (a :--> b) -> Term s a -> Term s b
# Term s (PAsData b) -> Term s b
forall (a :: S -> Type) (s :: S).
PIsData a =>
Term s (PAsData a) -> Term s a
pfromData Term s (PAsData b)
x
pdisLeft ::
forall (a :: S -> Type) (b :: S -> Type) (s :: S).
Term s (PEitherData a b :--> PBool)
pdisLeft :: forall (a :: S -> Type) (b :: S -> Type) (s :: S).
Term s (PEitherData a b :--> PBool)
pdisLeft = ClosedTerm (PEitherData a b :--> PBool)
-> Term s (PEitherData a b :--> PBool)
forall (a :: S -> Type) (s :: S).
HasCallStack =>
ClosedTerm a -> Term s a
phoistAcyclic (ClosedTerm (PEitherData a b :--> PBool)
-> Term s (PEitherData a b :--> PBool))
-> ClosedTerm (PEitherData a b :--> PBool)
-> Term s (PEitherData a b :--> PBool)
forall a b. (a -> b) -> a -> b
$ (Term s (PEitherData a b) -> Term s PBool)
-> Term s (PEitherData a b :--> PBool)
forall a (b :: S -> Type) (s :: S) (c :: S -> Type).
(PLamN a b s, HasCallStack) =>
(Term s c -> a) -> Term s (c :--> b)
forall (c :: S -> Type).
HasCallStack =>
(Term s c -> Term s PBool) -> Term s (c :--> PBool)
plam ((Term s (PEitherData a b) -> Term s PBool)
-> Term s (PEitherData a b :--> PBool))
-> (Term s (PEitherData a b) -> Term s PBool)
-> Term s (PEitherData a b :--> PBool)
forall a b. (a -> b) -> a -> b
$ \Term s (PEitherData a b)
t ->
Term s (PEitherData a b)
-> (PEitherData a b s -> Term s PBool) -> Term s PBool
forall (a :: S -> Type) (s :: S) (b :: S -> Type).
PlutusType a =>
Term s a -> (a s -> Term s b) -> Term s b
pmatch Term s (PEitherData a b)
t ((PEitherData a b s -> Term s PBool) -> Term s PBool)
-> (PEitherData a b s -> Term s PBool) -> Term s PBool
forall a b. (a -> b) -> a -> b
$ \case
PDLeft Term s (PAsData a)
_ -> PBool s -> Term s PBool
forall (a :: S -> Type) (s :: S). PlutusType a => a s -> Term s a
pcon PBool s
forall (s :: S). PBool s
PTrue
PDRight Term s (PAsData b)
_ -> PBool s -> Term s PBool
forall (a :: S -> Type) (s :: S). PlutusType a => a s -> Term s a
pcon PBool s
forall (s :: S). PBool s
PFalse
pdisRight ::
forall (a :: S -> Type) (b :: S -> Type) (s :: S).
Term s (PEitherData a b :--> PBool)
pdisRight :: forall (a :: S -> Type) (b :: S -> Type) (s :: S).
Term s (PEitherData a b :--> PBool)
pdisRight = ClosedTerm (PEitherData a b :--> PBool)
-> Term s (PEitherData a b :--> PBool)
forall (a :: S -> Type) (s :: S).
HasCallStack =>
ClosedTerm a -> Term s a
phoistAcyclic (ClosedTerm (PEitherData a b :--> PBool)
-> Term s (PEitherData a b :--> PBool))
-> ClosedTerm (PEitherData a b :--> PBool)
-> Term s (PEitherData a b :--> PBool)
forall a b. (a -> b) -> a -> b
$ (Term s (PEitherData a b) -> Term s PBool)
-> Term s (PEitherData a b :--> PBool)
forall a (b :: S -> Type) (s :: S) (c :: S -> Type).
(PLamN a b s, HasCallStack) =>
(Term s c -> a) -> Term s (c :--> b)
forall (c :: S -> Type).
HasCallStack =>
(Term s c -> Term s PBool) -> Term s (c :--> PBool)
plam ((Term s (PEitherData a b) -> Term s PBool)
-> Term s (PEitherData a b :--> PBool))
-> (Term s (PEitherData a b) -> Term s PBool)
-> Term s (PEitherData a b :--> PBool)
forall a b. (a -> b) -> a -> b
$ \Term s (PEitherData a b)
t ->
Term s (PEitherData a b)
-> (PEitherData a b s -> Term s PBool) -> Term s PBool
forall (a :: S -> Type) (s :: S) (b :: S -> Type).
PlutusType a =>
Term s a -> (a s -> Term s b) -> Term s b
pmatch Term s (PEitherData a b)
t ((PEitherData a b s -> Term s PBool) -> Term s PBool)
-> (PEitherData a b s -> Term s PBool) -> Term s PBool
forall a b. (a -> b) -> a -> b
$ \case
PDRight Term s (PAsData b)
_ -> PBool s -> Term s PBool
forall (a :: S -> Type) (s :: S). PlutusType a => a s -> Term s a
pcon PBool s
forall (s :: S). PBool s
PTrue
PDLeft Term s (PAsData a)
_ -> PBool s -> Term s PBool
forall (a :: S -> Type) (s :: S). PlutusType a => a s -> Term s a
pcon PBool s
forall (s :: S). PBool s
PFalse
pdfromLeft ::
forall (a :: S -> Type) (b :: S -> Type) (s :: S).
PIsData a =>
Term s (PEitherData a b :--> a)
pdfromLeft :: forall (a :: S -> Type) (b :: S -> Type) (s :: S).
PIsData a =>
Term s (PEitherData a b :--> a)
pdfromLeft = ClosedTerm (PEitherData a b :--> a)
-> Term s (PEitherData a b :--> a)
forall (a :: S -> Type) (s :: S).
HasCallStack =>
ClosedTerm a -> Term s a
phoistAcyclic (ClosedTerm (PEitherData a b :--> a)
-> Term s (PEitherData a b :--> a))
-> ClosedTerm (PEitherData a b :--> a)
-> Term s (PEitherData a b :--> a)
forall a b. (a -> b) -> a -> b
$ (Term s (PEitherData a b) -> Term s a)
-> Term s (PEitherData a b :--> a)
forall a (b :: S -> Type) (s :: S) (c :: S -> Type).
(PLamN a b s, HasCallStack) =>
(Term s c -> a) -> Term s (c :--> b)
forall (c :: S -> Type).
HasCallStack =>
(Term s c -> Term s a) -> Term s (c :--> a)
plam ((Term s (PEitherData a b) -> Term s a)
-> Term s (PEitherData a b :--> a))
-> (Term s (PEitherData a b) -> Term s a)
-> Term s (PEitherData a b :--> a)
forall a b. (a -> b) -> a -> b
$ \Term s (PEitherData a b)
t ->
Term s (PEitherData a b)
-> (PEitherData a b s -> Term s a) -> Term s a
forall (a :: S -> Type) (s :: S) (b :: S -> Type).
PlutusType a =>
Term s a -> (a s -> Term s b) -> Term s b
pmatch Term s (PEitherData a b)
t ((PEitherData a b s -> Term s a) -> Term s a)
-> (PEitherData a b s -> Term s a) -> Term s a
forall a b. (a -> b) -> a -> b
$ \case
PDLeft Term s (PAsData a)
x -> Term s (PAsData a) -> Term s a
forall (a :: S -> Type) (s :: S).
PIsData a =>
Term s (PAsData a) -> Term s a
pfromData Term s (PAsData a)
x
PDRight Term s (PAsData b)
_ -> Term s PString -> Term s a
forall (a :: S -> Type) (s :: S). Term s PString -> Term s a
ptraceInfoError Term s PString
"pdfromLeft: unexpected PDRight"
pdfromRight ::
forall (a :: S -> Type) (b :: S -> Type) (s :: S).
PIsData b =>
Term s (PEitherData a b :--> b)
pdfromRight :: forall (a :: S -> Type) (b :: S -> Type) (s :: S).
PIsData b =>
Term s (PEitherData a b :--> b)
pdfromRight = ClosedTerm (PEitherData a b :--> b)
-> Term s (PEitherData a b :--> b)
forall (a :: S -> Type) (s :: S).
HasCallStack =>
ClosedTerm a -> Term s a
phoistAcyclic (ClosedTerm (PEitherData a b :--> b)
-> Term s (PEitherData a b :--> b))
-> ClosedTerm (PEitherData a b :--> b)
-> Term s (PEitherData a b :--> b)
forall a b. (a -> b) -> a -> b
$ (Term s (PEitherData a b) -> Term s b)
-> Term s (PEitherData a b :--> b)
forall a (b :: S -> Type) (s :: S) (c :: S -> Type).
(PLamN a b s, HasCallStack) =>
(Term s c -> a) -> Term s (c :--> b)
forall (c :: S -> Type).
HasCallStack =>
(Term s c -> Term s b) -> Term s (c :--> b)
plam ((Term s (PEitherData a b) -> Term s b)
-> Term s (PEitherData a b :--> b))
-> (Term s (PEitherData a b) -> Term s b)
-> Term s (PEitherData a b :--> b)
forall a b. (a -> b) -> a -> b
$ \Term s (PEitherData a b)
t ->
Term s (PEitherData a b)
-> (PEitherData a b s -> Term s b) -> Term s b
forall (a :: S -> Type) (s :: S) (b :: S -> Type).
PlutusType a =>
Term s a -> (a s -> Term s b) -> Term s b
pmatch Term s (PEitherData a b)
t ((PEitherData a b s -> Term s b) -> Term s b)
-> (PEitherData a b s -> Term s b) -> Term s b
forall a b. (a -> b) -> a -> b
$ \case
PDRight Term s (PAsData b)
x -> Term s (PAsData b) -> Term s b
forall (a :: S -> Type) (s :: S).
PIsData a =>
Term s (PAsData a) -> Term s a
pfromData Term s (PAsData b)
x
PDLeft Term s (PAsData a)
_ -> Term s PString -> Term s b
forall (a :: S -> Type) (s :: S). Term s PString -> Term s a
ptraceInfoError Term s PString
"pdfromRight: unexpected PDLeft"