{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE RoleAnnotations #-}
{-# OPTIONS_GHC -Wno-orphans #-}
module Plutarch.LedgerApi.Value (
PValue (..),
PCurrencySymbol (..),
PTokenName (..),
AmountGuarantees (..),
PLovelace (..),
PAssetClass (..),
padaSymbol,
padaSymbolData,
padaToken,
psingleton,
psingletonData,
pconstantPositiveSingleton,
passertPositive,
passertNonZero,
passertSorted,
pforgetPositive,
pforgetSorted,
pnormalize,
padaOnlyValue,
pnoAdaValue,
pltPositive,
pltNonZero,
pleqPositive,
pleqNonZero,
pcheckBinRel,
pleftBiasedCurrencyUnion,
pleftBiasedTokenUnion,
punionResolvingCollisionsWith,
punionResolvingCollisionsWithData,
pvalueOf,
plovelaceValueOf,
pisAdaOnlyValue,
) where
import Data.ByteString (ByteString)
import Data.Kind (Type)
import GHC.Generics (Generic)
import Generics.SOP qualified as SOP
import Plutarch.LedgerApi.AssocMap qualified as AssocMap
import Plutarch.Prelude hiding (psingleton)
import Plutarch.Prelude qualified as PPrelude
import Plutarch.Unsafe (punsafeCoerce, punsafeDowncast)
import PlutusLedgerApi.V1.Value qualified as PlutusValue
import PlutusLedgerApi.V3 qualified as Plutus
import PlutusTx.Builtins.Internal qualified as PlutusTx
import PlutusTx.Prelude qualified as PlutusTx
newtype PLovelace (s :: S) = PLovelace (Term s PInteger)
deriving stock
(
(forall x. PLovelace s -> Rep (PLovelace s) x)
-> (forall x. Rep (PLovelace s) x -> PLovelace s)
-> Generic (PLovelace s)
forall x. Rep (PLovelace s) x -> PLovelace s
forall x. PLovelace s -> Rep (PLovelace s) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall (s :: S) x. Rep (PLovelace s) x -> PLovelace s
forall (s :: S) x. PLovelace s -> Rep (PLovelace s) x
$cfrom :: forall (s :: S) x. PLovelace s -> Rep (PLovelace s) x
from :: forall x. PLovelace s -> Rep (PLovelace s) x
$cto :: forall (s :: S) x. Rep (PLovelace s) x -> PLovelace s
to :: forall x. Rep (PLovelace s) x -> PLovelace s
Generic
)
deriving anyclass
(
All SListI (Code (PLovelace s))
All SListI (Code (PLovelace s)) =>
(PLovelace s -> Rep (PLovelace s))
-> (Rep (PLovelace s) -> PLovelace s) -> Generic (PLovelace s)
Rep (PLovelace s) -> PLovelace s
PLovelace s -> Rep (PLovelace s)
forall a.
All SListI (Code a) =>
(a -> Rep a) -> (Rep a -> a) -> Generic a
forall (s :: S). All SListI (Code (PLovelace s))
forall (s :: S). Rep (PLovelace s) -> PLovelace s
forall (s :: S). PLovelace s -> Rep (PLovelace s)
$cfrom :: forall (s :: S). PLovelace s -> Rep (PLovelace s)
from :: PLovelace s -> Rep (PLovelace s)
$cto :: forall (s :: S). Rep (PLovelace s) -> PLovelace s
to :: Rep (PLovelace s) -> PLovelace s
SOP.Generic
,
(forall (s :: S). Term s (PAsData PLovelace) -> Term s PLovelace)
-> (forall (s :: S). Term s PLovelace -> Term s PData)
-> PIsData PLovelace
forall (s :: S). Term s (PAsData PLovelace) -> Term s PLovelace
forall (s :: S). Term s PLovelace -> Term s PData
forall (a :: S -> Type).
(forall (s :: S). Term s (PAsData a) -> Term s a)
-> (forall (s :: S). Term s a -> Term s PData) -> PIsData a
$cpfromDataImpl :: forall (s :: S). Term s (PAsData PLovelace) -> Term s PLovelace
pfromDataImpl :: forall (s :: S). Term s (PAsData PLovelace) -> Term s PLovelace
$cpdataImpl :: forall (s :: S). Term s PLovelace -> Term s PData
pdataImpl :: forall (s :: S). Term s PLovelace -> Term s PData
PIsData
,
(forall (s :: S).
Term s PLovelace -> Term s PLovelace -> Term s PBool)
-> PEq PLovelace
forall (s :: S).
Term s PLovelace -> Term s PLovelace -> Term s PBool
forall (t :: S -> Type).
(forall (s :: S). Term s t -> Term s t -> Term s PBool) -> PEq t
$c#== :: forall (s :: S).
Term s PLovelace -> Term s PLovelace -> Term s PBool
#== :: forall (s :: S).
Term s PLovelace -> Term s PLovelace -> Term s PBool
PEq
,
PEq PLovelace
PEq PLovelace =>
(forall (s :: S).
Term s PLovelace -> Term s PLovelace -> Term s PBool)
-> (forall (s :: S).
Term s PLovelace -> Term s PLovelace -> Term s PBool)
-> (forall (s :: S).
Term s PLovelace -> Term s PLovelace -> Term s PLovelace)
-> (forall (s :: S).
Term s PLovelace -> Term s PLovelace -> Term s PLovelace)
-> POrd PLovelace
forall (s :: S).
Term s PLovelace -> Term s PLovelace -> Term s PBool
forall (s :: S).
Term s PLovelace -> Term s PLovelace -> Term s PLovelace
forall (t :: S -> Type).
PEq t =>
(forall (s :: S). Term s t -> Term s t -> Term s PBool)
-> (forall (s :: S). Term s t -> Term s t -> Term s PBool)
-> (forall (s :: S). Term s t -> Term s t -> Term s t)
-> (forall (s :: S). Term s t -> Term s t -> Term s t)
-> POrd t
$c#<= :: forall (s :: S).
Term s PLovelace -> Term s PLovelace -> Term s PBool
#<= :: forall (s :: S).
Term s PLovelace -> Term s PLovelace -> Term s PBool
$c#< :: forall (s :: S).
Term s PLovelace -> Term s PLovelace -> Term s PBool
#< :: forall (s :: S).
Term s PLovelace -> Term s PLovelace -> Term s PBool
$cpmax :: forall (s :: S).
Term s PLovelace -> Term s PLovelace -> Term s PLovelace
pmax :: forall (s :: S).
Term s PLovelace -> Term s PLovelace -> Term s PLovelace
$cpmin :: forall (s :: S).
Term s PLovelace -> Term s PLovelace -> Term s PLovelace
pmin :: forall (s :: S).
Term s PLovelace -> Term s PLovelace -> Term s PLovelace
POrd
,
(forall (s :: S). Bool -> Term s PLovelace -> Term s PString)
-> PShow PLovelace
forall (s :: S). Bool -> Term s PLovelace -> Term s PString
forall (t :: S -> Type).
(forall (s :: S). Bool -> Term s t -> Term s PString) -> PShow t
$cpshow' :: forall (s :: S). Bool -> Term s PLovelace -> Term s PString
pshow' :: forall (s :: S). Bool -> Term s PLovelace -> Term s PString
PShow
)
deriving
(
(forall (s :: S). PLovelace s -> Term s (PInner PLovelace))
-> (forall (s :: S) (b :: S -> Type).
Term s (PInner PLovelace) -> (PLovelace s -> Term s b) -> Term s b)
-> PlutusType PLovelace
forall (s :: S). PLovelace s -> Term s (PInner PLovelace)
forall (s :: S) (b :: S -> Type).
Term s (PInner PLovelace) -> (PLovelace s -> Term s b) -> Term s b
forall (a :: S -> Type).
(forall (s :: S). a s -> Term s (PInner a))
-> (forall (s :: S) (b :: S -> Type).
Term s (PInner a) -> (a s -> Term s b) -> Term s b)
-> PlutusType a
$cpcon' :: forall (s :: S). PLovelace s -> Term s (PInner PLovelace)
pcon' :: forall (s :: S). PLovelace s -> Term s (PInner PLovelace)
$cpmatch' :: forall (s :: S) (b :: S -> Type).
Term s (PInner PLovelace) -> (PLovelace s -> Term s b) -> Term s b
pmatch' :: forall (s :: S) (b :: S -> Type).
Term s (PInner PLovelace) -> (PLovelace s -> Term s b) -> Term s b
PlutusType
)
via (DeriveNewtypePlutusType PLovelace)
deriving via
DeriveNewtypePLiftable PLovelace Plutus.Lovelace
instance
PLiftable PLovelace
newtype PTokenName (s :: S) = PTokenName (Term s PByteString)
deriving stock
(
(forall x. PTokenName s -> Rep (PTokenName s) x)
-> (forall x. Rep (PTokenName s) x -> PTokenName s)
-> Generic (PTokenName s)
forall x. Rep (PTokenName s) x -> PTokenName s
forall x. PTokenName s -> Rep (PTokenName s) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall (s :: S) x. Rep (PTokenName s) x -> PTokenName s
forall (s :: S) x. PTokenName s -> Rep (PTokenName s) x
$cfrom :: forall (s :: S) x. PTokenName s -> Rep (PTokenName s) x
from :: forall x. PTokenName s -> Rep (PTokenName s) x
$cto :: forall (s :: S) x. Rep (PTokenName s) x -> PTokenName s
to :: forall x. Rep (PTokenName s) x -> PTokenName s
Generic
)
deriving anyclass
(
All SListI (Code (PTokenName s))
All SListI (Code (PTokenName s)) =>
(PTokenName s -> Rep (PTokenName s))
-> (Rep (PTokenName s) -> PTokenName s) -> Generic (PTokenName s)
Rep (PTokenName s) -> PTokenName s
PTokenName s -> Rep (PTokenName s)
forall a.
All SListI (Code a) =>
(a -> Rep a) -> (Rep a -> a) -> Generic a
forall (s :: S). All SListI (Code (PTokenName s))
forall (s :: S). Rep (PTokenName s) -> PTokenName s
forall (s :: S). PTokenName s -> Rep (PTokenName s)
$cfrom :: forall (s :: S). PTokenName s -> Rep (PTokenName s)
from :: PTokenName s -> Rep (PTokenName s)
$cto :: forall (s :: S). Rep (PTokenName s) -> PTokenName s
to :: Rep (PTokenName s) -> PTokenName s
SOP.Generic
,
(forall (s :: S). Term s (PAsData PTokenName) -> Term s PTokenName)
-> (forall (s :: S). Term s PTokenName -> Term s PData)
-> PIsData PTokenName
forall (s :: S). Term s (PAsData PTokenName) -> Term s PTokenName
forall (s :: S). Term s PTokenName -> Term s PData
forall (a :: S -> Type).
(forall (s :: S). Term s (PAsData a) -> Term s a)
-> (forall (s :: S). Term s a -> Term s PData) -> PIsData a
$cpfromDataImpl :: forall (s :: S). Term s (PAsData PTokenName) -> Term s PTokenName
pfromDataImpl :: forall (s :: S). Term s (PAsData PTokenName) -> Term s PTokenName
$cpdataImpl :: forall (s :: S). Term s PTokenName -> Term s PData
pdataImpl :: forall (s :: S). Term s PTokenName -> Term s PData
PIsData
,
(forall (s :: S).
Term s PTokenName -> Term s PTokenName -> Term s PBool)
-> PEq PTokenName
forall (s :: S).
Term s PTokenName -> Term s PTokenName -> Term s PBool
forall (t :: S -> Type).
(forall (s :: S). Term s t -> Term s t -> Term s PBool) -> PEq t
$c#== :: forall (s :: S).
Term s PTokenName -> Term s PTokenName -> Term s PBool
#== :: forall (s :: S).
Term s PTokenName -> Term s PTokenName -> Term s PBool
PEq
,
PEq PTokenName
PEq PTokenName =>
(forall (s :: S).
Term s PTokenName -> Term s PTokenName -> Term s PBool)
-> (forall (s :: S).
Term s PTokenName -> Term s PTokenName -> Term s PBool)
-> (forall (s :: S).
Term s PTokenName -> Term s PTokenName -> Term s PTokenName)
-> (forall (s :: S).
Term s PTokenName -> Term s PTokenName -> Term s PTokenName)
-> POrd PTokenName
forall (s :: S).
Term s PTokenName -> Term s PTokenName -> Term s PBool
forall (s :: S).
Term s PTokenName -> Term s PTokenName -> Term s PTokenName
forall (t :: S -> Type).
PEq t =>
(forall (s :: S). Term s t -> Term s t -> Term s PBool)
-> (forall (s :: S). Term s t -> Term s t -> Term s PBool)
-> (forall (s :: S). Term s t -> Term s t -> Term s t)
-> (forall (s :: S). Term s t -> Term s t -> Term s t)
-> POrd t
$c#<= :: forall (s :: S).
Term s PTokenName -> Term s PTokenName -> Term s PBool
#<= :: forall (s :: S).
Term s PTokenName -> Term s PTokenName -> Term s PBool
$c#< :: forall (s :: S).
Term s PTokenName -> Term s PTokenName -> Term s PBool
#< :: forall (s :: S).
Term s PTokenName -> Term s PTokenName -> Term s PBool
$cpmax :: forall (s :: S).
Term s PTokenName -> Term s PTokenName -> Term s PTokenName
pmax :: forall (s :: S).
Term s PTokenName -> Term s PTokenName -> Term s PTokenName
$cpmin :: forall (s :: S).
Term s PTokenName -> Term s PTokenName -> Term s PTokenName
pmin :: forall (s :: S).
Term s PTokenName -> Term s PTokenName -> Term s PTokenName
POrd
,
(forall (s :: S). Bool -> Term s PTokenName -> Term s PString)
-> PShow PTokenName
forall (s :: S). Bool -> Term s PTokenName -> Term s PString
forall (t :: S -> Type).
(forall (s :: S). Bool -> Term s t -> Term s PString) -> PShow t
$cpshow' :: forall (s :: S). Bool -> Term s PTokenName -> Term s PString
pshow' :: forall (s :: S). Bool -> Term s PTokenName -> Term s PString
PShow
)
deriving
(
(forall (s :: S). PTokenName s -> Term s (PInner PTokenName))
-> (forall (s :: S) (b :: S -> Type).
Term s (PInner PTokenName)
-> (PTokenName s -> Term s b) -> Term s b)
-> PlutusType PTokenName
forall (s :: S). PTokenName s -> Term s (PInner PTokenName)
forall (s :: S) (b :: S -> Type).
Term s (PInner PTokenName)
-> (PTokenName s -> Term s b) -> Term s b
forall (a :: S -> Type).
(forall (s :: S). a s -> Term s (PInner a))
-> (forall (s :: S) (b :: S -> Type).
Term s (PInner a) -> (a s -> Term s b) -> Term s b)
-> PlutusType a
$cpcon' :: forall (s :: S). PTokenName s -> Term s (PInner PTokenName)
pcon' :: forall (s :: S). PTokenName s -> Term s (PInner PTokenName)
$cpmatch' :: forall (s :: S) (b :: S -> Type).
Term s (PInner PTokenName)
-> (PTokenName s -> Term s b) -> Term s b
pmatch' :: forall (s :: S) (b :: S -> Type).
Term s (PInner PTokenName)
-> (PTokenName s -> Term s b) -> Term s b
PlutusType
)
via (DeriveNewtypePlutusType PTokenName)
instance PLiftable PTokenName where
type AsHaskell PTokenName = Plutus.TokenName
type PlutusRepr PTokenName = ByteString
{-# INLINEABLE haskToRepr #-}
haskToRepr :: AsHaskell PTokenName -> PlutusRepr PTokenName
haskToRepr (Plutus.TokenName (PlutusTx.BuiltinByteString ByteString
str)) = ByteString
PlutusRepr PTokenName
str
{-# INLINEABLE reprToHask #-}
reprToHask :: PlutusRepr PTokenName -> Either LiftError (AsHaskell PTokenName)
reprToHask = TokenName -> Either LiftError TokenName
forall a b. b -> Either a b
Right (TokenName -> Either LiftError TokenName)
-> (ByteString -> TokenName)
-> ByteString
-> Either LiftError TokenName
forall b c a. (b -> c) -> (a -> b) -> a -> c
. BuiltinByteString -> TokenName
Plutus.TokenName (BuiltinByteString -> TokenName)
-> (ByteString -> BuiltinByteString) -> ByteString -> TokenName
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> BuiltinByteString
PlutusTx.BuiltinByteString
{-# INLINEABLE reprToPlut #-}
reprToPlut :: forall (s :: S). PlutusRepr PTokenName -> PLifted s PTokenName
reprToPlut = PlutusRepr PTokenName -> PLifted s PTokenName
forall (a :: S -> Type) (s :: S).
(PLiftable a, Includes DefaultUni (PlutusRepr a)) =>
PlutusRepr a -> PLifted s a
reprToPlutUni
{-# INLINEABLE plutToRepr #-}
plutToRepr :: (forall (s :: S). PLifted s PTokenName)
-> Either LiftError (PlutusRepr PTokenName)
plutToRepr = (forall (s :: S). PLifted s PTokenName)
-> Either LiftError (PlutusRepr PTokenName)
forall (a :: S -> Type).
(PLiftable a, Includes DefaultUni (PlutusRepr a)) =>
(forall (s :: S). PLifted s a) -> Either LiftError (PlutusRepr a)
plutToReprUni
newtype PCurrencySymbol (s :: S) = PCurrencySymbol (Term s PByteString)
deriving stock
(
(forall x. PCurrencySymbol s -> Rep (PCurrencySymbol s) x)
-> (forall x. Rep (PCurrencySymbol s) x -> PCurrencySymbol s)
-> Generic (PCurrencySymbol s)
forall x. Rep (PCurrencySymbol s) x -> PCurrencySymbol s
forall x. PCurrencySymbol s -> Rep (PCurrencySymbol s) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall (s :: S) x. Rep (PCurrencySymbol s) x -> PCurrencySymbol s
forall (s :: S) x. PCurrencySymbol s -> Rep (PCurrencySymbol s) x
$cfrom :: forall (s :: S) x. PCurrencySymbol s -> Rep (PCurrencySymbol s) x
from :: forall x. PCurrencySymbol s -> Rep (PCurrencySymbol s) x
$cto :: forall (s :: S) x. Rep (PCurrencySymbol s) x -> PCurrencySymbol s
to :: forall x. Rep (PCurrencySymbol s) x -> PCurrencySymbol s
Generic
)
deriving anyclass
(
All SListI (Code (PCurrencySymbol s))
All SListI (Code (PCurrencySymbol s)) =>
(PCurrencySymbol s -> Rep (PCurrencySymbol s))
-> (Rep (PCurrencySymbol s) -> PCurrencySymbol s)
-> Generic (PCurrencySymbol s)
Rep (PCurrencySymbol s) -> PCurrencySymbol s
PCurrencySymbol s -> Rep (PCurrencySymbol s)
forall a.
All SListI (Code a) =>
(a -> Rep a) -> (Rep a -> a) -> Generic a
forall (s :: S). All SListI (Code (PCurrencySymbol s))
forall (s :: S). Rep (PCurrencySymbol s) -> PCurrencySymbol s
forall (s :: S). PCurrencySymbol s -> Rep (PCurrencySymbol s)
$cfrom :: forall (s :: S). PCurrencySymbol s -> Rep (PCurrencySymbol s)
from :: PCurrencySymbol s -> Rep (PCurrencySymbol s)
$cto :: forall (s :: S). Rep (PCurrencySymbol s) -> PCurrencySymbol s
to :: Rep (PCurrencySymbol s) -> PCurrencySymbol s
SOP.Generic
,
(forall (s :: S).
Term s (PAsData PCurrencySymbol) -> Term s PCurrencySymbol)
-> (forall (s :: S). Term s PCurrencySymbol -> Term s PData)
-> PIsData PCurrencySymbol
forall (s :: S).
Term s (PAsData PCurrencySymbol) -> Term s PCurrencySymbol
forall (s :: S). Term s PCurrencySymbol -> Term s PData
forall (a :: S -> Type).
(forall (s :: S). Term s (PAsData a) -> Term s a)
-> (forall (s :: S). Term s a -> Term s PData) -> PIsData a
$cpfromDataImpl :: forall (s :: S).
Term s (PAsData PCurrencySymbol) -> Term s PCurrencySymbol
pfromDataImpl :: forall (s :: S).
Term s (PAsData PCurrencySymbol) -> Term s PCurrencySymbol
$cpdataImpl :: forall (s :: S). Term s PCurrencySymbol -> Term s PData
pdataImpl :: forall (s :: S). Term s PCurrencySymbol -> Term s PData
PIsData
,
(forall (s :: S).
Term s PCurrencySymbol -> Term s PCurrencySymbol -> Term s PBool)
-> PEq PCurrencySymbol
forall (s :: S).
Term s PCurrencySymbol -> Term s PCurrencySymbol -> Term s PBool
forall (t :: S -> Type).
(forall (s :: S). Term s t -> Term s t -> Term s PBool) -> PEq t
$c#== :: forall (s :: S).
Term s PCurrencySymbol -> Term s PCurrencySymbol -> Term s PBool
#== :: forall (s :: S).
Term s PCurrencySymbol -> Term s PCurrencySymbol -> Term s PBool
PEq
,
PEq PCurrencySymbol
PEq PCurrencySymbol =>
(forall (s :: S).
Term s PCurrencySymbol -> Term s PCurrencySymbol -> Term s PBool)
-> (forall (s :: S).
Term s PCurrencySymbol -> Term s PCurrencySymbol -> Term s PBool)
-> (forall (s :: S).
Term s PCurrencySymbol
-> Term s PCurrencySymbol -> Term s PCurrencySymbol)
-> (forall (s :: S).
Term s PCurrencySymbol
-> Term s PCurrencySymbol -> Term s PCurrencySymbol)
-> POrd PCurrencySymbol
forall (s :: S).
Term s PCurrencySymbol -> Term s PCurrencySymbol -> Term s PBool
forall (s :: S).
Term s PCurrencySymbol
-> Term s PCurrencySymbol -> Term s PCurrencySymbol
forall (t :: S -> Type).
PEq t =>
(forall (s :: S). Term s t -> Term s t -> Term s PBool)
-> (forall (s :: S). Term s t -> Term s t -> Term s PBool)
-> (forall (s :: S). Term s t -> Term s t -> Term s t)
-> (forall (s :: S). Term s t -> Term s t -> Term s t)
-> POrd t
$c#<= :: forall (s :: S).
Term s PCurrencySymbol -> Term s PCurrencySymbol -> Term s PBool
#<= :: forall (s :: S).
Term s PCurrencySymbol -> Term s PCurrencySymbol -> Term s PBool
$c#< :: forall (s :: S).
Term s PCurrencySymbol -> Term s PCurrencySymbol -> Term s PBool
#< :: forall (s :: S).
Term s PCurrencySymbol -> Term s PCurrencySymbol -> Term s PBool
$cpmax :: forall (s :: S).
Term s PCurrencySymbol
-> Term s PCurrencySymbol -> Term s PCurrencySymbol
pmax :: forall (s :: S).
Term s PCurrencySymbol
-> Term s PCurrencySymbol -> Term s PCurrencySymbol
$cpmin :: forall (s :: S).
Term s PCurrencySymbol
-> Term s PCurrencySymbol -> Term s PCurrencySymbol
pmin :: forall (s :: S).
Term s PCurrencySymbol
-> Term s PCurrencySymbol -> Term s PCurrencySymbol
POrd
,
(forall (s :: S). Bool -> Term s PCurrencySymbol -> Term s PString)
-> PShow PCurrencySymbol
forall (s :: S). Bool -> Term s PCurrencySymbol -> Term s PString
forall (t :: S -> Type).
(forall (s :: S). Bool -> Term s t -> Term s PString) -> PShow t
$cpshow' :: forall (s :: S). Bool -> Term s PCurrencySymbol -> Term s PString
pshow' :: forall (s :: S). Bool -> Term s PCurrencySymbol -> Term s PString
PShow
)
deriving
(
(forall (s :: S).
PCurrencySymbol s -> Term s (PInner PCurrencySymbol))
-> (forall (s :: S) (b :: S -> Type).
Term s (PInner PCurrencySymbol)
-> (PCurrencySymbol s -> Term s b) -> Term s b)
-> PlutusType PCurrencySymbol
forall (s :: S).
PCurrencySymbol s -> Term s (PInner PCurrencySymbol)
forall (s :: S) (b :: S -> Type).
Term s (PInner PCurrencySymbol)
-> (PCurrencySymbol s -> Term s b) -> Term s b
forall (a :: S -> Type).
(forall (s :: S). a s -> Term s (PInner a))
-> (forall (s :: S) (b :: S -> Type).
Term s (PInner a) -> (a s -> Term s b) -> Term s b)
-> PlutusType a
$cpcon' :: forall (s :: S).
PCurrencySymbol s -> Term s (PInner PCurrencySymbol)
pcon' :: forall (s :: S).
PCurrencySymbol s -> Term s (PInner PCurrencySymbol)
$cpmatch' :: forall (s :: S) (b :: S -> Type).
Term s (PInner PCurrencySymbol)
-> (PCurrencySymbol s -> Term s b) -> Term s b
pmatch' :: forall (s :: S) (b :: S -> Type).
Term s (PInner PCurrencySymbol)
-> (PCurrencySymbol s -> Term s b) -> Term s b
PlutusType
)
via (DeriveNewtypePlutusType PTokenName)
instance PLiftable PCurrencySymbol where
type AsHaskell PCurrencySymbol = Plutus.CurrencySymbol
type PlutusRepr PCurrencySymbol = ByteString
{-# INLINEABLE haskToRepr #-}
haskToRepr :: AsHaskell PCurrencySymbol -> PlutusRepr PCurrencySymbol
haskToRepr (Plutus.CurrencySymbol (PlutusTx.BuiltinByteString ByteString
str)) = ByteString
PlutusRepr PCurrencySymbol
str
{-# INLINEABLE reprToHask #-}
reprToHask :: PlutusRepr PCurrencySymbol
-> Either LiftError (AsHaskell PCurrencySymbol)
reprToHask = CurrencySymbol -> Either LiftError CurrencySymbol
forall a b. b -> Either a b
Right (CurrencySymbol -> Either LiftError CurrencySymbol)
-> (ByteString -> CurrencySymbol)
-> ByteString
-> Either LiftError CurrencySymbol
forall b c a. (b -> c) -> (a -> b) -> a -> c
. BuiltinByteString -> CurrencySymbol
Plutus.CurrencySymbol (BuiltinByteString -> CurrencySymbol)
-> (ByteString -> BuiltinByteString)
-> ByteString
-> CurrencySymbol
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> BuiltinByteString
PlutusTx.BuiltinByteString
{-# INLINEABLE reprToPlut #-}
reprToPlut :: forall (s :: S).
PlutusRepr PCurrencySymbol -> PLifted s PCurrencySymbol
reprToPlut = PlutusRepr PCurrencySymbol -> PLifted s PCurrencySymbol
forall (a :: S -> Type) (s :: S).
(PLiftable a, Includes DefaultUni (PlutusRepr a)) =>
PlutusRepr a -> PLifted s a
reprToPlutUni
{-# INLINEABLE plutToRepr #-}
plutToRepr :: (forall (s :: S). PLifted s PCurrencySymbol)
-> Either LiftError (PlutusRepr PCurrencySymbol)
plutToRepr = (forall (s :: S). PLifted s PCurrencySymbol)
-> Either LiftError (PlutusRepr PCurrencySymbol)
forall (a :: S -> Type).
(PLiftable a, Includes DefaultUni (PlutusRepr a)) =>
(forall (s :: S). PLifted s a) -> Either LiftError (PlutusRepr a)
plutToReprUni
data AmountGuarantees = NoGuarantees | NonZero | Positive
newtype PValue (keys :: AssocMap.KeyGuarantees) (amounts :: AmountGuarantees) (s :: S)
= PValue (Term s (AssocMap.PMap keys PCurrencySymbol (AssocMap.PMap keys PTokenName PInteger)))
deriving stock
(
(forall x. PValue keys amounts s -> Rep (PValue keys amounts s) x)
-> (forall x.
Rep (PValue keys amounts s) x -> PValue keys amounts s)
-> Generic (PValue keys amounts s)
forall x. Rep (PValue keys amounts s) x -> PValue keys amounts s
forall x. PValue keys amounts s -> Rep (PValue keys amounts s) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall (keys :: KeyGuarantees) (amounts :: AmountGuarantees)
(s :: S) x.
Rep (PValue keys amounts s) x -> PValue keys amounts s
forall (keys :: KeyGuarantees) (amounts :: AmountGuarantees)
(s :: S) x.
PValue keys amounts s -> Rep (PValue keys amounts s) x
$cfrom :: forall (keys :: KeyGuarantees) (amounts :: AmountGuarantees)
(s :: S) x.
PValue keys amounts s -> Rep (PValue keys amounts s) x
from :: forall x. PValue keys amounts s -> Rep (PValue keys amounts s) x
$cto :: forall (keys :: KeyGuarantees) (amounts :: AmountGuarantees)
(s :: S) x.
Rep (PValue keys amounts s) x -> PValue keys amounts s
to :: forall x. Rep (PValue keys amounts s) x -> PValue keys amounts s
Generic
)
deriving anyclass
(
All SListI (Code (PValue keys amounts s))
All SListI (Code (PValue keys amounts s)) =>
(PValue keys amounts s -> Rep (PValue keys amounts s))
-> (Rep (PValue keys amounts s) -> PValue keys amounts s)
-> Generic (PValue keys amounts s)
Rep (PValue keys amounts s) -> PValue keys amounts s
PValue keys amounts s -> Rep (PValue keys amounts s)
forall a.
All SListI (Code a) =>
(a -> Rep a) -> (Rep a -> a) -> Generic a
forall (keys :: KeyGuarantees) (amounts :: AmountGuarantees)
(s :: S).
All SListI (Code (PValue keys amounts s))
forall (keys :: KeyGuarantees) (amounts :: AmountGuarantees)
(s :: S).
Rep (PValue keys amounts s) -> PValue keys amounts s
forall (keys :: KeyGuarantees) (amounts :: AmountGuarantees)
(s :: S).
PValue keys amounts s -> Rep (PValue keys amounts s)
$cfrom :: forall (keys :: KeyGuarantees) (amounts :: AmountGuarantees)
(s :: S).
PValue keys amounts s -> Rep (PValue keys amounts s)
from :: PValue keys amounts s -> Rep (PValue keys amounts s)
$cto :: forall (keys :: KeyGuarantees) (amounts :: AmountGuarantees)
(s :: S).
Rep (PValue keys amounts s) -> PValue keys amounts s
to :: Rep (PValue keys amounts s) -> PValue keys amounts s
SOP.Generic
,
(forall (s :: S).
Term s (PAsData (PValue keys amounts))
-> Term s (PValue keys amounts))
-> (forall (s :: S). Term s (PValue keys amounts) -> Term s PData)
-> PIsData (PValue keys amounts)
forall (s :: S).
Term s (PAsData (PValue keys amounts))
-> Term s (PValue keys amounts)
forall (s :: S). Term s (PValue keys amounts) -> Term s PData
forall (keys :: KeyGuarantees) (amounts :: AmountGuarantees)
(s :: S).
Term s (PAsData (PValue keys amounts))
-> Term s (PValue keys amounts)
forall (keys :: KeyGuarantees) (amounts :: AmountGuarantees)
(s :: S).
Term s (PValue keys amounts) -> Term s PData
forall (a :: S -> Type).
(forall (s :: S). Term s (PAsData a) -> Term s a)
-> (forall (s :: S). Term s a -> Term s PData) -> PIsData a
$cpfromDataImpl :: forall (keys :: KeyGuarantees) (amounts :: AmountGuarantees)
(s :: S).
Term s (PAsData (PValue keys amounts))
-> Term s (PValue keys amounts)
pfromDataImpl :: forall (s :: S).
Term s (PAsData (PValue keys amounts))
-> Term s (PValue keys amounts)
$cpdataImpl :: forall (keys :: KeyGuarantees) (amounts :: AmountGuarantees)
(s :: S).
Term s (PValue keys amounts) -> Term s PData
pdataImpl :: forall (s :: S). Term s (PValue keys amounts) -> Term s PData
PIsData
,
(forall (s :: S).
Bool -> Term s (PValue keys amounts) -> Term s PString)
-> PShow (PValue keys amounts)
forall (s :: S).
Bool -> Term s (PValue keys amounts) -> Term s PString
forall (keys :: KeyGuarantees) (amounts :: AmountGuarantees)
(s :: S).
Bool -> Term s (PValue keys amounts) -> Term s PString
forall (t :: S -> Type).
(forall (s :: S). Bool -> Term s t -> Term s PString) -> PShow t
$cpshow' :: forall (keys :: KeyGuarantees) (amounts :: AmountGuarantees)
(s :: S).
Bool -> Term s (PValue keys amounts) -> Term s PString
pshow' :: forall (s :: S).
Bool -> Term s (PValue keys amounts) -> Term s PString
PShow
)
deriving
(
(forall (s :: S).
PValue keys amounts s -> Term s (PInner (PValue keys amounts)))
-> (forall (s :: S) (b :: S -> Type).
Term s (PInner (PValue keys amounts))
-> (PValue keys amounts s -> Term s b) -> Term s b)
-> PlutusType (PValue keys amounts)
forall (s :: S).
PValue keys amounts s -> Term s (PInner (PValue keys amounts))
forall (s :: S) (b :: S -> Type).
Term s (PInner (PValue keys amounts))
-> (PValue keys amounts s -> Term s b) -> Term s b
forall (keys :: KeyGuarantees) (amounts :: AmountGuarantees)
(s :: S).
PValue keys amounts s -> Term s (PInner (PValue keys amounts))
forall (keys :: KeyGuarantees) (amounts :: AmountGuarantees)
(s :: S) (b :: S -> Type).
Term s (PInner (PValue keys amounts))
-> (PValue keys amounts s -> Term s b) -> Term s b
forall (a :: S -> Type).
(forall (s :: S). a s -> Term s (PInner a))
-> (forall (s :: S) (b :: S -> Type).
Term s (PInner a) -> (a s -> Term s b) -> Term s b)
-> PlutusType a
$cpcon' :: forall (keys :: KeyGuarantees) (amounts :: AmountGuarantees)
(s :: S).
PValue keys amounts s -> Term s (PInner (PValue keys amounts))
pcon' :: forall (s :: S).
PValue keys amounts s -> Term s (PInner (PValue keys amounts))
$cpmatch' :: forall (keys :: KeyGuarantees) (amounts :: AmountGuarantees)
(s :: S) (b :: S -> Type).
Term s (PInner (PValue keys amounts))
-> (PValue keys amounts s -> Term s b) -> Term s b
pmatch' :: forall (s :: S) (b :: S -> Type).
Term s (PInner (PValue keys amounts))
-> (PValue keys amounts s -> Term s b) -> Term s b
PlutusType
)
via (DeriveNewtypePlutusType (PValue keys amounts))
type role PValue nominal nominal nominal
deriving via
DeriveNewtypePLiftable
(PValue 'AssocMap.Unsorted 'NoGuarantees)
Plutus.Value
instance
PLiftable (PValue 'AssocMap.Unsorted 'NoGuarantees)
instance PEq (PValue 'AssocMap.Sorted 'Positive) where
Term s (PValue 'Sorted 'Positive)
a #== :: forall (s :: S).
Term s (PValue 'Sorted 'Positive)
-> Term s (PValue 'Sorted 'Positive) -> Term s PBool
#== Term s (PValue 'Sorted 'Positive)
b = Term s (PValue 'Sorted 'Positive)
-> Term s (PInner (PValue 'Sorted 'Positive))
forall (s :: S) (a :: S -> Type). Term s a -> Term s (PInner a)
pto Term s (PValue 'Sorted 'Positive)
a Term
s (PMap 'Sorted PCurrencySymbol (PMap 'Sorted PTokenName PInteger))
-> Term
s (PMap 'Sorted PCurrencySymbol (PMap 'Sorted PTokenName PInteger))
-> Term s PBool
forall (s :: S).
Term
s (PMap 'Sorted PCurrencySymbol (PMap 'Sorted PTokenName PInteger))
-> Term
s (PMap 'Sorted PCurrencySymbol (PMap 'Sorted PTokenName PInteger))
-> Term s PBool
forall (t :: S -> Type) (s :: S).
PEq t =>
Term s t -> Term s t -> Term s PBool
#== Term s (PValue 'Sorted 'Positive)
-> Term s (PInner (PValue 'Sorted 'Positive))
forall (s :: S) (a :: S -> Type). Term s a -> Term s (PInner a)
pto Term s (PValue 'Sorted 'Positive)
b
instance PEq (PValue 'AssocMap.Sorted 'NonZero) where
Term s (PValue 'Sorted 'NonZero)
a #== :: forall (s :: S).
Term s (PValue 'Sorted 'NonZero)
-> Term s (PValue 'Sorted 'NonZero) -> Term s PBool
#== Term s (PValue 'Sorted 'NonZero)
b = Term s (PValue 'Sorted 'NonZero)
-> Term s (PInner (PValue 'Sorted 'NonZero))
forall (s :: S) (a :: S -> Type). Term s a -> Term s (PInner a)
pto Term s (PValue 'Sorted 'NonZero)
a Term
s (PMap 'Sorted PCurrencySymbol (PMap 'Sorted PTokenName PInteger))
-> Term
s (PMap 'Sorted PCurrencySymbol (PMap 'Sorted PTokenName PInteger))
-> Term s PBool
forall (s :: S).
Term
s (PMap 'Sorted PCurrencySymbol (PMap 'Sorted PTokenName PInteger))
-> Term
s (PMap 'Sorted PCurrencySymbol (PMap 'Sorted PTokenName PInteger))
-> Term s PBool
forall (t :: S -> Type) (s :: S).
PEq t =>
Term s t -> Term s t -> Term s PBool
#== Term s (PValue 'Sorted 'NonZero)
-> Term s (PInner (PValue 'Sorted 'NonZero))
forall (s :: S) (a :: S -> Type). Term s a -> Term s (PInner a)
pto Term s (PValue 'Sorted 'NonZero)
b
pltPositive ::
forall (s :: S).
Term s (PValue 'AssocMap.Sorted 'Positive) ->
Term s (PValue 'AssocMap.Sorted 'Positive) ->
Term s PBool
pltPositive :: forall (s :: S).
Term s (PValue 'Sorted 'Positive)
-> Term s (PValue 'Sorted 'Positive) -> Term s PBool
pltPositive Term s (PValue 'Sorted 'Positive)
t1 Term s (PValue 'Sorted 'Positive)
t2 = Term s (PValue 'Sorted 'NonZero)
-> Term s (PValue 'Sorted 'NonZero) -> Term s PBool
forall (s :: S).
Term s (PValue 'Sorted 'NonZero)
-> Term s (PValue 'Sorted 'NonZero) -> Term s PBool
pltNonZero (Term s (PValue 'Sorted 'Positive)
-> Term s (PValue 'Sorted 'NonZero)
forall (a :: AmountGuarantees) (k :: KeyGuarantees) (s :: S).
Term s (PValue k 'Positive) -> Term s (PValue k a)
pforgetPositive Term s (PValue 'Sorted 'Positive)
t1) (Term s (PValue 'Sorted 'Positive)
-> Term s (PValue 'Sorted 'NonZero)
forall (a :: AmountGuarantees) (k :: KeyGuarantees) (s :: S).
Term s (PValue k 'Positive) -> Term s (PValue k a)
pforgetPositive Term s (PValue 'Sorted 'Positive)
t2)
pltNonZero ::
forall (s :: S).
Term s (PValue 'AssocMap.Sorted 'NonZero) ->
Term s (PValue 'AssocMap.Sorted 'NonZero) ->
Term s PBool
pltNonZero :: forall (s :: S).
Term s (PValue 'Sorted 'NonZero)
-> Term s (PValue 'Sorted 'NonZero) -> Term s PBool
pltNonZero Term s (PValue 'Sorted 'NonZero)
t1 Term s (PValue 'Sorted 'NonZero)
t2 = Term s (PValue 'Sorted 'NonZero)
-> Term s (PValue 'Sorted 'NonZero) -> Term s PBool
forall (s :: S).
Term s (PValue 'Sorted 'NonZero)
-> Term s (PValue 'Sorted 'NonZero) -> Term s PBool
pleqNonZero Term s (PValue 'Sorted 'NonZero)
t1 Term s (PValue 'Sorted 'NonZero)
t2 Term s PBool -> Term s PBool -> Term s PBool
forall (s :: S). Term s PBool -> Term s PBool -> Term s PBool
#&& (Term s (PBool :--> PBool)
forall (s :: S). Term s (PBool :--> PBool)
pnot Term s (PBool :--> PBool) -> Term s PBool -> Term s PBool
forall (s :: S) (a :: S -> Type) (b :: S -> Type).
Term s (a :--> b) -> Term s a -> Term s b
# (Term s (PValue 'Sorted 'NonZero)
t1 Term s (PValue 'Sorted 'NonZero)
-> Term s (PValue 'Sorted 'NonZero) -> Term s PBool
forall (s :: S).
Term s (PValue 'Sorted 'NonZero)
-> Term s (PValue 'Sorted 'NonZero) -> Term s PBool
forall (t :: S -> Type) (s :: S).
PEq t =>
Term s t -> Term s t -> Term s PBool
#== Term s (PValue 'Sorted 'NonZero)
t2))
pleqPositive ::
forall (s :: S).
Term s (PValue 'AssocMap.Sorted 'Positive) ->
Term s (PValue 'AssocMap.Sorted 'Positive) ->
Term s PBool
pleqPositive :: forall (s :: S).
Term s (PValue 'Sorted 'Positive)
-> Term s (PValue 'Sorted 'Positive) -> Term s PBool
pleqPositive Term s (PValue 'Sorted 'Positive)
t1 Term s (PValue 'Sorted 'Positive)
t2 = Term s (PValue 'Sorted 'NonZero)
-> Term s (PValue 'Sorted 'NonZero) -> Term s PBool
forall (s :: S).
Term s (PValue 'Sorted 'NonZero)
-> Term s (PValue 'Sorted 'NonZero) -> Term s PBool
pleqNonZero (Term s (PValue 'Sorted 'Positive)
-> Term s (PValue 'Sorted 'NonZero)
forall (a :: AmountGuarantees) (k :: KeyGuarantees) (s :: S).
Term s (PValue k 'Positive) -> Term s (PValue k a)
pforgetPositive Term s (PValue 'Sorted 'Positive)
t1) (Term s (PValue 'Sorted 'Positive)
-> Term s (PValue 'Sorted 'NonZero)
forall (a :: AmountGuarantees) (k :: KeyGuarantees) (s :: S).
Term s (PValue k 'Positive) -> Term s (PValue k a)
pforgetPositive Term s (PValue 'Sorted 'Positive)
t2)
pleqNonZero ::
forall (s :: S).
Term s (PValue 'AssocMap.Sorted 'NonZero) ->
Term s (PValue 'AssocMap.Sorted 'NonZero) ->
Term s PBool
pleqNonZero :: forall (s :: S).
Term s (PValue 'Sorted 'NonZero)
-> Term s (PValue 'Sorted 'NonZero) -> Term s PBool
pleqNonZero Term s (PValue 'Sorted 'NonZero)
t1 Term s (PValue 'Sorted 'NonZero)
t2 =
ClosedTerm
(PValue 'Sorted 'NonZero :--> (PValue 'Sorted 'NonZero :--> PBool))
-> Term
s
(PValue 'Sorted 'NonZero :--> (PValue 'Sorted 'NonZero :--> PBool))
forall (a :: S -> Type) (s :: S).
HasCallStack =>
ClosedTerm a -> Term s a
phoistAcyclic (Term
s
((PInteger :--> (PInteger :--> PBool))
:--> (PValue 'Sorted 'NonZero
:--> (PValue 'Sorted 'NonZero :--> PBool)))
forall (any0 :: AmountGuarantees) (any1 :: AmountGuarantees)
(s :: S).
Term
s
((PInteger :--> (PInteger :--> PBool))
:--> (PValue 'Sorted any0 :--> (PValue 'Sorted any1 :--> PBool)))
pcheckBinRel Term
s
((PInteger :--> (PInteger :--> PBool))
:--> (PValue 'Sorted 'NonZero
:--> (PValue 'Sorted 'NonZero :--> PBool)))
-> Term s (PInteger :--> (PInteger :--> PBool))
-> Term
s
(PValue 'Sorted 'NonZero :--> (PValue 'Sorted 'NonZero :--> PBool))
forall (s :: S) (a :: S -> Type) (b :: S -> Type).
Term s (a :--> b) -> Term s a -> Term s b
#$ ClosedTerm (PInteger :--> (PInteger :--> PBool))
-> Term s (PInteger :--> (PInteger :--> PBool))
forall (a :: S -> Type) (s :: S).
HasCallStack =>
ClosedTerm a -> Term s a
phoistAcyclic (ClosedTerm (PInteger :--> (PInteger :--> PBool))
-> Term s (PInteger :--> (PInteger :--> PBool)))
-> ClosedTerm (PInteger :--> (PInteger :--> PBool))
-> Term s (PInteger :--> (PInteger :--> PBool))
forall a b. (a -> b) -> a -> b
$ (Term s PInteger -> Term s PInteger -> Term s PBool)
-> Term s (PInteger :--> (PInteger :--> 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 PInteger -> Term s PBool)
-> Term s (c :--> (PInteger :--> PBool))
plam 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).
POrd t =>
Term s t -> Term s t -> Term s PBool
(#<=)) Term
s
(PValue 'Sorted 'NonZero :--> (PValue 'Sorted 'NonZero :--> PBool))
-> Term s (PValue 'Sorted 'NonZero)
-> Term s (PValue 'Sorted 'NonZero :--> PBool)
forall (s :: S) (a :: S -> Type) (b :: S -> Type).
Term s (a :--> b) -> Term s a -> Term s b
# Term s (PValue 'Sorted 'NonZero)
t1 Term s (PValue 'Sorted 'NonZero :--> PBool)
-> Term s (PValue 'Sorted 'NonZero) -> Term s PBool
forall (s :: S) (a :: S -> Type) (b :: S -> Type).
Term s (a :--> b) -> Term s a -> Term s b
# Term s (PValue 'Sorted 'NonZero)
t2
instance PEq (PValue 'AssocMap.Sorted 'NoGuarantees) where
Term s (PValue 'Sorted 'NoGuarantees)
a #== :: forall (s :: S).
Term s (PValue 'Sorted 'NoGuarantees)
-> Term s (PValue 'Sorted 'NoGuarantees) -> Term s PBool
#== Term s (PValue 'Sorted 'NoGuarantees)
b =
Term
s
((PMap 'Sorted PTokenName PInteger :--> PBool)
:--> (PMap
'Sorted PCurrencySymbol (PMap 'Sorted PTokenName PInteger)
:--> PBool))
forall (any :: KeyGuarantees) (k :: S -> Type) (v :: S -> Type)
(s :: S).
PIsData v =>
Term s ((v :--> PBool) :--> (PMap any k v :--> PBool))
AssocMap.pall
# (AssocMap.pall # plam (#== 0))
# pto (punionResolvingCollisionsWith AssocMap.Commutative # plam (-) # a # b)
instance PSemigroup (PValue 'AssocMap.Sorted 'Positive) where
{-# INLINEABLE (#<>) #-}
#<> :: forall (s :: S).
Term s (PValue 'Sorted 'Positive)
-> Term s (PValue 'Sorted 'Positive)
-> Term s (PValue 'Sorted 'Positive)
(#<>) = Term s (PValue 'Sorted 'Positive)
-> Term s (PValue 'Sorted 'Positive)
-> Term s (PValue 'Sorted 'Positive)
forall a. Semigroup a => a -> a -> a
(<>)
instance Semigroup (Term s (PValue 'AssocMap.Sorted 'Positive)) where
Term s (PValue 'Sorted 'Positive)
a <> :: Term s (PValue 'Sorted 'Positive)
-> Term s (PValue 'Sorted 'Positive)
-> Term s (PValue 'Sorted 'Positive)
<> Term s (PValue 'Sorted 'Positive)
b =
Term s (PInner (PValue 'Sorted 'Positive))
-> Term s (PValue 'Sorted 'Positive)
forall (s :: S) (a :: S -> Type). Term s (PInner a) -> Term s a
punsafeDowncast (Term s (PValue 'Sorted 'NoGuarantees)
-> Term s (PInner (PValue 'Sorted 'NoGuarantees))
forall (s :: S) (a :: S -> Type). Term s a -> Term s (PInner a)
pto (Term s (PValue 'Sorted 'NoGuarantees)
-> Term s (PInner (PValue 'Sorted 'NoGuarantees)))
-> Term s (PValue 'Sorted 'NoGuarantees)
-> Term s (PInner (PValue 'Sorted 'NoGuarantees))
forall a b. (a -> b) -> a -> b
$ Commutativity
-> Term
s
((PInteger :--> (PInteger :--> PInteger))
:--> (PValue 'Sorted 'Positive
:--> (PValue 'Sorted 'Positive :--> PValue 'Sorted 'NoGuarantees)))
forall (any0 :: AmountGuarantees) (any1 :: AmountGuarantees)
(s :: S).
Commutativity
-> Term
s
((PInteger :--> (PInteger :--> PInteger))
:--> (PValue 'Sorted any0
:--> (PValue 'Sorted any1 :--> PValue 'Sorted 'NoGuarantees)))
punionResolvingCollisionsWith Commutativity
AssocMap.Commutative Term
s
((PInteger :--> (PInteger :--> PInteger))
:--> (PValue 'Sorted 'Positive
:--> (PValue 'Sorted 'Positive :--> PValue 'Sorted 'NoGuarantees)))
-> Term s (PInteger :--> (PInteger :--> PInteger))
-> Term
s
(PValue 'Sorted 'Positive
:--> (PValue 'Sorted 'Positive :--> PValue 'Sorted 'NoGuarantees))
forall (s :: S) (a :: S -> Type) (b :: S -> Type).
Term s (a :--> b) -> Term s a -> Term s b
# (Term s PInteger -> Term s PInteger -> Term s PInteger)
-> Term s (PInteger :--> (PInteger :--> PInteger))
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 PInteger -> Term s PInteger)
-> Term s (c :--> (PInteger :--> PInteger))
plam Term s PInteger -> Term s PInteger -> Term s PInteger
forall a. Num a => a -> a -> a
(+) Term
s
(PValue 'Sorted 'Positive
:--> (PValue 'Sorted 'Positive :--> PValue 'Sorted 'NoGuarantees))
-> Term s (PValue 'Sorted 'Positive)
-> Term
s (PValue 'Sorted 'Positive :--> PValue 'Sorted 'NoGuarantees)
forall (s :: S) (a :: S -> Type) (b :: S -> Type).
Term s (a :--> b) -> Term s a -> Term s b
# Term s (PValue 'Sorted 'Positive)
a Term s (PValue 'Sorted 'Positive :--> PValue 'Sorted 'NoGuarantees)
-> Term s (PValue 'Sorted 'Positive)
-> Term s (PValue 'Sorted 'NoGuarantees)
forall (s :: S) (a :: S -> Type) (b :: S -> Type).
Term s (a :--> b) -> Term s a -> Term s b
# Term s (PValue 'Sorted 'Positive)
b)
instance PlutusTx.Semigroup (Term s (PValue 'AssocMap.Sorted 'Positive)) where
Term s (PValue 'Sorted 'Positive)
a <> :: Term s (PValue 'Sorted 'Positive)
-> Term s (PValue 'Sorted 'Positive)
-> Term s (PValue 'Sorted 'Positive)
<> Term s (PValue 'Sorted 'Positive)
b =
Term s (PInner (PValue 'Sorted 'Positive))
-> Term s (PValue 'Sorted 'Positive)
forall (s :: S) (a :: S -> Type). Term s (PInner a) -> Term s a
punsafeDowncast (Term s (PValue 'Sorted 'NoGuarantees)
-> Term s (PInner (PValue 'Sorted 'NoGuarantees))
forall (s :: S) (a :: S -> Type). Term s a -> Term s (PInner a)
pto (Term s (PValue 'Sorted 'NoGuarantees)
-> Term s (PInner (PValue 'Sorted 'NoGuarantees)))
-> Term s (PValue 'Sorted 'NoGuarantees)
-> Term s (PInner (PValue 'Sorted 'NoGuarantees))
forall a b. (a -> b) -> a -> b
$ Commutativity
-> Term
s
((PInteger :--> (PInteger :--> PInteger))
:--> (PValue 'Sorted 'Positive
:--> (PValue 'Sorted 'Positive :--> PValue 'Sorted 'NoGuarantees)))
forall (any0 :: AmountGuarantees) (any1 :: AmountGuarantees)
(s :: S).
Commutativity
-> Term
s
((PInteger :--> (PInteger :--> PInteger))
:--> (PValue 'Sorted any0
:--> (PValue 'Sorted any1 :--> PValue 'Sorted 'NoGuarantees)))
punionResolvingCollisionsWith Commutativity
AssocMap.Commutative Term
s
((PInteger :--> (PInteger :--> PInteger))
:--> (PValue 'Sorted 'Positive
:--> (PValue 'Sorted 'Positive :--> PValue 'Sorted 'NoGuarantees)))
-> Term s (PInteger :--> (PInteger :--> PInteger))
-> Term
s
(PValue 'Sorted 'Positive
:--> (PValue 'Sorted 'Positive :--> PValue 'Sorted 'NoGuarantees))
forall (s :: S) (a :: S -> Type) (b :: S -> Type).
Term s (a :--> b) -> Term s a -> Term s b
# (Term s PInteger -> Term s PInteger -> Term s PInteger)
-> Term s (PInteger :--> (PInteger :--> PInteger))
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 PInteger -> Term s PInteger)
-> Term s (c :--> (PInteger :--> PInteger))
plam Term s PInteger -> Term s PInteger -> Term s PInteger
forall a. Num a => a -> a -> a
(+) Term
s
(PValue 'Sorted 'Positive
:--> (PValue 'Sorted 'Positive :--> PValue 'Sorted 'NoGuarantees))
-> Term s (PValue 'Sorted 'Positive)
-> Term
s (PValue 'Sorted 'Positive :--> PValue 'Sorted 'NoGuarantees)
forall (s :: S) (a :: S -> Type) (b :: S -> Type).
Term s (a :--> b) -> Term s a -> Term s b
# Term s (PValue 'Sorted 'Positive)
a Term s (PValue 'Sorted 'Positive :--> PValue 'Sorted 'NoGuarantees)
-> Term s (PValue 'Sorted 'Positive)
-> Term s (PValue 'Sorted 'NoGuarantees)
forall (s :: S) (a :: S -> Type) (b :: S -> Type).
Term s (a :--> b) -> Term s a -> Term s b
# Term s (PValue 'Sorted 'Positive)
b)
instance PSemigroup (PValue 'AssocMap.Sorted 'NonZero) where
{-# INLINEABLE (#<>) #-}
#<> :: forall (s :: S).
Term s (PValue 'Sorted 'NonZero)
-> Term s (PValue 'Sorted 'NonZero)
-> Term s (PValue 'Sorted 'NonZero)
(#<>) = Term s (PValue 'Sorted 'NonZero)
-> Term s (PValue 'Sorted 'NonZero)
-> Term s (PValue 'Sorted 'NonZero)
forall a. Semigroup a => a -> a -> a
(<>)
instance Semigroup (Term s (PValue 'AssocMap.Sorted 'NonZero)) where
Term s (PValue 'Sorted 'NonZero)
a <> :: Term s (PValue 'Sorted 'NonZero)
-> Term s (PValue 'Sorted 'NonZero)
-> Term s (PValue 'Sorted 'NonZero)
<> Term s (PValue 'Sorted 'NonZero)
b =
Term s (PValue 'Sorted 'NoGuarantees :--> PValue 'Sorted 'NonZero)
forall (any :: AmountGuarantees) (s :: S).
Term s (PValue 'Sorted any :--> PValue 'Sorted 'NonZero)
pnormalize Term s (PValue 'Sorted 'NoGuarantees :--> PValue 'Sorted 'NonZero)
-> Term s (PValue 'Sorted 'NoGuarantees)
-> Term s (PValue 'Sorted 'NonZero)
forall (s :: S) (a :: S -> Type) (b :: S -> Type).
Term s (a :--> b) -> Term s a -> Term s b
#$ Commutativity
-> Term
s
((PInteger :--> (PInteger :--> PInteger))
:--> (PValue 'Sorted 'NonZero
:--> (PValue 'Sorted 'NonZero :--> PValue 'Sorted 'NoGuarantees)))
forall (any0 :: AmountGuarantees) (any1 :: AmountGuarantees)
(s :: S).
Commutativity
-> Term
s
((PInteger :--> (PInteger :--> PInteger))
:--> (PValue 'Sorted any0
:--> (PValue 'Sorted any1 :--> PValue 'Sorted 'NoGuarantees)))
punionResolvingCollisionsWith Commutativity
AssocMap.Commutative Term
s
((PInteger :--> (PInteger :--> PInteger))
:--> (PValue 'Sorted 'NonZero
:--> (PValue 'Sorted 'NonZero :--> PValue 'Sorted 'NoGuarantees)))
-> Term s (PInteger :--> (PInteger :--> PInteger))
-> Term
s
(PValue 'Sorted 'NonZero
:--> (PValue 'Sorted 'NonZero :--> PValue 'Sorted 'NoGuarantees))
forall (s :: S) (a :: S -> Type) (b :: S -> Type).
Term s (a :--> b) -> Term s a -> Term s b
# (Term s PInteger -> Term s PInteger -> Term s PInteger)
-> Term s (PInteger :--> (PInteger :--> PInteger))
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 PInteger -> Term s PInteger)
-> Term s (c :--> (PInteger :--> PInteger))
plam Term s PInteger -> Term s PInteger -> Term s PInteger
forall a. Num a => a -> a -> a
(+) Term
s
(PValue 'Sorted 'NonZero
:--> (PValue 'Sorted 'NonZero :--> PValue 'Sorted 'NoGuarantees))
-> Term s (PValue 'Sorted 'NonZero)
-> Term
s (PValue 'Sorted 'NonZero :--> PValue 'Sorted 'NoGuarantees)
forall (s :: S) (a :: S -> Type) (b :: S -> Type).
Term s (a :--> b) -> Term s a -> Term s b
# Term s (PValue 'Sorted 'NonZero)
a Term s (PValue 'Sorted 'NonZero :--> PValue 'Sorted 'NoGuarantees)
-> Term s (PValue 'Sorted 'NonZero)
-> Term s (PValue 'Sorted 'NoGuarantees)
forall (s :: S) (a :: S -> Type) (b :: S -> Type).
Term s (a :--> b) -> Term s a -> Term s b
# Term s (PValue 'Sorted 'NonZero)
b
instance PlutusTx.Semigroup (Term s (PValue 'AssocMap.Sorted 'NonZero)) where
Term s (PValue 'Sorted 'NonZero)
a <> :: Term s (PValue 'Sorted 'NonZero)
-> Term s (PValue 'Sorted 'NonZero)
-> Term s (PValue 'Sorted 'NonZero)
<> Term s (PValue 'Sorted 'NonZero)
b =
Term s (PValue 'Sorted 'NoGuarantees :--> PValue 'Sorted 'NonZero)
forall (any :: AmountGuarantees) (s :: S).
Term s (PValue 'Sorted any :--> PValue 'Sorted 'NonZero)
pnormalize Term s (PValue 'Sorted 'NoGuarantees :--> PValue 'Sorted 'NonZero)
-> Term s (PValue 'Sorted 'NoGuarantees)
-> Term s (PValue 'Sorted 'NonZero)
forall (s :: S) (a :: S -> Type) (b :: S -> Type).
Term s (a :--> b) -> Term s a -> Term s b
#$ Commutativity
-> Term
s
((PInteger :--> (PInteger :--> PInteger))
:--> (PValue 'Sorted 'NonZero
:--> (PValue 'Sorted 'NonZero :--> PValue 'Sorted 'NoGuarantees)))
forall (any0 :: AmountGuarantees) (any1 :: AmountGuarantees)
(s :: S).
Commutativity
-> Term
s
((PInteger :--> (PInteger :--> PInteger))
:--> (PValue 'Sorted any0
:--> (PValue 'Sorted any1 :--> PValue 'Sorted 'NoGuarantees)))
punionResolvingCollisionsWith Commutativity
AssocMap.Commutative Term
s
((PInteger :--> (PInteger :--> PInteger))
:--> (PValue 'Sorted 'NonZero
:--> (PValue 'Sorted 'NonZero :--> PValue 'Sorted 'NoGuarantees)))
-> Term s (PInteger :--> (PInteger :--> PInteger))
-> Term
s
(PValue 'Sorted 'NonZero
:--> (PValue 'Sorted 'NonZero :--> PValue 'Sorted 'NoGuarantees))
forall (s :: S) (a :: S -> Type) (b :: S -> Type).
Term s (a :--> b) -> Term s a -> Term s b
# (Term s PInteger -> Term s PInteger -> Term s PInteger)
-> Term s (PInteger :--> (PInteger :--> PInteger))
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 PInteger -> Term s PInteger)
-> Term s (c :--> (PInteger :--> PInteger))
plam Term s PInteger -> Term s PInteger -> Term s PInteger
forall a. Num a => a -> a -> a
(+) Term
s
(PValue 'Sorted 'NonZero
:--> (PValue 'Sorted 'NonZero :--> PValue 'Sorted 'NoGuarantees))
-> Term s (PValue 'Sorted 'NonZero)
-> Term
s (PValue 'Sorted 'NonZero :--> PValue 'Sorted 'NoGuarantees)
forall (s :: S) (a :: S -> Type) (b :: S -> Type).
Term s (a :--> b) -> Term s a -> Term s b
# Term s (PValue 'Sorted 'NonZero)
a Term s (PValue 'Sorted 'NonZero :--> PValue 'Sorted 'NoGuarantees)
-> Term s (PValue 'Sorted 'NonZero)
-> Term s (PValue 'Sorted 'NoGuarantees)
forall (s :: S) (a :: S -> Type) (b :: S -> Type).
Term s (a :--> b) -> Term s a -> Term s b
# Term s (PValue 'Sorted 'NonZero)
b
instance PSemigroup (PValue 'AssocMap.Sorted 'NoGuarantees) where
{-# INLINEABLE (#<>) #-}
#<> :: forall (s :: S).
Term s (PValue 'Sorted 'NoGuarantees)
-> Term s (PValue 'Sorted 'NoGuarantees)
-> Term s (PValue 'Sorted 'NoGuarantees)
(#<>) = Term s (PValue 'Sorted 'NoGuarantees)
-> Term s (PValue 'Sorted 'NoGuarantees)
-> Term s (PValue 'Sorted 'NoGuarantees)
forall a. Semigroup a => a -> a -> a
(<>)
instance Semigroup (Term s (PValue 'AssocMap.Sorted 'NoGuarantees)) where
Term s (PValue 'Sorted 'NoGuarantees)
a <> :: Term s (PValue 'Sorted 'NoGuarantees)
-> Term s (PValue 'Sorted 'NoGuarantees)
-> Term s (PValue 'Sorted 'NoGuarantees)
<> Term s (PValue 'Sorted 'NoGuarantees)
b =
Commutativity
-> Term
s
((PInteger :--> (PInteger :--> PInteger))
:--> (PValue 'Sorted 'NoGuarantees
:--> (PValue 'Sorted 'NoGuarantees
:--> PValue 'Sorted 'NoGuarantees)))
forall (any0 :: AmountGuarantees) (any1 :: AmountGuarantees)
(s :: S).
Commutativity
-> Term
s
((PInteger :--> (PInteger :--> PInteger))
:--> (PValue 'Sorted any0
:--> (PValue 'Sorted any1 :--> PValue 'Sorted 'NoGuarantees)))
punionResolvingCollisionsWith Commutativity
AssocMap.Commutative Term
s
((PInteger :--> (PInteger :--> PInteger))
:--> (PValue 'Sorted 'NoGuarantees
:--> (PValue 'Sorted 'NoGuarantees
:--> PValue 'Sorted 'NoGuarantees)))
-> Term s (PInteger :--> (PInteger :--> PInteger))
-> Term
s
(PValue 'Sorted 'NoGuarantees
:--> (PValue 'Sorted 'NoGuarantees
:--> PValue 'Sorted 'NoGuarantees))
forall (s :: S) (a :: S -> Type) (b :: S -> Type).
Term s (a :--> b) -> Term s a -> Term s b
# (Term s PInteger -> Term s PInteger -> Term s PInteger)
-> Term s (PInteger :--> (PInteger :--> PInteger))
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 PInteger -> Term s PInteger)
-> Term s (c :--> (PInteger :--> PInteger))
plam Term s PInteger -> Term s PInteger -> Term s PInteger
forall a. Num a => a -> a -> a
(+) Term
s
(PValue 'Sorted 'NoGuarantees
:--> (PValue 'Sorted 'NoGuarantees
:--> PValue 'Sorted 'NoGuarantees))
-> Term s (PValue 'Sorted 'NoGuarantees)
-> Term
s (PValue 'Sorted 'NoGuarantees :--> PValue 'Sorted 'NoGuarantees)
forall (s :: S) (a :: S -> Type) (b :: S -> Type).
Term s (a :--> b) -> Term s a -> Term s b
# Term s (PValue 'Sorted 'NoGuarantees)
a Term
s (PValue 'Sorted 'NoGuarantees :--> PValue 'Sorted 'NoGuarantees)
-> Term s (PValue 'Sorted 'NoGuarantees)
-> Term s (PValue 'Sorted 'NoGuarantees)
forall (s :: S) (a :: S -> Type) (b :: S -> Type).
Term s (a :--> b) -> Term s a -> Term s b
# Term s (PValue 'Sorted 'NoGuarantees)
b
instance PlutusTx.Semigroup (Term s (PValue 'AssocMap.Sorted 'NoGuarantees)) where
Term s (PValue 'Sorted 'NoGuarantees)
a <> :: Term s (PValue 'Sorted 'NoGuarantees)
-> Term s (PValue 'Sorted 'NoGuarantees)
-> Term s (PValue 'Sorted 'NoGuarantees)
<> Term s (PValue 'Sorted 'NoGuarantees)
b =
Commutativity
-> Term
s
((PInteger :--> (PInteger :--> PInteger))
:--> (PValue 'Sorted 'NoGuarantees
:--> (PValue 'Sorted 'NoGuarantees
:--> PValue 'Sorted 'NoGuarantees)))
forall (any0 :: AmountGuarantees) (any1 :: AmountGuarantees)
(s :: S).
Commutativity
-> Term
s
((PInteger :--> (PInteger :--> PInteger))
:--> (PValue 'Sorted any0
:--> (PValue 'Sorted any1 :--> PValue 'Sorted 'NoGuarantees)))
punionResolvingCollisionsWith Commutativity
AssocMap.Commutative Term
s
((PInteger :--> (PInteger :--> PInteger))
:--> (PValue 'Sorted 'NoGuarantees
:--> (PValue 'Sorted 'NoGuarantees
:--> PValue 'Sorted 'NoGuarantees)))
-> Term s (PInteger :--> (PInteger :--> PInteger))
-> Term
s
(PValue 'Sorted 'NoGuarantees
:--> (PValue 'Sorted 'NoGuarantees
:--> PValue 'Sorted 'NoGuarantees))
forall (s :: S) (a :: S -> Type) (b :: S -> Type).
Term s (a :--> b) -> Term s a -> Term s b
# (Term s PInteger -> Term s PInteger -> Term s PInteger)
-> Term s (PInteger :--> (PInteger :--> PInteger))
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 PInteger -> Term s PInteger)
-> Term s (c :--> (PInteger :--> PInteger))
plam Term s PInteger -> Term s PInteger -> Term s PInteger
forall a. Num a => a -> a -> a
(+) Term
s
(PValue 'Sorted 'NoGuarantees
:--> (PValue 'Sorted 'NoGuarantees
:--> PValue 'Sorted 'NoGuarantees))
-> Term s (PValue 'Sorted 'NoGuarantees)
-> Term
s (PValue 'Sorted 'NoGuarantees :--> PValue 'Sorted 'NoGuarantees)
forall (s :: S) (a :: S -> Type) (b :: S -> Type).
Term s (a :--> b) -> Term s a -> Term s b
# Term s (PValue 'Sorted 'NoGuarantees)
a Term
s (PValue 'Sorted 'NoGuarantees :--> PValue 'Sorted 'NoGuarantees)
-> Term s (PValue 'Sorted 'NoGuarantees)
-> Term s (PValue 'Sorted 'NoGuarantees)
forall (s :: S) (a :: S -> Type) (b :: S -> Type).
Term s (a :--> b) -> Term s a -> Term s b
# Term s (PValue 'Sorted 'NoGuarantees)
b
instance
PSemigroup (PValue 'AssocMap.Sorted normalization) =>
PMonoid (PValue 'AssocMap.Sorted normalization)
where
{-# INLINEABLE pmempty #-}
pmempty :: forall (s :: S). Term s (PValue 'Sorted normalization)
pmempty = PValue 'Sorted normalization s
-> Term s (PValue 'Sorted normalization)
forall (a :: S -> Type) (s :: S). PlutusType a => a s -> Term s a
pcon (Term
s (PMap 'Sorted PCurrencySymbol (PMap 'Sorted PTokenName PInteger))
-> PValue 'Sorted normalization s
forall (keys :: KeyGuarantees) (amounts :: AmountGuarantees)
(s :: S).
Term s (PMap keys PCurrencySymbol (PMap keys PTokenName PInteger))
-> PValue keys amounts s
PValue Term
s (PMap 'Sorted PCurrencySymbol (PMap 'Sorted PTokenName PInteger))
forall (s :: S) (k :: S -> Type) (v :: S -> Type).
Term s (PMap 'Sorted k v)
AssocMap.pempty)
instance
Semigroup (Term s (PValue 'AssocMap.Sorted normalization)) =>
Monoid (Term s (PValue 'AssocMap.Sorted normalization))
where
mempty :: Term s (PValue 'Sorted normalization)
mempty = PValue 'Sorted normalization s
-> Term s (PValue 'Sorted normalization)
forall (a :: S -> Type) (s :: S). PlutusType a => a s -> Term s a
pcon (Term
s (PMap 'Sorted PCurrencySymbol (PMap 'Sorted PTokenName PInteger))
-> PValue 'Sorted normalization s
forall (keys :: KeyGuarantees) (amounts :: AmountGuarantees)
(s :: S).
Term s (PMap keys PCurrencySymbol (PMap keys PTokenName PInteger))
-> PValue keys amounts s
PValue Term
s (PMap 'Sorted PCurrencySymbol (PMap 'Sorted PTokenName PInteger))
forall (s :: S) (k :: S -> Type) (v :: S -> Type).
Term s (PMap 'Sorted k v)
AssocMap.pempty)
instance
PlutusTx.Semigroup (Term s (PValue 'AssocMap.Sorted normalization)) =>
PlutusTx.Monoid (Term s (PValue 'AssocMap.Sorted normalization))
where
mempty :: Term s (PValue 'Sorted normalization)
mempty = PValue 'Sorted normalization s
-> Term s (PValue 'Sorted normalization)
forall (a :: S -> Type) (s :: S). PlutusType a => a s -> Term s a
pcon (Term
s (PMap 'Sorted PCurrencySymbol (PMap 'Sorted PTokenName PInteger))
-> PValue 'Sorted normalization s
forall (keys :: KeyGuarantees) (amounts :: AmountGuarantees)
(s :: S).
Term s (PMap keys PCurrencySymbol (PMap keys PTokenName PInteger))
-> PValue keys amounts s
PValue Term
s (PMap 'Sorted PCurrencySymbol (PMap 'Sorted PTokenName PInteger))
forall (s :: S) (k :: S -> Type) (v :: S -> Type).
Term s (PMap 'Sorted k v)
AssocMap.pempty)
instance
PlutusTx.Semigroup (Term s (PValue 'AssocMap.Sorted 'NoGuarantees)) =>
PlutusTx.Group (Term s (PValue 'AssocMap.Sorted 'NoGuarantees))
where
inv :: Term s (PValue 'Sorted 'NoGuarantees)
-> Term s (PValue 'Sorted 'NoGuarantees)
inv Term s (PValue 'Sorted 'NoGuarantees)
a = Term
s
((PInteger :--> PInteger)
:--> (PValue 'Sorted 'NoGuarantees
:--> PValue 'Sorted 'NoGuarantees))
forall (k :: KeyGuarantees) (a :: AmountGuarantees) (s :: S).
Term
s
((PInteger :--> PInteger)
:--> (PValue k a :--> PValue k 'NoGuarantees))
pmapAmounts Term
s
((PInteger :--> PInteger)
:--> (PValue 'Sorted 'NoGuarantees
:--> PValue 'Sorted 'NoGuarantees))
-> Term s (PInteger :--> PInteger)
-> Term
s (PValue 'Sorted 'NoGuarantees :--> PValue 'Sorted 'NoGuarantees)
forall (s :: S) (a :: S -> Type) (b :: S -> Type).
Term s (a :--> b) -> Term s a -> Term s b
# (Term s PInteger -> Term s PInteger)
-> Term s (PInteger :--> PInteger)
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 PInteger) -> Term s (c :--> PInteger)
plam Term s PInteger -> Term s PInteger
forall a. Num a => a -> a
negate Term
s (PValue 'Sorted 'NoGuarantees :--> PValue 'Sorted 'NoGuarantees)
-> Term s (PValue 'Sorted 'NoGuarantees)
-> Term s (PValue 'Sorted 'NoGuarantees)
forall (s :: S) (a :: S -> Type) (b :: S -> Type).
Term s (a :--> b) -> Term s a -> Term s b
# Term s (PValue 'Sorted 'NoGuarantees)
a
instance
PlutusTx.Semigroup (Term s (PValue 'AssocMap.Sorted 'NonZero)) =>
PlutusTx.Group (Term s (PValue 'AssocMap.Sorted 'NonZero))
where
inv :: Term s (PValue 'Sorted 'NonZero)
-> Term s (PValue 'Sorted 'NonZero)
inv Term s (PValue 'Sorted 'NonZero)
a =
Term s (PValue 'Sorted 'NoGuarantees)
-> Term s (PValue 'Sorted 'NonZero)
forall (b :: S -> Type) (a :: S -> Type) (s :: S).
Term s a -> Term s b
punsafeCoerce (Term s (PValue 'Sorted 'NoGuarantees)
-> Term s (PValue 'Sorted 'NonZero))
-> Term s (PValue 'Sorted 'NoGuarantees)
-> Term s (PValue 'Sorted 'NonZero)
forall a b. (a -> b) -> a -> b
$ Term s (PValue 'Sorted 'NoGuarantees)
-> Term s (PValue 'Sorted 'NoGuarantees)
forall a. Group a => a -> a
PlutusTx.inv (Term s (PValue 'Sorted 'NonZero)
-> Term s (PValue 'Sorted 'NoGuarantees)
forall (b :: S -> Type) (a :: S -> Type) (s :: S).
Term s a -> Term s b
punsafeCoerce Term s (PValue 'Sorted 'NonZero)
a :: Term s (PValue 'AssocMap.Sorted 'NoGuarantees))
newtype PAssetClass (s :: S) = PAssetClass (Term s (PBuiltinPair (PAsData PCurrencySymbol) (PAsData PTokenName)))
deriving stock
(
(forall x. PAssetClass s -> Rep (PAssetClass s) x)
-> (forall x. Rep (PAssetClass s) x -> PAssetClass s)
-> Generic (PAssetClass s)
forall x. Rep (PAssetClass s) x -> PAssetClass s
forall x. PAssetClass s -> Rep (PAssetClass s) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall (s :: S) x. Rep (PAssetClass s) x -> PAssetClass s
forall (s :: S) x. PAssetClass s -> Rep (PAssetClass s) x
$cfrom :: forall (s :: S) x. PAssetClass s -> Rep (PAssetClass s) x
from :: forall x. PAssetClass s -> Rep (PAssetClass s) x
$cto :: forall (s :: S) x. Rep (PAssetClass s) x -> PAssetClass s
to :: forall x. Rep (PAssetClass s) x -> PAssetClass s
Generic
)
deriving anyclass
(
All SListI (Code (PAssetClass s))
All SListI (Code (PAssetClass s)) =>
(PAssetClass s -> Rep (PAssetClass s))
-> (Rep (PAssetClass s) -> PAssetClass s)
-> Generic (PAssetClass s)
Rep (PAssetClass s) -> PAssetClass s
PAssetClass s -> Rep (PAssetClass s)
forall a.
All SListI (Code a) =>
(a -> Rep a) -> (Rep a -> a) -> Generic a
forall (s :: S). All SListI (Code (PAssetClass s))
forall (s :: S). Rep (PAssetClass s) -> PAssetClass s
forall (s :: S). PAssetClass s -> Rep (PAssetClass s)
$cfrom :: forall (s :: S). PAssetClass s -> Rep (PAssetClass s)
from :: PAssetClass s -> Rep (PAssetClass s)
$cto :: forall (s :: S). Rep (PAssetClass s) -> PAssetClass s
to :: Rep (PAssetClass s) -> PAssetClass s
SOP.Generic
,
(forall (s :: S).
Term s (PAsData PAssetClass) -> Term s PAssetClass)
-> (forall (s :: S). Term s PAssetClass -> Term s PData)
-> PIsData PAssetClass
forall (s :: S). Term s (PAsData PAssetClass) -> Term s PAssetClass
forall (s :: S). Term s PAssetClass -> Term s PData
forall (a :: S -> Type).
(forall (s :: S). Term s (PAsData a) -> Term s a)
-> (forall (s :: S). Term s a -> Term s PData) -> PIsData a
$cpfromDataImpl :: forall (s :: S). Term s (PAsData PAssetClass) -> Term s PAssetClass
pfromDataImpl :: forall (s :: S). Term s (PAsData PAssetClass) -> Term s PAssetClass
$cpdataImpl :: forall (s :: S). Term s PAssetClass -> Term s PData
pdataImpl :: forall (s :: S). Term s PAssetClass -> Term s PData
PIsData
,
(forall (s :: S).
Term s PAssetClass -> Term s PAssetClass -> Term s PBool)
-> PEq PAssetClass
forall (s :: S).
Term s PAssetClass -> Term s PAssetClass -> Term s PBool
forall (t :: S -> Type).
(forall (s :: S). Term s t -> Term s t -> Term s PBool) -> PEq t
$c#== :: forall (s :: S).
Term s PAssetClass -> Term s PAssetClass -> Term s PBool
#== :: forall (s :: S).
Term s PAssetClass -> Term s PAssetClass -> Term s PBool
PEq
,
(forall (s :: S). Bool -> Term s PAssetClass -> Term s PString)
-> PShow PAssetClass
forall (s :: S). Bool -> Term s PAssetClass -> Term s PString
forall (t :: S -> Type).
(forall (s :: S). Bool -> Term s t -> Term s PString) -> PShow t
$cpshow' :: forall (s :: S). Bool -> Term s PAssetClass -> Term s PString
pshow' :: forall (s :: S). Bool -> Term s PAssetClass -> Term s PString
PShow
)
deriving
(
(forall (s :: S). PAssetClass s -> Term s (PInner PAssetClass))
-> (forall (s :: S) (b :: S -> Type).
Term s (PInner PAssetClass)
-> (PAssetClass s -> Term s b) -> Term s b)
-> PlutusType PAssetClass
forall (s :: S). PAssetClass s -> Term s (PInner PAssetClass)
forall (s :: S) (b :: S -> Type).
Term s (PInner PAssetClass)
-> (PAssetClass s -> Term s b) -> Term s b
forall (a :: S -> Type).
(forall (s :: S). a s -> Term s (PInner a))
-> (forall (s :: S) (b :: S -> Type).
Term s (PInner a) -> (a s -> Term s b) -> Term s b)
-> PlutusType a
$cpcon' :: forall (s :: S). PAssetClass s -> Term s (PInner PAssetClass)
pcon' :: forall (s :: S). PAssetClass s -> Term s (PInner PAssetClass)
$cpmatch' :: forall (s :: S) (b :: S -> Type).
Term s (PInner PAssetClass)
-> (PAssetClass s -> Term s b) -> Term s b
pmatch' :: forall (s :: S) (b :: S -> Type).
Term s (PInner PAssetClass)
-> (PAssetClass s -> Term s b) -> Term s b
PlutusType
)
via (DeriveNewtypePlutusType PAssetClass)
instance POrd PAssetClass where
{-# INLINEABLE (#<=) #-}
Term s PAssetClass
ac1 #<= :: forall (s :: S).
Term s PAssetClass -> Term s PAssetClass -> Term s PBool
#<= Term s PAssetClass
ac2 = Term s PAssetClass
-> (PAssetClass 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 PAssetClass
ac1 ((PAssetClass s -> Term s PBool) -> Term s PBool)
-> (PAssetClass s -> Term s PBool) -> Term s PBool
forall a b. (a -> b) -> a -> b
$ \(PAssetClass Term
s (PBuiltinPair (PAsData PCurrencySymbol) (PAsData PTokenName))
pair1) ->
Term s PAssetClass
-> (PAssetClass 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 PAssetClass
ac2 ((PAssetClass s -> Term s PBool) -> Term s PBool)
-> (PAssetClass s -> Term s PBool) -> Term s PBool
forall a b. (a -> b) -> a -> b
$ \(PAssetClass Term
s (PBuiltinPair (PAsData PCurrencySymbol) (PAsData PTokenName))
pair2) ->
Term s PCurrencySymbol
-> (Term s PCurrencySymbol -> Term s PBool) -> Term s PBool
forall (s :: S) (a :: S -> Type) (b :: S -> Type).
Term s a -> (Term s a -> Term s b) -> Term s b
plet (Term s (PAsData PCurrencySymbol) -> Term s PCurrencySymbol
forall (a :: S -> Type) (s :: S).
PIsData a =>
Term s (PAsData a) -> Term s a
pfromData (Term s (PAsData PCurrencySymbol) -> Term s PCurrencySymbol)
-> Term s (PAsData PCurrencySymbol) -> Term s PCurrencySymbol
forall a b. (a -> b) -> a -> b
$ Term
s
(PBuiltinPair (PAsData PCurrencySymbol) (PAsData PTokenName)
:--> PAsData PCurrencySymbol)
forall (s :: S) (a :: S -> Type) (b :: S -> Type).
Term s (PBuiltinPair a b :--> a)
pfstBuiltin Term
s
(PBuiltinPair (PAsData PCurrencySymbol) (PAsData PTokenName)
:--> PAsData PCurrencySymbol)
-> Term
s (PBuiltinPair (PAsData PCurrencySymbol) (PAsData PTokenName))
-> Term s (PAsData PCurrencySymbol)
forall (s :: S) (a :: S -> Type) (b :: S -> Type).
Term s (a :--> b) -> Term s a -> Term s b
# Term
s (PBuiltinPair (PAsData PCurrencySymbol) (PAsData PTokenName))
pair1) ((Term s PCurrencySymbol -> Term s PBool) -> Term s PBool)
-> (Term s PCurrencySymbol -> Term s PBool) -> Term s PBool
forall a b. (a -> b) -> a -> b
$ \Term s PCurrencySymbol
fst1 ->
Term s PCurrencySymbol
-> (Term s PCurrencySymbol -> Term s PBool) -> Term s PBool
forall (s :: S) (a :: S -> Type) (b :: S -> Type).
Term s a -> (Term s a -> Term s b) -> Term s b
plet (Term s (PAsData PCurrencySymbol) -> Term s PCurrencySymbol
forall (a :: S -> Type) (s :: S).
PIsData a =>
Term s (PAsData a) -> Term s a
pfromData (Term s (PAsData PCurrencySymbol) -> Term s PCurrencySymbol)
-> Term s (PAsData PCurrencySymbol) -> Term s PCurrencySymbol
forall a b. (a -> b) -> a -> b
$ Term
s
(PBuiltinPair (PAsData PCurrencySymbol) (PAsData PTokenName)
:--> PAsData PCurrencySymbol)
forall (s :: S) (a :: S -> Type) (b :: S -> Type).
Term s (PBuiltinPair a b :--> a)
pfstBuiltin Term
s
(PBuiltinPair (PAsData PCurrencySymbol) (PAsData PTokenName)
:--> PAsData PCurrencySymbol)
-> Term
s (PBuiltinPair (PAsData PCurrencySymbol) (PAsData PTokenName))
-> Term s (PAsData PCurrencySymbol)
forall (s :: S) (a :: S -> Type) (b :: S -> Type).
Term s (a :--> b) -> Term s a -> Term s b
# Term
s (PBuiltinPair (PAsData PCurrencySymbol) (PAsData PTokenName))
pair2) ((Term s PCurrencySymbol -> Term s PBool) -> Term s PBool)
-> (Term s PCurrencySymbol -> Term s PBool) -> Term s PBool
forall a b. (a -> b) -> a -> b
$ \Term s PCurrencySymbol
fst2 ->
(Term s PCurrencySymbol
fst1 Term s PCurrencySymbol -> Term s PCurrencySymbol -> Term s PBool
forall (s :: S).
Term s PCurrencySymbol -> Term s PCurrencySymbol -> Term s PBool
forall (t :: S -> Type) (s :: S).
POrd t =>
Term s t -> Term s t -> Term s PBool
#< Term s PCurrencySymbol
fst2)
#|| ( (fst1 #== fst2)
#&& let snd1 = pfromData $ psndBuiltin # pair1
snd2 = pfromData $ psndBuiltin # pair2
in snd1 #<= snd2
)
{-# INLINEABLE (#<) #-}
Term s PAssetClass
ac1 #< :: forall (s :: S).
Term s PAssetClass -> Term s PAssetClass -> Term s PBool
#< Term s PAssetClass
ac2 = Term s PAssetClass
-> (PAssetClass 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 PAssetClass
ac1 ((PAssetClass s -> Term s PBool) -> Term s PBool)
-> (PAssetClass s -> Term s PBool) -> Term s PBool
forall a b. (a -> b) -> a -> b
$ \(PAssetClass Term
s (PBuiltinPair (PAsData PCurrencySymbol) (PAsData PTokenName))
pair1) ->
Term s PAssetClass
-> (PAssetClass 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 PAssetClass
ac2 ((PAssetClass s -> Term s PBool) -> Term s PBool)
-> (PAssetClass s -> Term s PBool) -> Term s PBool
forall a b. (a -> b) -> a -> b
$ \(PAssetClass Term
s (PBuiltinPair (PAsData PCurrencySymbol) (PAsData PTokenName))
pair2) ->
Term s PCurrencySymbol
-> (Term s PCurrencySymbol -> Term s PBool) -> Term s PBool
forall (s :: S) (a :: S -> Type) (b :: S -> Type).
Term s a -> (Term s a -> Term s b) -> Term s b
plet (Term s (PAsData PCurrencySymbol) -> Term s PCurrencySymbol
forall (a :: S -> Type) (s :: S).
PIsData a =>
Term s (PAsData a) -> Term s a
pfromData (Term s (PAsData PCurrencySymbol) -> Term s PCurrencySymbol)
-> Term s (PAsData PCurrencySymbol) -> Term s PCurrencySymbol
forall a b. (a -> b) -> a -> b
$ Term
s
(PBuiltinPair (PAsData PCurrencySymbol) (PAsData PTokenName)
:--> PAsData PCurrencySymbol)
forall (s :: S) (a :: S -> Type) (b :: S -> Type).
Term s (PBuiltinPair a b :--> a)
pfstBuiltin Term
s
(PBuiltinPair (PAsData PCurrencySymbol) (PAsData PTokenName)
:--> PAsData PCurrencySymbol)
-> Term
s (PBuiltinPair (PAsData PCurrencySymbol) (PAsData PTokenName))
-> Term s (PAsData PCurrencySymbol)
forall (s :: S) (a :: S -> Type) (b :: S -> Type).
Term s (a :--> b) -> Term s a -> Term s b
# Term
s (PBuiltinPair (PAsData PCurrencySymbol) (PAsData PTokenName))
pair1) ((Term s PCurrencySymbol -> Term s PBool) -> Term s PBool)
-> (Term s PCurrencySymbol -> Term s PBool) -> Term s PBool
forall a b. (a -> b) -> a -> b
$ \Term s PCurrencySymbol
fst1 ->
Term s PCurrencySymbol
-> (Term s PCurrencySymbol -> Term s PBool) -> Term s PBool
forall (s :: S) (a :: S -> Type) (b :: S -> Type).
Term s a -> (Term s a -> Term s b) -> Term s b
plet (Term s (PAsData PCurrencySymbol) -> Term s PCurrencySymbol
forall (a :: S -> Type) (s :: S).
PIsData a =>
Term s (PAsData a) -> Term s a
pfromData (Term s (PAsData PCurrencySymbol) -> Term s PCurrencySymbol)
-> Term s (PAsData PCurrencySymbol) -> Term s PCurrencySymbol
forall a b. (a -> b) -> a -> b
$ Term
s
(PBuiltinPair (PAsData PCurrencySymbol) (PAsData PTokenName)
:--> PAsData PCurrencySymbol)
forall (s :: S) (a :: S -> Type) (b :: S -> Type).
Term s (PBuiltinPair a b :--> a)
pfstBuiltin Term
s
(PBuiltinPair (PAsData PCurrencySymbol) (PAsData PTokenName)
:--> PAsData PCurrencySymbol)
-> Term
s (PBuiltinPair (PAsData PCurrencySymbol) (PAsData PTokenName))
-> Term s (PAsData PCurrencySymbol)
forall (s :: S) (a :: S -> Type) (b :: S -> Type).
Term s (a :--> b) -> Term s a -> Term s b
# Term
s (PBuiltinPair (PAsData PCurrencySymbol) (PAsData PTokenName))
pair2) ((Term s PCurrencySymbol -> Term s PBool) -> Term s PBool)
-> (Term s PCurrencySymbol -> Term s PBool) -> Term s PBool
forall a b. (a -> b) -> a -> b
$ \Term s PCurrencySymbol
fst2 ->
(Term s PCurrencySymbol
fst1 Term s PCurrencySymbol -> Term s PCurrencySymbol -> Term s PBool
forall (s :: S).
Term s PCurrencySymbol -> Term s PCurrencySymbol -> Term s PBool
forall (t :: S -> Type) (s :: S).
POrd t =>
Term s t -> Term s t -> Term s PBool
#< Term s PCurrencySymbol
fst2)
#|| ( (fst1 #== fst2)
#&& let snd1 = pfromData $ psndBuiltin # pair1
snd2 = pfromData $ psndBuiltin # pair2
in snd1 #< snd2
)
deriving via
DeriveNewtypePLiftable PAssetClass PlutusValue.AssetClass
instance
PLiftable PAssetClass
pforgetPositive ::
forall (a :: AmountGuarantees) (k :: AssocMap.KeyGuarantees) (s :: S).
Term s (PValue k 'Positive) ->
Term s (PValue k a)
pforgetPositive :: forall (a :: AmountGuarantees) (k :: KeyGuarantees) (s :: S).
Term s (PValue k 'Positive) -> Term s (PValue k a)
pforgetPositive = Term s (PValue k 'Positive) -> Term s (PValue k a)
forall (b :: S -> Type) (a :: S -> Type) (s :: S).
Term s a -> Term s b
punsafeCoerce
pcheckBinRel ::
forall (any0 :: AmountGuarantees) (any1 :: AmountGuarantees) (s :: S).
Term
s
( (PInteger :--> PInteger :--> PBool)
:--> PValue 'AssocMap.Sorted any0
:--> PValue 'AssocMap.Sorted any1
:--> PBool
)
pcheckBinRel :: forall (any0 :: AmountGuarantees) (any1 :: AmountGuarantees)
(s :: S).
Term
s
((PInteger :--> (PInteger :--> PBool))
:--> (PValue 'Sorted any0 :--> (PValue 'Sorted any1 :--> PBool)))
pcheckBinRel = ClosedTerm
((PInteger :--> (PInteger :--> PBool))
:--> (PValue 'Sorted any0 :--> (PValue 'Sorted any1 :--> PBool)))
-> Term
s
((PInteger :--> (PInteger :--> PBool))
:--> (PValue 'Sorted any0 :--> (PValue 'Sorted any1 :--> PBool)))
forall (a :: S -> Type) (s :: S).
HasCallStack =>
ClosedTerm a -> Term s a
phoistAcyclic (ClosedTerm
((PInteger :--> (PInteger :--> PBool))
:--> (PValue 'Sorted any0 :--> (PValue 'Sorted any1 :--> PBool)))
-> Term
s
((PInteger :--> (PInteger :--> PBool))
:--> (PValue 'Sorted any0 :--> (PValue 'Sorted any1 :--> PBool))))
-> ClosedTerm
((PInteger :--> (PInteger :--> PBool))
:--> (PValue 'Sorted any0 :--> (PValue 'Sorted any1 :--> PBool)))
-> Term
s
((PInteger :--> (PInteger :--> PBool))
:--> (PValue 'Sorted any0 :--> (PValue 'Sorted any1 :--> PBool)))
forall a b. (a -> b) -> a -> b
$
(Term s (PInteger :--> (PInteger :--> PBool))
-> Term
s (PValue 'Sorted any0 :--> (PValue 'Sorted any1 :--> PBool)))
-> Term
s
((PInteger :--> (PInteger :--> PBool))
:--> (PValue 'Sorted any0 :--> (PValue 'Sorted any1 :--> 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 (PValue 'Sorted any0 :--> (PValue 'Sorted any1 :--> PBool)))
-> Term
s
(c
:--> (PValue 'Sorted any0 :--> (PValue 'Sorted any1 :--> PBool)))
plam ((Term s (PInteger :--> (PInteger :--> PBool))
-> Term
s (PValue 'Sorted any0 :--> (PValue 'Sorted any1 :--> PBool)))
-> Term
s
((PInteger :--> (PInteger :--> PBool))
:--> (PValue 'Sorted any0 :--> (PValue 'Sorted any1 :--> PBool))))
-> (Term s (PInteger :--> (PInteger :--> PBool))
-> Term
s (PValue 'Sorted any0 :--> (PValue 'Sorted any1 :--> PBool)))
-> Term
s
((PInteger :--> (PInteger :--> PBool))
:--> (PValue 'Sorted any0 :--> (PValue 'Sorted any1 :--> PBool)))
forall a b. (a -> b) -> a -> b
$ \Term s (PInteger :--> (PInteger :--> PBool))
f ->
forall (b :: S -> Type) (a :: S -> Type) (s :: S).
Term s a -> Term s b
punsafeCoerce @(PValue AssocMap.Sorted any0 :--> PValue AssocMap.Sorted any1 :--> PBool) (Term
s
(PMap 'Sorted PCurrencySymbol (PMap 'Sorted PTokenName PInteger)
:--> (PMap
'Sorted PCurrencySymbol (PMap 'Sorted PTokenName PInteger)
:--> PBool))
-> Term
s (PValue 'Sorted any0 :--> (PValue 'Sorted any1 :--> PBool)))
-> Term
s
(PMap 'Sorted PCurrencySymbol (PMap 'Sorted PTokenName PInteger)
:--> (PMap
'Sorted PCurrencySymbol (PMap 'Sorted PTokenName PInteger)
:--> PBool))
-> Term
s (PValue 'Sorted any0 :--> (PValue 'Sorted any1 :--> PBool))
forall a b. (a -> b) -> a -> b
$
forall (k :: S -> Type) (v :: S -> Type) (s :: S).
(POrd k, PIsData k, PIsData v) =>
Term
s
((v :--> (v :--> PBool))
:--> (v
:--> (PMap 'Sorted k v :--> (PMap 'Sorted k v :--> PBool))))
AssocMap.pcheckBinRel @PCurrencySymbol Term
s
((PMap 'Sorted PTokenName PInteger
:--> (PMap 'Sorted PTokenName PInteger :--> PBool))
:--> (PMap 'Sorted PTokenName PInteger
:--> (PMap
'Sorted PCurrencySymbol (PMap 'Sorted PTokenName PInteger)
:--> (PMap
'Sorted PCurrencySymbol (PMap 'Sorted PTokenName PInteger)
:--> PBool))))
-> Term
s
(PMap 'Sorted PTokenName PInteger
:--> (PMap 'Sorted PTokenName PInteger :--> PBool))
-> Term
s
(PMap 'Sorted PTokenName PInteger
:--> (PMap
'Sorted PCurrencySymbol (PMap 'Sorted PTokenName PInteger)
:--> (PMap
'Sorted PCurrencySymbol (PMap 'Sorted PTokenName PInteger)
:--> PBool)))
forall (s :: S) (a :: S -> Type) (b :: S -> Type).
Term s (a :--> b) -> Term s a -> Term s b
# (forall (k :: S -> Type) (v :: S -> Type) (s :: S).
(POrd k, PIsData k, PIsData v) =>
Term
s
((v :--> (v :--> PBool))
:--> (v
:--> (PMap 'Sorted k v :--> (PMap 'Sorted k v :--> PBool))))
AssocMap.pcheckBinRel @PTokenName Term
s
((PInteger :--> (PInteger :--> PBool))
:--> (PInteger
:--> (PMap 'Sorted PTokenName PInteger
:--> (PMap 'Sorted PTokenName PInteger :--> PBool))))
-> Term s (PInteger :--> (PInteger :--> PBool))
-> Term
s
(PInteger
:--> (PMap 'Sorted PTokenName PInteger
:--> (PMap 'Sorted PTokenName PInteger :--> PBool)))
forall (s :: S) (a :: S -> Type) (b :: S -> Type).
Term s (a :--> b) -> Term s a -> Term s b
# Term s (PInteger :--> (PInteger :--> PBool))
f Term
s
(PInteger
:--> (PMap 'Sorted PTokenName PInteger
:--> (PMap 'Sorted PTokenName PInteger :--> PBool)))
-> Term s PInteger
-> Term
s
(PMap 'Sorted PTokenName PInteger
:--> (PMap 'Sorted PTokenName PInteger :--> PBool))
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
(PMap 'Sorted PTokenName PInteger
:--> (PMap
'Sorted PCurrencySymbol (PMap 'Sorted PTokenName PInteger)
:--> (PMap
'Sorted PCurrencySymbol (PMap 'Sorted PTokenName PInteger)
:--> PBool)))
-> Term s (PMap 'Sorted PTokenName PInteger)
-> Term
s
(PMap 'Sorted PCurrencySymbol (PMap 'Sorted PTokenName PInteger)
:--> (PMap
'Sorted PCurrencySymbol (PMap 'Sorted PTokenName PInteger)
:--> PBool))
forall (s :: S) (a :: S -> Type) (b :: S -> Type).
Term s (a :--> b) -> Term s a -> Term s b
# Term s (PMap 'Sorted PTokenName PInteger)
forall (s :: S) (k :: S -> Type) (v :: S -> Type).
Term s (PMap 'Sorted k v)
AssocMap.pempty
punionResolvingCollisionsWith ::
forall (any0 :: AmountGuarantees) (any1 :: AmountGuarantees) (s :: S).
AssocMap.Commutativity ->
Term
s
( (PInteger :--> PInteger :--> PInteger)
:--> PValue 'AssocMap.Sorted any0
:--> PValue 'AssocMap.Sorted any1
:--> PValue 'AssocMap.Sorted 'NoGuarantees
)
punionResolvingCollisionsWith :: forall (any0 :: AmountGuarantees) (any1 :: AmountGuarantees)
(s :: S).
Commutativity
-> Term
s
((PInteger :--> (PInteger :--> PInteger))
:--> (PValue 'Sorted any0
:--> (PValue 'Sorted any1 :--> PValue 'Sorted 'NoGuarantees)))
punionResolvingCollisionsWith Commutativity
commutativity = ClosedTerm
((PInteger :--> (PInteger :--> PInteger))
:--> (PValue 'Sorted any0
:--> (PValue 'Sorted any1 :--> PValue 'Sorted 'NoGuarantees)))
-> Term
s
((PInteger :--> (PInteger :--> PInteger))
:--> (PValue 'Sorted any0
:--> (PValue 'Sorted any1 :--> PValue 'Sorted 'NoGuarantees)))
forall (a :: S -> Type) (s :: S).
HasCallStack =>
ClosedTerm a -> Term s a
phoistAcyclic (ClosedTerm
((PInteger :--> (PInteger :--> PInteger))
:--> (PValue 'Sorted any0
:--> (PValue 'Sorted any1 :--> PValue 'Sorted 'NoGuarantees)))
-> Term
s
((PInteger :--> (PInteger :--> PInteger))
:--> (PValue 'Sorted any0
:--> (PValue 'Sorted any1 :--> PValue 'Sorted 'NoGuarantees))))
-> ClosedTerm
((PInteger :--> (PInteger :--> PInteger))
:--> (PValue 'Sorted any0
:--> (PValue 'Sorted any1 :--> PValue 'Sorted 'NoGuarantees)))
-> Term
s
((PInteger :--> (PInteger :--> PInteger))
:--> (PValue 'Sorted any0
:--> (PValue 'Sorted any1 :--> PValue 'Sorted 'NoGuarantees)))
forall a b. (a -> b) -> a -> b
$
(Term s (PInteger :--> (PInteger :--> PInteger))
-> Term s (PValue 'Sorted any0)
-> Term s (PValue 'Sorted any1)
-> Term s (PValue 'Sorted 'NoGuarantees))
-> Term
s
((PInteger :--> (PInteger :--> PInteger))
:--> (PValue 'Sorted any0
:--> (PValue 'Sorted any1 :--> PValue 'Sorted 'NoGuarantees)))
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 (PValue 'Sorted any0)
-> Term s (PValue 'Sorted any1)
-> Term s (PValue 'Sorted 'NoGuarantees))
-> Term
s
(c
:--> (PValue 'Sorted any0
:--> (PValue 'Sorted any1 :--> PValue 'Sorted 'NoGuarantees)))
plam ((Term s (PInteger :--> (PInteger :--> PInteger))
-> Term s (PValue 'Sorted any0)
-> Term s (PValue 'Sorted any1)
-> Term s (PValue 'Sorted 'NoGuarantees))
-> Term
s
((PInteger :--> (PInteger :--> PInteger))
:--> (PValue 'Sorted any0
:--> (PValue 'Sorted any1 :--> PValue 'Sorted 'NoGuarantees))))
-> (Term s (PInteger :--> (PInteger :--> PInteger))
-> Term s (PValue 'Sorted any0)
-> Term s (PValue 'Sorted any1)
-> Term s (PValue 'Sorted 'NoGuarantees))
-> Term
s
((PInteger :--> (PInteger :--> PInteger))
:--> (PValue 'Sorted any0
:--> (PValue 'Sorted any1 :--> PValue 'Sorted 'NoGuarantees)))
forall a b. (a -> b) -> a -> b
$ \Term s (PInteger :--> (PInteger :--> PInteger))
combine Term s (PValue 'Sorted any0)
x Term s (PValue 'Sorted any1)
y ->
PValue 'Sorted 'NoGuarantees s
-> Term s (PValue 'Sorted 'NoGuarantees)
forall (a :: S -> Type) (s :: S). PlutusType a => a s -> Term s a
pcon (PValue 'Sorted 'NoGuarantees s
-> Term s (PValue 'Sorted 'NoGuarantees))
-> (Term
s (PMap 'Sorted PCurrencySymbol (PMap 'Sorted PTokenName PInteger))
-> PValue 'Sorted 'NoGuarantees s)
-> Term
s (PMap 'Sorted PCurrencySymbol (PMap 'Sorted PTokenName PInteger))
-> Term s (PValue 'Sorted 'NoGuarantees)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Term
s (PMap 'Sorted PCurrencySymbol (PMap 'Sorted PTokenName PInteger))
-> PValue 'Sorted 'NoGuarantees s
forall (keys :: KeyGuarantees) (amounts :: AmountGuarantees)
(s :: S).
Term s (PMap keys PCurrencySymbol (PMap keys PTokenName PInteger))
-> PValue keys amounts s
PValue (Term
s (PMap 'Sorted PCurrencySymbol (PMap 'Sorted PTokenName PInteger))
-> Term s (PValue 'Sorted 'NoGuarantees))
-> Term
s (PMap 'Sorted PCurrencySymbol (PMap 'Sorted PTokenName PInteger))
-> Term s (PValue 'Sorted 'NoGuarantees)
forall a b. (a -> b) -> a -> b
$
Commutativity
-> Term
s
((PMap 'Sorted PTokenName PInteger
:--> (PMap 'Sorted PTokenName PInteger
:--> PMap 'Sorted PTokenName PInteger))
:--> (PMap
'Sorted PCurrencySymbol (PMap 'Sorted PTokenName PInteger)
:--> (PMap
'Sorted PCurrencySymbol (PMap 'Sorted PTokenName PInteger)
:--> PMap
'Sorted PCurrencySymbol (PMap 'Sorted PTokenName PInteger))))
forall (k :: S -> Type) (v :: S -> Type) (s :: S).
(POrd k, PIsData k, PIsData v) =>
Commutativity
-> Term
s
((v :--> (v :--> v))
:--> (PMap 'Sorted k v
:--> (PMap 'Sorted k v :--> PMap 'Sorted k v)))
AssocMap.punionResolvingCollisionsWith Commutativity
commutativity
# plam (\x' y' -> AssocMap.punionResolvingCollisionsWith commutativity # combine # x' # y')
# pto x
# pto y
pnormalize ::
forall (any :: AmountGuarantees) (s :: S).
Term s (PValue 'AssocMap.Sorted any :--> PValue 'AssocMap.Sorted 'NonZero)
pnormalize :: forall (any :: AmountGuarantees) (s :: S).
Term s (PValue 'Sorted any :--> PValue 'Sorted 'NonZero)
pnormalize = ClosedTerm (PValue 'Sorted any :--> PValue 'Sorted 'NonZero)
-> Term s (PValue 'Sorted any :--> PValue 'Sorted 'NonZero)
forall (a :: S -> Type) (s :: S).
HasCallStack =>
ClosedTerm a -> Term s a
phoistAcyclic (ClosedTerm (PValue 'Sorted any :--> PValue 'Sorted 'NonZero)
-> Term s (PValue 'Sorted any :--> PValue 'Sorted 'NonZero))
-> ClosedTerm (PValue 'Sorted any :--> PValue 'Sorted 'NonZero)
-> Term s (PValue 'Sorted any :--> PValue 'Sorted 'NonZero)
forall a b. (a -> b) -> a -> b
$
(Term s (PValue 'Sorted any) -> Term s (PValue 'Sorted 'NonZero))
-> Term s (PValue 'Sorted any :--> PValue 'Sorted 'NonZero)
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 (PValue 'Sorted 'NonZero))
-> Term s (c :--> PValue 'Sorted 'NonZero)
plam ((Term s (PValue 'Sorted any) -> Term s (PValue 'Sorted 'NonZero))
-> Term s (PValue 'Sorted any :--> PValue 'Sorted 'NonZero))
-> (Term s (PValue 'Sorted any)
-> Term s (PValue 'Sorted 'NonZero))
-> Term s (PValue 'Sorted any :--> PValue 'Sorted 'NonZero)
forall a b. (a -> b) -> a -> b
$ \Term s (PValue 'Sorted any)
value ->
PValue 'Sorted 'NonZero s -> Term s (PValue 'Sorted 'NonZero)
forall (a :: S -> Type) (s :: S). PlutusType a => a s -> Term s a
pcon (PValue 'Sorted 'NonZero s -> Term s (PValue 'Sorted 'NonZero))
-> (Term
s (PMap 'Sorted PCurrencySymbol (PMap 'Sorted PTokenName PInteger))
-> PValue 'Sorted 'NonZero s)
-> Term
s (PMap 'Sorted PCurrencySymbol (PMap 'Sorted PTokenName PInteger))
-> Term s (PValue 'Sorted 'NonZero)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Term
s (PMap 'Sorted PCurrencySymbol (PMap 'Sorted PTokenName PInteger))
-> PValue 'Sorted 'NonZero s
forall (keys :: KeyGuarantees) (amounts :: AmountGuarantees)
(s :: S).
Term s (PMap keys PCurrencySymbol (PMap keys PTokenName PInteger))
-> PValue keys amounts s
PValue (Term
s (PMap 'Sorted PCurrencySymbol (PMap 'Sorted PTokenName PInteger))
-> Term s (PValue 'Sorted 'NonZero))
-> Term
s (PMap 'Sorted PCurrencySymbol (PMap 'Sorted PTokenName PInteger))
-> Term s (PValue 'Sorted 'NonZero)
forall a b. (a -> b) -> a -> b
$
Term
s
((PMap 'Sorted PTokenName PInteger
:--> PMaybe (PMap 'Sorted PTokenName PInteger))
:--> (PMap
'Sorted PCurrencySymbol (PMap 'Sorted PTokenName PInteger)
:--> PMap
'Sorted PCurrencySymbol (PMap 'Sorted PTokenName PInteger)))
forall (g :: KeyGuarantees) (k :: S -> Type) (a :: S -> Type)
(b :: S -> Type) (s :: S).
(PIsData a, PIsData b) =>
Term s ((a :--> PMaybe b) :--> (PMap g k a :--> PMap g k b))
AssocMap.pmapMaybe Term
s
((PMap 'Sorted PTokenName PInteger
:--> PMaybe (PMap 'Sorted PTokenName PInteger))
:--> (PMap
'Sorted PCurrencySymbol (PMap 'Sorted PTokenName PInteger)
:--> PMap
'Sorted PCurrencySymbol (PMap 'Sorted PTokenName PInteger)))
-> Term
s
(PMap 'Sorted PTokenName PInteger
:--> PMaybe (PMap 'Sorted PTokenName PInteger))
-> Term
s
(PMap 'Sorted PCurrencySymbol (PMap 'Sorted PTokenName PInteger)
:--> PMap
'Sorted PCurrencySymbol (PMap 'Sorted PTokenName PInteger))
forall (s :: S) (a :: S -> Type) (b :: S -> Type).
Term s (a :--> b) -> Term s a -> Term s b
# (Term s (PMap 'Sorted PTokenName PInteger)
-> Term s (PMaybe (PMap 'Sorted PTokenName PInteger)))
-> Term
s
(PMap 'Sorted PTokenName PInteger
:--> PMaybe (PMap 'Sorted PTokenName PInteger))
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 (PMap 'Sorted PTokenName PInteger)))
-> Term s (c :--> PMaybe (PMap 'Sorted PTokenName PInteger))
plam Term s (PMap 'Sorted PTokenName PInteger)
-> Term s (PMaybe (PMap 'Sorted PTokenName PInteger))
forall (s' :: S) (k :: S -> Type) (any1 :: KeyGuarantees).
Term s' (PMap any1 k PInteger)
-> Term s' (PMaybe (PMap any1 k PInteger))
normalizeTokenMap Term
s
(PMap 'Sorted PCurrencySymbol (PMap 'Sorted PTokenName PInteger)
:--> PMap
'Sorted PCurrencySymbol (PMap 'Sorted PTokenName PInteger))
-> Term
s (PMap 'Sorted PCurrencySymbol (PMap 'Sorted PTokenName PInteger))
-> Term
s (PMap 'Sorted PCurrencySymbol (PMap 'Sorted PTokenName PInteger))
forall (s :: S) (a :: S -> Type) (b :: S -> Type).
Term s (a :--> b) -> Term s a -> Term s b
# Term s (PValue 'Sorted any) -> Term s (PInner (PValue 'Sorted any))
forall (s :: S) (a :: S -> Type). Term s a -> Term s (PInner a)
pto Term s (PValue 'Sorted any)
value
where
normalizeTokenMap ::
forall (s' :: S) (k :: S -> Type) (any1 :: AssocMap.KeyGuarantees).
Term s' (AssocMap.PMap any1 k PInteger) ->
Term s' (PMaybe (AssocMap.PMap any1 k PInteger))
normalizeTokenMap :: forall (s' :: S) (k :: S -> Type) (any1 :: KeyGuarantees).
Term s' (PMap any1 k PInteger)
-> Term s' (PMaybe (PMap any1 k PInteger))
normalizeTokenMap Term s' (PMap any1 k PInteger)
tokenMap =
Term s' (PMap any1 k PInteger)
-> (Term s' (PMap any1 k PInteger)
-> Term s' (PMaybe (PMap any1 k PInteger)))
-> Term s' (PMaybe (PMap any1 k PInteger))
forall (s :: S) (a :: S -> Type) (b :: S -> Type).
Term s a -> (Term s a -> Term s b) -> Term s b
plet (Term
s'
((PAsData PInteger :--> PMaybe (PAsData PInteger))
:--> (PMap any1 k PInteger :--> PMap any1 k PInteger))
forall (g :: KeyGuarantees) (k :: S -> Type) (a :: S -> Type)
(b :: S -> Type) (s :: S).
Term
s
((PAsData a :--> PMaybe (PAsData b))
:--> (PMap g k a :--> PMap g k b))
AssocMap.pmapMaybeData Term
s'
((PAsData PInteger :--> PMaybe (PAsData PInteger))
:--> (PMap any1 k PInteger :--> PMap any1 k PInteger))
-> Term s' (PAsData PInteger :--> PMaybe (PAsData PInteger))
-> Term s' (PMap any1 k PInteger :--> PMap any1 k PInteger)
forall (s :: S) (a :: S -> Type) (b :: S -> Type).
Term s (a :--> b) -> Term s a -> Term s b
# (Term s' (PAsData PInteger) -> Term s' (PMaybe (PAsData PInteger)))
-> Term s' (PAsData PInteger :--> PMaybe (PAsData PInteger))
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 (PAsData PInteger)))
-> Term s' (c :--> PMaybe (PAsData PInteger))
plam Term s' (PAsData PInteger) -> Term s' (PMaybe (PAsData PInteger))
forall (s' :: S).
Term s' (PAsData PInteger) -> Term s' (PMaybe (PAsData PInteger))
nonZero Term s' (PMap any1 k PInteger :--> PMap any1 k PInteger)
-> Term s' (PMap any1 k PInteger) -> Term s' (PMap any1 k PInteger)
forall (s :: S) (a :: S -> Type) (b :: S -> Type).
Term s (a :--> b) -> Term s a -> Term s b
# Term s' (PMap any1 k PInteger)
tokenMap) ((Term s' (PMap any1 k PInteger)
-> Term s' (PMaybe (PMap any1 k PInteger)))
-> Term s' (PMaybe (PMap any1 k PInteger)))
-> (Term s' (PMap any1 k PInteger)
-> Term s' (PMaybe (PMap any1 k PInteger)))
-> Term s' (PMaybe (PMap any1 k PInteger))
forall a b. (a -> b) -> a -> b
$ \Term s' (PMap any1 k PInteger)
normalMap ->
Term s' PBool
-> Term s' (PMaybe (PMap any1 k PInteger))
-> Term s' (PMaybe (PMap any1 k PInteger))
-> Term s' (PMaybe (PMap any1 k PInteger))
forall (a :: S -> Type) (s :: S).
Term s PBool -> Term s a -> Term s a -> Term s a
pif
(Term s' (PMap any1 k PInteger :--> PBool)
forall (any :: KeyGuarantees) (k :: S -> Type) (v :: S -> Type)
(s :: S).
Term s (PMap any k v :--> PBool)
AssocMap.pnull Term s' (PMap any1 k PInteger :--> PBool)
-> Term s' (PMap any1 k PInteger) -> Term s' PBool
forall (s :: S) (a :: S -> Type) (b :: S -> Type).
Term s (a :--> b) -> Term s a -> Term s b
# Term s' (PMap any1 k PInteger)
normalMap)
(PMaybe (PMap any1 k PInteger) s'
-> Term s' (PMaybe (PMap any1 k PInteger))
forall (a :: S -> Type) (s :: S). PlutusType a => a s -> Term s a
pcon PMaybe (PMap any1 k PInteger) s'
forall (a :: S -> Type) (s :: S). PMaybe a s
PNothing)
(PMaybe (PMap any1 k PInteger) s'
-> Term s' (PMaybe (PMap any1 k PInteger))
forall (a :: S -> Type) (s :: S). PlutusType a => a s -> Term s a
pcon (PMaybe (PMap any1 k PInteger) s'
-> Term s' (PMaybe (PMap any1 k PInteger)))
-> PMaybe (PMap any1 k PInteger) s'
-> Term s' (PMaybe (PMap any1 k PInteger))
forall a b. (a -> b) -> a -> b
$ Term s' (PMap any1 k PInteger) -> PMaybe (PMap any1 k PInteger) s'
forall (a :: S -> Type) (s :: S). Term s a -> PMaybe a s
PJust Term s' (PMap any1 k PInteger)
normalMap)
nonZero ::
forall (s' :: S).
Term s' (PAsData PInteger) ->
Term s' (PMaybe (PAsData PInteger))
nonZero :: forall (s' :: S).
Term s' (PAsData PInteger) -> Term s' (PMaybe (PAsData PInteger))
nonZero Term s' (PAsData PInteger)
intData =
Term s' PBool
-> Term s' (PMaybe (PAsData PInteger))
-> Term s' (PMaybe (PAsData PInteger))
-> Term s' (PMaybe (PAsData PInteger))
forall (a :: S -> Type) (s :: S).
Term s PBool -> Term s a -> Term s a -> Term s a
pif (Term s' (PAsData PInteger)
intData Term s' (PAsData PInteger)
-> Term s' (PAsData PInteger) -> Term s' PBool
forall (s :: S).
Term s (PAsData PInteger)
-> Term s (PAsData PInteger) -> Term s PBool
forall (t :: S -> Type) (s :: S).
PEq t =>
Term s t -> Term s t -> Term s PBool
#== Term s' (PAsData PInteger)
forall (s :: S). Term s (PAsData PInteger)
zeroData) (PMaybe (PAsData PInteger) s' -> Term s' (PMaybe (PAsData PInteger))
forall (a :: S -> Type) (s :: S). PlutusType a => a s -> Term s a
pcon PMaybe (PAsData PInteger) s'
forall (a :: S -> Type) (s :: S). PMaybe a s
PNothing) (PMaybe (PAsData PInteger) s' -> Term s' (PMaybe (PAsData PInteger))
forall (a :: S -> Type) (s :: S). PlutusType a => a s -> Term s a
pcon (PMaybe (PAsData PInteger) s'
-> Term s' (PMaybe (PAsData PInteger)))
-> PMaybe (PAsData PInteger) s'
-> Term s' (PMaybe (PAsData PInteger))
forall a b. (a -> b) -> a -> b
$ Term s' (PAsData PInteger) -> PMaybe (PAsData PInteger) s'
forall (a :: S -> Type) (s :: S). Term s a -> PMaybe a s
PJust Term s' (PAsData PInteger)
intData)
passertPositive ::
forall (kg :: AssocMap.KeyGuarantees) (ag :: AmountGuarantees) (s :: S).
Term s (PValue kg ag :--> PValue kg 'Positive)
passertPositive :: forall (kg :: KeyGuarantees) (ag :: AmountGuarantees) (s :: S).
Term s (PValue kg ag :--> PValue kg 'Positive)
passertPositive = ClosedTerm (PValue kg ag :--> PValue kg 'Positive)
-> Term s (PValue kg ag :--> PValue kg 'Positive)
forall (a :: S -> Type) (s :: S).
HasCallStack =>
ClosedTerm a -> Term s a
phoistAcyclic (ClosedTerm (PValue kg ag :--> PValue kg 'Positive)
-> Term s (PValue kg ag :--> PValue kg 'Positive))
-> ClosedTerm (PValue kg ag :--> PValue kg 'Positive)
-> Term s (PValue kg ag :--> PValue kg 'Positive)
forall a b. (a -> b) -> a -> b
$
(Term s (PValue kg ag) -> Term s (PValue kg 'Positive))
-> Term s (PValue kg ag :--> PValue kg 'Positive)
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 (PValue kg 'Positive))
-> Term s (c :--> PValue kg 'Positive)
plam ((Term s (PValue kg ag) -> Term s (PValue kg 'Positive))
-> Term s (PValue kg ag :--> PValue kg 'Positive))
-> (Term s (PValue kg ag) -> Term s (PValue kg 'Positive))
-> Term s (PValue kg ag :--> PValue kg 'Positive)
forall a b. (a -> b) -> a -> b
$ \Term s (PValue kg ag)
value ->
Term s PBool
-> Term s (PValue kg 'Positive)
-> Term s (PValue kg 'Positive)
-> Term s (PValue kg 'Positive)
forall (a :: S -> Type) (s :: S).
Term s PBool -> Term s a -> Term s a -> Term s a
pif
( Term
s
((PMap kg PTokenName PInteger :--> PBool)
:--> (PMap kg PCurrencySymbol (PMap kg PTokenName PInteger)
:--> PBool))
forall (any :: KeyGuarantees) (k :: S -> Type) (v :: S -> Type)
(s :: S).
PIsData v =>
Term s ((v :--> PBool) :--> (PMap any k v :--> PBool))
AssocMap.pall
# plam (\submap -> AssocMap.pall # plam (0 #<) # submap)
# pto value
)
(Term s (PInner (PValue kg 'Positive))
-> Term s (PValue kg 'Positive)
forall (s :: S) (a :: S -> Type). Term s (PInner a) -> Term s a
punsafeDowncast (Term s (PInner (PValue kg 'Positive))
-> Term s (PValue kg 'Positive))
-> Term s (PInner (PValue kg 'Positive))
-> Term s (PValue kg 'Positive)
forall a b. (a -> b) -> a -> b
$ Term s (PValue kg ag) -> Term s (PInner (PValue kg ag))
forall (s :: S) (a :: S -> Type). Term s a -> Term s (PInner a)
pto Term s (PValue kg ag)
value)
(Term s PString -> Term s (PValue kg 'Positive)
forall (a :: S -> Type) (s :: S). Term s PString -> Term s a
ptraceInfoError Term s PString
"Negative amount in Value")
pconstantPositiveSingleton ::
forall (s :: S).
(forall (s' :: S). Term s' PCurrencySymbol) ->
(forall (s' :: S). Term s' PTokenName) ->
(forall (s' :: S). Term s' PInteger) ->
Term s (PValue 'AssocMap.Sorted 'Positive)
pconstantPositiveSingleton :: forall (s :: S).
(forall (s' :: S). Term s' PCurrencySymbol)
-> (forall (s' :: S). Term s' PTokenName)
-> (forall (s' :: S). Term s' PInteger)
-> Term s (PValue 'Sorted 'Positive)
pconstantPositiveSingleton forall (s' :: S). Term s' PCurrencySymbol
symbol forall (s' :: S). Term s' PTokenName
token forall (s' :: S). Term s' PInteger
amount
| (forall (s' :: S). Term s' PInteger) -> AsHaskell PInteger
forall (a :: S -> Type).
PLiftable a =>
(forall (s :: S). Term s a) -> AsHaskell a
plift Term s PInteger
forall (s' :: S). Term s' PInteger
amount AsHaskell PInteger -> AsHaskell PInteger -> Bool
forall a. Eq a => a -> a -> Bool
== AsHaskell PInteger
0 = Term s (PValue 'Sorted 'Positive)
forall a. Monoid a => a
mempty
| (forall (s' :: S). Term s' PInteger) -> AsHaskell PInteger
forall (a :: S -> Type).
PLiftable a =>
(forall (s :: S). Term s a) -> AsHaskell a
plift Term s PInteger
forall (s' :: S). Term s' PInteger
amount AsHaskell PInteger -> AsHaskell PInteger -> Bool
forall a. Ord a => a -> a -> Bool
< AsHaskell PInteger
0 = [Char] -> Term s (PValue 'Sorted 'Positive)
forall a. HasCallStack => [Char] -> a
error [Char]
"Negative amount"
| Bool
otherwise = Term s (PInner (PValue 'Sorted 'Positive))
-> Term s (PValue 'Sorted 'Positive)
forall (s :: S) (a :: S -> Type). Term s (PInner a) -> Term s a
punsafeDowncast (Term
s
(PCurrencySymbol
:--> (PMap 'Sorted PTokenName PInteger
:--> PMap
'Sorted PCurrencySymbol (PMap 'Sorted PTokenName PInteger)))
forall (k :: S -> Type) (v :: S -> Type) (s :: S).
(PIsData k, PIsData v) =>
Term s (k :--> (v :--> PMap 'Sorted k v))
AssocMap.psingleton Term
s
(PCurrencySymbol
:--> (PMap 'Sorted PTokenName PInteger
:--> PMap
'Sorted PCurrencySymbol (PMap 'Sorted PTokenName PInteger)))
-> Term s PCurrencySymbol
-> Term
s
(PMap 'Sorted PTokenName PInteger
:--> PMap
'Sorted PCurrencySymbol (PMap 'Sorted PTokenName PInteger))
forall (s :: S) (a :: S -> Type) (b :: S -> Type).
Term s (a :--> b) -> Term s a -> Term s b
# Term s PCurrencySymbol
forall (s' :: S). Term s' PCurrencySymbol
symbol Term
s
(PMap 'Sorted PTokenName PInteger
:--> PMap
'Sorted PCurrencySymbol (PMap 'Sorted PTokenName PInteger))
-> Term s (PMap 'Sorted PTokenName PInteger)
-> Term
s (PMap 'Sorted PCurrencySymbol (PMap 'Sorted PTokenName PInteger))
forall (s :: S) (a :: S -> Type) (b :: S -> Type).
Term s (a :--> b) -> Term s a -> Term s b
#$ Term
s
(PTokenName :--> (PInteger :--> PMap 'Sorted PTokenName PInteger))
forall (k :: S -> Type) (v :: S -> Type) (s :: S).
(PIsData k, PIsData v) =>
Term s (k :--> (v :--> PMap 'Sorted k v))
AssocMap.psingleton Term
s
(PTokenName :--> (PInteger :--> PMap 'Sorted PTokenName PInteger))
-> Term s PTokenName
-> Term s (PInteger :--> PMap 'Sorted PTokenName PInteger)
forall (s :: S) (a :: S -> Type) (b :: S -> Type).
Term s (a :--> b) -> Term s a -> Term s b
# Term s PTokenName
forall (s' :: S). Term s' PTokenName
token Term s (PInteger :--> PMap 'Sorted PTokenName PInteger)
-> Term s PInteger -> Term s (PMap 'Sorted PTokenName PInteger)
forall (s :: S) (a :: S -> Type) (b :: S -> Type).
Term s (a :--> b) -> Term s a -> Term s b
# Term s PInteger
forall (s' :: S). Term s' PInteger
amount)
padaSymbol :: forall (s :: S). Term s PCurrencySymbol
padaSymbol :: forall (s' :: S). Term s' PCurrencySymbol
padaSymbol = AsHaskell PCurrencySymbol -> Term s PCurrencySymbol
forall (a :: S -> Type) (s :: S).
PLiftable a =>
AsHaskell a -> Term s a
pconstant AsHaskell PCurrencySymbol
CurrencySymbol
Plutus.adaSymbol
padaSymbolData :: forall (s :: S). Term s (PAsData PCurrencySymbol)
padaSymbolData :: forall (s :: S). Term s (PAsData PCurrencySymbol)
padaSymbolData = Term s PCurrencySymbol -> Term s (PAsData PCurrencySymbol)
forall (a :: S -> Type) (s :: S).
PIsData a =>
Term s a -> Term s (PAsData a)
pdata Term s PCurrencySymbol
forall (s' :: S). Term s' PCurrencySymbol
padaSymbol
padaToken :: Term s PTokenName
padaToken :: forall (s' :: S). Term s' PTokenName
padaToken = AsHaskell PTokenName -> Term s PTokenName
forall (a :: S -> Type) (s :: S).
PLiftable a =>
AsHaskell a -> Term s a
pconstant AsHaskell PTokenName
TokenName
Plutus.adaToken
pforgetSorted ::
forall (a :: AmountGuarantees) (k :: AssocMap.KeyGuarantees) (s :: S).
Term s (PValue 'AssocMap.Sorted a) ->
Term s (PValue k a)
pforgetSorted :: forall (a :: AmountGuarantees) (k :: KeyGuarantees) (s :: S).
Term s (PValue 'Sorted a) -> Term s (PValue k a)
pforgetSorted = Term s (PValue 'Sorted a) -> Term s (PValue k a)
forall (b :: S -> Type) (a :: S -> Type) (s :: S).
Term s a -> Term s b
punsafeCoerce
psingleton ::
forall (s :: S).
Term
s
(PCurrencySymbol :--> PTokenName :--> PInteger :--> PValue 'AssocMap.Sorted 'NonZero)
psingleton :: forall (s :: S).
Term
s
(PCurrencySymbol
:--> (PTokenName :--> (PInteger :--> PValue 'Sorted 'NonZero)))
psingleton = (forall (s :: S).
Term
s
(PCurrencySymbol
:--> (PTokenName :--> (PInteger :--> PValue 'Sorted 'NonZero))))
-> Term
s
(PCurrencySymbol
:--> (PTokenName :--> (PInteger :--> PValue 'Sorted 'NonZero)))
forall (a :: S -> Type) (s :: S).
HasCallStack =>
ClosedTerm a -> Term s a
phoistAcyclic ((forall (s :: S).
Term
s
(PCurrencySymbol
:--> (PTokenName :--> (PInteger :--> PValue 'Sorted 'NonZero))))
-> Term
s
(PCurrencySymbol
:--> (PTokenName :--> (PInteger :--> PValue 'Sorted 'NonZero))))
-> (forall (s :: S).
Term
s
(PCurrencySymbol
:--> (PTokenName :--> (PInteger :--> PValue 'Sorted 'NonZero))))
-> Term
s
(PCurrencySymbol
:--> (PTokenName :--> (PInteger :--> PValue 'Sorted 'NonZero)))
forall a b. (a -> b) -> a -> b
$
(Term s PCurrencySymbol
-> Term s PTokenName
-> Term s PInteger
-> Term s (PValue 'Sorted 'NonZero))
-> Term
s
(PCurrencySymbol
:--> (PTokenName :--> (PInteger :--> PValue 'Sorted 'NonZero)))
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 PTokenName
-> Term s PInteger
-> Term s (PValue 'Sorted 'NonZero))
-> Term
s
(c :--> (PTokenName :--> (PInteger :--> PValue 'Sorted 'NonZero)))
plam ((Term s PCurrencySymbol
-> Term s PTokenName
-> Term s PInteger
-> Term s (PValue 'Sorted 'NonZero))
-> Term
s
(PCurrencySymbol
:--> (PTokenName :--> (PInteger :--> PValue 'Sorted 'NonZero))))
-> (Term s PCurrencySymbol
-> Term s PTokenName
-> Term s PInteger
-> Term s (PValue 'Sorted 'NonZero))
-> Term
s
(PCurrencySymbol
:--> (PTokenName :--> (PInteger :--> PValue 'Sorted 'NonZero)))
forall a b. (a -> b) -> a -> b
$ \Term s PCurrencySymbol
symbol Term s PTokenName
token Term s PInteger
amount ->
Term s PBool
-> Term s (PValue 'Sorted 'NonZero)
-> Term s (PValue 'Sorted 'NonZero)
-> Term s (PValue 'Sorted 'NonZero)
forall (a :: S -> Type) (s :: S).
Term s PBool -> Term s a -> Term s a -> Term s a
pif
(Term s PInteger
amount 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)
Term s (PValue 'Sorted 'NonZero)
forall a. Monoid a => a
mempty
(Term s (PInner (PValue 'Sorted 'NonZero))
-> Term s (PValue 'Sorted 'NonZero)
forall (s :: S) (a :: S -> Type). Term s (PInner a) -> Term s a
punsafeDowncast (Term s (PInner (PValue 'Sorted 'NonZero))
-> Term s (PValue 'Sorted 'NonZero))
-> Term s (PInner (PValue 'Sorted 'NonZero))
-> Term s (PValue 'Sorted 'NonZero)
forall a b. (a -> b) -> a -> b
$ Term
s
(PCurrencySymbol
:--> (PMap 'Sorted PTokenName PInteger
:--> PMap
'Sorted PCurrencySymbol (PMap 'Sorted PTokenName PInteger)))
forall (k :: S -> Type) (v :: S -> Type) (s :: S).
(PIsData k, PIsData v) =>
Term s (k :--> (v :--> PMap 'Sorted k v))
AssocMap.psingleton Term
s
(PCurrencySymbol
:--> (PMap 'Sorted PTokenName PInteger
:--> PMap
'Sorted PCurrencySymbol (PMap 'Sorted PTokenName PInteger)))
-> Term s PCurrencySymbol
-> Term
s
(PMap 'Sorted PTokenName PInteger
:--> PMap
'Sorted PCurrencySymbol (PMap 'Sorted PTokenName PInteger))
forall (s :: S) (a :: S -> Type) (b :: S -> Type).
Term s (a :--> b) -> Term s a -> Term s b
# Term s PCurrencySymbol
symbol Term
s
(PMap 'Sorted PTokenName PInteger
:--> PMap
'Sorted PCurrencySymbol (PMap 'Sorted PTokenName PInteger))
-> Term s (PMap 'Sorted PTokenName PInteger)
-> Term
s (PMap 'Sorted PCurrencySymbol (PMap 'Sorted PTokenName PInteger))
forall (s :: S) (a :: S -> Type) (b :: S -> Type).
Term s (a :--> b) -> Term s a -> Term s b
#$ Term
s
(PTokenName :--> (PInteger :--> PMap 'Sorted PTokenName PInteger))
forall (k :: S -> Type) (v :: S -> Type) (s :: S).
(PIsData k, PIsData v) =>
Term s (k :--> (v :--> PMap 'Sorted k v))
AssocMap.psingleton Term
s
(PTokenName :--> (PInteger :--> PMap 'Sorted PTokenName PInteger))
-> Term s PTokenName
-> Term s (PInteger :--> PMap 'Sorted PTokenName PInteger)
forall (s :: S) (a :: S -> Type) (b :: S -> Type).
Term s (a :--> b) -> Term s a -> Term s b
# Term s PTokenName
token Term s (PInteger :--> PMap 'Sorted PTokenName PInteger)
-> Term s PInteger -> Term s (PMap 'Sorted PTokenName PInteger)
forall (s :: S) (a :: S -> Type) (b :: S -> Type).
Term s (a :--> b) -> Term s a -> Term s b
# Term s PInteger
amount)
psingletonData ::
forall (s :: S).
Term
s
( PAsData PCurrencySymbol
:--> PAsData PTokenName
:--> PAsData PInteger
:--> PValue 'AssocMap.Sorted 'NonZero
)
psingletonData :: forall (s :: S).
Term
s
(PAsData PCurrencySymbol
:--> (PAsData PTokenName
:--> (PAsData PInteger :--> PValue 'Sorted 'NonZero)))
psingletonData = (forall (s :: S).
Term
s
(PAsData PCurrencySymbol
:--> (PAsData PTokenName
:--> (PAsData PInteger :--> PValue 'Sorted 'NonZero))))
-> Term
s
(PAsData PCurrencySymbol
:--> (PAsData PTokenName
:--> (PAsData PInteger :--> PValue 'Sorted 'NonZero)))
forall (a :: S -> Type) (s :: S).
HasCallStack =>
ClosedTerm a -> Term s a
phoistAcyclic ((forall (s :: S).
Term
s
(PAsData PCurrencySymbol
:--> (PAsData PTokenName
:--> (PAsData PInteger :--> PValue 'Sorted 'NonZero))))
-> Term
s
(PAsData PCurrencySymbol
:--> (PAsData PTokenName
:--> (PAsData PInteger :--> PValue 'Sorted 'NonZero))))
-> (forall (s :: S).
Term
s
(PAsData PCurrencySymbol
:--> (PAsData PTokenName
:--> (PAsData PInteger :--> PValue 'Sorted 'NonZero))))
-> Term
s
(PAsData PCurrencySymbol
:--> (PAsData PTokenName
:--> (PAsData PInteger :--> PValue 'Sorted 'NonZero)))
forall a b. (a -> b) -> a -> b
$
(Term s (PAsData PCurrencySymbol)
-> Term s (PAsData PTokenName)
-> Term s (PAsData PInteger)
-> Term s (PValue 'Sorted 'NonZero))
-> Term
s
(PAsData PCurrencySymbol
:--> (PAsData PTokenName
:--> (PAsData PInteger :--> PValue 'Sorted 'NonZero)))
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 (PAsData PTokenName)
-> Term s (PAsData PInteger)
-> Term s (PValue 'Sorted 'NonZero))
-> Term
s
(c
:--> (PAsData PTokenName
:--> (PAsData PInteger :--> PValue 'Sorted 'NonZero)))
plam ((Term s (PAsData PCurrencySymbol)
-> Term s (PAsData PTokenName)
-> Term s (PAsData PInteger)
-> Term s (PValue 'Sorted 'NonZero))
-> Term
s
(PAsData PCurrencySymbol
:--> (PAsData PTokenName
:--> (PAsData PInteger :--> PValue 'Sorted 'NonZero))))
-> (Term s (PAsData PCurrencySymbol)
-> Term s (PAsData PTokenName)
-> Term s (PAsData PInteger)
-> Term s (PValue 'Sorted 'NonZero))
-> Term
s
(PAsData PCurrencySymbol
:--> (PAsData PTokenName
:--> (PAsData PInteger :--> PValue 'Sorted 'NonZero)))
forall a b. (a -> b) -> a -> b
$ \Term s (PAsData PCurrencySymbol)
symbol Term s (PAsData PTokenName)
token Term s (PAsData PInteger)
amount ->
Term s PBool
-> Term s (PValue 'Sorted 'NonZero)
-> Term s (PValue 'Sorted 'NonZero)
-> Term s (PValue 'Sorted 'NonZero)
forall (a :: S -> Type) (s :: S).
Term s PBool -> Term s a -> Term s a -> Term s a
pif
(Term s (PAsData PInteger)
amount Term s (PAsData PInteger)
-> Term s (PAsData PInteger) -> Term s PBool
forall (s :: S).
Term s (PAsData PInteger)
-> Term s (PAsData PInteger) -> Term s PBool
forall (t :: S -> Type) (s :: S).
PEq t =>
Term s t -> Term s t -> Term s PBool
#== Term s (PAsData PInteger)
forall (s :: S). Term s (PAsData PInteger)
zeroData)
Term s (PValue 'Sorted 'NonZero)
forall a. Monoid a => a
mempty
( Term s (PInner (PValue 'Sorted 'NonZero))
-> Term s (PValue 'Sorted 'NonZero)
forall (s :: S) (a :: S -> Type). Term s (PInner a) -> Term s a
punsafeDowncast
( Term
s
(PAsData PCurrencySymbol
:--> (PAsData (PMap 'Sorted PTokenName PInteger)
:--> PMap
'Sorted PCurrencySymbol (PMap 'Sorted PTokenName PInteger)))
forall (k :: S -> Type) (v :: S -> Type) (s :: S).
Term s (PAsData k :--> (PAsData v :--> PMap 'Sorted k v))
AssocMap.psingletonData
# symbol
#$ pdata
$ AssocMap.psingletonData # token # amount
)
)
pvalueOf ::
forall (anyKey :: AssocMap.KeyGuarantees) (anyAmount :: AmountGuarantees) (s :: S).
Term s (PValue anyKey anyAmount :--> PCurrencySymbol :--> PTokenName :--> PInteger)
pvalueOf :: forall (anyKey :: KeyGuarantees) (anyAmount :: AmountGuarantees)
(s :: S).
Term
s
(PValue anyKey anyAmount
:--> (PCurrencySymbol :--> (PTokenName :--> PInteger)))
pvalueOf = ClosedTerm
(PValue anyKey anyAmount
:--> (PCurrencySymbol :--> (PTokenName :--> PInteger)))
-> Term
s
(PValue anyKey anyAmount
:--> (PCurrencySymbol :--> (PTokenName :--> PInteger)))
forall (a :: S -> Type) (s :: S).
HasCallStack =>
ClosedTerm a -> Term s a
phoistAcyclic (ClosedTerm
(PValue anyKey anyAmount
:--> (PCurrencySymbol :--> (PTokenName :--> PInteger)))
-> Term
s
(PValue anyKey anyAmount
:--> (PCurrencySymbol :--> (PTokenName :--> PInteger))))
-> ClosedTerm
(PValue anyKey anyAmount
:--> (PCurrencySymbol :--> (PTokenName :--> PInteger)))
-> Term
s
(PValue anyKey anyAmount
:--> (PCurrencySymbol :--> (PTokenName :--> PInteger)))
forall a b. (a -> b) -> a -> b
$
(Term s (PValue anyKey anyAmount)
-> Term s PCurrencySymbol -> Term s PTokenName -> Term s PInteger)
-> Term
s
(PValue anyKey anyAmount
:--> (PCurrencySymbol :--> (PTokenName :--> PInteger)))
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 PCurrencySymbol -> Term s PTokenName -> Term s PInteger)
-> Term
s (c :--> (PCurrencySymbol :--> (PTokenName :--> PInteger)))
plam ((Term s (PValue anyKey anyAmount)
-> Term s PCurrencySymbol -> Term s PTokenName -> Term s PInteger)
-> Term
s
(PValue anyKey anyAmount
:--> (PCurrencySymbol :--> (PTokenName :--> PInteger))))
-> (Term s (PValue anyKey anyAmount)
-> Term s PCurrencySymbol -> Term s PTokenName -> Term s PInteger)
-> Term
s
(PValue anyKey anyAmount
:--> (PCurrencySymbol :--> (PTokenName :--> PInteger)))
forall a b. (a -> b) -> a -> b
$ \Term s (PValue anyKey anyAmount)
value Term s PCurrencySymbol
symbol Term s PTokenName
token ->
Term
s
(PCurrencySymbol
:--> (PInteger
:--> ((PAsData (PMap anyKey PTokenName PInteger) :--> PInteger)
:--> (PMap anyKey PCurrencySymbol (PMap anyKey PTokenName PInteger)
:--> PInteger))))
forall (k :: S -> Type) (v :: S -> Type) (any :: KeyGuarantees)
(r :: S -> Type) (s :: S).
PIsData k =>
Term
s (k :--> (r :--> ((PAsData v :--> r) :--> (PMap any k v :--> r))))
AssocMap.pfoldAt
# symbol
# 0
# plam (\m -> AssocMap.pfoldAt # token # 0 # plam pfromData # pfromData m)
# pto value
plovelaceValueOf ::
forall (v :: AmountGuarantees) (s :: S).
Term s (PValue 'AssocMap.Sorted v :--> PInteger)
plovelaceValueOf :: forall (v :: AmountGuarantees) (s :: S).
Term s (PValue 'Sorted v :--> PInteger)
plovelaceValueOf = ClosedTerm (PValue 'Sorted v :--> PInteger)
-> Term s (PValue 'Sorted v :--> PInteger)
forall (a :: S -> Type) (s :: S).
HasCallStack =>
ClosedTerm a -> Term s a
phoistAcyclic (ClosedTerm (PValue 'Sorted v :--> PInteger)
-> Term s (PValue 'Sorted v :--> PInteger))
-> ClosedTerm (PValue 'Sorted v :--> PInteger)
-> Term s (PValue 'Sorted v :--> PInteger)
forall a b. (a -> b) -> a -> b
$
(Term s (PValue 'Sorted v) -> Term s PInteger)
-> Term s (PValue 'Sorted v :--> PInteger)
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 PInteger) -> Term s (c :--> PInteger)
plam ((Term s (PValue 'Sorted v) -> Term s PInteger)
-> Term s (PValue 'Sorted v :--> PInteger))
-> (Term s (PValue 'Sorted v) -> Term s PInteger)
-> Term s (PValue 'Sorted v :--> PInteger)
forall a b. (a -> b) -> a -> b
$ \Term s (PValue 'Sorted v)
value ->
Term
s
(PBuiltinList
(PBuiltinPair
(PAsData PCurrencySymbol)
(PAsData (PMap 'Sorted PTokenName PInteger))))
-> (PBuiltinList
(PBuiltinPair
(PAsData PCurrencySymbol)
(PAsData (PMap 'Sorted PTokenName PInteger)))
s
-> Term s PInteger)
-> Term s PInteger
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 (PMap 'Sorted PCurrencySymbol (PMap 'Sorted PTokenName PInteger))
-> Term
s
(PInner
(PMap 'Sorted PCurrencySymbol (PMap 'Sorted PTokenName PInteger)))
forall (s :: S) (a :: S -> Type). Term s a -> Term s (PInner a)
pto (Term
s (PMap 'Sorted PCurrencySymbol (PMap 'Sorted PTokenName PInteger))
-> Term
s
(PInner
(PMap 'Sorted PCurrencySymbol (PMap 'Sorted PTokenName PInteger))))
-> Term
s (PMap 'Sorted PCurrencySymbol (PMap 'Sorted PTokenName PInteger))
-> Term
s
(PInner
(PMap 'Sorted PCurrencySymbol (PMap 'Sorted PTokenName PInteger)))
forall a b. (a -> b) -> a -> b
$ Term s (PValue 'Sorted v) -> Term s (PInner (PValue 'Sorted v))
forall (s :: S) (a :: S -> Type). Term s a -> Term s (PInner a)
pto Term s (PValue 'Sorted v)
value) ((PBuiltinList
(PBuiltinPair
(PAsData PCurrencySymbol)
(PAsData (PMap 'Sorted PTokenName PInteger)))
s
-> Term s PInteger)
-> Term s PInteger)
-> (PBuiltinList
(PBuiltinPair
(PAsData PCurrencySymbol)
(PAsData (PMap 'Sorted PTokenName PInteger)))
s
-> Term s PInteger)
-> Term s PInteger
forall a b. (a -> b) -> a -> b
$ \case
PBuiltinList
(PBuiltinPair
(PAsData PCurrencySymbol)
(PAsData (PMap 'Sorted PTokenName PInteger)))
s
PNil -> Term s PInteger
0
PCons Term
s
(PBuiltinPair
(PAsData PCurrencySymbol)
(PAsData (PMap 'Sorted PTokenName PInteger)))
x Term
s
(PBuiltinList
(PBuiltinPair
(PAsData PCurrencySymbol)
(PAsData (PMap 'Sorted PTokenName PInteger))))
_ ->
Term s (PBool :--> (PInteger :--> (PInteger :--> PInteger)))
forall (a :: S -> Type) (s :: S).
Term s (PBool :--> (a :--> (a :--> a)))
pif'
# (pfstBuiltin # x #== padaSymbolData)
# pfromData (psndBuiltin #$ phead #$ pto $ pfromData $ psndBuiltin # x)
# 0
pleftBiasedCurrencyUnion ::
forall (any0 :: AmountGuarantees) (any1 :: AmountGuarantees) (s :: S).
Term
s
( PValue 'AssocMap.Sorted any0
:--> PValue 'AssocMap.Sorted any1
:--> PValue 'AssocMap.Sorted 'NoGuarantees
)
pleftBiasedCurrencyUnion :: forall (any0 :: AmountGuarantees) (any1 :: AmountGuarantees)
(s :: S).
Term
s
(PValue 'Sorted any0
:--> (PValue 'Sorted any1 :--> PValue 'Sorted 'NoGuarantees))
pleftBiasedCurrencyUnion = ClosedTerm
(PValue 'Sorted any0
:--> (PValue 'Sorted any1 :--> PValue 'Sorted 'NoGuarantees))
-> Term
s
(PValue 'Sorted any0
:--> (PValue 'Sorted any1 :--> PValue 'Sorted 'NoGuarantees))
forall (a :: S -> Type) (s :: S).
HasCallStack =>
ClosedTerm a -> Term s a
phoistAcyclic (ClosedTerm
(PValue 'Sorted any0
:--> (PValue 'Sorted any1 :--> PValue 'Sorted 'NoGuarantees))
-> Term
s
(PValue 'Sorted any0
:--> (PValue 'Sorted any1 :--> PValue 'Sorted 'NoGuarantees)))
-> ClosedTerm
(PValue 'Sorted any0
:--> (PValue 'Sorted any1 :--> PValue 'Sorted 'NoGuarantees))
-> Term
s
(PValue 'Sorted any0
:--> (PValue 'Sorted any1 :--> PValue 'Sorted 'NoGuarantees))
forall a b. (a -> b) -> a -> b
$
(Term s (PValue 'Sorted any0)
-> Term s (PValue 'Sorted any1)
-> Term s (PValue 'Sorted 'NoGuarantees))
-> Term
s
(PValue 'Sorted any0
:--> (PValue 'Sorted any1 :--> PValue 'Sorted 'NoGuarantees))
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 (PValue 'Sorted any1)
-> Term s (PValue 'Sorted 'NoGuarantees))
-> Term
s (c :--> (PValue 'Sorted any1 :--> PValue 'Sorted 'NoGuarantees))
plam ((Term s (PValue 'Sorted any0)
-> Term s (PValue 'Sorted any1)
-> Term s (PValue 'Sorted 'NoGuarantees))
-> Term
s
(PValue 'Sorted any0
:--> (PValue 'Sorted any1 :--> PValue 'Sorted 'NoGuarantees)))
-> (Term s (PValue 'Sorted any0)
-> Term s (PValue 'Sorted any1)
-> Term s (PValue 'Sorted 'NoGuarantees))
-> Term
s
(PValue 'Sorted any0
:--> (PValue 'Sorted any1 :--> PValue 'Sorted 'NoGuarantees))
forall a b. (a -> b) -> a -> b
$
\Term s (PValue 'Sorted any0)
x Term s (PValue 'Sorted any1)
y -> PValue 'Sorted 'NoGuarantees s
-> Term s (PValue 'Sorted 'NoGuarantees)
forall (a :: S -> Type) (s :: S). PlutusType a => a s -> Term s a
pcon (PValue 'Sorted 'NoGuarantees s
-> Term s (PValue 'Sorted 'NoGuarantees))
-> (Term
s (PMap 'Sorted PCurrencySymbol (PMap 'Sorted PTokenName PInteger))
-> PValue 'Sorted 'NoGuarantees s)
-> Term
s (PMap 'Sorted PCurrencySymbol (PMap 'Sorted PTokenName PInteger))
-> Term s (PValue 'Sorted 'NoGuarantees)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Term
s (PMap 'Sorted PCurrencySymbol (PMap 'Sorted PTokenName PInteger))
-> PValue 'Sorted 'NoGuarantees s
forall (keys :: KeyGuarantees) (amounts :: AmountGuarantees)
(s :: S).
Term s (PMap keys PCurrencySymbol (PMap keys PTokenName PInteger))
-> PValue keys amounts s
PValue (Term
s (PMap 'Sorted PCurrencySymbol (PMap 'Sorted PTokenName PInteger))
-> Term s (PValue 'Sorted 'NoGuarantees))
-> Term
s (PMap 'Sorted PCurrencySymbol (PMap 'Sorted PTokenName PInteger))
-> Term s (PValue 'Sorted 'NoGuarantees)
forall a b. (a -> b) -> a -> b
$ Term
s
(PMap 'Sorted PCurrencySymbol (PMap 'Sorted PTokenName PInteger)
:--> (PMap
'Sorted PCurrencySymbol (PMap 'Sorted PTokenName PInteger)
:--> PMap
'Sorted PCurrencySymbol (PMap 'Sorted PTokenName PInteger)))
forall (k :: S -> Type) (v :: S -> Type) (s :: S).
(POrd k, PIsData k, PIsData v) =>
Term
s (PMap 'Sorted k v :--> (PMap 'Sorted k v :--> PMap 'Sorted k v))
AssocMap.pleftBiasedUnion Term
s
(PMap 'Sorted PCurrencySymbol (PMap 'Sorted PTokenName PInteger)
:--> (PMap
'Sorted PCurrencySymbol (PMap 'Sorted PTokenName PInteger)
:--> PMap
'Sorted PCurrencySymbol (PMap 'Sorted PTokenName PInteger)))
-> Term
s (PMap 'Sorted PCurrencySymbol (PMap 'Sorted PTokenName PInteger))
-> Term
s
(PMap 'Sorted PCurrencySymbol (PMap 'Sorted PTokenName PInteger)
:--> PMap
'Sorted PCurrencySymbol (PMap 'Sorted PTokenName PInteger))
forall (s :: S) (a :: S -> Type) (b :: S -> Type).
Term s (a :--> b) -> Term s a -> Term s b
# Term s (PValue 'Sorted any0)
-> Term s (PInner (PValue 'Sorted any0))
forall (s :: S) (a :: S -> Type). Term s a -> Term s (PInner a)
pto Term s (PValue 'Sorted any0)
x Term
s
(PMap 'Sorted PCurrencySymbol (PMap 'Sorted PTokenName PInteger)
:--> PMap
'Sorted PCurrencySymbol (PMap 'Sorted PTokenName PInteger))
-> Term
s (PMap 'Sorted PCurrencySymbol (PMap 'Sorted PTokenName PInteger))
-> Term
s (PMap 'Sorted PCurrencySymbol (PMap 'Sorted PTokenName PInteger))
forall (s :: S) (a :: S -> Type) (b :: S -> Type).
Term s (a :--> b) -> Term s a -> Term s b
# Term s (PValue 'Sorted any1)
-> Term s (PInner (PValue 'Sorted any1))
forall (s :: S) (a :: S -> Type). Term s a -> Term s (PInner a)
pto Term s (PValue 'Sorted any1)
y
pleftBiasedTokenUnion ::
forall (any0 :: AmountGuarantees) (any1 :: AmountGuarantees) (s :: S).
Term
s
( PValue 'AssocMap.Sorted any0
:--> PValue 'AssocMap.Sorted any1
:--> PValue 'AssocMap.Sorted 'NoGuarantees
)
pleftBiasedTokenUnion :: forall (any0 :: AmountGuarantees) (any1 :: AmountGuarantees)
(s :: S).
Term
s
(PValue 'Sorted any0
:--> (PValue 'Sorted any1 :--> PValue 'Sorted 'NoGuarantees))
pleftBiasedTokenUnion = ClosedTerm
(PValue 'Sorted any0
:--> (PValue 'Sorted any1 :--> PValue 'Sorted 'NoGuarantees))
-> Term
s
(PValue 'Sorted any0
:--> (PValue 'Sorted any1 :--> PValue 'Sorted 'NoGuarantees))
forall (a :: S -> Type) (s :: S).
HasCallStack =>
ClosedTerm a -> Term s a
phoistAcyclic (ClosedTerm
(PValue 'Sorted any0
:--> (PValue 'Sorted any1 :--> PValue 'Sorted 'NoGuarantees))
-> Term
s
(PValue 'Sorted any0
:--> (PValue 'Sorted any1 :--> PValue 'Sorted 'NoGuarantees)))
-> ClosedTerm
(PValue 'Sorted any0
:--> (PValue 'Sorted any1 :--> PValue 'Sorted 'NoGuarantees))
-> Term
s
(PValue 'Sorted any0
:--> (PValue 'Sorted any1 :--> PValue 'Sorted 'NoGuarantees))
forall a b. (a -> b) -> a -> b
$
(Term s (PValue 'Sorted any0)
-> Term s (PValue 'Sorted any1)
-> Term s (PValue 'Sorted 'NoGuarantees))
-> Term
s
(PValue 'Sorted any0
:--> (PValue 'Sorted any1 :--> PValue 'Sorted 'NoGuarantees))
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 (PValue 'Sorted any1)
-> Term s (PValue 'Sorted 'NoGuarantees))
-> Term
s (c :--> (PValue 'Sorted any1 :--> PValue 'Sorted 'NoGuarantees))
plam ((Term s (PValue 'Sorted any0)
-> Term s (PValue 'Sorted any1)
-> Term s (PValue 'Sorted 'NoGuarantees))
-> Term
s
(PValue 'Sorted any0
:--> (PValue 'Sorted any1 :--> PValue 'Sorted 'NoGuarantees)))
-> (Term s (PValue 'Sorted any0)
-> Term s (PValue 'Sorted any1)
-> Term s (PValue 'Sorted 'NoGuarantees))
-> Term
s
(PValue 'Sorted any0
:--> (PValue 'Sorted any1 :--> PValue 'Sorted 'NoGuarantees))
forall a b. (a -> b) -> a -> b
$ \Term s (PValue 'Sorted any0)
x Term s (PValue 'Sorted any1)
y ->
PValue 'Sorted 'NoGuarantees s
-> Term s (PValue 'Sorted 'NoGuarantees)
forall (a :: S -> Type) (s :: S). PlutusType a => a s -> Term s a
pcon (PValue 'Sorted 'NoGuarantees s
-> Term s (PValue 'Sorted 'NoGuarantees))
-> (Term
s (PMap 'Sorted PCurrencySymbol (PMap 'Sorted PTokenName PInteger))
-> PValue 'Sorted 'NoGuarantees s)
-> Term
s (PMap 'Sorted PCurrencySymbol (PMap 'Sorted PTokenName PInteger))
-> Term s (PValue 'Sorted 'NoGuarantees)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Term
s (PMap 'Sorted PCurrencySymbol (PMap 'Sorted PTokenName PInteger))
-> PValue 'Sorted 'NoGuarantees s
forall (keys :: KeyGuarantees) (amounts :: AmountGuarantees)
(s :: S).
Term s (PMap keys PCurrencySymbol (PMap keys PTokenName PInteger))
-> PValue keys amounts s
PValue (Term
s (PMap 'Sorted PCurrencySymbol (PMap 'Sorted PTokenName PInteger))
-> Term s (PValue 'Sorted 'NoGuarantees))
-> Term
s (PMap 'Sorted PCurrencySymbol (PMap 'Sorted PTokenName PInteger))
-> Term s (PValue 'Sorted 'NoGuarantees)
forall a b. (a -> b) -> a -> b
$
Commutativity
-> Term
s
((PMap 'Sorted PTokenName PInteger
:--> (PMap 'Sorted PTokenName PInteger
:--> PMap 'Sorted PTokenName PInteger))
:--> (PMap
'Sorted PCurrencySymbol (PMap 'Sorted PTokenName PInteger)
:--> (PMap
'Sorted PCurrencySymbol (PMap 'Sorted PTokenName PInteger)
:--> PMap
'Sorted PCurrencySymbol (PMap 'Sorted PTokenName PInteger))))
forall (k :: S -> Type) (v :: S -> Type) (s :: S).
(POrd k, PIsData k, PIsData v) =>
Commutativity
-> Term
s
((v :--> (v :--> v))
:--> (PMap 'Sorted k v
:--> (PMap 'Sorted k v :--> PMap 'Sorted k v)))
AssocMap.punionResolvingCollisionsWith Commutativity
AssocMap.NonCommutative
# plam (\x' y' -> AssocMap.pleftBiasedUnion # x' # y')
# pto x
# pto y
punionResolvingCollisionsWithData ::
forall (any0 :: AmountGuarantees) (any1 :: AmountGuarantees) (s :: S).
AssocMap.Commutativity ->
Term
s
( (PAsData PInteger :--> PAsData PInteger :--> PAsData PInteger)
:--> PValue 'AssocMap.Sorted any0
:--> PValue 'AssocMap.Sorted any1
:--> PValue 'AssocMap.Sorted 'NoGuarantees
)
punionResolvingCollisionsWithData :: forall (any0 :: AmountGuarantees) (any1 :: AmountGuarantees)
(s :: S).
Commutativity
-> Term
s
((PAsData PInteger :--> (PAsData PInteger :--> PAsData PInteger))
:--> (PValue 'Sorted any0
:--> (PValue 'Sorted any1 :--> PValue 'Sorted 'NoGuarantees)))
punionResolvingCollisionsWithData Commutativity
commutativity = ClosedTerm
((PAsData PInteger :--> (PAsData PInteger :--> PAsData PInteger))
:--> (PValue 'Sorted any0
:--> (PValue 'Sorted any1 :--> PValue 'Sorted 'NoGuarantees)))
-> Term
s
((PAsData PInteger :--> (PAsData PInteger :--> PAsData PInteger))
:--> (PValue 'Sorted any0
:--> (PValue 'Sorted any1 :--> PValue 'Sorted 'NoGuarantees)))
forall (a :: S -> Type) (s :: S).
HasCallStack =>
ClosedTerm a -> Term s a
phoistAcyclic (ClosedTerm
((PAsData PInteger :--> (PAsData PInteger :--> PAsData PInteger))
:--> (PValue 'Sorted any0
:--> (PValue 'Sorted any1 :--> PValue 'Sorted 'NoGuarantees)))
-> Term
s
((PAsData PInteger :--> (PAsData PInteger :--> PAsData PInteger))
:--> (PValue 'Sorted any0
:--> (PValue 'Sorted any1 :--> PValue 'Sorted 'NoGuarantees))))
-> ClosedTerm
((PAsData PInteger :--> (PAsData PInteger :--> PAsData PInteger))
:--> (PValue 'Sorted any0
:--> (PValue 'Sorted any1 :--> PValue 'Sorted 'NoGuarantees)))
-> Term
s
((PAsData PInteger :--> (PAsData PInteger :--> PAsData PInteger))
:--> (PValue 'Sorted any0
:--> (PValue 'Sorted any1 :--> PValue 'Sorted 'NoGuarantees)))
forall a b. (a -> b) -> a -> b
$
(Term
s (PAsData PInteger :--> (PAsData PInteger :--> PAsData PInteger))
-> Term s (PValue 'Sorted any0)
-> Term s (PValue 'Sorted any1)
-> Term s (PValue 'Sorted 'NoGuarantees))
-> Term
s
((PAsData PInteger :--> (PAsData PInteger :--> PAsData PInteger))
:--> (PValue 'Sorted any0
:--> (PValue 'Sorted any1 :--> PValue 'Sorted 'NoGuarantees)))
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 (PValue 'Sorted any0)
-> Term s (PValue 'Sorted any1)
-> Term s (PValue 'Sorted 'NoGuarantees))
-> Term
s
(c
:--> (PValue 'Sorted any0
:--> (PValue 'Sorted any1 :--> PValue 'Sorted 'NoGuarantees)))
plam ((Term
s (PAsData PInteger :--> (PAsData PInteger :--> PAsData PInteger))
-> Term s (PValue 'Sorted any0)
-> Term s (PValue 'Sorted any1)
-> Term s (PValue 'Sorted 'NoGuarantees))
-> Term
s
((PAsData PInteger :--> (PAsData PInteger :--> PAsData PInteger))
:--> (PValue 'Sorted any0
:--> (PValue 'Sorted any1 :--> PValue 'Sorted 'NoGuarantees))))
-> (Term
s (PAsData PInteger :--> (PAsData PInteger :--> PAsData PInteger))
-> Term s (PValue 'Sorted any0)
-> Term s (PValue 'Sorted any1)
-> Term s (PValue 'Sorted 'NoGuarantees))
-> Term
s
((PAsData PInteger :--> (PAsData PInteger :--> PAsData PInteger))
:--> (PValue 'Sorted any0
:--> (PValue 'Sorted any1 :--> PValue 'Sorted 'NoGuarantees)))
forall a b. (a -> b) -> a -> b
$ \Term
s (PAsData PInteger :--> (PAsData PInteger :--> PAsData PInteger))
combine Term s (PValue 'Sorted any0)
x Term s (PValue 'Sorted any1)
y ->
PValue 'Sorted 'NoGuarantees s
-> Term s (PValue 'Sorted 'NoGuarantees)
forall (a :: S -> Type) (s :: S). PlutusType a => a s -> Term s a
pcon (PValue 'Sorted 'NoGuarantees s
-> Term s (PValue 'Sorted 'NoGuarantees))
-> (Term
s (PMap 'Sorted PCurrencySymbol (PMap 'Sorted PTokenName PInteger))
-> PValue 'Sorted 'NoGuarantees s)
-> Term
s (PMap 'Sorted PCurrencySymbol (PMap 'Sorted PTokenName PInteger))
-> Term s (PValue 'Sorted 'NoGuarantees)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Term
s (PMap 'Sorted PCurrencySymbol (PMap 'Sorted PTokenName PInteger))
-> PValue 'Sorted 'NoGuarantees s
forall (keys :: KeyGuarantees) (amounts :: AmountGuarantees)
(s :: S).
Term s (PMap keys PCurrencySymbol (PMap keys PTokenName PInteger))
-> PValue keys amounts s
PValue (Term
s (PMap 'Sorted PCurrencySymbol (PMap 'Sorted PTokenName PInteger))
-> Term s (PValue 'Sorted 'NoGuarantees))
-> Term
s (PMap 'Sorted PCurrencySymbol (PMap 'Sorted PTokenName PInteger))
-> Term s (PValue 'Sorted 'NoGuarantees)
forall a b. (a -> b) -> a -> b
$
Commutativity
-> Term
s
((PMap 'Sorted PTokenName PInteger
:--> (PMap 'Sorted PTokenName PInteger
:--> PMap 'Sorted PTokenName PInteger))
:--> (PMap
'Sorted PCurrencySymbol (PMap 'Sorted PTokenName PInteger)
:--> (PMap
'Sorted PCurrencySymbol (PMap 'Sorted PTokenName PInteger)
:--> PMap
'Sorted PCurrencySymbol (PMap 'Sorted PTokenName PInteger))))
forall (k :: S -> Type) (v :: S -> Type) (s :: S).
(POrd k, PIsData k, PIsData v) =>
Commutativity
-> Term
s
((v :--> (v :--> v))
:--> (PMap 'Sorted k v
:--> (PMap 'Sorted k v :--> PMap 'Sorted k v)))
AssocMap.punionResolvingCollisionsWith Commutativity
commutativity
# plam (\x' y' -> AssocMap.punionResolvingCollisionsWithData commutativity # combine # x' # y')
# pto x
# pto y
passertSorted ::
forall (anyKey :: AssocMap.KeyGuarantees) (anyAmount :: AmountGuarantees) (s :: S).
Term s (PValue anyKey anyAmount :--> PValue 'AssocMap.Sorted 'NonZero)
passertSorted :: forall (anyKey :: KeyGuarantees) (anyAmount :: AmountGuarantees)
(s :: S).
Term s (PValue anyKey anyAmount :--> PValue 'Sorted 'NonZero)
passertSorted = ClosedTerm (PValue anyKey anyAmount :--> PValue 'Sorted 'NonZero)
-> Term s (PValue anyKey anyAmount :--> PValue 'Sorted 'NonZero)
forall (a :: S -> Type) (s :: S).
HasCallStack =>
ClosedTerm a -> Term s a
phoistAcyclic (ClosedTerm (PValue anyKey anyAmount :--> PValue 'Sorted 'NonZero)
-> Term s (PValue anyKey anyAmount :--> PValue 'Sorted 'NonZero))
-> ClosedTerm
(PValue anyKey anyAmount :--> PValue 'Sorted 'NonZero)
-> Term s (PValue anyKey anyAmount :--> PValue 'Sorted 'NonZero)
forall a b. (a -> b) -> a -> b
$
(Term s (PValue anyKey anyAmount)
-> Term s (PValue 'Sorted 'NonZero))
-> Term s (PValue anyKey anyAmount :--> PValue 'Sorted 'NonZero)
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 (PValue 'Sorted 'NonZero))
-> Term s (c :--> PValue 'Sorted 'NonZero)
plam ((Term s (PValue anyKey anyAmount)
-> Term s (PValue 'Sorted 'NonZero))
-> Term s (PValue anyKey anyAmount :--> PValue 'Sorted 'NonZero))
-> (Term s (PValue anyKey anyAmount)
-> Term s (PValue 'Sorted 'NonZero))
-> Term s (PValue anyKey anyAmount :--> PValue 'Sorted 'NonZero)
forall a b. (a -> b) -> a -> b
$ \Term s (PValue anyKey anyAmount)
value ->
Term s PBool
-> Term s (PValue 'Sorted 'NonZero)
-> Term s (PValue 'Sorted 'NonZero)
-> Term s (PValue 'Sorted 'NonZero)
forall (a :: S -> Type) (s :: S).
Term s PBool -> Term s a -> Term s a -> Term s a
pif
( Term
s
((PMap anyKey PTokenName PInteger :--> PBool)
:--> (PMap anyKey PCurrencySymbol (PMap anyKey PTokenName PInteger)
:--> PBool))
forall (k :: S -> Type) (v :: S -> Type) (any :: KeyGuarantees)
(s :: S).
PIsData v =>
Term s ((v :--> PBool) :--> (PMap any k v :--> PBool))
AssocMap.pany
# plam
( \submap ->
AssocMap.pnull
# (AssocMap.passertSorted # submap)
#|| AssocMap.pany
# plam (#== 0)
# submap
)
# pto value
)
(Term s PString -> Term s (PValue 'Sorted 'NonZero)
forall (a :: S -> Type) (s :: S). Term s PString -> Term s a
ptraceInfoError Term s PString
"Abnormal Value")
(Term s (PValue 'Sorted 'NonZero)
-> Term s (PValue 'Sorted 'NonZero))
-> (Term
s (PMap 'Sorted PCurrencySymbol (PMap 'Sorted PTokenName PInteger))
-> Term s (PValue 'Sorted 'NonZero))
-> Term
s (PMap 'Sorted PCurrencySymbol (PMap 'Sorted PTokenName PInteger))
-> Term s (PValue 'Sorted 'NonZero)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. PValue 'Sorted 'NonZero s -> Term s (PValue 'Sorted 'NonZero)
forall (a :: S -> Type) (s :: S). PlutusType a => a s -> Term s a
pcon
(PValue 'Sorted 'NonZero s -> Term s (PValue 'Sorted 'NonZero))
-> (Term
s (PMap 'Sorted PCurrencySymbol (PMap 'Sorted PTokenName PInteger))
-> PValue 'Sorted 'NonZero s)
-> Term
s (PMap 'Sorted PCurrencySymbol (PMap 'Sorted PTokenName PInteger))
-> Term s (PValue 'Sorted 'NonZero)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Term
s (PMap 'Sorted PCurrencySymbol (PMap 'Sorted PTokenName PInteger))
-> PValue 'Sorted 'NonZero s
forall (keys :: KeyGuarantees) (amounts :: AmountGuarantees)
(s :: S).
Term s (PMap keys PCurrencySymbol (PMap keys PTokenName PInteger))
-> PValue keys amounts s
PValue
(Term
s (PMap 'Sorted PCurrencySymbol (PMap 'Sorted PTokenName PInteger))
-> Term s (PValue 'Sorted 'NonZero))
-> Term
s (PMap 'Sorted PCurrencySymbol (PMap 'Sorted PTokenName PInteger))
-> Term s (PValue 'Sorted 'NonZero)
forall a b. (a -> b) -> a -> b
$ Term
s
(PMap Any PCurrencySymbol (PMap 'Sorted PTokenName PInteger)
:--> PMap
'Sorted PCurrencySymbol (PMap 'Sorted PTokenName PInteger))
forall (k :: S -> Type) (v :: S -> Type) (any :: KeyGuarantees)
(s :: S).
(POrd k, PIsData k) =>
Term s (PMap any k v :--> PMap 'Sorted k v)
AssocMap.passertSorted Term
s
(PMap Any PCurrencySymbol (PMap 'Sorted PTokenName PInteger)
:--> PMap
'Sorted PCurrencySymbol (PMap 'Sorted PTokenName PInteger))
-> Term
s (PMap Any PCurrencySymbol (PMap 'Sorted PTokenName PInteger))
-> Term
s (PMap 'Sorted PCurrencySymbol (PMap 'Sorted PTokenName PInteger))
forall (s :: S) (a :: S -> Type) (b :: S -> Type).
Term s (a :--> b) -> Term s a -> Term s b
#$ Term
s (PMap anyKey PCurrencySymbol (PMap anyKey PTokenName PInteger))
-> Term
s (PMap Any PCurrencySymbol (PMap 'Sorted PTokenName PInteger))
forall (b :: S -> Type) (a :: S -> Type) (s :: S).
Term s a -> Term s b
punsafeCoerce
(Term
s (PMap anyKey PCurrencySymbol (PMap anyKey PTokenName PInteger))
-> Term
s (PMap Any PCurrencySymbol (PMap 'Sorted PTokenName PInteger)))
-> Term
s (PMap anyKey PCurrencySymbol (PMap anyKey PTokenName PInteger))
-> Term
s (PMap Any PCurrencySymbol (PMap 'Sorted PTokenName PInteger))
forall a b. (a -> b) -> a -> b
$ Term s (PValue anyKey anyAmount)
-> Term s (PInner (PValue anyKey anyAmount))
forall (s :: S) (a :: S -> Type). Term s a -> Term s (PInner a)
pto Term s (PValue anyKey anyAmount)
value
pisAdaOnlyValue ::
forall (s :: S).
Term s (PValue 'AssocMap.Sorted 'Positive :--> PBool)
pisAdaOnlyValue :: forall (s :: S). Term s (PValue 'Sorted 'Positive :--> PBool)
pisAdaOnlyValue = (forall (s :: S). Term s (PValue 'Sorted 'Positive :--> PBool))
-> Term s (PValue 'Sorted 'Positive :--> PBool)
forall (a :: S -> Type) (s :: S).
HasCallStack =>
ClosedTerm a -> Term s a
phoistAcyclic ((forall (s :: S). Term s (PValue 'Sorted 'Positive :--> PBool))
-> Term s (PValue 'Sorted 'Positive :--> PBool))
-> (forall (s :: S). Term s (PValue 'Sorted 'Positive :--> PBool))
-> Term s (PValue 'Sorted 'Positive :--> PBool)
forall a b. (a -> b) -> a -> b
$
(Term s (PValue 'Sorted 'Positive) -> Term s PBool)
-> Term s (PValue 'Sorted 'Positive :--> 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 (PValue 'Sorted 'Positive) -> Term s PBool)
-> Term s (PValue 'Sorted 'Positive :--> PBool))
-> (Term s (PValue 'Sorted 'Positive) -> Term s PBool)
-> Term s (PValue 'Sorted 'Positive :--> PBool)
forall a b. (a -> b) -> a -> b
$ \Term s (PValue 'Sorted 'Positive)
value ->
Term
s
(PBuiltinList
(PBuiltinPair
(PAsData PCurrencySymbol)
(PAsData (PMap 'Sorted PTokenName PInteger))))
-> (PBuiltinList
(PBuiltinPair
(PAsData PCurrencySymbol)
(PAsData (PMap 'Sorted PTokenName PInteger)))
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 (PMap 'Sorted PCurrencySymbol (PMap 'Sorted PTokenName PInteger))
-> Term
s
(PInner
(PMap 'Sorted PCurrencySymbol (PMap 'Sorted PTokenName PInteger)))
forall (s :: S) (a :: S -> Type). Term s a -> Term s (PInner a)
pto (Term
s (PMap 'Sorted PCurrencySymbol (PMap 'Sorted PTokenName PInteger))
-> Term
s
(PInner
(PMap 'Sorted PCurrencySymbol (PMap 'Sorted PTokenName PInteger))))
-> Term
s (PMap 'Sorted PCurrencySymbol (PMap 'Sorted PTokenName PInteger))
-> Term
s
(PInner
(PMap 'Sorted PCurrencySymbol (PMap 'Sorted PTokenName PInteger)))
forall a b. (a -> b) -> a -> b
$ Term s (PValue 'Sorted 'Positive)
-> Term s (PInner (PValue 'Sorted 'Positive))
forall (s :: S) (a :: S -> Type). Term s a -> Term s (PInner a)
pto Term s (PValue 'Sorted 'Positive)
value) ((PBuiltinList
(PBuiltinPair
(PAsData PCurrencySymbol)
(PAsData (PMap 'Sorted PTokenName PInteger)))
s
-> Term s PBool)
-> Term s PBool)
-> (PBuiltinList
(PBuiltinPair
(PAsData PCurrencySymbol)
(PAsData (PMap 'Sorted PTokenName PInteger)))
s
-> Term s PBool)
-> Term s PBool
forall a b. (a -> b) -> a -> b
$ \case
PBuiltinList
(PBuiltinPair
(PAsData PCurrencySymbol)
(PAsData (PMap 'Sorted PTokenName PInteger)))
s
PNil -> 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
PCons Term
s
(PBuiltinPair
(PAsData PCurrencySymbol)
(PAsData (PMap 'Sorted PTokenName PInteger)))
x Term
s
(PBuiltinList
(PBuiltinPair
(PAsData PCurrencySymbol)
(PAsData (PMap 'Sorted PTokenName PInteger))))
xs -> Term s (PBool :--> (PBool :--> PBool))
forall (s :: S). Term s (PBool :--> (PBool :--> PBool))
pand' Term s (PBool :--> (PBool :--> PBool))
-> Term s PBool -> Term s (PBool :--> PBool)
forall (s :: S) (a :: S -> Type) (b :: S -> Type).
Term s (a :--> b) -> Term s a -> Term s b
# (Term
s
(PBuiltinList
(PBuiltinPair
(PAsData PCurrencySymbol)
(PAsData (PMap 'Sorted PTokenName PInteger)))
:--> PBool)
forall (a :: S -> Type) (s :: S).
PElemConstraint PBuiltinList a =>
Term s (PBuiltinList a :--> PBool)
forall (list :: (S -> Type) -> S -> Type) (a :: S -> Type)
(s :: S).
(PListLike list, PElemConstraint list a) =>
Term s (list a :--> PBool)
pnull Term
s
(PBuiltinList
(PBuiltinPair
(PAsData PCurrencySymbol)
(PAsData (PMap 'Sorted PTokenName PInteger)))
:--> PBool)
-> Term
s
(PBuiltinList
(PBuiltinPair
(PAsData PCurrencySymbol)
(PAsData (PMap 'Sorted PTokenName PInteger))))
-> Term s PBool
forall (s :: S) (a :: S -> Type) (b :: S -> Type).
Term s (a :--> b) -> Term s a -> Term s b
# Term
s
(PBuiltinList
(PBuiltinPair
(PAsData PCurrencySymbol)
(PAsData (PMap 'Sorted PTokenName PInteger))))
xs) Term s (PBool :--> PBool) -> Term s PBool -> Term s PBool
forall (s :: S) (a :: S -> Type) (b :: S -> Type).
Term s (a :--> b) -> Term s a -> Term s b
# (Term
s
(PBuiltinPair
(PAsData PCurrencySymbol)
(PAsData (PMap 'Sorted PTokenName PInteger))
:--> PAsData PCurrencySymbol)
forall (s :: S) (a :: S -> Type) (b :: S -> Type).
Term s (PBuiltinPair a b :--> a)
pfstBuiltin Term
s
(PBuiltinPair
(PAsData PCurrencySymbol)
(PAsData (PMap 'Sorted PTokenName PInteger))
:--> PAsData PCurrencySymbol)
-> Term
s
(PBuiltinPair
(PAsData PCurrencySymbol)
(PAsData (PMap 'Sorted PTokenName PInteger)))
-> Term s (PAsData PCurrencySymbol)
forall (s :: S) (a :: S -> Type) (b :: S -> Type).
Term s (a :--> b) -> Term s a -> Term s b
# Term
s
(PBuiltinPair
(PAsData PCurrencySymbol)
(PAsData (PMap 'Sorted PTokenName PInteger)))
x Term s (PAsData PCurrencySymbol)
-> Term s (PAsData PCurrencySymbol) -> Term s PBool
forall (s :: S).
Term s (PAsData PCurrencySymbol)
-> Term s (PAsData PCurrencySymbol) -> Term s PBool
forall (t :: S -> Type) (s :: S).
PEq t =>
Term s t -> Term s t -> Term s PBool
#== Term s (PAsData PCurrencySymbol)
forall (s :: S). Term s (PAsData PCurrencySymbol)
padaSymbolData)
padaOnlyValue ::
forall (v :: AmountGuarantees) (s :: S).
Term s (PValue 'AssocMap.Sorted v :--> PValue 'AssocMap.Sorted v)
padaOnlyValue :: forall (v :: AmountGuarantees) (s :: S).
Term s (PValue 'Sorted v :--> PValue 'Sorted v)
padaOnlyValue = ClosedTerm (PValue 'Sorted v :--> PValue 'Sorted v)
-> Term s (PValue 'Sorted v :--> PValue 'Sorted v)
forall (a :: S -> Type) (s :: S).
HasCallStack =>
ClosedTerm a -> Term s a
phoistAcyclic (ClosedTerm (PValue 'Sorted v :--> PValue 'Sorted v)
-> Term s (PValue 'Sorted v :--> PValue 'Sorted v))
-> ClosedTerm (PValue 'Sorted v :--> PValue 'Sorted v)
-> Term s (PValue 'Sorted v :--> PValue 'Sorted v)
forall a b. (a -> b) -> a -> b
$
(Term s (PValue 'Sorted v) -> Term s (PValue 'Sorted v))
-> Term s (PValue 'Sorted v :--> PValue 'Sorted v)
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 (PValue 'Sorted v))
-> Term s (c :--> PValue 'Sorted v)
plam ((Term s (PValue 'Sorted v) -> Term s (PValue 'Sorted v))
-> Term s (PValue 'Sorted v :--> PValue 'Sorted v))
-> (Term s (PValue 'Sorted v) -> Term s (PValue 'Sorted v))
-> Term s (PValue 'Sorted v :--> PValue 'Sorted v)
forall a b. (a -> b) -> a -> b
$ \Term s (PValue 'Sorted v)
value ->
Term
s
(PBuiltinList
(PBuiltinPair
(PAsData PCurrencySymbol)
(PAsData (PMap 'Sorted PTokenName PInteger))))
-> (PBuiltinList
(PBuiltinPair
(PAsData PCurrencySymbol)
(PAsData (PMap 'Sorted PTokenName PInteger)))
s
-> Term s (PValue 'Sorted v))
-> Term s (PValue 'Sorted v)
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 (PMap 'Sorted PCurrencySymbol (PMap 'Sorted PTokenName PInteger))
-> Term
s
(PInner
(PMap 'Sorted PCurrencySymbol (PMap 'Sorted PTokenName PInteger)))
forall (s :: S) (a :: S -> Type). Term s a -> Term s (PInner a)
pto (Term
s (PMap 'Sorted PCurrencySymbol (PMap 'Sorted PTokenName PInteger))
-> Term
s
(PInner
(PMap 'Sorted PCurrencySymbol (PMap 'Sorted PTokenName PInteger))))
-> Term
s (PMap 'Sorted PCurrencySymbol (PMap 'Sorted PTokenName PInteger))
-> Term
s
(PInner
(PMap 'Sorted PCurrencySymbol (PMap 'Sorted PTokenName PInteger)))
forall a b. (a -> b) -> a -> b
$ Term s (PValue 'Sorted v) -> Term s (PInner (PValue 'Sorted v))
forall (s :: S) (a :: S -> Type). Term s a -> Term s (PInner a)
pto Term s (PValue 'Sorted v)
value) ((PBuiltinList
(PBuiltinPair
(PAsData PCurrencySymbol)
(PAsData (PMap 'Sorted PTokenName PInteger)))
s
-> Term s (PValue 'Sorted v))
-> Term s (PValue 'Sorted v))
-> (PBuiltinList
(PBuiltinPair
(PAsData PCurrencySymbol)
(PAsData (PMap 'Sorted PTokenName PInteger)))
s
-> Term s (PValue 'Sorted v))
-> Term s (PValue 'Sorted v)
forall a b. (a -> b) -> a -> b
$ \case
PBuiltinList
(PBuiltinPair
(PAsData PCurrencySymbol)
(PAsData (PMap 'Sorted PTokenName PInteger)))
s
PNil -> Term s (PValue 'Sorted v)
value
PCons Term
s
(PBuiltinPair
(PAsData PCurrencySymbol)
(PAsData (PMap 'Sorted PTokenName PInteger)))
x Term
s
(PBuiltinList
(PBuiltinPair
(PAsData PCurrencySymbol)
(PAsData (PMap 'Sorted PTokenName PInteger))))
_ ->
Term
s
(PBool
:--> (PValue 'Sorted v
:--> (PValue 'Sorted v :--> PValue 'Sorted v)))
forall (a :: S -> Type) (s :: S).
Term s (PBool :--> (a :--> (a :--> a)))
pif'
# (pfstBuiltin # x #== padaSymbolData)
# pcon (PValue $ pcon $ AssocMap.PMap $ PPrelude.psingleton # x)
# pcon (PValue AssocMap.pempty)
pnoAdaValue ::
forall (v :: AmountGuarantees) (s :: S).
Term s (PValue 'AssocMap.Sorted v :--> PValue 'AssocMap.Sorted v)
pnoAdaValue :: forall (v :: AmountGuarantees) (s :: S).
Term s (PValue 'Sorted v :--> PValue 'Sorted v)
pnoAdaValue = ClosedTerm (PValue 'Sorted v :--> PValue 'Sorted v)
-> Term s (PValue 'Sorted v :--> PValue 'Sorted v)
forall (a :: S -> Type) (s :: S).
HasCallStack =>
ClosedTerm a -> Term s a
phoistAcyclic (ClosedTerm (PValue 'Sorted v :--> PValue 'Sorted v)
-> Term s (PValue 'Sorted v :--> PValue 'Sorted v))
-> ClosedTerm (PValue 'Sorted v :--> PValue 'Sorted v)
-> Term s (PValue 'Sorted v :--> PValue 'Sorted v)
forall a b. (a -> b) -> a -> b
$
(Term s (PValue 'Sorted v) -> Term s (PValue 'Sorted v))
-> Term s (PValue 'Sorted v :--> PValue 'Sorted v)
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 (PValue 'Sorted v))
-> Term s (c :--> PValue 'Sorted v)
plam ((Term s (PValue 'Sorted v) -> Term s (PValue 'Sorted v))
-> Term s (PValue 'Sorted v :--> PValue 'Sorted v))
-> (Term s (PValue 'Sorted v) -> Term s (PValue 'Sorted v))
-> Term s (PValue 'Sorted v :--> PValue 'Sorted v)
forall a b. (a -> b) -> a -> b
$ \Term s (PValue 'Sorted v)
value ->
Term
s
(PBuiltinList
(PBuiltinPair
(PAsData PCurrencySymbol)
(PAsData (PMap 'Sorted PTokenName PInteger))))
-> (PBuiltinList
(PBuiltinPair
(PAsData PCurrencySymbol)
(PAsData (PMap 'Sorted PTokenName PInteger)))
s
-> Term s (PValue 'Sorted v))
-> Term s (PValue 'Sorted v)
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 (PMap 'Sorted PCurrencySymbol (PMap 'Sorted PTokenName PInteger))
-> Term
s
(PInner
(PMap 'Sorted PCurrencySymbol (PMap 'Sorted PTokenName PInteger)))
forall (s :: S) (a :: S -> Type). Term s a -> Term s (PInner a)
pto (Term
s (PMap 'Sorted PCurrencySymbol (PMap 'Sorted PTokenName PInteger))
-> Term
s
(PInner
(PMap 'Sorted PCurrencySymbol (PMap 'Sorted PTokenName PInteger))))
-> Term
s (PMap 'Sorted PCurrencySymbol (PMap 'Sorted PTokenName PInteger))
-> Term
s
(PInner
(PMap 'Sorted PCurrencySymbol (PMap 'Sorted PTokenName PInteger)))
forall a b. (a -> b) -> a -> b
$ Term s (PValue 'Sorted v) -> Term s (PInner (PValue 'Sorted v))
forall (s :: S) (a :: S -> Type). Term s a -> Term s (PInner a)
pto Term s (PValue 'Sorted v)
value) ((PBuiltinList
(PBuiltinPair
(PAsData PCurrencySymbol)
(PAsData (PMap 'Sorted PTokenName PInteger)))
s
-> Term s (PValue 'Sorted v))
-> Term s (PValue 'Sorted v))
-> (PBuiltinList
(PBuiltinPair
(PAsData PCurrencySymbol)
(PAsData (PMap 'Sorted PTokenName PInteger)))
s
-> Term s (PValue 'Sorted v))
-> Term s (PValue 'Sorted v)
forall a b. (a -> b) -> a -> b
$ \case
PBuiltinList
(PBuiltinPair
(PAsData PCurrencySymbol)
(PAsData (PMap 'Sorted PTokenName PInteger)))
s
PNil -> Term s (PValue 'Sorted v)
value
PCons Term
s
(PBuiltinPair
(PAsData PCurrencySymbol)
(PAsData (PMap 'Sorted PTokenName PInteger)))
x Term
s
(PBuiltinList
(PBuiltinPair
(PAsData PCurrencySymbol)
(PAsData (PMap 'Sorted PTokenName PInteger))))
xs -> Term
s
(PBool
:--> (PValue 'Sorted v
:--> (PValue 'Sorted v :--> PValue 'Sorted v)))
forall (a :: S -> Type) (s :: S).
Term s (PBool :--> (a :--> (a :--> a)))
pif' Term
s
(PBool
:--> (PValue 'Sorted v
:--> (PValue 'Sorted v :--> PValue 'Sorted v)))
-> Term s PBool
-> Term
s (PValue 'Sorted v :--> (PValue 'Sorted v :--> PValue 'Sorted v))
forall (s :: S) (a :: S -> Type) (b :: S -> Type).
Term s (a :--> b) -> Term s a -> Term s b
# (Term
s
(PBuiltinPair
(PAsData PCurrencySymbol)
(PAsData (PMap 'Sorted PTokenName PInteger))
:--> PAsData PCurrencySymbol)
forall (s :: S) (a :: S -> Type) (b :: S -> Type).
Term s (PBuiltinPair a b :--> a)
pfstBuiltin Term
s
(PBuiltinPair
(PAsData PCurrencySymbol)
(PAsData (PMap 'Sorted PTokenName PInteger))
:--> PAsData PCurrencySymbol)
-> Term
s
(PBuiltinPair
(PAsData PCurrencySymbol)
(PAsData (PMap 'Sorted PTokenName PInteger)))
-> Term s (PAsData PCurrencySymbol)
forall (s :: S) (a :: S -> Type) (b :: S -> Type).
Term s (a :--> b) -> Term s a -> Term s b
# Term
s
(PBuiltinPair
(PAsData PCurrencySymbol)
(PAsData (PMap 'Sorted PTokenName PInteger)))
x Term s (PAsData PCurrencySymbol)
-> Term s (PAsData PCurrencySymbol) -> Term s PBool
forall (s :: S).
Term s (PAsData PCurrencySymbol)
-> Term s (PAsData PCurrencySymbol) -> Term s PBool
forall (t :: S -> Type) (s :: S).
PEq t =>
Term s t -> Term s t -> Term s PBool
#== Term s (PAsData PCurrencySymbol)
forall (s :: S). Term s (PAsData PCurrencySymbol)
padaSymbolData) Term
s (PValue 'Sorted v :--> (PValue 'Sorted v :--> PValue 'Sorted v))
-> Term s (PValue 'Sorted v)
-> Term s (PValue 'Sorted v :--> PValue 'Sorted v)
forall (s :: S) (a :: S -> Type) (b :: S -> Type).
Term s (a :--> b) -> Term s a -> Term s b
# PValue 'Sorted v s -> Term s (PValue 'Sorted v)
forall (a :: S -> Type) (s :: S). PlutusType a => a s -> Term s a
pcon (Term
s (PMap 'Sorted PCurrencySymbol (PMap 'Sorted PTokenName PInteger))
-> PValue 'Sorted v s
forall (keys :: KeyGuarantees) (amounts :: AmountGuarantees)
(s :: S).
Term s (PMap keys PCurrencySymbol (PMap keys PTokenName PInteger))
-> PValue keys amounts s
PValue (Term
s (PMap 'Sorted PCurrencySymbol (PMap 'Sorted PTokenName PInteger))
-> PValue 'Sorted v s)
-> Term
s (PMap 'Sorted PCurrencySymbol (PMap 'Sorted PTokenName PInteger))
-> PValue 'Sorted v s
forall a b. (a -> b) -> a -> b
$ PMap 'Sorted PCurrencySymbol (PMap 'Sorted PTokenName PInteger) s
-> Term
s (PMap 'Sorted PCurrencySymbol (PMap 'Sorted PTokenName PInteger))
forall (a :: S -> Type) (s :: S). PlutusType a => a s -> Term s a
pcon (PMap 'Sorted PCurrencySymbol (PMap 'Sorted PTokenName PInteger) s
-> Term
s
(PMap 'Sorted PCurrencySymbol (PMap 'Sorted PTokenName PInteger)))
-> PMap
'Sorted PCurrencySymbol (PMap 'Sorted PTokenName PInteger) s
-> Term
s (PMap 'Sorted PCurrencySymbol (PMap 'Sorted PTokenName PInteger))
forall a b. (a -> b) -> a -> b
$ Term
s
(PBuiltinList
(PBuiltinPair
(PAsData PCurrencySymbol)
(PAsData (PMap 'Sorted PTokenName PInteger))))
-> PMap
'Sorted PCurrencySymbol (PMap 'Sorted PTokenName PInteger) s
forall (keysort :: KeyGuarantees) (k :: S -> Type) (v :: S -> Type)
(s :: S).
Term s (PBuiltinList (PBuiltinPair (PAsData k) (PAsData v)))
-> PMap keysort k v s
AssocMap.PMap Term
s
(PBuiltinList
(PBuiltinPair
(PAsData PCurrencySymbol)
(PAsData (PMap 'Sorted PTokenName PInteger))))
xs) Term s (PValue 'Sorted v :--> PValue 'Sorted v)
-> Term s (PValue 'Sorted v) -> Term s (PValue 'Sorted v)
forall (s :: S) (a :: S -> Type) (b :: S -> Type).
Term s (a :--> b) -> Term s a -> Term s b
# Term s (PValue 'Sorted v)
value
zeroData :: forall (s :: S). Term s (PAsData PInteger)
zeroData :: forall (s :: S). Term s (PAsData PInteger)
zeroData = Term s PInteger -> Term s (PAsData PInteger)
forall (a :: S -> Type) (s :: S).
PIsData a =>
Term s a -> Term s (PAsData a)
pdata Term s PInteger
0
pmapAmounts ::
forall (k :: AssocMap.KeyGuarantees) (a :: AmountGuarantees) (s :: S).
Term s ((PInteger :--> PInteger) :--> PValue k a :--> PValue k 'NoGuarantees)
pmapAmounts :: forall (k :: KeyGuarantees) (a :: AmountGuarantees) (s :: S).
Term
s
((PInteger :--> PInteger)
:--> (PValue k a :--> PValue k 'NoGuarantees))
pmapAmounts = ClosedTerm
((PInteger :--> PInteger)
:--> (PValue k a :--> PValue k 'NoGuarantees))
-> Term
s
((PInteger :--> PInteger)
:--> (PValue k a :--> PValue k 'NoGuarantees))
forall (a :: S -> Type) (s :: S).
HasCallStack =>
ClosedTerm a -> Term s a
phoistAcyclic (ClosedTerm
((PInteger :--> PInteger)
:--> (PValue k a :--> PValue k 'NoGuarantees))
-> Term
s
((PInteger :--> PInteger)
:--> (PValue k a :--> PValue k 'NoGuarantees)))
-> ClosedTerm
((PInteger :--> PInteger)
:--> (PValue k a :--> PValue k 'NoGuarantees))
-> Term
s
((PInteger :--> PInteger)
:--> (PValue k a :--> PValue k 'NoGuarantees))
forall a b. (a -> b) -> a -> b
$
(Term s (PInteger :--> PInteger)
-> Term s (PValue k a) -> Term s (PValue k 'NoGuarantees))
-> Term
s
((PInteger :--> PInteger)
:--> (PValue k a :--> PValue k 'NoGuarantees))
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 (PValue k a) -> Term s (PValue k 'NoGuarantees))
-> Term s (c :--> (PValue k a :--> PValue k 'NoGuarantees))
plam ((Term s (PInteger :--> PInteger)
-> Term s (PValue k a) -> Term s (PValue k 'NoGuarantees))
-> Term
s
((PInteger :--> PInteger)
:--> (PValue k a :--> PValue k 'NoGuarantees)))
-> (Term s (PInteger :--> PInteger)
-> Term s (PValue k a) -> Term s (PValue k 'NoGuarantees))
-> Term
s
((PInteger :--> PInteger)
:--> (PValue k a :--> PValue k 'NoGuarantees))
forall a b. (a -> b) -> a -> b
$
\Term s (PInteger :--> PInteger)
f Term s (PValue k a)
v -> PValue k 'NoGuarantees s -> Term s (PValue k 'NoGuarantees)
forall (a :: S -> Type) (s :: S). PlutusType a => a s -> Term s a
pcon (PValue k 'NoGuarantees s -> Term s (PValue k 'NoGuarantees))
-> PValue k 'NoGuarantees s -> Term s (PValue k 'NoGuarantees)
forall a b. (a -> b) -> a -> b
$ Term s (PMap k PCurrencySymbol (PMap k PTokenName PInteger))
-> PValue k 'NoGuarantees s
forall (keys :: KeyGuarantees) (amounts :: AmountGuarantees)
(s :: S).
Term s (PMap keys PCurrencySymbol (PMap keys PTokenName PInteger))
-> PValue keys amounts s
PValue (Term s (PMap k PCurrencySymbol (PMap k PTokenName PInteger))
-> PValue k 'NoGuarantees s)
-> Term s (PMap k PCurrencySymbol (PMap k PTokenName PInteger))
-> PValue k 'NoGuarantees s
forall a b. (a -> b) -> a -> b
$ Term
s
((PMap k PTokenName PInteger :--> PMap k PTokenName PInteger)
:--> (PMap k PCurrencySymbol (PMap k PTokenName PInteger)
:--> PMap k PCurrencySymbol (PMap k PTokenName PInteger)))
forall (g :: KeyGuarantees) (k :: S -> Type) (a :: S -> Type)
(b :: S -> Type) (s :: S).
(PIsData a, PIsData b) =>
Term s ((a :--> b) :--> (PMap g k a :--> PMap g k b))
AssocMap.pmap Term
s
((PMap k PTokenName PInteger :--> PMap k PTokenName PInteger)
:--> (PMap k PCurrencySymbol (PMap k PTokenName PInteger)
:--> PMap k PCurrencySymbol (PMap k PTokenName PInteger)))
-> Term
s (PMap k PTokenName PInteger :--> PMap k PTokenName PInteger)
-> Term
s
(PMap k PCurrencySymbol (PMap k PTokenName PInteger)
:--> PMap k PCurrencySymbol (PMap k PTokenName PInteger))
forall (s :: S) (a :: S -> Type) (b :: S -> Type).
Term s (a :--> b) -> Term s a -> Term s b
# (Term s (PMap k PTokenName PInteger)
-> Term s (PMap k PTokenName PInteger))
-> Term
s (PMap k PTokenName PInteger :--> PMap k PTokenName PInteger)
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 (PMap k PTokenName PInteger))
-> Term s (c :--> PMap k PTokenName PInteger)
plam (Term
s
((PInteger :--> PInteger)
:--> (PMap k PTokenName PInteger :--> PMap k PTokenName PInteger))
forall (g :: KeyGuarantees) (k :: S -> Type) (a :: S -> Type)
(b :: S -> Type) (s :: S).
(PIsData a, PIsData b) =>
Term s ((a :--> b) :--> (PMap g k a :--> PMap g k b))
AssocMap.pmap Term
s
((PInteger :--> PInteger)
:--> (PMap k PTokenName PInteger :--> PMap k PTokenName PInteger))
-> Term s (PInteger :--> PInteger)
-> Term
s (PMap k PTokenName PInteger :--> PMap k PTokenName PInteger)
forall (s :: S) (a :: S -> Type) (b :: S -> Type).
Term s (a :--> b) -> Term s a -> Term s b
# Term s (PInteger :--> PInteger)
f Term s (PMap k PTokenName PInteger :--> PMap k PTokenName PInteger)
-> Term s (PMap k PTokenName PInteger)
-> Term s (PMap k PTokenName PInteger)
forall (s :: S) (a :: S -> Type) (b :: S -> Type).
Term s (a :--> b) -> Term s a -> Term s b
#) Term
s
(PMap k PCurrencySymbol (PMap k PTokenName PInteger)
:--> PMap k PCurrencySymbol (PMap k PTokenName PInteger))
-> Term s (PMap k PCurrencySymbol (PMap k PTokenName PInteger))
-> Term s (PMap k PCurrencySymbol (PMap k PTokenName PInteger))
forall (s :: S) (a :: S -> Type) (b :: S -> Type).
Term s (a :--> b) -> Term s a -> Term s b
# Term s (PValue k a) -> Term s (PInner (PValue k a))
forall (s :: S) (a :: S -> Type). Term s a -> Term s (PInner a)
pto Term s (PValue k a)
v
passertNonZero ::
forall (kg :: AssocMap.KeyGuarantees) (ag :: AmountGuarantees).
( forall (s :: S). Term s (PValue kg ag :--> PValue kg 'NonZero)
)
passertNonZero :: forall (kg :: KeyGuarantees) (ag :: AmountGuarantees) (s :: S).
Term s (PValue kg ag :--> PValue kg 'NonZero)
passertNonZero = (Term s (PValue kg ag) -> Term s (PValue kg 'NonZero))
-> Term s (PValue kg ag :--> PValue kg 'NonZero)
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 (PValue kg 'NonZero))
-> Term s (c :--> PValue kg 'NonZero)
plam ((Term s (PValue kg ag) -> Term s (PValue kg 'NonZero))
-> Term s (PValue kg ag :--> PValue kg 'NonZero))
-> (Term s (PValue kg ag) -> Term s (PValue kg 'NonZero))
-> Term s (PValue kg ag :--> PValue kg 'NonZero)
forall a b. (a -> b) -> a -> b
$ \Term s (PValue kg ag)
val ->
Term s PBool
-> Term s (PValue kg 'NonZero)
-> Term s (PValue kg 'NonZero)
-> Term s (PValue kg 'NonZero)
forall (a :: S -> Type) (s :: S).
Term s PBool -> Term s a -> Term s a -> Term s a
pif (Term
s
(PBuiltinList
(PBuiltinPair
(PAsData PCurrencySymbol) (PAsData (PMap kg PTokenName PInteger)))
:--> PBool)
forall (s' :: S) (k :: KeyGuarantees).
Term
s'
(PBuiltinList
(PBuiltinPair
(PAsData PCurrencySymbol) (PAsData (PMap k PTokenName PInteger)))
:--> PBool)
outer Term
s
(PBuiltinList
(PBuiltinPair
(PAsData PCurrencySymbol) (PAsData (PMap kg PTokenName PInteger)))
:--> PBool)
-> Term
s
(PBuiltinList
(PBuiltinPair
(PAsData PCurrencySymbol) (PAsData (PMap kg PTokenName PInteger))))
-> Term s PBool
forall (s :: S) (a :: S -> Type) (b :: S -> Type).
Term s (a :--> b) -> Term s a -> Term s b
#$ Term s (PMap kg PCurrencySymbol (PMap kg PTokenName PInteger))
-> Term
s
(PBuiltinList
(PBuiltinPair
(PAsData PCurrencySymbol) (PAsData (PMap kg PTokenName PInteger))))
Term s (PMap kg PCurrencySymbol (PMap kg PTokenName PInteger))
-> Term
s (PInner (PMap kg PCurrencySymbol (PMap kg PTokenName PInteger)))
forall (s :: S) (a :: S -> Type). Term s a -> Term s (PInner a)
pto (Term s (PMap kg PCurrencySymbol (PMap kg PTokenName PInteger))
-> Term
s
(PBuiltinList
(PBuiltinPair
(PAsData PCurrencySymbol)
(PAsData (PMap kg PTokenName PInteger)))))
-> (Term s (PValue kg ag)
-> Term s (PMap kg PCurrencySymbol (PMap kg PTokenName PInteger)))
-> Term s (PValue kg ag)
-> Term
s
(PBuiltinList
(PBuiltinPair
(PAsData PCurrencySymbol) (PAsData (PMap kg PTokenName PInteger))))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Term s (PValue kg ag) -> Term s (PInner (PValue kg ag))
Term s (PValue kg ag)
-> Term s (PMap kg PCurrencySymbol (PMap kg PTokenName PInteger))
forall (s :: S) (a :: S -> Type). Term s a -> Term s (PInner a)
pto (Term s (PValue kg ag)
-> Term
s
(PBuiltinList
(PBuiltinPair
(PAsData PCurrencySymbol)
(PAsData (PMap kg PTokenName PInteger)))))
-> Term s (PValue kg ag)
-> Term
s
(PBuiltinList
(PBuiltinPair
(PAsData PCurrencySymbol) (PAsData (PMap kg PTokenName PInteger))))
forall a b. (a -> b) -> a -> b
$ Term s (PValue kg ag)
val) (Term s (PValue kg ag) -> Term s (PValue kg 'NonZero)
forall (b :: S -> Type) (a :: S -> Type) (s :: S).
Term s a -> Term s b
punsafeCoerce Term s (PValue kg ag)
val) (Term s PString -> Term s (PValue kg 'NonZero)
forall (a :: S -> Type) (s :: S). Term s PString -> Term s a
ptraceInfoError Term s PString
"Zero amount in Value")
where
outer ::
forall (s' :: S) (k :: AssocMap.KeyGuarantees).
Term s' (PBuiltinList (PBuiltinPair (PAsData PCurrencySymbol) (PAsData (AssocMap.PMap k PTokenName PInteger))) :--> PBool)
outer :: forall (s' :: S) (k :: KeyGuarantees).
Term
s'
(PBuiltinList
(PBuiltinPair
(PAsData PCurrencySymbol) (PAsData (PMap k PTokenName PInteger)))
:--> PBool)
outer = Term
s'
(((PBuiltinList
(PBuiltinPair
(PAsData PCurrencySymbol) (PAsData (PMap k PTokenName PInteger)))
:--> PBool)
:--> (PBuiltinList
(PBuiltinPair
(PAsData PCurrencySymbol) (PAsData (PMap k PTokenName PInteger)))
:--> PBool))
:--> (PBuiltinList
(PBuiltinPair
(PAsData PCurrencySymbol) (PAsData (PMap k PTokenName PInteger)))
:--> PBool))
forall (s :: S) (a :: S -> Type) (b :: S -> Type).
Term s (((a :--> b) :--> (a :--> b)) :--> (a :--> b))
pfix Term
s'
(((PBuiltinList
(PBuiltinPair
(PAsData PCurrencySymbol) (PAsData (PMap k PTokenName PInteger)))
:--> PBool)
:--> (PBuiltinList
(PBuiltinPair
(PAsData PCurrencySymbol) (PAsData (PMap k PTokenName PInteger)))
:--> PBool))
:--> (PBuiltinList
(PBuiltinPair
(PAsData PCurrencySymbol) (PAsData (PMap k PTokenName PInteger)))
:--> PBool))
-> Term
s'
((PBuiltinList
(PBuiltinPair
(PAsData PCurrencySymbol) (PAsData (PMap k PTokenName PInteger)))
:--> PBool)
:--> (PBuiltinList
(PBuiltinPair
(PAsData PCurrencySymbol) (PAsData (PMap k PTokenName PInteger)))
:--> PBool))
-> Term
s'
(PBuiltinList
(PBuiltinPair
(PAsData PCurrencySymbol) (PAsData (PMap k PTokenName PInteger)))
:--> PBool)
forall (s :: S) (a :: S -> Type) (b :: S -> Type).
Term s (a :--> b) -> Term s a -> Term s b
#$ (Term
s'
(PBuiltinList
(PBuiltinPair
(PAsData PCurrencySymbol) (PAsData (PMap k PTokenName PInteger)))
:--> PBool)
-> Term
s'
(PBuiltinList
(PBuiltinPair
(PAsData PCurrencySymbol) (PAsData (PMap k PTokenName PInteger))))
-> Term s' PBool)
-> Term
s'
((PBuiltinList
(PBuiltinPair
(PAsData PCurrencySymbol) (PAsData (PMap k PTokenName PInteger)))
:--> PBool)
:--> (PBuiltinList
(PBuiltinPair
(PAsData PCurrencySymbol) (PAsData (PMap k PTokenName PInteger)))
:--> 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'
(PBuiltinList
(PBuiltinPair
(PAsData PCurrencySymbol) (PAsData (PMap k PTokenName PInteger))))
-> Term s' PBool)
-> Term
s'
(c
:--> (PBuiltinList
(PBuiltinPair
(PAsData PCurrencySymbol) (PAsData (PMap k PTokenName PInteger)))
:--> PBool))
plam ((Term
s'
(PBuiltinList
(PBuiltinPair
(PAsData PCurrencySymbol) (PAsData (PMap k PTokenName PInteger)))
:--> PBool)
-> Term
s'
(PBuiltinList
(PBuiltinPair
(PAsData PCurrencySymbol) (PAsData (PMap k PTokenName PInteger))))
-> Term s' PBool)
-> Term
s'
((PBuiltinList
(PBuiltinPair
(PAsData PCurrencySymbol) (PAsData (PMap k PTokenName PInteger)))
:--> PBool)
:--> (PBuiltinList
(PBuiltinPair
(PAsData PCurrencySymbol) (PAsData (PMap k PTokenName PInteger)))
:--> PBool)))
-> (Term
s'
(PBuiltinList
(PBuiltinPair
(PAsData PCurrencySymbol) (PAsData (PMap k PTokenName PInteger)))
:--> PBool)
-> Term
s'
(PBuiltinList
(PBuiltinPair
(PAsData PCurrencySymbol) (PAsData (PMap k PTokenName PInteger))))
-> Term s' PBool)
-> Term
s'
((PBuiltinList
(PBuiltinPair
(PAsData PCurrencySymbol) (PAsData (PMap k PTokenName PInteger)))
:--> PBool)
:--> (PBuiltinList
(PBuiltinPair
(PAsData PCurrencySymbol) (PAsData (PMap k PTokenName PInteger)))
:--> PBool))
forall a b. (a -> b) -> a -> b
$ \Term
s'
(PBuiltinList
(PBuiltinPair
(PAsData PCurrencySymbol) (PAsData (PMap k PTokenName PInteger)))
:--> PBool)
self Term
s'
(PBuiltinList
(PBuiltinPair
(PAsData PCurrencySymbol) (PAsData (PMap k PTokenName PInteger))))
m ->
Term
s'
(PBuiltinList
(PBuiltinPair
(PAsData PCurrencySymbol) (PAsData (PMap k PTokenName PInteger))))
-> (PBuiltinList
(PBuiltinPair
(PAsData PCurrencySymbol) (PAsData (PMap k PTokenName PInteger)))
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'
(PBuiltinList
(PBuiltinPair
(PAsData PCurrencySymbol) (PAsData (PMap k PTokenName PInteger))))
m ((PBuiltinList
(PBuiltinPair
(PAsData PCurrencySymbol) (PAsData (PMap k PTokenName PInteger)))
s'
-> Term s' PBool)
-> Term s' PBool)
-> (PBuiltinList
(PBuiltinPair
(PAsData PCurrencySymbol) (PAsData (PMap k PTokenName PInteger)))
s'
-> Term s' PBool)
-> Term s' PBool
forall a b. (a -> b) -> a -> b
$ \case
PCons Term
s'
(PBuiltinPair
(PAsData PCurrencySymbol) (PAsData (PMap k PTokenName PInteger)))
x Term
s'
(PBuiltinList
(PBuiltinPair
(PAsData PCurrencySymbol) (PAsData (PMap k PTokenName PInteger))))
xs -> Term
s'
(PBuiltinList
(PBuiltinPair (PAsData PTokenName) (PAsData PInteger))
:--> PBool)
ClosedTerm
(PBuiltinList
(PBuiltinPair (PAsData PTokenName) (PAsData PInteger))
:--> PBool)
inner Term
s'
(PBuiltinList
(PBuiltinPair (PAsData PTokenName) (PAsData PInteger))
:--> PBool)
-> Term
s'
(PBuiltinList
(PBuiltinPair (PAsData PTokenName) (PAsData PInteger)))
-> Term s' PBool
forall (s :: S) (a :: S -> Type) (b :: S -> Type).
Term s (a :--> b) -> Term s a -> Term s b
# (Term s' (PMap k PTokenName PInteger)
-> Term
s'
(PBuiltinList
(PBuiltinPair (PAsData PTokenName) (PAsData PInteger)))
Term s' (PMap k PTokenName PInteger)
-> Term s' (PInner (PMap k PTokenName PInteger))
forall (s :: S) (a :: S -> Type). Term s a -> Term s (PInner a)
pto (Term s' (PMap k PTokenName PInteger)
-> Term
s'
(PBuiltinList
(PBuiltinPair (PAsData PTokenName) (PAsData PInteger))))
-> (Term s' (PAsData (PMap k PTokenName PInteger))
-> Term s' (PMap k PTokenName PInteger))
-> Term s' (PAsData (PMap k PTokenName PInteger))
-> Term
s'
(PBuiltinList
(PBuiltinPair (PAsData PTokenName) (PAsData PInteger)))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Term s' (PAsData (PMap k PTokenName PInteger))
-> Term s' (PMap k PTokenName PInteger)
forall (a :: S -> Type) (s :: S).
PIsData a =>
Term s (PAsData a) -> Term s a
pfromData (Term s' (PAsData (PMap k PTokenName PInteger))
-> Term
s'
(PBuiltinList
(PBuiltinPair (PAsData PTokenName) (PAsData PInteger))))
-> Term s' (PAsData (PMap k PTokenName PInteger))
-> Term
s'
(PBuiltinList
(PBuiltinPair (PAsData PTokenName) (PAsData PInteger)))
forall a b. (a -> b) -> a -> b
$ Term
s'
(PBuiltinPair
(PAsData PCurrencySymbol) (PAsData (PMap k PTokenName PInteger))
:--> PAsData (PMap k PTokenName PInteger))
forall (s :: S) (a :: S -> Type) (b :: S -> Type).
Term s (PBuiltinPair a b :--> b)
psndBuiltin Term
s'
(PBuiltinPair
(PAsData PCurrencySymbol) (PAsData (PMap k PTokenName PInteger))
:--> PAsData (PMap k PTokenName PInteger))
-> Term
s'
(PBuiltinPair
(PAsData PCurrencySymbol) (PAsData (PMap k PTokenName PInteger)))
-> Term s' (PAsData (PMap k PTokenName PInteger))
forall (s :: S) (a :: S -> Type) (b :: S -> Type).
Term s (a :--> b) -> Term s a -> Term s b
# Term
s'
(PBuiltinPair
(PAsData PCurrencySymbol) (PAsData (PMap k PTokenName PInteger)))
x) Term s' PBool -> Term s' PBool -> Term s' PBool
forall (s :: S). Term s PBool -> Term s PBool -> Term s PBool
#&& Term
s'
(PBuiltinList
(PBuiltinPair
(PAsData PCurrencySymbol) (PAsData (PMap k PTokenName PInteger)))
:--> PBool)
self Term
s'
(PBuiltinList
(PBuiltinPair
(PAsData PCurrencySymbol) (PAsData (PMap k PTokenName PInteger)))
:--> PBool)
-> Term
s'
(PBuiltinList
(PBuiltinPair
(PAsData PCurrencySymbol) (PAsData (PMap k PTokenName PInteger))))
-> Term s' PBool
forall (s :: S) (a :: S -> Type) (b :: S -> Type).
Term s (a :--> b) -> Term s a -> Term s b
# Term
s'
(PBuiltinList
(PBuiltinPair
(PAsData PCurrencySymbol) (PAsData (PMap k PTokenName PInteger))))
xs
PBuiltinList
(PBuiltinPair
(PAsData PCurrencySymbol) (PAsData (PMap k PTokenName PInteger)))
s'
PNil -> 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
inner :: ClosedTerm (PBuiltinList (PBuiltinPair (PAsData PTokenName) (PAsData PInteger)) :--> PBool)
inner :: ClosedTerm
(PBuiltinList
(PBuiltinPair (PAsData PTokenName) (PAsData PInteger))
:--> PBool)
inner = Term
s
(((PBuiltinList
(PBuiltinPair (PAsData PTokenName) (PAsData PInteger))
:--> PBool)
:--> (PBuiltinList
(PBuiltinPair (PAsData PTokenName) (PAsData PInteger))
:--> PBool))
:--> (PBuiltinList
(PBuiltinPair (PAsData PTokenName) (PAsData PInteger))
:--> PBool))
forall (s :: S) (a :: S -> Type) (b :: S -> Type).
Term s (((a :--> b) :--> (a :--> b)) :--> (a :--> b))
pfix Term
s
(((PBuiltinList
(PBuiltinPair (PAsData PTokenName) (PAsData PInteger))
:--> PBool)
:--> (PBuiltinList
(PBuiltinPair (PAsData PTokenName) (PAsData PInteger))
:--> PBool))
:--> (PBuiltinList
(PBuiltinPair (PAsData PTokenName) (PAsData PInteger))
:--> PBool))
-> Term
s
((PBuiltinList
(PBuiltinPair (PAsData PTokenName) (PAsData PInteger))
:--> PBool)
:--> (PBuiltinList
(PBuiltinPair (PAsData PTokenName) (PAsData PInteger))
:--> PBool))
-> Term
s
(PBuiltinList
(PBuiltinPair (PAsData PTokenName) (PAsData PInteger))
:--> PBool)
forall (s :: S) (a :: S -> Type) (b :: S -> Type).
Term s (a :--> b) -> Term s a -> Term s b
#$ (Term
s
(PBuiltinList
(PBuiltinPair (PAsData PTokenName) (PAsData PInteger))
:--> PBool)
-> Term
s
(PBuiltinList
(PBuiltinPair (PAsData PTokenName) (PAsData PInteger)))
-> Term s PBool)
-> Term
s
((PBuiltinList
(PBuiltinPair (PAsData PTokenName) (PAsData PInteger))
:--> PBool)
:--> (PBuiltinList
(PBuiltinPair (PAsData PTokenName) (PAsData PInteger))
:--> 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
(PBuiltinList
(PBuiltinPair (PAsData PTokenName) (PAsData PInteger)))
-> Term s PBool)
-> Term
s
(c
:--> (PBuiltinList
(PBuiltinPair (PAsData PTokenName) (PAsData PInteger))
:--> PBool))
plam ((Term
s
(PBuiltinList
(PBuiltinPair (PAsData PTokenName) (PAsData PInteger))
:--> PBool)
-> Term
s
(PBuiltinList
(PBuiltinPair (PAsData PTokenName) (PAsData PInteger)))
-> Term s PBool)
-> Term
s
((PBuiltinList
(PBuiltinPair (PAsData PTokenName) (PAsData PInteger))
:--> PBool)
:--> (PBuiltinList
(PBuiltinPair (PAsData PTokenName) (PAsData PInteger))
:--> PBool)))
-> (Term
s
(PBuiltinList
(PBuiltinPair (PAsData PTokenName) (PAsData PInteger))
:--> PBool)
-> Term
s
(PBuiltinList
(PBuiltinPair (PAsData PTokenName) (PAsData PInteger)))
-> Term s PBool)
-> Term
s
((PBuiltinList
(PBuiltinPair (PAsData PTokenName) (PAsData PInteger))
:--> PBool)
:--> (PBuiltinList
(PBuiltinPair (PAsData PTokenName) (PAsData PInteger))
:--> PBool))
forall a b. (a -> b) -> a -> b
$ \Term
s
(PBuiltinList
(PBuiltinPair (PAsData PTokenName) (PAsData PInteger))
:--> PBool)
self Term
s
(PBuiltinList
(PBuiltinPair (PAsData PTokenName) (PAsData PInteger)))
m ->
Term
s
(PBuiltinList
(PBuiltinPair (PAsData PTokenName) (PAsData PInteger)))
-> (PBuiltinList
(PBuiltinPair (PAsData PTokenName) (PAsData PInteger)) 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
(PBuiltinList
(PBuiltinPair (PAsData PTokenName) (PAsData PInteger)))
m ((PBuiltinList
(PBuiltinPair (PAsData PTokenName) (PAsData PInteger)) s
-> Term s PBool)
-> Term s PBool)
-> (PBuiltinList
(PBuiltinPair (PAsData PTokenName) (PAsData PInteger)) s
-> Term s PBool)
-> Term s PBool
forall a b. (a -> b) -> a -> b
$ \case
PCons Term s (PBuiltinPair (PAsData PTokenName) (PAsData PInteger))
x Term
s
(PBuiltinList
(PBuiltinPair (PAsData PTokenName) (PAsData PInteger)))
xs -> Term s (PBool :--> PBool)
forall (s :: S). Term s (PBool :--> PBool)
pnot Term s (PBool :--> PBool) -> Term s PBool -> Term s PBool
forall (s :: S) (a :: S -> Type) (b :: S -> Type).
Term s (a :--> b) -> Term s a -> Term s b
# (Term
s
(PBuiltinPair (PAsData PTokenName) (PAsData PInteger)
:--> PAsData PInteger)
forall (s :: S) (a :: S -> Type) (b :: S -> Type).
Term s (PBuiltinPair a b :--> b)
psndBuiltin Term
s
(PBuiltinPair (PAsData PTokenName) (PAsData PInteger)
:--> PAsData PInteger)
-> Term s (PBuiltinPair (PAsData PTokenName) (PAsData PInteger))
-> Term s (PAsData PInteger)
forall (s :: S) (a :: S -> Type) (b :: S -> Type).
Term s (a :--> b) -> Term s a -> Term s b
# Term s (PBuiltinPair (PAsData PTokenName) (PAsData PInteger))
x Term s (PAsData PInteger)
-> Term s (PAsData PInteger) -> Term s PBool
forall (s :: S).
Term s (PAsData PInteger)
-> Term s (PAsData PInteger) -> Term s PBool
forall (t :: S -> Type) (s :: S).
PEq t =>
Term s t -> Term s t -> Term s PBool
#== forall (a :: S -> Type) (s :: S).
PLiftable a =>
AsHaskell a -> Term s a
pconstant @(PAsData PInteger) Integer
AsHaskell (PAsData PInteger)
0) Term s PBool -> Term s PBool -> Term s PBool
forall (s :: S). Term s PBool -> Term s PBool -> Term s PBool
#&& Term
s
(PBuiltinList
(PBuiltinPair (PAsData PTokenName) (PAsData PInteger))
:--> PBool)
self Term
s
(PBuiltinList
(PBuiltinPair (PAsData PTokenName) (PAsData PInteger))
:--> PBool)
-> Term
s
(PBuiltinList
(PBuiltinPair (PAsData PTokenName) (PAsData PInteger)))
-> Term s PBool
forall (s :: S) (a :: S -> Type) (b :: S -> Type).
Term s (a :--> b) -> Term s a -> Term s b
# Term
s
(PBuiltinList
(PBuiltinPair (PAsData PTokenName) (PAsData PInteger)))
xs
PBuiltinList
(PBuiltinPair (PAsData PTokenName) (PAsData PInteger)) s
PNil -> 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