{-# LANGUAGE PackageImports #-}
{-# LANGUAGE PolyKinds #-}
module Plutarch.Extra.TermCont (
module Extra,
pguardWithC,
pguardShowC,
) where
import "plutarch-extra" Plutarch.Extra.TermCont as Extra (
pguardC,
pguardC',
pletC,
pletFieldsC,
pmatchC,
ptraceC,
ptryFromC,
)
pguardWithC ::
forall (r :: S -> Type) (pt :: S -> Type) (s :: S).
(Term s pt -> Term s PString) ->
(Term s pt -> Term s PBool) ->
Term s pt ->
TermCont @r s ()
pguardWithC :: forall (r :: S -> Type) (pt :: S -> Type) (s :: S).
(Term s pt -> Term s PString)
-> (Term s pt -> Term s PBool) -> Term s pt -> TermCont s ()
pguardWithC Term s pt -> Term s PString
tracer Term s pt -> Term s PBool
checker Term s pt
object =
forall {r :: S -> Type} (s :: S).
Term s PString -> Term s PBool -> TermCont s ()
pguardC (Term s pt -> Term s PString
tracer Term s pt
object) (Term s pt -> Term s PBool
checker Term s pt
object)
{-# DEPRECATED pguardShowC "This is very heavy on-chain." #-}
pguardShowC ::
forall (r :: S -> Type) (pt :: S -> Type) (s :: S).
PShow pt =>
Term s PString ->
(Term s pt -> Term s PBool) ->
Term s pt ->
TermCont @r s ()
pguardShowC :: forall (r :: S -> Type) (pt :: S -> Type) (s :: S).
PShow pt =>
Term s PString
-> (Term s pt -> Term s PBool) -> Term s pt -> TermCont s ()
pguardShowC Term s PString
message =
forall (r :: S -> Type) (pt :: S -> Type) (s :: S).
(Term s pt -> Term s PString)
-> (Term s pt -> Term s PBool) -> Term s pt -> TermCont s ()
pguardWithC (\Term s pt
t -> Term s PString
message forall a. Semigroup a => a -> a -> a
<> Term s PString
" Guarded object was: " forall a. Semigroup a => a -> a -> a
<> forall (a :: S -> Type) (s :: S).
PShow a =>
Term s a -> Term s PString
pshow Term s pt
t)