{-# LANGUAGE UndecidableInstances #-}
module Plutarch.Maybe (
PMaybe (..),
pjust,
pnothing,
pisJust,
pfromJust,
ptraceIfNothing,
pfromMaybe,
pmaybe,
passertPJust,
pmapMaybe,
) where
import Data.Kind (Type)
import GHC.Generics (Generic)
import Generics.SOP qualified as SOP
import Plutarch.Builtin.Bool (PBool)
import Plutarch.Builtin.String (PString, ptraceInfo)
import Plutarch.Internal.Eq (PEq)
import Plutarch.Internal.Lift (
PLiftable (
AsHaskell,
PlutusRepr,
haskToRepr,
plutToRepr,
reprToHask,
reprToPlut
),
PLiftedClosed,
getPLiftedClosed,
mkPLifted,
mkPLiftedClosed,
pconstant,
pliftedFromClosed,
pliftedToClosed,
)
import Plutarch.Internal.PLam (plam)
import Plutarch.Internal.PlutusType (
PlutusType,
pcon,
pmatch,
)
import Plutarch.Internal.Term (
S,
Term,
perror,
phoistAcyclic,
(#),
(:-->),
)
import Plutarch.Repr.SOP (DeriveAsSOPStruct (DeriveAsSOPStruct))
data PMaybe (a :: S -> Type) (s :: S)
= PJust (Term s a)
| PNothing
deriving stock
(
(forall x. PMaybe a s -> Rep (PMaybe a s) x)
-> (forall x. Rep (PMaybe a s) x -> PMaybe a s)
-> Generic (PMaybe a s)
forall x. Rep (PMaybe a s) x -> PMaybe a s
forall x. PMaybe a s -> Rep (PMaybe a s) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall (a :: S -> Type) (s :: S) x.
Rep (PMaybe a s) x -> PMaybe a s
forall (a :: S -> Type) (s :: S) x.
PMaybe a s -> Rep (PMaybe a s) x
$cfrom :: forall (a :: S -> Type) (s :: S) x.
PMaybe a s -> Rep (PMaybe a s) x
from :: forall x. PMaybe a s -> Rep (PMaybe a s) x
$cto :: forall (a :: S -> Type) (s :: S) x.
Rep (PMaybe a s) x -> PMaybe a s
to :: forall x. Rep (PMaybe a s) x -> PMaybe a s
Generic
)
deriving anyclass
(
All @[Type] (SListI @Type) (Code (PMaybe a s))
All @[Type] (SListI @Type) (Code (PMaybe a s)) =>
(PMaybe a s -> Rep (PMaybe a s))
-> (Rep (PMaybe a s) -> PMaybe a s) -> Generic (PMaybe a s)
Rep (PMaybe a s) -> PMaybe a s
PMaybe a s -> Rep (PMaybe a s)
forall a.
All @[Type] (SListI @Type) (Code a) =>
(a -> Rep a) -> (Rep a -> a) -> Generic a
forall (a :: S -> Type) (s :: S).
All @[Type] (SListI @Type) (Code (PMaybe a s))
forall (a :: S -> Type) (s :: S). Rep (PMaybe a s) -> PMaybe a s
forall (a :: S -> Type) (s :: S). PMaybe a s -> Rep (PMaybe a s)
$cfrom :: forall (a :: S -> Type) (s :: S). PMaybe a s -> Rep (PMaybe a s)
from :: PMaybe a s -> Rep (PMaybe a s)
$cto :: forall (a :: S -> Type) (s :: S). Rep (PMaybe a s) -> PMaybe a s
to :: Rep (PMaybe a s) -> PMaybe a s
SOP.Generic
,
(forall (s :: S).
Term s (PMaybe a) -> Term s (PMaybe a) -> Term s PBool)
-> PEq (PMaybe a)
forall (s :: S).
Term s (PMaybe a) -> Term s (PMaybe a) -> Term s PBool
forall (a :: S -> Type) (s :: S).
PEq a =>
Term s (PMaybe a) -> Term s (PMaybe a) -> Term s PBool
forall (t :: S -> Type).
(forall (s :: S). Term s t -> Term s t -> Term s PBool) -> PEq t
$c#== :: forall (a :: S -> Type) (s :: S).
PEq a =>
Term s (PMaybe a) -> Term s (PMaybe a) -> Term s PBool
#== :: forall (s :: S).
Term s (PMaybe a) -> Term s (PMaybe a) -> Term s PBool
PEq
)
deriving via DeriveAsSOPStruct (PMaybe a) instance PlutusType (PMaybe a)
instance PLiftable a => PLiftable (PMaybe a) where
type AsHaskell (PMaybe a) = Maybe (AsHaskell a)
type PlutusRepr (PMaybe a) = PLiftedClosed (PMaybe a)
{-# INLINEABLE haskToRepr #-}
haskToRepr :: AsHaskell (PMaybe a) -> PlutusRepr (PMaybe a)
haskToRepr = \case
Maybe (AsHaskell a)
AsHaskell (PMaybe a)
Nothing -> (forall (s :: S). Term s (PMaybe a)) -> PLiftedClosed (PMaybe a)
forall (a :: S -> Type).
(forall (s :: S). Term s a) -> PLiftedClosed a
mkPLiftedClosed ((forall (s :: S). Term s (PMaybe a)) -> PLiftedClosed (PMaybe a))
-> (forall (s :: S). Term s (PMaybe a)) -> PLiftedClosed (PMaybe a)
forall a b. (a -> b) -> a -> b
$ PMaybe a s -> Term s (PMaybe a)
forall (a :: S -> Type) (s :: S). PlutusType a => a s -> Term s a
pcon PMaybe a s
forall (a :: S -> Type) (s :: S). PMaybe a s
PNothing
Just AsHaskell a
x -> (forall (s :: S). Term s (PMaybe a)) -> PLiftedClosed (PMaybe a)
forall (a :: S -> Type).
(forall (s :: S). Term s a) -> PLiftedClosed a
mkPLiftedClosed ((forall (s :: S). Term s (PMaybe a)) -> PLiftedClosed (PMaybe a))
-> (forall (s :: S). Term s (PMaybe a)) -> PLiftedClosed (PMaybe a)
forall a b. (a -> b) -> a -> b
$ PMaybe a s -> Term s (PMaybe a)
forall (a :: S -> Type) (s :: S). PlutusType a => a s -> Term s a
pcon (PMaybe a s -> Term s (PMaybe a))
-> PMaybe a s -> Term s (PMaybe a)
forall a b. (a -> b) -> a -> b
$ Term s a -> PMaybe a s
forall (a :: S -> Type) (s :: S). Term s a -> PMaybe a s
PJust (forall (a :: S -> Type) (s :: S).
PLiftable a =>
AsHaskell a -> Term s a
pconstant @a AsHaskell a
x)
{-# INLINEABLE reprToHask #-}
reprToHask :: PlutusRepr (PMaybe a) -> Either LiftError (AsHaskell (PMaybe a))
reprToHask PlutusRepr (PMaybe a)
x = do
Bool
isJust :: 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 (PMaybe a :--> PBool)
forall (a :: S -> Type) (s :: S). Term s (PMaybe a :--> PBool)
pisJust Term s (PMaybe a :--> PBool) -> Term s (PMaybe a) -> Term s PBool
forall (s :: S) (a :: S -> Type) (b :: S -> Type).
Term s (a :--> b) -> Term s a -> Term s b
# PLiftedClosed (PMaybe a) -> forall (s :: S). Term s (PMaybe a)
forall (a :: S -> Type).
PLiftedClosed a -> forall (s :: S). Term s a
getPLiftedClosed PlutusRepr (PMaybe a)
PLiftedClosed (PMaybe a)
x)
if Bool
isJust
then do
PlutusRepr a
vr :: 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 (PMaybe a :--> a)
forall (a :: S -> Type) (s :: S). Term s (PMaybe a :--> a)
pfromJust Term s (PMaybe a :--> a) -> Term s (PMaybe a) -> Term s a
forall (s :: S) (a :: S -> Type) (b :: S -> Type).
Term s (a :--> b) -> Term s a -> Term s b
# PLiftedClosed (PMaybe a) -> forall (s :: S). Term s (PMaybe a)
forall (a :: S -> Type).
PLiftedClosed a -> forall (s :: S). Term s a
getPLiftedClosed PlutusRepr (PMaybe a)
PLiftedClosed (PMaybe a)
x)
AsHaskell a
vh :: AsHaskell a <- forall (a :: S -> Type).
PLiftable a =>
PlutusRepr a -> Either LiftError (AsHaskell a)
reprToHask @a PlutusRepr a
vr
Maybe (AsHaskell a) -> Either LiftError (Maybe (AsHaskell a))
forall a. a -> Either LiftError a
forall (f :: Type -> Type) a. Applicative f => a -> f a
pure (Maybe (AsHaskell a) -> Either LiftError (Maybe (AsHaskell a)))
-> Maybe (AsHaskell a) -> Either LiftError (Maybe (AsHaskell a))
forall a b. (a -> b) -> a -> b
$ AsHaskell a -> Maybe (AsHaskell a)
forall a. a -> Maybe a
Just AsHaskell a
vh
else Maybe (AsHaskell a) -> Either LiftError (Maybe (AsHaskell a))
forall a. a -> Either LiftError a
forall (f :: Type -> Type) a. Applicative f => a -> f a
pure Maybe (AsHaskell a)
forall a. Maybe a
Nothing
{-# INLINEABLE reprToPlut #-}
reprToPlut :: forall (s :: S). PlutusRepr (PMaybe a) -> PLifted s (PMaybe a)
reprToPlut = PlutusRepr (PMaybe a) -> PLifted s (PMaybe a)
PLiftedClosed (PMaybe a) -> PLifted s (PMaybe a)
forall (a :: S -> Type) (s :: S). PLiftedClosed a -> PLifted s a
pliftedFromClosed
{-# INLINEABLE plutToRepr #-}
plutToRepr :: (forall (s :: S). PLifted s (PMaybe a))
-> Either LiftError (PlutusRepr (PMaybe a))
plutToRepr = PLiftedClosed (PMaybe a)
-> Either LiftError (PLiftedClosed (PMaybe a))
forall a b. b -> Either a b
Right (PLiftedClosed (PMaybe a)
-> Either LiftError (PLiftedClosed (PMaybe a)))
-> ((forall (s :: S). PLifted s (PMaybe a))
-> PLiftedClosed (PMaybe a))
-> (forall (s :: S). PLifted s (PMaybe a))
-> Either LiftError (PLiftedClosed (PMaybe a))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (forall (s :: S). PLifted s (PMaybe a)) -> PLiftedClosed (PMaybe a)
forall (a :: S -> Type).
(forall (s :: S). PLifted s a) -> PLiftedClosed a
pliftedToClosed
pfromJust ::
forall (a :: S -> Type) (s :: S).
Term s (PMaybe a :--> a)
pfromJust :: forall (a :: S -> Type) (s :: S). Term s (PMaybe a :--> a)
pfromJust = ClosedTerm (PMaybe a :--> a) -> Term s (PMaybe a :--> a)
forall (a :: S -> Type) (s :: S).
HasCallStack =>
ClosedTerm a -> Term s a
phoistAcyclic (ClosedTerm (PMaybe a :--> a) -> Term s (PMaybe a :--> a))
-> ClosedTerm (PMaybe a :--> a) -> Term s (PMaybe a :--> a)
forall a b. (a -> b) -> a -> b
$
(Term s (PMaybe a) -> Term s a) -> Term s (PMaybe a :--> 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 (PMaybe a) -> Term s a) -> Term s (PMaybe a :--> a))
-> (Term s (PMaybe a) -> Term s a) -> Term s (PMaybe a :--> a)
forall a b. (a -> b) -> a -> b
$ \Term s (PMaybe a)
t -> Term s (PMaybe a) -> (PMaybe a 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 (PMaybe a)
t ((PMaybe a s -> Term s a) -> Term s a)
-> (PMaybe a s -> Term s a) -> Term s a
forall a b. (a -> b) -> a -> b
$ \case
PMaybe a s
PNothing -> Term s PString -> Term s a -> Term s a
forall (a :: S -> Type) (s :: S).
Term s PString -> Term s a -> Term s a
ptraceInfo Term s PString
"pfromJust: found PNothing" Term s a
forall (s :: S) (a :: S -> Type). Term s a
perror
PJust Term s a
x -> Term s a
x
ptraceIfNothing ::
forall (a :: S -> Type) (s :: S).
Term s PString ->
Term s (PMaybe a) ->
Term s a
ptraceIfNothing :: forall (a :: S -> Type) (s :: S).
Term s PString -> Term s (PMaybe a) -> Term s a
ptraceIfNothing Term s PString
err Term s (PMaybe a)
t = Term s (PMaybe a) -> (PMaybe a 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 (PMaybe a)
t ((PMaybe a s -> Term s a) -> Term s a)
-> (PMaybe a s -> Term s a) -> Term s a
forall a b. (a -> b) -> a -> b
$ \case
PMaybe a s
PNothing -> Term s PString -> Term s a -> Term s a
forall (a :: S -> Type) (s :: S).
Term s PString -> Term s a -> Term s a
ptraceInfo Term s PString
err Term s a
forall (s :: S) (a :: S -> Type). Term s a
perror
PJust Term s a
x -> Term s a
x
pisJust ::
forall (a :: S -> Type) (s :: S).
Term s (PMaybe a :--> PBool)
pisJust :: forall (a :: S -> Type) (s :: S). Term s (PMaybe a :--> PBool)
pisJust = ClosedTerm (PMaybe a :--> PBool) -> Term s (PMaybe a :--> PBool)
forall (a :: S -> Type) (s :: S).
HasCallStack =>
ClosedTerm a -> Term s a
phoistAcyclic (ClosedTerm (PMaybe a :--> PBool) -> Term s (PMaybe a :--> PBool))
-> ClosedTerm (PMaybe a :--> PBool) -> Term s (PMaybe a :--> PBool)
forall a b. (a -> b) -> a -> b
$
(Term s (PMaybe a) -> Term s PBool) -> Term s (PMaybe a :--> 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 (PMaybe a) -> Term s PBool)
-> Term s (PMaybe a :--> PBool))
-> (Term s (PMaybe a) -> Term s PBool)
-> Term s (PMaybe a :--> PBool)
forall a b. (a -> b) -> a -> b
$ \Term s (PMaybe a)
v' ->
Term s (PMaybe a) -> (PMaybe a 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 (PMaybe a)
v' ((PMaybe a s -> Term s PBool) -> Term s PBool)
-> (PMaybe a s -> Term s PBool) -> Term s PBool
forall a b. (a -> b) -> a -> b
$ \case
PJust Term s a
_ -> AsHaskell PBool -> Term s PBool
forall (a :: S -> Type) (s :: S).
PLiftable a =>
AsHaskell a -> Term s a
pconstant Bool
AsHaskell PBool
True
PMaybe a s
_ -> AsHaskell PBool -> Term s PBool
forall (a :: S -> Type) (s :: S).
PLiftable a =>
AsHaskell a -> Term s a
pconstant Bool
AsHaskell PBool
False
pfromMaybe ::
forall (a :: S -> Type) (s :: S).
Term s (a :--> PMaybe a :--> a)
pfromMaybe :: forall (a :: S -> Type) (s :: S). Term s (a :--> (PMaybe a :--> a))
pfromMaybe = ClosedTerm (a :--> (PMaybe a :--> a))
-> Term s (a :--> (PMaybe a :--> a))
forall (a :: S -> Type) (s :: S).
HasCallStack =>
ClosedTerm a -> Term s a
phoistAcyclic (ClosedTerm (a :--> (PMaybe a :--> a))
-> Term s (a :--> (PMaybe a :--> a)))
-> ClosedTerm (a :--> (PMaybe a :--> a))
-> Term s (a :--> (PMaybe a :--> a))
forall a b. (a -> b) -> a -> b
$
(Term s a -> Term s (PMaybe a) -> Term s a)
-> Term s (a :--> (PMaybe a :--> 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 (PMaybe a) -> Term s a)
-> Term s (c :--> (PMaybe a :--> a))
plam ((Term s a -> Term s (PMaybe a) -> Term s a)
-> Term s (a :--> (PMaybe a :--> a)))
-> (Term s a -> Term s (PMaybe a) -> Term s a)
-> Term s (a :--> (PMaybe a :--> a))
forall a b. (a -> b) -> a -> b
$ \Term s a
e Term s (PMaybe a)
a -> Term s (PMaybe a) -> (PMaybe a 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 (PMaybe a)
a ((PMaybe a s -> Term s a) -> Term s a)
-> (PMaybe a s -> Term s a) -> Term s 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 :: S -> Type) (s :: S).
Term s (a :--> PMaybe a)
pjust :: forall (a :: S -> Type) (s :: S). Term s (a :--> PMaybe a)
pjust = ClosedTerm (a :--> PMaybe a) -> Term s (a :--> PMaybe a)
forall (a :: S -> Type) (s :: S).
HasCallStack =>
ClosedTerm a -> Term s a
phoistAcyclic (ClosedTerm (a :--> PMaybe a) -> Term s (a :--> PMaybe a))
-> ClosedTerm (a :--> PMaybe a) -> Term s (a :--> PMaybe a)
forall a b. (a -> b) -> a -> b
$ (Term s a -> Term s (PMaybe a)) -> Term s (a :--> PMaybe 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 (PMaybe a)) -> Term s (c :--> PMaybe a)
plam ((Term s a -> Term s (PMaybe a)) -> Term s (a :--> PMaybe a))
-> (Term s a -> Term s (PMaybe a)) -> Term s (a :--> PMaybe a)
forall a b. (a -> b) -> a -> b
$ PMaybe a s -> Term s (PMaybe a)
forall (a :: S -> Type) (s :: S). PlutusType a => a s -> Term s a
pcon (PMaybe a s -> Term s (PMaybe a))
-> (Term s a -> PMaybe a s) -> Term s a -> Term s (PMaybe a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Term s a -> PMaybe a s
forall (a :: S -> Type) (s :: S). Term s a -> PMaybe a s
PJust
pnothing ::
forall (a :: S -> Type) (s :: S).
Term s (PMaybe a)
pnothing :: forall (a :: S -> Type) (s :: S). Term s (PMaybe a)
pnothing = ClosedTerm (PMaybe a) -> Term s (PMaybe a)
forall (a :: S -> Type) (s :: S).
HasCallStack =>
ClosedTerm a -> Term s a
phoistAcyclic (ClosedTerm (PMaybe a) -> Term s (PMaybe a))
-> ClosedTerm (PMaybe a) -> Term s (PMaybe a)
forall a b. (a -> b) -> a -> b
$ PMaybe a s -> Term s (PMaybe a)
forall (a :: S -> Type) (s :: S). PlutusType a => a s -> Term s a
pcon PMaybe a s
forall (a :: S -> Type) (s :: S). PMaybe a s
PNothing
pmaybe ::
forall (b :: S -> Type) (a :: S -> Type) (s :: S).
Term s (b :--> (a :--> b) :--> PMaybe a :--> b)
pmaybe :: forall (b :: S -> Type) (a :: S -> Type) (s :: S).
Term s (b :--> ((a :--> b) :--> (PMaybe a :--> b)))
pmaybe = ClosedTerm (b :--> ((a :--> b) :--> (PMaybe a :--> b)))
-> Term s (b :--> ((a :--> b) :--> (PMaybe a :--> b)))
forall (a :: S -> Type) (s :: S).
HasCallStack =>
ClosedTerm a -> Term s a
phoistAcyclic (ClosedTerm (b :--> ((a :--> b) :--> (PMaybe a :--> b)))
-> Term s (b :--> ((a :--> b) :--> (PMaybe a :--> b))))
-> ClosedTerm (b :--> ((a :--> b) :--> (PMaybe a :--> b)))
-> Term s (b :--> ((a :--> b) :--> (PMaybe a :--> b)))
forall a b. (a -> b) -> a -> b
$
(Term s b -> Term s (a :--> b) -> Term s (PMaybe a) -> Term s b)
-> Term s (b :--> ((a :--> b) :--> (PMaybe 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 (a :--> b) -> Term s (PMaybe a) -> Term s b)
-> Term s (c :--> ((a :--> b) :--> (PMaybe a :--> b)))
plam ((Term s b -> Term s (a :--> b) -> Term s (PMaybe a) -> Term s b)
-> Term s (b :--> ((a :--> b) :--> (PMaybe a :--> b))))
-> (Term s b -> Term s (a :--> b) -> Term s (PMaybe a) -> Term s b)
-> Term s (b :--> ((a :--> b) :--> (PMaybe a :--> b)))
forall a b. (a -> b) -> a -> b
$ \Term s b
d Term s (a :--> b)
f -> (Term s (PMaybe a) -> (PMaybe a s -> Term s b) -> Term s b)
-> (PMaybe a s -> Term s b) -> Term s (PMaybe a) -> Term s b
forall a b c. (a -> b -> c) -> b -> a -> c
flip Term s (PMaybe a) -> (PMaybe a 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 ((PMaybe a s -> Term s b) -> Term s (PMaybe a) -> Term s b)
-> (PMaybe a s -> Term s b) -> Term s (PMaybe a) -> Term s b
forall a b. (a -> b) -> a -> b
$ \case
PJust Term s a
v -> Term s (a :--> b)
f Term s (a :--> b) -> Term s a -> Term s b
forall (s :: S) (a :: S -> Type) (b :: S -> Type).
Term s (a :--> b) -> Term s a -> Term s b
# Term s a
v
PMaybe a s
_ -> Term s b
d
passertPJust ::
forall (a :: S -> Type) (s :: S).
Term s (PString :--> PMaybe a :--> a)
passertPJust :: forall (a :: S -> Type) (s :: S).
Term s (PString :--> (PMaybe a :--> a))
passertPJust = ClosedTerm (PString :--> (PMaybe a :--> a))
-> Term s (PString :--> (PMaybe a :--> a))
forall (a :: S -> Type) (s :: S).
HasCallStack =>
ClosedTerm a -> Term s a
phoistAcyclic (ClosedTerm (PString :--> (PMaybe a :--> a))
-> Term s (PString :--> (PMaybe a :--> a)))
-> ClosedTerm (PString :--> (PMaybe a :--> a))
-> Term s (PString :--> (PMaybe a :--> a))
forall a b. (a -> b) -> a -> b
$
(Term s PString -> Term s (PMaybe a) -> Term s a)
-> Term s (PString :--> (PMaybe a :--> 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 (PMaybe a) -> Term s a)
-> Term s (c :--> (PMaybe a :--> a))
plam ((Term s PString -> Term s (PMaybe a) -> Term s a)
-> Term s (PString :--> (PMaybe a :--> a)))
-> (Term s PString -> Term s (PMaybe a) -> Term s a)
-> Term s (PString :--> (PMaybe a :--> a))
forall a b. (a -> b) -> a -> b
$ \Term s PString
emsg Term s (PMaybe a)
mv' -> Term s (PMaybe a) -> (PMaybe a 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 (PMaybe a)
mv' ((PMaybe a s -> Term s a) -> Term s a)
-> (PMaybe a s -> Term s a) -> Term s a
forall a b. (a -> b) -> a -> b
$ \case
PJust Term s a
v -> Term s a
v
PMaybe a s
_ -> Term s PString -> Term s a -> Term s a
forall (a :: S -> Type) (s :: S).
Term s PString -> Term s a -> Term s a
ptraceInfo Term s PString
emsg Term s a
forall (s :: S) (a :: S -> Type). Term s a
perror
pmapMaybe :: Term s ((a :--> b) :--> PMaybe a :--> PMaybe b)
pmapMaybe :: forall (s :: S) (a :: S -> Type) (b :: S -> Type).
Term s ((a :--> b) :--> (PMaybe a :--> PMaybe b))
pmapMaybe = ClosedTerm ((a :--> b) :--> (PMaybe a :--> PMaybe b))
-> Term s ((a :--> b) :--> (PMaybe a :--> PMaybe b))
forall (a :: S -> Type) (s :: S).
HasCallStack =>
ClosedTerm a -> Term s a
phoistAcyclic (ClosedTerm ((a :--> b) :--> (PMaybe a :--> PMaybe b))
-> Term s ((a :--> b) :--> (PMaybe a :--> PMaybe b)))
-> ClosedTerm ((a :--> b) :--> (PMaybe a :--> PMaybe b))
-> Term s ((a :--> b) :--> (PMaybe a :--> PMaybe b))
forall a b. (a -> b) -> a -> b
$
(Term s (a :--> b) -> Term s (PMaybe a) -> Term s (PMaybe b))
-> Term s ((a :--> b) :--> (PMaybe a :--> PMaybe 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 (PMaybe a) -> Term s (PMaybe b))
-> Term s (c :--> (PMaybe a :--> PMaybe b))
plam ((Term s (a :--> b) -> Term s (PMaybe a) -> Term s (PMaybe b))
-> Term s ((a :--> b) :--> (PMaybe a :--> PMaybe b)))
-> (Term s (a :--> b) -> Term s (PMaybe a) -> Term s (PMaybe b))
-> Term s ((a :--> b) :--> (PMaybe a :--> PMaybe b))
forall a b. (a -> b) -> a -> b
$ \Term s (a :--> b)
f Term s (PMaybe a)
mv -> Term s (PMaybe a)
-> (PMaybe a s -> Term s (PMaybe b)) -> Term s (PMaybe 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 (PMaybe a)
mv ((PMaybe a s -> Term s (PMaybe b)) -> Term s (PMaybe b))
-> (PMaybe a s -> Term s (PMaybe b)) -> Term s (PMaybe b)
forall a b. (a -> b) -> a -> b
$ \case
PJust Term s a
v -> Term s (b :--> PMaybe b)
forall (a :: S -> Type) (s :: S). Term s (a :--> PMaybe a)
pjust Term s (b :--> PMaybe b) -> Term s b -> Term s (PMaybe b)
forall (s :: S) (a :: S -> Type) (b :: S -> Type).
Term s (a :--> b) -> Term s a -> Term s b
# (Term s (a :--> b)
f Term s (a :--> b) -> Term s a -> Term s b
forall (s :: S) (a :: S -> Type) (b :: S -> Type).
Term s (a :--> b) -> Term s a -> Term s b
# Term s a
v)
PMaybe a s
PNothing -> Term s (PMaybe b)
forall (a :: S -> Type) (s :: S). Term s (PMaybe a)
pnothing