module Plutarch.Extra.Maybe (
pfromJust,
ptraceIfNothing,
pisJust,
pmaybe,
pfromMaybe,
pjust,
pnothing,
pfromDJust,
pisDJust,
pmaybeData,
pdjust,
pdnothing,
pmaybeToMaybeData,
pexpectJustC,
passertPJust,
passertPDJust,
) where
import Plutarch.Api.V1.Maybe (PMaybeData (PDJust, PDNothing))
import Plutarch.Prelude
pfromJust ::
forall (a :: PType) (s :: S).
Term s (PMaybe a :--> a)
pfromJust :: forall (a :: PType) (s :: S). Term s (PMaybe a :--> a)
pfromJust = forall (a :: PType) (s :: S).
HasCallStack =>
ClosedTerm a -> Term s a
phoistAcyclic forall a b. (a -> b) -> a -> b
$
forall a (b :: PType) (s :: S) (c :: PType).
(PLamN a b s, HasCallStack) =>
(Term s c -> a) -> Term s (c :--> b)
plam forall a b. (a -> b) -> a -> b
$ \Term s (PMaybe a)
t -> forall (a :: PType) (s :: S) (b :: PType).
PlutusType a =>
Term s a -> (a s -> Term s b) -> Term s b
pmatch Term s (PMaybe a)
t forall a b. (a -> b) -> a -> b
$ \case
PMaybe a s
PNothing -> forall (s :: S) (a :: PType). Term s PString -> Term s a
ptraceError Term s PString
"pfromJust: found PNothing"
PJust Term s a
x -> Term s a
x
ptraceIfNothing ::
forall (a :: PType) (s :: S).
Term s PString ->
Term s (PMaybe a) ->
Term s a
ptraceIfNothing :: forall (a :: PType) (s :: S).
Term s PString -> Term s (PMaybe a) -> Term s a
ptraceIfNothing Term s PString
err Term s (PMaybe a)
t = forall (a :: PType) (s :: S) (b :: PType).
PlutusType a =>
Term s a -> (a s -> Term s b) -> Term s b
pmatch Term s (PMaybe a)
t forall a b. (a -> b) -> a -> b
$ \case
PMaybe a s
PNothing -> forall (s :: S) (a :: PType). Term s PString -> Term s a
ptraceError Term s PString
err
PJust Term s a
x -> Term s a
x
pisJust ::
forall (a :: PType) (s :: S).
Term s (PMaybe a :--> PBool)
pisJust :: forall (a :: PType) (s :: S). Term s (PMaybe a :--> PBool)
pisJust = forall (a :: PType) (s :: S).
HasCallStack =>
ClosedTerm a -> Term s a
phoistAcyclic forall a b. (a -> b) -> a -> b
$
forall a (b :: PType) (s :: S) (c :: PType).
(PLamN a b s, HasCallStack) =>
(Term s c -> a) -> Term s (c :--> b)
plam forall a b. (a -> b) -> a -> b
$ \Term s (PMaybe a)
v' ->
forall (a :: PType) (s :: S) (b :: PType).
PlutusType a =>
Term s a -> (a s -> Term s b) -> Term s b
pmatch Term s (PMaybe a)
v' forall a b. (a -> b) -> a -> b
$ \case
PJust Term s a
_ -> forall (p :: PType) (s :: S). PLift p => PLifted p -> Term s p
pconstant Bool
True
PMaybe a s
_ -> forall (p :: PType) (s :: S). PLift p => PLifted p -> Term s p
pconstant Bool
False
pfromMaybe ::
forall (a :: PType) (s :: S).
Term s (a :--> PMaybe a :--> a)
pfromMaybe :: forall (a :: PType) (s :: S). Term s (a :--> (PMaybe a :--> a))
pfromMaybe = forall (a :: PType) (s :: S).
HasCallStack =>
ClosedTerm a -> Term s a
phoistAcyclic forall a b. (a -> b) -> a -> b
$
forall a (b :: PType) (s :: S) (c :: PType).
(PLamN a b s, HasCallStack) =>
(Term s c -> a) -> Term s (c :--> b)
plam forall a b. (a -> b) -> a -> b
$ \Term s a
e Term s (PMaybe a)
a -> forall (a :: PType) (s :: S) (b :: PType).
PlutusType a =>
Term s a -> (a s -> Term s b) -> Term s b
pmatch Term s (PMaybe a)
a forall a b. (a -> b) -> a -> b
$ \case
PJust Term s a
a' -> Term s a
a'
PMaybe a s
PNothing -> Term s a
e
pjust :: forall (a :: PType) (s :: S). Term s (a :--> PMaybe a)
pjust :: forall (a :: PType) (s :: S). Term s (a :--> PMaybe a)
pjust = forall (a :: PType) (s :: S).
HasCallStack =>
ClosedTerm a -> Term s a
phoistAcyclic forall a b. (a -> b) -> a -> b
$ forall a (b :: PType) (s :: S) (c :: PType).
(PLamN a b s, HasCallStack) =>
(Term s c -> a) -> Term s (c :--> b)
plam forall a b. (a -> b) -> a -> b
$ forall (a :: PType) (s :: S). PlutusType a => a s -> Term s a
pcon forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (a :: PType) (s :: S). Term s a -> PMaybe a s
PJust
pnothing :: forall (a :: PType) (s :: S). Term s (PMaybe a)
pnothing :: forall (a :: PType) (s :: S). Term s (PMaybe a)
pnothing = forall (a :: PType) (s :: S).
HasCallStack =>
ClosedTerm a -> Term s a
phoistAcyclic forall a b. (a -> b) -> a -> b
$ forall (a :: PType) (s :: S). PlutusType a => a s -> Term s a
pcon forall (a :: PType) (s :: S). PMaybe a s
PNothing
pmaybe ::
forall (b :: PType) (a :: PType) (s :: S).
Term s (b :--> (a :--> b) :--> PMaybe a :--> b)
pmaybe :: forall (b :: PType) (a :: PType) (s :: S).
Term s (b :--> ((a :--> b) :--> (PMaybe a :--> b)))
pmaybe = forall (a :: PType) (s :: S).
HasCallStack =>
ClosedTerm a -> Term s a
phoistAcyclic forall a b. (a -> b) -> a -> b
$
forall a (b :: PType) (s :: S) (c :: PType).
(PLamN a b s, HasCallStack) =>
(Term s c -> a) -> Term s (c :--> b)
plam forall a b. (a -> b) -> a -> b
$ \Term s b
d Term s (a :--> b)
f -> forall a b c. (a -> b -> c) -> b -> a -> c
flip forall (a :: PType) (s :: S) (b :: PType).
PlutusType a =>
Term s a -> (a s -> Term s b) -> Term s b
pmatch forall a b. (a -> b) -> a -> b
$ \case
PJust Term s a
v -> Term s (a :--> b)
f forall (s :: S) (a :: PType) (b :: PType).
HasCallStack =>
Term s (a :--> b) -> Term s a -> Term s b
# Term s a
v
PMaybe a s
_ -> Term s b
d
pfromDJust ::
forall (a :: PType) (s :: S).
(PIsData a) =>
Term s (PMaybeData a :--> a)
pfromDJust :: forall (a :: PType) (s :: S).
PIsData a =>
Term s (PMaybeData a :--> a)
pfromDJust = forall (a :: PType) (s :: S).
HasCallStack =>
ClosedTerm a -> Term s a
phoistAcyclic forall a b. (a -> b) -> a -> b
$
forall a (b :: PType) (s :: S) (c :: PType).
(PLamN a b s, HasCallStack) =>
(Term s c -> a) -> Term s (c :--> b)
plam forall a b. (a -> b) -> a -> b
$ \Term s (PMaybeData a)
t -> forall (a :: PType) (s :: S) (b :: PType).
PlutusType a =>
Term s a -> (a s -> Term s b) -> Term s b
pmatch Term s (PMaybeData a)
t forall a b. (a -> b) -> a -> b
$ \case
PDNothing Term s (PDataRecord ('[] @PLabeledType))
_ -> forall (s :: S) (a :: PType). Term s PString -> Term s a
ptraceError Term s PString
"pfromDJust: found PDNothing"
PDJust Term
s
(PDataRecord ((':) @PLabeledType ("_0" ':= a) ('[] @PLabeledType)))
x -> forall (a :: PType) (s :: S).
PIsData a =>
Term s (PAsData a) -> Term s a
pfromData forall a b. (a -> b) -> a -> b
$ forall (name :: Symbol) (b :: PType) (p :: PType) (s :: S)
(a :: PType) (as :: [PLabeledType]) (n :: Nat).
(PDataFields p,
(as :: [PLabeledType]) ~ (PFields p :: [PLabeledType]),
(n :: Nat) ~ (PLabelIndex name as :: Nat), KnownNat n,
(a :: PType) ~ (PUnLabel (IndexList @PLabeledType n as) :: PType),
PFromDataable a b) =>
Term s (p :--> b)
pfield @"_0" forall (s :: S) (a :: PType) (b :: PType).
HasCallStack =>
Term s (a :--> b) -> Term s a -> Term s b
# Term
s
(PDataRecord ((':) @PLabeledType ("_0" ':= a) ('[] @PLabeledType)))
x
pisDJust ::
forall (a :: PType) (s :: S).
Term s (PMaybeData a :--> PBool)
pisDJust :: forall (a :: PType) (s :: S). Term s (PMaybeData a :--> PBool)
pisDJust = forall (a :: PType) (s :: S).
HasCallStack =>
ClosedTerm a -> Term s a
phoistAcyclic forall a b. (a -> b) -> a -> b
$
forall a (b :: PType) (s :: S) (c :: PType).
(PLamN a b s, HasCallStack) =>
(Term s c -> a) -> Term s (c :--> b)
plam forall a b. (a -> b) -> a -> b
$ \Term s (PMaybeData a)
x -> forall (a :: PType) (s :: S) (b :: PType).
PlutusType a =>
Term s a -> (a s -> Term s b) -> Term s b
pmatch Term s (PMaybeData a)
x forall a b. (a -> b) -> a -> b
$ \case
PDJust Term
s
(PDataRecord ((':) @PLabeledType ("_0" ':= a) ('[] @PLabeledType)))
_ -> forall (p :: PType) (s :: S). PLift p => PLifted p -> Term s p
pconstant Bool
True
PMaybeData a s
_ -> forall (p :: PType) (s :: S). PLift p => PLifted p -> Term s p
pconstant Bool
False
pmaybeData ::
forall (a :: PType) (b :: PType) (s :: S).
PIsData a =>
Term s (b :--> (a :--> b) :--> PMaybeData a :--> b)
pmaybeData :: forall (a :: PType) (b :: PType) (s :: S).
PIsData a =>
Term s (b :--> ((a :--> b) :--> (PMaybeData a :--> b)))
pmaybeData = forall (a :: PType) (s :: S).
HasCallStack =>
ClosedTerm a -> Term s a
phoistAcyclic forall a b. (a -> b) -> a -> b
$
forall a (b :: PType) (s :: S) (c :: PType).
(PLamN a b s, HasCallStack) =>
(Term s c -> a) -> Term s (c :--> b)
plam forall a b. (a -> b) -> a -> b
$ \Term s b
d Term s (a :--> b)
f Term s (PMaybeData a)
m -> forall (a :: PType) (s :: S) (b :: PType).
PlutusType a =>
Term s a -> (a s -> Term s b) -> Term s b
pmatch Term s (PMaybeData a)
m forall a b. (a -> b) -> a -> b
$
\case
PDJust Term
s
(PDataRecord ((':) @PLabeledType ("_0" ':= a) ('[] @PLabeledType)))
x -> Term s (a :--> b)
f forall (s :: S) (a :: PType) (b :: PType).
HasCallStack =>
Term s (a :--> b) -> Term s a -> Term s b
#$ forall (name :: Symbol) (b :: PType) (p :: PType) (s :: S)
(a :: PType) (as :: [PLabeledType]) (n :: Nat).
(PDataFields p,
(as :: [PLabeledType]) ~ (PFields p :: [PLabeledType]),
(n :: Nat) ~ (PLabelIndex name as :: Nat), KnownNat n,
(a :: PType) ~ (PUnLabel (IndexList @PLabeledType n as) :: PType),
PFromDataable a b) =>
Term s (p :--> b)
pfield @"_0" forall (s :: S) (a :: PType) (b :: PType).
HasCallStack =>
Term s (a :--> b) -> Term s a -> Term s b
# Term
s
(PDataRecord ((':) @PLabeledType ("_0" ':= a) ('[] @PLabeledType)))
x
PMaybeData a s
_ -> Term s b
d
pdjust ::
forall (a :: PType) (s :: S).
PIsData a =>
Term s (a :--> PMaybeData a)
pdjust :: forall (a :: PType) (s :: S).
PIsData a =>
Term s (a :--> PMaybeData a)
pdjust = forall (a :: PType) (s :: S).
HasCallStack =>
ClosedTerm a -> Term s a
phoistAcyclic forall a b. (a -> b) -> a -> b
$
forall a (b :: PType) (s :: S) (c :: PType).
(PLamN a b s, HasCallStack) =>
(Term s c -> a) -> Term s (c :--> b)
plam forall a b. (a -> b) -> a -> b
$
\Term s a
x -> forall (a :: PType) (s :: S). PlutusType a => a s -> Term s a
pcon forall a b. (a -> b) -> a -> b
$ forall (a :: PType) (s :: S).
Term
s
(PDataRecord ((':) @PLabeledType ("_0" ':= a) ('[] @PLabeledType)))
-> PMaybeData a s
PDJust forall a b. (a -> b) -> a -> b
$ forall (label :: Symbol) (a :: PType) (l :: [PLabeledType])
(s :: S).
Term
s
(PAsData a
:--> (PDataRecord l
:--> PDataRecord ((':) @PLabeledType (label ':= a) l)))
pdcons @"_0" forall (s :: S) (a :: PType) (b :: PType).
HasCallStack =>
Term s (a :--> b) -> Term s a -> Term s b
# forall (a :: PType) (s :: S).
PIsData a =>
Term s a -> Term s (PAsData a)
pdata Term s a
x forall (s :: S) (a :: PType) (b :: PType).
HasCallStack =>
Term s (a :--> b) -> Term s a -> Term s b
#$ forall (s :: S). Term s (PDataRecord ('[] @PLabeledType))
pdnil
pdnothing ::
forall (a :: PType) (s :: S).
Term s (PMaybeData a)
pdnothing :: forall (a :: PType) (s :: S). Term s (PMaybeData a)
pdnothing = forall (a :: PType) (s :: S).
HasCallStack =>
ClosedTerm a -> Term s a
phoistAcyclic forall a b. (a -> b) -> a -> b
$ forall (a :: PType) (s :: S). PlutusType a => a s -> Term s a
pcon forall a b. (a -> b) -> a -> b
$ forall (a :: PType) (s :: S).
Term s (PDataRecord ('[] @PLabeledType)) -> PMaybeData a s
PDNothing forall (s :: S). Term s (PDataRecord ('[] @PLabeledType))
pdnil
pmaybeToMaybeData ::
forall (a :: PType) (s :: S).
(PIsData a) =>
Term s (PMaybe a :--> PMaybeData a)
pmaybeToMaybeData :: forall (a :: PType) (s :: S).
PIsData a =>
Term s (PMaybe a :--> PMaybeData a)
pmaybeToMaybeData = forall (a :: PType) (s :: S).
HasCallStack =>
ClosedTerm a -> Term s a
phoistAcyclic forall a b. (a -> b) -> a -> b
$
forall a (b :: PType) (s :: S) (c :: PType).
(PLamN a b s, HasCallStack) =>
(Term s c -> a) -> Term s (c :--> b)
plam forall a b. (a -> b) -> a -> b
$ \Term s (PMaybe a)
t -> forall (a :: PType) (s :: S) (b :: PType).
PlutusType a =>
Term s a -> (a s -> Term s b) -> Term s b
pmatch Term s (PMaybe a)
t forall a b. (a -> b) -> a -> b
$ \case
PMaybe a s
PNothing -> forall (a :: PType) (s :: S). PlutusType a => a s -> Term s a
pcon forall a b. (a -> b) -> a -> b
$ forall (a :: PType) (s :: S).
Term s (PDataRecord ('[] @PLabeledType)) -> PMaybeData a s
PDNothing forall (s :: S). Term s (PDataRecord ('[] @PLabeledType))
pdnil
PJust Term s a
x -> forall (a :: PType) (s :: S). PlutusType a => a s -> Term s a
pcon forall a b. (a -> b) -> a -> b
$ forall (a :: PType) (s :: S).
Term
s
(PDataRecord ((':) @PLabeledType ("_0" ':= a) ('[] @PLabeledType)))
-> PMaybeData a s
PDJust forall a b. (a -> b) -> a -> b
$ forall (label :: Symbol) (a :: PType) (l :: [PLabeledType])
(s :: S).
Term
s
(PAsData a
:--> (PDataRecord l
:--> PDataRecord ((':) @PLabeledType (label ':= a) l)))
pdcons @"_0" forall (s :: S) (a :: PType) (b :: PType).
HasCallStack =>
Term s (a :--> b) -> Term s a -> Term s b
# forall (a :: PType) (s :: S).
PIsData a =>
Term s a -> Term s (PAsData a)
pdata Term s a
x forall (s :: S) (a :: PType) (b :: PType).
HasCallStack =>
Term s (a :--> b) -> Term s a -> Term s b
# forall (s :: S). Term s (PDataRecord ('[] @PLabeledType))
pdnil
pexpectJustC ::
forall (a :: PType) (r :: PType) (s :: S).
Term s r ->
Term s (PMaybe a) ->
TermCont @r s (Term s a)
pexpectJustC :: forall (a :: PType) (r :: PType) (s :: S).
Term s r -> Term s (PMaybe a) -> TermCont @r s (Term s a)
pexpectJustC Term s r
escape Term s (PMaybe a)
ma = forall a (s :: S) (r :: PType).
((a -> Term s r) -> Term s r) -> TermCont @r s a
tcont forall a b. (a -> b) -> a -> b
$ \Term s a -> Term s r
f ->
forall (a :: PType) (s :: S) (b :: PType).
PlutusType a =>
Term s a -> (a s -> Term s b) -> Term s b
pmatch Term s (PMaybe a)
ma forall a b. (a -> b) -> a -> b
$ \case
PJust Term s a
v -> Term s a -> Term s r
f Term s a
v
PMaybe a s
PNothing -> Term s r
escape
passertPJust :: forall (a :: PType) (s :: S). Term s (PString :--> PMaybe a :--> a)
passertPJust :: forall (a :: PType) (s :: S).
Term s (PString :--> (PMaybe a :--> a))
passertPJust = forall (a :: PType) (s :: S).
HasCallStack =>
ClosedTerm a -> Term s a
phoistAcyclic forall a b. (a -> b) -> a -> b
$
forall a (b :: PType) (s :: S) (c :: PType).
(PLamN a b s, HasCallStack) =>
(Term s c -> a) -> Term s (c :--> b)
plam forall a b. (a -> b) -> a -> b
$ \Term s PString
emsg Term s (PMaybe a)
mv' -> forall (a :: PType) (s :: S) (b :: PType).
PlutusType a =>
Term s a -> (a s -> Term s b) -> Term s b
pmatch Term s (PMaybe a)
mv' forall a b. (a -> b) -> a -> b
$ \case
PJust Term s a
v -> Term s a
v
PMaybe a s
_ -> forall (s :: S) (a :: PType). Term s PString -> Term s a
ptraceError Term s PString
emsg
passertPDJust :: forall (a :: PType) (s :: S). (PIsData a) => Term s (PString :--> PMaybeData a :--> a)
passertPDJust :: forall (a :: PType) (s :: S).
PIsData a =>
Term s (PString :--> (PMaybeData a :--> a))
passertPDJust = forall (a :: PType) (s :: S).
HasCallStack =>
ClosedTerm a -> Term s a
phoistAcyclic forall a b. (a -> b) -> a -> b
$
forall a (b :: PType) (s :: S) (c :: PType).
(PLamN a b s, HasCallStack) =>
(Term s c -> a) -> Term s (c :--> b)
plam forall a b. (a -> b) -> a -> b
$ \Term s PString
emsg Term s (PMaybeData a)
mv' -> forall (a :: PType) (s :: S) (b :: PType).
PlutusType a =>
Term s a -> (a s -> Term s b) -> Term s b
pmatch Term s (PMaybeData a)
mv' forall a b. (a -> b) -> a -> b
$ \case
PDJust ((forall (name :: Symbol) (b :: PType) (p :: PType) (s :: S)
(a :: PType) (as :: [PLabeledType]) (n :: Nat).
(PDataFields p,
(as :: [PLabeledType]) ~ (PFields p :: [PLabeledType]),
(n :: Nat) ~ (PLabelIndex name as :: Nat), KnownNat n,
(a :: PType) ~ (PUnLabel (IndexList @PLabeledType n as) :: PType),
PFromDataable a b) =>
Term s (p :--> b)
pfield @"_0" #) -> Term s a
v) -> Term s a
v
PMaybeData a s
_ -> forall (s :: S) (a :: PType). Term s PString -> Term s a
ptraceError Term s PString
emsg