-- TODO: this module adds a copy of the 'Value' type
-- in which the underlying maps are 'Data.AssocMap'.
-- !!WARNING!!: this is currently experimental so do not use in production code!

-- editorconfig-checker-disable-file
{-# LANGUAGE BlockArguments     #-}
{-# LANGUAGE DataKinds          #-}
{-# LANGUAGE DeriveAnyClass     #-}
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE DerivingVia        #-}
{-# LANGUAGE FlexibleInstances  #-}
{-# LANGUAGE LambdaCase         #-}
{-# LANGUAGE NoImplicitPrelude  #-}
{-# LANGUAGE OverloadedStrings  #-}
{-# LANGUAGE TemplateHaskell    #-}
{-# LANGUAGE TypeApplications   #-}
{-# LANGUAGE TypeFamilies       #-}
{-# LANGUAGE ViewPatterns       #-}

-- Prevent unboxing, which the plugin can't deal with
{-# OPTIONS_GHC -fno-omit-interface-pragmas #-}
{-# OPTIONS_GHC -fno-spec-constr #-}
{-# OPTIONS_GHC -fno-specialise #-}
{-# OPTIONS_GHC -fexpose-all-unfoldings #-}
-- We need -fexpose-all-unfoldings to compile the Marlowe validator
-- with GHC 9.6.2.
-- TODO. Look into this more closely: see https://github.com/IntersectMBO/plutus/issues/6172.

-- | Functions for working with 'Value'.
module PlutusLedgerApi.V1.Data.Value (
    -- ** Currency symbols
      CurrencySymbol(..)
    , currencySymbol
    , adaSymbol
    -- ** Token names
    , TokenName(..)
    , tokenName
    , toString
    , adaToken
    -- * Asset classes
    , AssetClass(..)
    , assetClass
    , assetClassValue
    , assetClassValueOf
    -- ** Value
    , Value(..)
    , singleton
    , valueOf
    , currencySymbolValueOf
    , lovelaceValue
    , lovelaceValueOf
    , scale
    , symbols
      -- * Partial order operations
    , geq
    , gt
    , leq
    , lt
      -- * Etc.
    , isZero
    , split
    , unionWith
    , flattenValue
    , Lovelace (..)
    ) where

import Prelude qualified as Haskell

import Control.DeepSeq (NFData)
import Data.ByteString qualified as BS
import Data.Data (Data, Typeable)
import Data.Function ((&))
import Data.String (IsString (fromString))
import Data.Text (Text)
import Data.Text qualified as Text
import Data.Text.Encoding qualified as E
import GHC.Generics (Generic)
import PlutusLedgerApi.V1 (UnsafeFromData (unsafeFromBuiltinData))
import PlutusLedgerApi.V1.Bytes (LedgerBytes (LedgerBytes), encodeByteString)
import PlutusTx qualified
import PlutusTx.Blueprint.Class (HasBlueprintSchema (..))
import PlutusTx.Blueprint.Definition (HasBlueprintDefinition (..), definitionIdFromType,
                                      definitionRef)
import PlutusTx.Blueprint.Schema (MapSchema (..), PairSchema (..), Schema (..), withSchemaInfo)
import PlutusTx.Blueprint.Schema.Annotation (SchemaInfo (..), emptySchemaInfo)
import PlutusTx.Builtins qualified as B
import PlutusTx.Builtins.Internal (BuiltinList, BuiltinPair)
import PlutusTx.Builtins.Internal qualified as BI
import PlutusTx.Data.AssocMap qualified as Map
import PlutusTx.Lift (makeLift)
import PlutusTx.Ord qualified as Ord
import PlutusTx.Prelude as PlutusTx hiding (sort)
import PlutusTx.Show qualified as PlutusTx
import PlutusTx.These (These (..))
import Prettyprinter (Pretty, (<>))
import Prettyprinter.Extras (PrettyShow (PrettyShow))

{- | ByteString representing the currency, hashed with /BLAKE2b-224/.
It is empty for `Ada`, 28 bytes for `MintingPolicyHash`.
Forms an `AssetClass` along with `TokenName`.
A `Value` is a map from `CurrencySymbol`'s to a map from `TokenName` to an `Integer`.

This is a simple type without any validation, __use with caution__.
You may want to add checks for its invariants. See the
 [Shelley ledger specification](https://github.com/IntersectMBO/cardano-ledger/releases/download/cardano-ledger-spec-2023-04-03/shelley-ledger.pdf).
-}
newtype CurrencySymbol = CurrencySymbol
  { CurrencySymbol -> BuiltinByteString
unCurrencySymbol :: PlutusTx.BuiltinByteString
  }
  deriving
    ( -- | from hex encoding
      String -> CurrencySymbol
(String -> CurrencySymbol) -> IsString CurrencySymbol
forall a. (String -> a) -> IsString a
$cfromString :: String -> CurrencySymbol
fromString :: String -> CurrencySymbol
IsString
    , -- | using hex encoding
      Int -> CurrencySymbol -> ShowS
[CurrencySymbol] -> ShowS
CurrencySymbol -> String
(Int -> CurrencySymbol -> ShowS)
-> (CurrencySymbol -> String)
-> ([CurrencySymbol] -> ShowS)
-> Show CurrencySymbol
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> CurrencySymbol -> ShowS
showsPrec :: Int -> CurrencySymbol -> ShowS
$cshow :: CurrencySymbol -> String
show :: CurrencySymbol -> String
$cshowList :: [CurrencySymbol] -> ShowS
showList :: [CurrencySymbol] -> ShowS
Haskell.Show
    , -- | using hex encoding
      (forall ann. CurrencySymbol -> Doc ann)
-> (forall ann. [CurrencySymbol] -> Doc ann)
-> Pretty CurrencySymbol
forall ann. [CurrencySymbol] -> Doc ann
forall ann. CurrencySymbol -> Doc ann
forall a.
(forall ann. a -> Doc ann)
-> (forall ann. [a] -> Doc ann) -> Pretty a
$cpretty :: forall ann. CurrencySymbol -> Doc ann
pretty :: forall ann. CurrencySymbol -> Doc ann
$cprettyList :: forall ann. [CurrencySymbol] -> Doc ann
prettyList :: forall ann. [CurrencySymbol] -> Doc ann
Pretty
    )
    via LedgerBytes
  deriving stock ((forall x. CurrencySymbol -> Rep CurrencySymbol x)
-> (forall x. Rep CurrencySymbol x -> CurrencySymbol)
-> Generic CurrencySymbol
forall x. Rep CurrencySymbol x -> CurrencySymbol
forall x. CurrencySymbol -> Rep CurrencySymbol x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. CurrencySymbol -> Rep CurrencySymbol x
from :: forall x. CurrencySymbol -> Rep CurrencySymbol x
$cto :: forall x. Rep CurrencySymbol x -> CurrencySymbol
to :: forall x. Rep CurrencySymbol x -> CurrencySymbol
Generic, Typeable CurrencySymbol
Typeable CurrencySymbol =>
(forall (c :: * -> *).
 (forall d b. Data d => c (d -> b) -> d -> c b)
 -> (forall g. g -> c g) -> CurrencySymbol -> c CurrencySymbol)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c CurrencySymbol)
-> (CurrencySymbol -> Constr)
-> (CurrencySymbol -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c CurrencySymbol))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e))
    -> Maybe (c CurrencySymbol))
-> ((forall b. Data b => b -> b)
    -> CurrencySymbol -> CurrencySymbol)
-> (forall r r'.
    (r -> r' -> r)
    -> r -> (forall d. Data d => d -> r') -> CurrencySymbol -> r)
-> (forall r r'.
    (r' -> r -> r)
    -> r -> (forall d. Data d => d -> r') -> CurrencySymbol -> r)
-> (forall u.
    (forall d. Data d => d -> u) -> CurrencySymbol -> [u])
-> (forall u.
    Int -> (forall d. Data d => d -> u) -> CurrencySymbol -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d)
    -> CurrencySymbol -> m CurrencySymbol)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d)
    -> CurrencySymbol -> m CurrencySymbol)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d)
    -> CurrencySymbol -> m CurrencySymbol)
-> Data CurrencySymbol
CurrencySymbol -> Constr
CurrencySymbol -> DataType
(forall b. Data b => b -> b) -> CurrencySymbol -> CurrencySymbol
forall a.
Typeable a =>
(forall (c :: * -> *).
 (forall d b. Data d => c (d -> b) -> d -> c b)
 -> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
    (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
    (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u.
Int -> (forall d. Data d => d -> u) -> CurrencySymbol -> u
forall u. (forall d. Data d => d -> u) -> CurrencySymbol -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> CurrencySymbol -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> CurrencySymbol -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> CurrencySymbol -> m CurrencySymbol
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> CurrencySymbol -> m CurrencySymbol
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c CurrencySymbol
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> CurrencySymbol -> c CurrencySymbol
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c CurrencySymbol)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c CurrencySymbol)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> CurrencySymbol -> c CurrencySymbol
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> CurrencySymbol -> c CurrencySymbol
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c CurrencySymbol
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c CurrencySymbol
$ctoConstr :: CurrencySymbol -> Constr
toConstr :: CurrencySymbol -> Constr
$cdataTypeOf :: CurrencySymbol -> DataType
dataTypeOf :: CurrencySymbol -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c CurrencySymbol)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c CurrencySymbol)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c CurrencySymbol)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c CurrencySymbol)
$cgmapT :: (forall b. Data b => b -> b) -> CurrencySymbol -> CurrencySymbol
gmapT :: (forall b. Data b => b -> b) -> CurrencySymbol -> CurrencySymbol
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> CurrencySymbol -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> CurrencySymbol -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> CurrencySymbol -> r
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> CurrencySymbol -> r
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> CurrencySymbol -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> CurrencySymbol -> [u]
$cgmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> CurrencySymbol -> u
gmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> CurrencySymbol -> u
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> CurrencySymbol -> m CurrencySymbol
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> CurrencySymbol -> m CurrencySymbol
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> CurrencySymbol -> m CurrencySymbol
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> CurrencySymbol -> m CurrencySymbol
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> CurrencySymbol -> m CurrencySymbol
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> CurrencySymbol -> m CurrencySymbol
Data, Typeable)
  deriving newtype
    ( CurrencySymbol -> CurrencySymbol -> Bool
(CurrencySymbol -> CurrencySymbol -> Bool)
-> (CurrencySymbol -> CurrencySymbol -> Bool) -> Eq CurrencySymbol
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: CurrencySymbol -> CurrencySymbol -> Bool
== :: CurrencySymbol -> CurrencySymbol -> Bool
$c/= :: CurrencySymbol -> CurrencySymbol -> Bool
/= :: CurrencySymbol -> CurrencySymbol -> Bool
Haskell.Eq
    , Eq CurrencySymbol
Eq CurrencySymbol =>
(CurrencySymbol -> CurrencySymbol -> Ordering)
-> (CurrencySymbol -> CurrencySymbol -> Bool)
-> (CurrencySymbol -> CurrencySymbol -> Bool)
-> (CurrencySymbol -> CurrencySymbol -> Bool)
-> (CurrencySymbol -> CurrencySymbol -> Bool)
-> (CurrencySymbol -> CurrencySymbol -> CurrencySymbol)
-> (CurrencySymbol -> CurrencySymbol -> CurrencySymbol)
-> Ord CurrencySymbol
CurrencySymbol -> CurrencySymbol -> Bool
CurrencySymbol -> CurrencySymbol -> Ordering
CurrencySymbol -> CurrencySymbol -> CurrencySymbol
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: CurrencySymbol -> CurrencySymbol -> Ordering
compare :: CurrencySymbol -> CurrencySymbol -> Ordering
$c< :: CurrencySymbol -> CurrencySymbol -> Bool
< :: CurrencySymbol -> CurrencySymbol -> Bool
$c<= :: CurrencySymbol -> CurrencySymbol -> Bool
<= :: CurrencySymbol -> CurrencySymbol -> Bool
$c> :: CurrencySymbol -> CurrencySymbol -> Bool
> :: CurrencySymbol -> CurrencySymbol -> Bool
$c>= :: CurrencySymbol -> CurrencySymbol -> Bool
>= :: CurrencySymbol -> CurrencySymbol -> Bool
$cmax :: CurrencySymbol -> CurrencySymbol -> CurrencySymbol
max :: CurrencySymbol -> CurrencySymbol -> CurrencySymbol
$cmin :: CurrencySymbol -> CurrencySymbol -> CurrencySymbol
min :: CurrencySymbol -> CurrencySymbol -> CurrencySymbol
Haskell.Ord
    , CurrencySymbol -> CurrencySymbol -> Bool
(CurrencySymbol -> CurrencySymbol -> Bool) -> Eq CurrencySymbol
forall a. (a -> a -> Bool) -> Eq a
$c== :: CurrencySymbol -> CurrencySymbol -> Bool
== :: CurrencySymbol -> CurrencySymbol -> Bool
Eq
    , Eq CurrencySymbol
Eq CurrencySymbol =>
(CurrencySymbol -> CurrencySymbol -> Ordering)
-> (CurrencySymbol -> CurrencySymbol -> Bool)
-> (CurrencySymbol -> CurrencySymbol -> Bool)
-> (CurrencySymbol -> CurrencySymbol -> Bool)
-> (CurrencySymbol -> CurrencySymbol -> Bool)
-> (CurrencySymbol -> CurrencySymbol -> CurrencySymbol)
-> (CurrencySymbol -> CurrencySymbol -> CurrencySymbol)
-> Ord CurrencySymbol
CurrencySymbol -> CurrencySymbol -> Bool
CurrencySymbol -> CurrencySymbol -> Ordering
CurrencySymbol -> CurrencySymbol -> CurrencySymbol
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: CurrencySymbol -> CurrencySymbol -> Ordering
compare :: CurrencySymbol -> CurrencySymbol -> Ordering
$c< :: CurrencySymbol -> CurrencySymbol -> Bool
< :: CurrencySymbol -> CurrencySymbol -> Bool
$c<= :: CurrencySymbol -> CurrencySymbol -> Bool
<= :: CurrencySymbol -> CurrencySymbol -> Bool
$c> :: CurrencySymbol -> CurrencySymbol -> Bool
> :: CurrencySymbol -> CurrencySymbol -> Bool
$c>= :: CurrencySymbol -> CurrencySymbol -> Bool
>= :: CurrencySymbol -> CurrencySymbol -> Bool
$cmax :: CurrencySymbol -> CurrencySymbol -> CurrencySymbol
max :: CurrencySymbol -> CurrencySymbol -> CurrencySymbol
$cmin :: CurrencySymbol -> CurrencySymbol -> CurrencySymbol
min :: CurrencySymbol -> CurrencySymbol -> CurrencySymbol
Ord
    , CurrencySymbol -> BuiltinData
(CurrencySymbol -> BuiltinData) -> ToData CurrencySymbol
forall a. (a -> BuiltinData) -> ToData a
$ctoBuiltinData :: CurrencySymbol -> BuiltinData
toBuiltinData :: CurrencySymbol -> BuiltinData
PlutusTx.ToData
    , BuiltinData -> Maybe CurrencySymbol
(BuiltinData -> Maybe CurrencySymbol) -> FromData CurrencySymbol
forall a. (BuiltinData -> Maybe a) -> FromData a
$cfromBuiltinData :: BuiltinData -> Maybe CurrencySymbol
fromBuiltinData :: BuiltinData -> Maybe CurrencySymbol
PlutusTx.FromData
    , BuiltinData -> CurrencySymbol
(BuiltinData -> CurrencySymbol) -> UnsafeFromData CurrencySymbol
forall a. (BuiltinData -> a) -> UnsafeFromData a
$cunsafeFromBuiltinData :: BuiltinData -> CurrencySymbol
unsafeFromBuiltinData :: BuiltinData -> CurrencySymbol
PlutusTx.UnsafeFromData
    )
  deriving anyclass (CurrencySymbol -> ()
(CurrencySymbol -> ()) -> NFData CurrencySymbol
forall a. (a -> ()) -> NFData a
$crnf :: CurrencySymbol -> ()
rnf :: CurrencySymbol -> ()
NFData, DefinitionId
DefinitionId -> HasBlueprintDefinition CurrencySymbol
forall t. DefinitionId -> HasBlueprintDefinition t
$cdefinitionId :: DefinitionId
definitionId :: DefinitionId
HasBlueprintDefinition)

instance HasBlueprintSchema CurrencySymbol referencedTypes where
  {-# INLINABLE schema #-}
  schema :: Schema referencedTypes
schema = forall t (referencedTypes :: [*]).
HasBlueprintSchema t referencedTypes =>
Schema referencedTypes
schema @PlutusTx.BuiltinByteString
    Schema referencedTypes
-> (Schema referencedTypes -> Schema referencedTypes)
-> Schema referencedTypes
forall a b. a -> (a -> b) -> b
& (SchemaInfo -> SchemaInfo)
-> Schema referencedTypes -> Schema referencedTypes
forall (referencedTypes :: [*]).
(SchemaInfo -> SchemaInfo)
-> Schema referencedTypes -> Schema referencedTypes
withSchemaInfo \SchemaInfo
info ->
      SchemaInfo
info { title = Just "CurrencySymbol" }

{-# INLINABLE currencySymbol #-}
-- | Creates `CurrencySymbol` from raw `ByteString`.
currencySymbol :: BS.ByteString -> CurrencySymbol
currencySymbol :: ByteString -> CurrencySymbol
currencySymbol = BuiltinByteString -> CurrencySymbol
CurrencySymbol (BuiltinByteString -> CurrencySymbol)
-> (ByteString -> BuiltinByteString)
-> ByteString
-> CurrencySymbol
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> BuiltinByteString
ByteString -> ToBuiltin ByteString
forall a. HasToBuiltin a => a -> ToBuiltin a
PlutusTx.toBuiltin

{- | ByteString of a name of a token.
Shown as UTF-8 string when possible.
Should be no longer than 32 bytes, empty for Ada.
Forms an `AssetClass` along with a `CurrencySymbol`.

This is a simple type without any validation, __use with caution__.
You may want to add checks for its invariants. See the
 [Shelley ledger specification](https://github.com/IntersectMBO/cardano-ledger/releases/download/cardano-ledger-spec-2023-04-03/shelley-ledger.pdf).
-}
newtype TokenName = TokenName {TokenName -> BuiltinByteString
unTokenName :: PlutusTx.BuiltinByteString}
  deriving stock ((forall x. TokenName -> Rep TokenName x)
-> (forall x. Rep TokenName x -> TokenName) -> Generic TokenName
forall x. Rep TokenName x -> TokenName
forall x. TokenName -> Rep TokenName x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. TokenName -> Rep TokenName x
from :: forall x. TokenName -> Rep TokenName x
$cto :: forall x. Rep TokenName x -> TokenName
to :: forall x. Rep TokenName x -> TokenName
Generic, Typeable TokenName
Typeable TokenName =>
(forall (c :: * -> *).
 (forall d b. Data d => c (d -> b) -> d -> c b)
 -> (forall g. g -> c g) -> TokenName -> c TokenName)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c TokenName)
-> (TokenName -> Constr)
-> (TokenName -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c TokenName))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TokenName))
-> ((forall b. Data b => b -> b) -> TokenName -> TokenName)
-> (forall r r'.
    (r -> r' -> r)
    -> r -> (forall d. Data d => d -> r') -> TokenName -> r)
-> (forall r r'.
    (r' -> r -> r)
    -> r -> (forall d. Data d => d -> r') -> TokenName -> r)
-> (forall u. (forall d. Data d => d -> u) -> TokenName -> [u])
-> (forall u.
    Int -> (forall d. Data d => d -> u) -> TokenName -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> TokenName -> m TokenName)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> TokenName -> m TokenName)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> TokenName -> m TokenName)
-> Data TokenName
TokenName -> Constr
TokenName -> DataType
(forall b. Data b => b -> b) -> TokenName -> TokenName
forall a.
Typeable a =>
(forall (c :: * -> *).
 (forall d b. Data d => c (d -> b) -> d -> c b)
 -> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
    (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
    (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> TokenName -> u
forall u. (forall d. Data d => d -> u) -> TokenName -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> TokenName -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> TokenName -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> TokenName -> m TokenName
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> TokenName -> m TokenName
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c TokenName
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> TokenName -> c TokenName
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c TokenName)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TokenName)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> TokenName -> c TokenName
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> TokenName -> c TokenName
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c TokenName
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c TokenName
$ctoConstr :: TokenName -> Constr
toConstr :: TokenName -> Constr
$cdataTypeOf :: TokenName -> DataType
dataTypeOf :: TokenName -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c TokenName)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c TokenName)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TokenName)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TokenName)
$cgmapT :: (forall b. Data b => b -> b) -> TokenName -> TokenName
gmapT :: (forall b. Data b => b -> b) -> TokenName -> TokenName
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> TokenName -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> TokenName -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> TokenName -> r
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> TokenName -> r
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> TokenName -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> TokenName -> [u]
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> TokenName -> u
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> TokenName -> u
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> TokenName -> m TokenName
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> TokenName -> m TokenName
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> TokenName -> m TokenName
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> TokenName -> m TokenName
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> TokenName -> m TokenName
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> TokenName -> m TokenName
Data, Typeable)
  deriving newtype
    ( TokenName -> TokenName -> Bool
(TokenName -> TokenName -> Bool)
-> (TokenName -> TokenName -> Bool) -> Eq TokenName
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: TokenName -> TokenName -> Bool
== :: TokenName -> TokenName -> Bool
$c/= :: TokenName -> TokenName -> Bool
/= :: TokenName -> TokenName -> Bool
Haskell.Eq
    , Eq TokenName
Eq TokenName =>
(TokenName -> TokenName -> Ordering)
-> (TokenName -> TokenName -> Bool)
-> (TokenName -> TokenName -> Bool)
-> (TokenName -> TokenName -> Bool)
-> (TokenName -> TokenName -> Bool)
-> (TokenName -> TokenName -> TokenName)
-> (TokenName -> TokenName -> TokenName)
-> Ord TokenName
TokenName -> TokenName -> Bool
TokenName -> TokenName -> Ordering
TokenName -> TokenName -> TokenName
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: TokenName -> TokenName -> Ordering
compare :: TokenName -> TokenName -> Ordering
$c< :: TokenName -> TokenName -> Bool
< :: TokenName -> TokenName -> Bool
$c<= :: TokenName -> TokenName -> Bool
<= :: TokenName -> TokenName -> Bool
$c> :: TokenName -> TokenName -> Bool
> :: TokenName -> TokenName -> Bool
$c>= :: TokenName -> TokenName -> Bool
>= :: TokenName -> TokenName -> Bool
$cmax :: TokenName -> TokenName -> TokenName
max :: TokenName -> TokenName -> TokenName
$cmin :: TokenName -> TokenName -> TokenName
min :: TokenName -> TokenName -> TokenName
Haskell.Ord
    , TokenName -> TokenName -> Bool
(TokenName -> TokenName -> Bool) -> Eq TokenName
forall a. (a -> a -> Bool) -> Eq a
$c== :: TokenName -> TokenName -> Bool
== :: TokenName -> TokenName -> Bool
Eq
    , Eq TokenName
Eq TokenName =>
(TokenName -> TokenName -> Ordering)
-> (TokenName -> TokenName -> Bool)
-> (TokenName -> TokenName -> Bool)
-> (TokenName -> TokenName -> Bool)
-> (TokenName -> TokenName -> Bool)
-> (TokenName -> TokenName -> TokenName)
-> (TokenName -> TokenName -> TokenName)
-> Ord TokenName
TokenName -> TokenName -> Bool
TokenName -> TokenName -> Ordering
TokenName -> TokenName -> TokenName
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: TokenName -> TokenName -> Ordering
compare :: TokenName -> TokenName -> Ordering
$c< :: TokenName -> TokenName -> Bool
< :: TokenName -> TokenName -> Bool
$c<= :: TokenName -> TokenName -> Bool
<= :: TokenName -> TokenName -> Bool
$c> :: TokenName -> TokenName -> Bool
> :: TokenName -> TokenName -> Bool
$c>= :: TokenName -> TokenName -> Bool
>= :: TokenName -> TokenName -> Bool
$cmax :: TokenName -> TokenName -> TokenName
max :: TokenName -> TokenName -> TokenName
$cmin :: TokenName -> TokenName -> TokenName
min :: TokenName -> TokenName -> TokenName
Ord
    , TokenName -> BuiltinData
(TokenName -> BuiltinData) -> ToData TokenName
forall a. (a -> BuiltinData) -> ToData a
$ctoBuiltinData :: TokenName -> BuiltinData
toBuiltinData :: TokenName -> BuiltinData
PlutusTx.ToData
    , BuiltinData -> Maybe TokenName
(BuiltinData -> Maybe TokenName) -> FromData TokenName
forall a. (BuiltinData -> Maybe a) -> FromData a
$cfromBuiltinData :: BuiltinData -> Maybe TokenName
fromBuiltinData :: BuiltinData -> Maybe TokenName
PlutusTx.FromData
    , BuiltinData -> TokenName
(BuiltinData -> TokenName) -> UnsafeFromData TokenName
forall a. (BuiltinData -> a) -> UnsafeFromData a
$cunsafeFromBuiltinData :: BuiltinData -> TokenName
unsafeFromBuiltinData :: BuiltinData -> TokenName
PlutusTx.UnsafeFromData
    )
  deriving anyclass (TokenName -> ()
(TokenName -> ()) -> NFData TokenName
forall a. (a -> ()) -> NFData a
$crnf :: TokenName -> ()
rnf :: TokenName -> ()
NFData, DefinitionId
DefinitionId -> HasBlueprintDefinition TokenName
forall t. DefinitionId -> HasBlueprintDefinition t
$cdefinitionId :: DefinitionId
definitionId :: DefinitionId
HasBlueprintDefinition)
  deriving ((forall ann. TokenName -> Doc ann)
-> (forall ann. [TokenName] -> Doc ann) -> Pretty TokenName
forall ann. [TokenName] -> Doc ann
forall ann. TokenName -> Doc ann
forall a.
(forall ann. a -> Doc ann)
-> (forall ann. [a] -> Doc ann) -> Pretty a
$cpretty :: forall ann. TokenName -> Doc ann
pretty :: forall ann. TokenName -> Doc ann
$cprettyList :: forall ann. [TokenName] -> Doc ann
prettyList :: forall ann. [TokenName] -> Doc ann
Pretty) via (PrettyShow TokenName)

-- | UTF-8 encoding. Doesn't verify length.
instance IsString TokenName where
    fromString :: String -> TokenName
fromString = Text -> TokenName
fromText (Text -> TokenName) -> (String -> Text) -> String -> TokenName
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Text
Text.pack

instance HasBlueprintSchema TokenName referencedTypes where
  {-# INLINABLE schema #-}
  schema :: Schema referencedTypes
schema = forall t (referencedTypes :: [*]).
HasBlueprintSchema t referencedTypes =>
Schema referencedTypes
schema @PlutusTx.BuiltinByteString
    Schema referencedTypes
-> (Schema referencedTypes -> Schema referencedTypes)
-> Schema referencedTypes
forall a b. a -> (a -> b) -> b
& (SchemaInfo -> SchemaInfo)
-> Schema referencedTypes -> Schema referencedTypes
forall (referencedTypes :: [*]).
(SchemaInfo -> SchemaInfo)
-> Schema referencedTypes -> Schema referencedTypes
withSchemaInfo \SchemaInfo
info ->
      SchemaInfo
info { title = Just "TokenName" }

{-# INLINABLE tokenName #-}
-- | Creates `TokenName` from raw `BS.ByteString`.
tokenName :: BS.ByteString -> TokenName
tokenName :: ByteString -> TokenName
tokenName = BuiltinByteString -> TokenName
TokenName (BuiltinByteString -> TokenName)
-> (ByteString -> BuiltinByteString) -> ByteString -> TokenName
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> BuiltinByteString
ByteString -> ToBuiltin ByteString
forall a. HasToBuiltin a => a -> ToBuiltin a
PlutusTx.toBuiltin

fromText :: Text -> TokenName
fromText :: Text -> TokenName
fromText = ByteString -> TokenName
tokenName (ByteString -> TokenName)
-> (Text -> ByteString) -> Text -> TokenName
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> ByteString
E.encodeUtf8

fromTokenName :: (BS.ByteString -> r) -> (Text -> r) -> TokenName -> r
fromTokenName :: forall r. (ByteString -> r) -> (Text -> r) -> TokenName -> r
fromTokenName ByteString -> r
handleBytestring Text -> r
handleText (TokenName BuiltinByteString
bs) =
  (UnicodeException -> r)
-> (Text -> r) -> Either UnicodeException Text -> r
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either (\UnicodeException
_ -> ByteString -> r
handleBytestring (ByteString -> r) -> ByteString -> r
forall a b. (a -> b) -> a -> b
$ BuiltinByteString -> FromBuiltin BuiltinByteString
forall arep. HasFromBuiltin arep => arep -> FromBuiltin arep
PlutusTx.fromBuiltin BuiltinByteString
bs) Text -> r
handleText (Either UnicodeException Text -> r)
-> Either UnicodeException Text -> r
forall a b. (a -> b) -> a -> b
$
    ByteString -> Either UnicodeException Text
E.decodeUtf8' (BuiltinByteString -> FromBuiltin BuiltinByteString
forall arep. HasFromBuiltin arep => arep -> FromBuiltin arep
PlutusTx.fromBuiltin BuiltinByteString
bs)

-- | Encode a `ByteString` to a hex `Text`.
asBase16 :: BS.ByteString -> Text
asBase16 :: ByteString -> Text
asBase16 ByteString
bs = [Text] -> Text
Text.concat [Text
"0x", ByteString -> Text
encodeByteString ByteString
bs]

-- | Wrap the input `Text` in double quotes.
quoted :: Text -> Text
quoted :: Text -> Text
quoted Text
s = [Text] -> Text
Text.concat [Text
"\"", Text
s, Text
"\""]

{- | Turn a TokenName to a hex-encoded 'String'

Compared to `show` , it will not surround the string with double-quotes.
-}
toString :: TokenName -> Haskell.String
toString :: TokenName -> String
toString = Text -> String
Text.unpack (Text -> String) -> (TokenName -> Text) -> TokenName -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ByteString -> Text) -> (Text -> Text) -> TokenName -> Text
forall r. (ByteString -> r) -> (Text -> r) -> TokenName -> r
fromTokenName ByteString -> Text
asBase16 Text -> Text
forall a. a -> a
id

instance Haskell.Show TokenName where
    show :: TokenName -> String
show = Text -> String
Text.unpack (Text -> String) -> (TokenName -> Text) -> TokenName -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ByteString -> Text) -> (Text -> Text) -> TokenName -> Text
forall r. (ByteString -> r) -> (Text -> r) -> TokenName -> r
fromTokenName ByteString -> Text
asBase16 Text -> Text
quoted

{-# INLINABLE adaSymbol #-}
-- | The 'CurrencySymbol' of the 'Ada' currency.
adaSymbol :: CurrencySymbol
adaSymbol :: CurrencySymbol
adaSymbol = BuiltinByteString -> CurrencySymbol
CurrencySymbol BuiltinByteString
emptyByteString

{-# INLINABLE adaToken #-}
-- | The 'TokenName' of the 'Ada' currency.
adaToken :: TokenName
adaToken :: TokenName
adaToken = BuiltinByteString -> TokenName
TokenName BuiltinByteString
emptyByteString

-- | An asset class, identified by a `CurrencySymbol` and a `TokenName`.
newtype AssetClass = AssetClass {AssetClass -> (CurrencySymbol, TokenName)
unAssetClass :: (CurrencySymbol, TokenName)}
  deriving stock ((forall x. AssetClass -> Rep AssetClass x)
-> (forall x. Rep AssetClass x -> AssetClass) -> Generic AssetClass
forall x. Rep AssetClass x -> AssetClass
forall x. AssetClass -> Rep AssetClass x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. AssetClass -> Rep AssetClass x
from :: forall x. AssetClass -> Rep AssetClass x
$cto :: forall x. Rep AssetClass x -> AssetClass
to :: forall x. Rep AssetClass x -> AssetClass
Generic, Typeable AssetClass
Typeable AssetClass =>
(forall (c :: * -> *).
 (forall d b. Data d => c (d -> b) -> d -> c b)
 -> (forall g. g -> c g) -> AssetClass -> c AssetClass)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c AssetClass)
-> (AssetClass -> Constr)
-> (AssetClass -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c AssetClass))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e))
    -> Maybe (c AssetClass))
-> ((forall b. Data b => b -> b) -> AssetClass -> AssetClass)
-> (forall r r'.
    (r -> r' -> r)
    -> r -> (forall d. Data d => d -> r') -> AssetClass -> r)
-> (forall r r'.
    (r' -> r -> r)
    -> r -> (forall d. Data d => d -> r') -> AssetClass -> r)
-> (forall u. (forall d. Data d => d -> u) -> AssetClass -> [u])
-> (forall u.
    Int -> (forall d. Data d => d -> u) -> AssetClass -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> AssetClass -> m AssetClass)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> AssetClass -> m AssetClass)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> AssetClass -> m AssetClass)
-> Data AssetClass
AssetClass -> Constr
AssetClass -> DataType
(forall b. Data b => b -> b) -> AssetClass -> AssetClass
forall a.
Typeable a =>
(forall (c :: * -> *).
 (forall d b. Data d => c (d -> b) -> d -> c b)
 -> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
    (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
    (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> AssetClass -> u
forall u. (forall d. Data d => d -> u) -> AssetClass -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> AssetClass -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> AssetClass -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> AssetClass -> m AssetClass
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> AssetClass -> m AssetClass
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c AssetClass
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> AssetClass -> c AssetClass
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c AssetClass)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c AssetClass)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> AssetClass -> c AssetClass
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> AssetClass -> c AssetClass
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c AssetClass
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c AssetClass
$ctoConstr :: AssetClass -> Constr
toConstr :: AssetClass -> Constr
$cdataTypeOf :: AssetClass -> DataType
dataTypeOf :: AssetClass -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c AssetClass)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c AssetClass)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c AssetClass)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c AssetClass)
$cgmapT :: (forall b. Data b => b -> b) -> AssetClass -> AssetClass
gmapT :: (forall b. Data b => b -> b) -> AssetClass -> AssetClass
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> AssetClass -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> AssetClass -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> AssetClass -> r
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> AssetClass -> r
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> AssetClass -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> AssetClass -> [u]
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> AssetClass -> u
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> AssetClass -> u
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> AssetClass -> m AssetClass
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> AssetClass -> m AssetClass
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> AssetClass -> m AssetClass
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> AssetClass -> m AssetClass
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> AssetClass -> m AssetClass
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> AssetClass -> m AssetClass
Data, Typeable)
  deriving newtype
    ( AssetClass -> AssetClass -> Bool
(AssetClass -> AssetClass -> Bool)
-> (AssetClass -> AssetClass -> Bool) -> Eq AssetClass
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: AssetClass -> AssetClass -> Bool
== :: AssetClass -> AssetClass -> Bool
$c/= :: AssetClass -> AssetClass -> Bool
/= :: AssetClass -> AssetClass -> Bool
Haskell.Eq
    , Eq AssetClass
Eq AssetClass =>
(AssetClass -> AssetClass -> Ordering)
-> (AssetClass -> AssetClass -> Bool)
-> (AssetClass -> AssetClass -> Bool)
-> (AssetClass -> AssetClass -> Bool)
-> (AssetClass -> AssetClass -> Bool)
-> (AssetClass -> AssetClass -> AssetClass)
-> (AssetClass -> AssetClass -> AssetClass)
-> Ord AssetClass
AssetClass -> AssetClass -> Bool
AssetClass -> AssetClass -> Ordering
AssetClass -> AssetClass -> AssetClass
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: AssetClass -> AssetClass -> Ordering
compare :: AssetClass -> AssetClass -> Ordering
$c< :: AssetClass -> AssetClass -> Bool
< :: AssetClass -> AssetClass -> Bool
$c<= :: AssetClass -> AssetClass -> Bool
<= :: AssetClass -> AssetClass -> Bool
$c> :: AssetClass -> AssetClass -> Bool
> :: AssetClass -> AssetClass -> Bool
$c>= :: AssetClass -> AssetClass -> Bool
>= :: AssetClass -> AssetClass -> Bool
$cmax :: AssetClass -> AssetClass -> AssetClass
max :: AssetClass -> AssetClass -> AssetClass
$cmin :: AssetClass -> AssetClass -> AssetClass
min :: AssetClass -> AssetClass -> AssetClass
Haskell.Ord
    , Int -> AssetClass -> ShowS
[AssetClass] -> ShowS
AssetClass -> String
(Int -> AssetClass -> ShowS)
-> (AssetClass -> String)
-> ([AssetClass] -> ShowS)
-> Show AssetClass
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> AssetClass -> ShowS
showsPrec :: Int -> AssetClass -> ShowS
$cshow :: AssetClass -> String
show :: AssetClass -> String
$cshowList :: [AssetClass] -> ShowS
showList :: [AssetClass] -> ShowS
Haskell.Show
    , AssetClass -> AssetClass -> Bool
(AssetClass -> AssetClass -> Bool) -> Eq AssetClass
forall a. (a -> a -> Bool) -> Eq a
$c== :: AssetClass -> AssetClass -> Bool
== :: AssetClass -> AssetClass -> Bool
Eq
    , Eq AssetClass
Eq AssetClass =>
(AssetClass -> AssetClass -> Ordering)
-> (AssetClass -> AssetClass -> Bool)
-> (AssetClass -> AssetClass -> Bool)
-> (AssetClass -> AssetClass -> Bool)
-> (AssetClass -> AssetClass -> Bool)
-> (AssetClass -> AssetClass -> AssetClass)
-> (AssetClass -> AssetClass -> AssetClass)
-> Ord AssetClass
AssetClass -> AssetClass -> Bool
AssetClass -> AssetClass -> Ordering
AssetClass -> AssetClass -> AssetClass
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: AssetClass -> AssetClass -> Ordering
compare :: AssetClass -> AssetClass -> Ordering
$c< :: AssetClass -> AssetClass -> Bool
< :: AssetClass -> AssetClass -> Bool
$c<= :: AssetClass -> AssetClass -> Bool
<= :: AssetClass -> AssetClass -> Bool
$c> :: AssetClass -> AssetClass -> Bool
> :: AssetClass -> AssetClass -> Bool
$c>= :: AssetClass -> AssetClass -> Bool
>= :: AssetClass -> AssetClass -> Bool
$cmax :: AssetClass -> AssetClass -> AssetClass
max :: AssetClass -> AssetClass -> AssetClass
$cmin :: AssetClass -> AssetClass -> AssetClass
min :: AssetClass -> AssetClass -> AssetClass
Ord
    , AssetClass -> BuiltinData
(AssetClass -> BuiltinData) -> ToData AssetClass
forall a. (a -> BuiltinData) -> ToData a
$ctoBuiltinData :: AssetClass -> BuiltinData
toBuiltinData :: AssetClass -> BuiltinData
PlutusTx.ToData
    , BuiltinData -> Maybe AssetClass
(BuiltinData -> Maybe AssetClass) -> FromData AssetClass
forall a. (BuiltinData -> Maybe a) -> FromData a
$cfromBuiltinData :: BuiltinData -> Maybe AssetClass
fromBuiltinData :: BuiltinData -> Maybe AssetClass
PlutusTx.FromData
    , BuiltinData -> AssetClass
(BuiltinData -> AssetClass) -> UnsafeFromData AssetClass
forall a. (BuiltinData -> a) -> UnsafeFromData a
$cunsafeFromBuiltinData :: BuiltinData -> AssetClass
unsafeFromBuiltinData :: BuiltinData -> AssetClass
PlutusTx.UnsafeFromData
    )
  deriving anyclass (AssetClass -> ()
(AssetClass -> ()) -> NFData AssetClass
forall a. (a -> ()) -> NFData a
$crnf :: AssetClass -> ()
rnf :: AssetClass -> ()
NFData, DefinitionId
DefinitionId -> HasBlueprintDefinition AssetClass
forall t. DefinitionId -> HasBlueprintDefinition t
$cdefinitionId :: DefinitionId
definitionId :: DefinitionId
HasBlueprintDefinition)
  deriving ((forall ann. AssetClass -> Doc ann)
-> (forall ann. [AssetClass] -> Doc ann) -> Pretty AssetClass
forall ann. [AssetClass] -> Doc ann
forall ann. AssetClass -> Doc ann
forall a.
(forall ann. a -> Doc ann)
-> (forall ann. [a] -> Doc ann) -> Pretty a
$cpretty :: forall ann. AssetClass -> Doc ann
pretty :: forall ann. AssetClass -> Doc ann
$cprettyList :: forall ann. [AssetClass] -> Doc ann
prettyList :: forall ann. [AssetClass] -> Doc ann
Pretty) via (PrettyShow (CurrencySymbol, TokenName))

instance HasBlueprintSchema AssetClass referencedTypes where
  {-# INLINEABLE schema #-}
  schema :: Schema referencedTypes
schema =
    SchemaInfo -> PairSchema referencedTypes -> Schema referencedTypes
forall (referencedTypes :: [*]).
SchemaInfo -> PairSchema referencedTypes -> Schema referencedTypes
SchemaBuiltInPair SchemaInfo
emptySchemaInfo (PairSchema referencedTypes -> Schema referencedTypes)
-> PairSchema referencedTypes -> Schema referencedTypes
forall a b. (a -> b) -> a -> b
$
      MkPairSchema
        { $sel:left:MkPairSchema :: Schema referencedTypes
left = forall t (referencedTypes :: [*]).
HasBlueprintSchema t referencedTypes =>
Schema referencedTypes
schema @CurrencySymbol
        , $sel:right:MkPairSchema :: Schema referencedTypes
right = forall t (referencedTypes :: [*]).
HasBlueprintSchema t referencedTypes =>
Schema referencedTypes
schema @TokenName
        }

{-# INLINABLE assetClass #-}
-- | The curried version of 'AssetClass' constructor
assetClass :: CurrencySymbol -> TokenName -> AssetClass
assetClass :: CurrencySymbol -> TokenName -> AssetClass
assetClass CurrencySymbol
s TokenName
t = (CurrencySymbol, TokenName) -> AssetClass
AssetClass (CurrencySymbol
s, TokenName
t)

{- Note [Value vs value]
We call two completely different things "values": the 'Value' type and a value within a key-value
pair. To distinguish between the two we write the former with a capital "V" and enclosed in single
quotes and we write the latter with a lower case "v" and without the quotes, i.e. 'Value' vs value.
-}

{- Note [Optimising Value]

We have attempted to improve the performance of 'Value' and other usages of
'PlutusTx.AssocMap.Map' by choosing a different representation for 'PlutusTx.AssocMap.Map',
see https://github.com/IntersectMBO/plutus/pull/5697.
This approach has been found to not be suitable, as the PR's description mentions.

Another approach was to define a specialised 'ByteStringMap', where the key type was 'BuiltinByteString',
since that is the representation of both 'CurrencySymbol' and 'TokenName'.
Unfortunately, this approach actually had worse performance in practice. We believe it is worse
because having two map libraries would make some optimisations, such as CSE, less effective.
We base this on the fact that turning off all optimisations ended up making the code more performant.
See https://github.com/IntersectMBO/plutus/pull/5779 for details on the experiment done.
-}

-- See Note [Value vs value].
-- See Note [Optimising Value].
{- | The 'Value' type represents a collection of amounts of different currencies.
We can think of 'Value' as a vector space whose dimensions are currencies.

Operations on currencies are usually implemented /pointwise/. That is,
we apply the operation to the quantities for each currency in turn. So
when we add two 'Value's the resulting 'Value' has, for each currency,
the sum of the quantities of /that particular/ currency in the argument
'Value'. The effect of this is that the currencies in the 'Value' are "independent",
and are operated on separately.

Whenever we need to get the quantity of a currency in a 'Value' where there
is no explicit quantity of that currency in the 'Value', then the quantity is
taken to be zero.

There is no 'Ord Value' instance since 'Value' is only a partial order, so 'compare' can't
do the right thing in some cases.
 -}
newtype Value = Value { Value -> Map CurrencySymbol (Map TokenName Integer)
getValue :: Map.Map CurrencySymbol (Map.Map TokenName Integer) }
    deriving stock ((forall x. Value -> Rep Value x)
-> (forall x. Rep Value x -> Value) -> Generic Value
forall x. Rep Value x -> Value
forall x. Value -> Rep Value x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. Value -> Rep Value x
from :: forall x. Value -> Rep Value x
$cto :: forall x. Rep Value x -> Value
to :: forall x. Rep Value x -> Value
Generic, Typeable, Int -> Value -> ShowS
[Value] -> ShowS
Value -> String
(Int -> Value -> ShowS)
-> (Value -> String) -> ([Value] -> ShowS) -> Show Value
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Value -> ShowS
showsPrec :: Int -> Value -> ShowS
$cshow :: Value -> String
show :: Value -> String
$cshowList :: [Value] -> ShowS
showList :: [Value] -> ShowS
Haskell.Show)
    deriving newtype (Value -> BuiltinData
(Value -> BuiltinData) -> ToData Value
forall a. (a -> BuiltinData) -> ToData a
$ctoBuiltinData :: Value -> BuiltinData
toBuiltinData :: Value -> BuiltinData
PlutusTx.ToData, BuiltinData -> Maybe Value
(BuiltinData -> Maybe Value) -> FromData Value
forall a. (BuiltinData -> Maybe a) -> FromData a
$cfromBuiltinData :: BuiltinData -> Maybe Value
fromBuiltinData :: BuiltinData -> Maybe Value
PlutusTx.FromData, BuiltinData -> Value
(BuiltinData -> Value) -> UnsafeFromData Value
forall a. (BuiltinData -> a) -> UnsafeFromData a
$cunsafeFromBuiltinData :: BuiltinData -> Value
unsafeFromBuiltinData :: BuiltinData -> Value
PlutusTx.UnsafeFromData)
    deriving (forall ann. Value -> Doc ann)
-> (forall ann. [Value] -> Doc ann) -> Pretty Value
forall ann. [Value] -> Doc ann
forall ann. Value -> Doc ann
forall a.
(forall ann. a -> Doc ann)
-> (forall ann. [a] -> Doc ann) -> Pretty a
$cpretty :: forall ann. Value -> Doc ann
pretty :: forall ann. Value -> Doc ann
$cprettyList :: forall ann. [Value] -> Doc ann
prettyList :: forall ann. [Value] -> Doc ann
Pretty via (PrettyShow Value)

instance HasBlueprintDefinition Value where
  type Unroll Value = '[Value, CurrencySymbol, TokenName, Integer]
  definitionId :: DefinitionId
definitionId = forall t. Typeable t => DefinitionId
definitionIdFromType @Value

instance HasBlueprintSchema Value referencedTypes where
  {-# INLINABLE schema #-}
  schema :: Schema referencedTypes
schema =
    SchemaInfo -> MapSchema referencedTypes -> Schema referencedTypes
forall (referencedTypes :: [*]).
SchemaInfo -> MapSchema referencedTypes -> Schema referencedTypes
SchemaMap
      SchemaInfo
emptySchemaInfo
        { title = Just "Value" }
      MkMapSchema
        { $sel:keySchema:MkMapSchema :: Schema referencedTypes
keySchema = forall t (ts :: [*]). HasBlueprintDefinition t => Schema ts
definitionRef @CurrencySymbol
        , $sel:valueSchema:MkMapSchema :: Schema referencedTypes
valueSchema =
            SchemaInfo -> MapSchema referencedTypes -> Schema referencedTypes
forall (referencedTypes :: [*]).
SchemaInfo -> MapSchema referencedTypes -> Schema referencedTypes
SchemaMap SchemaInfo
emptySchemaInfo MkMapSchema
              { $sel:keySchema:MkMapSchema :: Schema referencedTypes
keySchema = forall t (ts :: [*]). HasBlueprintDefinition t => Schema ts
definitionRef @TokenName
              , $sel:valueSchema:MkMapSchema :: Schema referencedTypes
valueSchema = forall t (ts :: [*]). HasBlueprintDefinition t => Schema ts
definitionRef @Integer
              , $sel:minItems:MkMapSchema :: Maybe Natural
minItems = Maybe Natural
forall a. Maybe a
Nothing
              , $sel:maxItems:MkMapSchema :: Maybe Natural
maxItems = Maybe Natural
forall a. Maybe a
Nothing
              }
        , $sel:minItems:MkMapSchema :: Maybe Natural
minItems = Maybe Natural
forall a. Maybe a
Nothing
        , $sel:maxItems:MkMapSchema :: Maybe Natural
maxItems = Maybe Natural
forall a. Maybe a
Nothing
        }

instance Haskell.Eq Value where
    == :: Value -> Value -> Bool
(==) = Value -> Value -> Bool
eq

instance Eq Value where
    {-# INLINABLE (==) #-}
    == :: Value -> Value -> Bool
(==) = Value -> Value -> Bool
eq

instance Haskell.Semigroup Value where
    <> :: Value -> Value -> Value
(<>) = (Integer -> Integer -> Integer) -> Value -> Value -> Value
unionWith Integer -> Integer -> Integer
forall a. AdditiveSemigroup a => a -> a -> a
(+)

instance Semigroup Value where
    {-# INLINABLE (<>) #-}
    <> :: Value -> Value -> Value
(<>) = (Integer -> Integer -> Integer) -> Value -> Value -> Value
unionWith Integer -> Integer -> Integer
forall a. AdditiveSemigroup a => a -> a -> a
(+)

instance Haskell.Monoid Value where
    mempty :: Value
mempty = Map CurrencySymbol (Map TokenName Integer) -> Value
Value Map CurrencySymbol (Map TokenName Integer)
forall k a. Map k a
Map.empty

instance Monoid Value where
    {-# INLINABLE mempty #-}
    mempty :: Value
mempty = Map CurrencySymbol (Map TokenName Integer) -> Value
Value Map CurrencySymbol (Map TokenName Integer)
forall k a. Map k a
Map.empty

instance Group Value where
    {-# INLINABLE inv #-}
    inv :: Value -> Value
inv = forall s v. Module s v => s -> v -> v
scale @Integer @Value (-Integer
1)

deriving via (Additive Value) instance AdditiveSemigroup Value
deriving via (Additive Value) instance AdditiveMonoid Value
deriving via (Additive Value) instance AdditiveGroup Value

instance Module Integer Value where
    {-# INLINABLE scale #-}
    scale :: Integer -> Value -> Value
scale Integer
i (Value Map CurrencySymbol (Map TokenName Integer)
xs) = Map CurrencySymbol (Map TokenName Integer) -> Value
Value ((Map TokenName Integer -> Map TokenName Integer)
-> Map CurrencySymbol (Map TokenName Integer)
-> Map CurrencySymbol (Map TokenName Integer)
forall k a b.
(UnsafeFromData a, ToData b) =>
(a -> b) -> Map k a -> Map k b
Map.map ((Integer -> Integer)
-> Map TokenName Integer -> Map TokenName Integer
forall k a b.
(UnsafeFromData a, ToData b) =>
(a -> b) -> Map k a -> Map k b
Map.map (\Integer
i' -> Integer
i Integer -> Integer -> Integer
forall a. MultiplicativeSemigroup a => a -> a -> a
* Integer
i')) Map CurrencySymbol (Map TokenName Integer)
xs)

instance JoinSemiLattice Value where
    {-# INLINABLE (\/) #-}
    \/ :: Value -> Value -> Value
(\/) = (Integer -> Integer -> Integer) -> Value -> Value -> Value
unionWith Integer -> Integer -> Integer
forall a. Ord a => a -> a -> a
Ord.max

instance MeetSemiLattice Value where
    {-# INLINABLE (/\) #-}
    /\ :: Value -> Value -> Value
(/\) = (Integer -> Integer -> Integer) -> Value -> Value -> Value
unionWith Integer -> Integer -> Integer
forall a. Ord a => a -> a -> a
Ord.min

{-# INLINABLE valueOf #-}
-- | Get the quantity of the given currency in the 'Value'.
-- Assumes that the underlying map doesn't contain duplicate keys.
valueOf :: Value -> CurrencySymbol -> TokenName -> Integer
valueOf :: Value -> CurrencySymbol -> TokenName -> Integer
valueOf (Value Map CurrencySymbol (Map TokenName Integer)
mp) CurrencySymbol
cur TokenName
tn =
    case CurrencySymbol
-> Map CurrencySymbol (Map TokenName Integer)
-> Maybe (Map TokenName Integer)
forall k a. (ToData k, UnsafeFromData a) => k -> Map k a -> Maybe a
Map.lookup CurrencySymbol
cur Map CurrencySymbol (Map TokenName Integer)
mp of
        Maybe (Map TokenName Integer)
Nothing -> Integer
0
        Just Map TokenName Integer
i  -> case TokenName -> Map TokenName Integer -> Maybe Integer
forall k a. (ToData k, UnsafeFromData a) => k -> Map k a -> Maybe a
Map.lookup TokenName
tn Map TokenName Integer
i of
            Maybe Integer
Nothing -> Integer
0
            Just Integer
v  -> Integer
v

{-# INLINABLE currencySymbolValueOf #-}
-- | Get the total value of the currency symbol in the 'Value' map.
-- Assumes that the underlying map doesn't contain duplicate keys.
currencySymbolValueOf :: Value -> CurrencySymbol -> Integer
currencySymbolValueOf :: Value -> CurrencySymbol -> Integer
currencySymbolValueOf (Value Map CurrencySymbol (Map TokenName Integer)
mp) CurrencySymbol
cur = case CurrencySymbol
-> Map CurrencySymbol (Map TokenName Integer)
-> Maybe (Map TokenName Integer)
forall k a. (ToData k, UnsafeFromData a) => k -> Map k a -> Maybe a
Map.lookup CurrencySymbol
cur Map CurrencySymbol (Map TokenName Integer)
mp of
    Maybe (Map TokenName Integer)
Nothing     -> Integer
0
    Just Map TokenName Integer
tokens ->
        -- This is more efficient than `PlutusTx.sum (Map.elems tokens)`, because
        -- the latter materializes the intermediate result of `Map.elems tokens`.
        (Integer -> Integer -> Integer)
-> Integer -> Map TokenName Integer -> Integer
forall a b k.
UnsafeFromData a =>
(a -> b -> b) -> b -> Map k a -> b
Map.foldr (\Integer
amt Integer
acc -> Integer
amt Integer -> Integer -> Integer
forall a. AdditiveSemigroup a => a -> a -> a
+ Integer
acc) Integer
0 Map TokenName Integer
tokens

{-# INLINABLE symbols #-}
-- | The list of 'CurrencySymbol's of a 'Value'.
symbols :: Value -> BuiltinList BuiltinData
symbols :: Value -> BuiltinList BuiltinData
symbols (Value Map CurrencySymbol (Map TokenName Integer)
mp) = Map CurrencySymbol (Map TokenName Integer)
-> BuiltinList BuiltinData
forall k a. Map k a -> BuiltinList BuiltinData
Map.keys Map CurrencySymbol (Map TokenName Integer)
mp

{-# INLINABLE singleton #-}
-- | Make a 'Value' containing only the given quantity of the given currency.
singleton :: CurrencySymbol -> TokenName -> Integer -> Value
singleton :: CurrencySymbol -> TokenName -> Integer -> Value
singleton CurrencySymbol
c TokenName
tn Integer
i = Map CurrencySymbol (Map TokenName Integer) -> Value
Value (CurrencySymbol
-> Map TokenName Integer
-> Map CurrencySymbol (Map TokenName Integer)
forall k a. (ToData k, ToData a) => k -> a -> Map k a
Map.singleton CurrencySymbol
c (TokenName -> Integer -> Map TokenName Integer
forall k a. (ToData k, ToData a) => k -> a -> Map k a
Map.singleton TokenName
tn Integer
i))

{-# INLINABLE lovelaceValue #-}
-- | A 'Value' containing the given quantity of Lovelace.
lovelaceValue :: Lovelace -> Value
lovelaceValue :: Lovelace -> Value
lovelaceValue = CurrencySymbol -> TokenName -> Integer -> Value
singleton CurrencySymbol
adaSymbol TokenName
adaToken (Integer -> Value) -> (Lovelace -> Integer) -> Lovelace -> Value
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Lovelace -> Integer
getLovelace

{-# INLINABLE lovelaceValueOf #-}
-- | Get the quantity of Lovelace in the 'Value'.
lovelaceValueOf :: Value -> Lovelace
lovelaceValueOf :: Value -> Lovelace
lovelaceValueOf Value
v = Integer -> Lovelace
Lovelace (Value -> CurrencySymbol -> TokenName -> Integer
valueOf Value
v CurrencySymbol
adaSymbol TokenName
adaToken)

{-# INLINABLE assetClassValue #-}
-- | A 'Value' containing the given amount of the asset class.
assetClassValue :: AssetClass -> Integer -> Value
assetClassValue :: AssetClass -> Integer -> Value
assetClassValue (AssetClass (CurrencySymbol
c, TokenName
t)) Integer
i = CurrencySymbol -> TokenName -> Integer -> Value
singleton CurrencySymbol
c TokenName
t Integer
i

{-# INLINABLE assetClassValueOf #-}
-- | Get the quantity of the given 'AssetClass' class in the 'Value'.
assetClassValueOf :: Value -> AssetClass -> Integer
assetClassValueOf :: Value -> AssetClass -> Integer
assetClassValueOf Value
v (AssetClass (CurrencySymbol
c, TokenName
t)) = Value -> CurrencySymbol -> TokenName -> Integer
valueOf Value
v CurrencySymbol
c TokenName
t

{-# INLINABLE unionVal #-}
-- | Combine two 'Value' maps, assumes the well-definedness of the two maps.
unionVal :: Value -> Value -> Map.Map CurrencySymbol (Map.Map TokenName (These Integer Integer))
unionVal :: Value
-> Value
-> Map CurrencySymbol (Map TokenName (These Integer Integer))
unionVal (Value Map CurrencySymbol (Map TokenName Integer)
l) (Value Map CurrencySymbol (Map TokenName Integer)
r) =
    let
        combined :: Map
  CurrencySymbol
  (These (Map TokenName Integer) (Map TokenName Integer))
combined = Map CurrencySymbol (Map TokenName Integer)
-> Map CurrencySymbol (Map TokenName Integer)
-> Map
     CurrencySymbol
     (These (Map TokenName Integer) (Map TokenName Integer))
forall k a b.
(UnsafeFromData a, UnsafeFromData b, ToData a, ToData b) =>
Map k a -> Map k b -> Map k (These a b)
Map.union Map CurrencySymbol (Map TokenName Integer)
l Map CurrencySymbol (Map TokenName Integer)
r
        unThese :: These (Map k a) (Map k b) -> Map k (These a b)
unThese These (Map k a) (Map k b)
k = case These (Map k a) (Map k b)
k of
            This Map k a
a    -> (a -> These a b) -> Map k a -> Map k (These a b)
forall k a b.
(UnsafeFromData a, ToData b) =>
(a -> b) -> Map k a -> Map k b
Map.map a -> These a b
forall a b. a -> These a b
This Map k a
a
            That Map k b
b    -> (b -> These a b) -> Map k b -> Map k (These a b)
forall k a b.
(UnsafeFromData a, ToData b) =>
(a -> b) -> Map k a -> Map k b
Map.map b -> These a b
forall a b. b -> These a b
That Map k b
b
            These Map k a
a Map k b
b -> Map k a -> Map k b -> Map k (These a b)
forall k a b.
(UnsafeFromData a, UnsafeFromData b, ToData a, ToData b) =>
Map k a -> Map k b -> Map k (These a b)
Map.union Map k a
a Map k b
b
    in (These (Map TokenName Integer) (Map TokenName Integer)
 -> Map TokenName (These Integer Integer))
-> Map
     CurrencySymbol
     (These (Map TokenName Integer) (Map TokenName Integer))
-> Map CurrencySymbol (Map TokenName (These Integer Integer))
forall k a b.
(UnsafeFromData a, ToData b) =>
(a -> b) -> Map k a -> Map k b
Map.map These (Map TokenName Integer) (Map TokenName Integer)
-> Map TokenName (These Integer Integer)
forall {a} {b} {k}.
(ToData a, ToData b, UnsafeFromData a, UnsafeFromData b) =>
These (Map k a) (Map k b) -> Map k (These a b)
unThese Map
  CurrencySymbol
  (These (Map TokenName Integer) (Map TokenName Integer))
combined

{-# INLINABLE unionWith #-}
-- | Combine two 'Value' maps with the argument function.
-- Assumes the well-definedness of the two maps.
unionWith :: (Integer -> Integer -> Integer) -> Value -> Value -> Value
unionWith :: (Integer -> Integer -> Integer) -> Value -> Value -> Value
unionWith Integer -> Integer -> Integer
f Value
ls Value
rs =
    let
        combined :: Map CurrencySymbol (Map TokenName (These Integer Integer))
combined = Value
-> Value
-> Map CurrencySymbol (Map TokenName (These Integer Integer))
unionVal Value
ls Value
rs
        unThese :: These Integer Integer -> Integer
unThese These Integer Integer
k' = case These Integer Integer
k' of
            This Integer
a    -> Integer -> Integer -> Integer
f Integer
a Integer
0
            That Integer
b    -> Integer -> Integer -> Integer
f Integer
0 Integer
b
            These Integer
a Integer
b -> Integer -> Integer -> Integer
f Integer
a Integer
b
    in Map CurrencySymbol (Map TokenName Integer) -> Value
Value ((Map TokenName (These Integer Integer) -> Map TokenName Integer)
-> Map CurrencySymbol (Map TokenName (These Integer Integer))
-> Map CurrencySymbol (Map TokenName Integer)
forall k a b.
(UnsafeFromData a, ToData b) =>
(a -> b) -> Map k a -> Map k b
Map.map ((These Integer Integer -> Integer)
-> Map TokenName (These Integer Integer) -> Map TokenName Integer
forall k a b.
(UnsafeFromData a, ToData b) =>
(a -> b) -> Map k a -> Map k b
Map.map These Integer Integer -> Integer
unThese) Map CurrencySymbol (Map TokenName (These Integer Integer))
combined)

{-# INLINABLE flattenValue #-}
-- | Convert a 'Value' to a simple list, keeping only the non-zero amounts.
-- Note that the result isn't sorted, meaning @v1 == v2@ doesn't generally imply
-- @flattenValue v1 == flattenValue v2@.
-- Also assumes that there are no duplicate keys in the 'Value' 'Map'.
flattenValue :: Value -> [(CurrencySymbol, TokenName, Integer)]
flattenValue :: Value -> [(CurrencySymbol, TokenName, Integer)]
flattenValue Value
v = [(CurrencySymbol, TokenName, Integer)]
-> [(CurrencySymbol, Map TokenName Integer)]
-> [(CurrencySymbol, TokenName, Integer)]
forall {c} {b} {a}.
(Eq c, Num c, UnsafeFromData b, UnsafeFromData c) =>
[(a, b, c)] -> [(a, Map b c)] -> [(a, b, c)]
goOuter [] (Map CurrencySymbol (Map TokenName Integer)
-> [(CurrencySymbol, Map TokenName Integer)]
forall k a.
(UnsafeFromData k, UnsafeFromData a) =>
Map k a -> [(k, a)]
Map.toList (Map CurrencySymbol (Map TokenName Integer)
 -> [(CurrencySymbol, Map TokenName Integer)])
-> Map CurrencySymbol (Map TokenName Integer)
-> [(CurrencySymbol, Map TokenName Integer)]
forall a b. (a -> b) -> a -> b
$ Value -> Map CurrencySymbol (Map TokenName Integer)
getValue Value
v)
  where
    goOuter :: [(a, b, c)] -> [(a, Map b c)] -> [(a, b, c)]
goOuter [(a, b, c)]
acc []             = [(a, b, c)]
acc
    goOuter [(a, b, c)]
acc ((a
cs, Map b c
m) : [(a, Map b c)]
tl) = [(a, b, c)] -> [(a, Map b c)] -> [(a, b, c)]
goOuter (a -> [(a, b, c)] -> [(b, c)] -> [(a, b, c)]
forall {c} {a} {b}.
(Eq c, Num c) =>
a -> [(a, b, c)] -> [(b, c)] -> [(a, b, c)]
goInner a
cs [(a, b, c)]
acc (Map b c -> [(b, c)]
forall k a.
(UnsafeFromData k, UnsafeFromData a) =>
Map k a -> [(k, a)]
Map.toList Map b c
m)) [(a, Map b c)]
tl

    goInner :: a -> [(a, b, c)] -> [(b, c)] -> [(a, b, c)]
goInner a
_ [(a, b, c)]
acc [] = [(a, b, c)]
acc
    goInner a
cs [(a, b, c)]
acc ((b
tn, c
a) : [(b, c)]
tl)
        | c
a c -> c -> Bool
forall a. Eq a => a -> a -> Bool
/= c
0    = a -> [(a, b, c)] -> [(b, c)] -> [(a, b, c)]
goInner a
cs ((a
cs, b
tn, c
a) (a, b, c) -> [(a, b, c)] -> [(a, b, c)]
forall a. a -> [a] -> [a]
: [(a, b, c)]
acc) [(b, c)]
tl
        | Bool
otherwise = a -> [(a, b, c)] -> [(b, c)] -> [(a, b, c)]
goInner a
cs [(a, b, c)]
acc [(b, c)]
tl

-- Num operations

{-# INLINABLE isZero #-}
-- | Check whether a 'Value' is zero.
isZero :: Value -> Bool
isZero :: Value -> Bool
isZero (Value Map CurrencySymbol (Map TokenName Integer)
xs) = (Map TokenName Integer -> Bool)
-> Map CurrencySymbol (Map TokenName Integer) -> Bool
forall k a. UnsafeFromData a => (a -> Bool) -> Map k a -> Bool
Map.all ((Integer -> Bool) -> Map TokenName Integer -> Bool
forall k a. UnsafeFromData a => (a -> Bool) -> Map k a -> Bool
Map.all (\Integer
i -> Integer
0 Integer -> Integer -> Bool
forall a. Eq a => a -> a -> Bool
== Integer
i)) Map CurrencySymbol (Map TokenName Integer)
xs

{-# INLINABLE checkPred #-}
-- | Checks whether a predicate holds for all the values in a 'Value'
-- union. Assumes the well-definedness of the two underlying 'Map's.
checkPred :: (These Integer Integer -> Bool) -> Value -> Value -> Bool
checkPred :: (These Integer Integer -> Bool) -> Value -> Value -> Bool
checkPred These Integer Integer -> Bool
f Value
l Value
r =
    let
      inner :: Map.Map TokenName (These Integer Integer) -> Bool
      inner :: Map TokenName (These Integer Integer) -> Bool
inner = (These Integer Integer -> Bool)
-> Map TokenName (These Integer Integer) -> Bool
forall k a. UnsafeFromData a => (a -> Bool) -> Map k a -> Bool
Map.all These Integer Integer -> Bool
f
    in
      (Map TokenName (These Integer Integer) -> Bool)
-> Map CurrencySymbol (Map TokenName (These Integer Integer))
-> Bool
forall k a. UnsafeFromData a => (a -> Bool) -> Map k a -> Bool
Map.all Map TokenName (These Integer Integer) -> Bool
inner (Value
-> Value
-> Map CurrencySymbol (Map TokenName (These Integer Integer))
unionVal Value
l Value
r)

{-# INLINABLE checkBinRel #-}
-- | Check whether a binary relation holds for value pairs of two 'Value' maps,
--   supplying 0 where a key is only present in one of them.
checkBinRel :: (Integer -> Integer -> Bool) -> Value -> Value -> Bool
checkBinRel :: (Integer -> Integer -> Bool) -> Value -> Value -> Bool
checkBinRel Integer -> Integer -> Bool
f Value
l Value
r =
    let
        unThese :: These Integer Integer -> Bool
unThese These Integer Integer
k' = case These Integer Integer
k' of
            This Integer
a    -> Integer -> Integer -> Bool
f Integer
a Integer
0
            That Integer
b    -> Integer -> Integer -> Bool
f Integer
0 Integer
b
            These Integer
a Integer
b -> Integer -> Integer -> Bool
f Integer
a Integer
b
    in (These Integer Integer -> Bool) -> Value -> Value -> Bool
checkPred These Integer Integer -> Bool
unThese Value
l Value
r

{-# INLINABLE geq #-}
-- | Check whether one 'Value' is greater than or equal to another. See 'Value' for an explanation
-- of how operations on 'Value's work.
geq :: Value -> Value -> Bool
-- If both are zero then checkBinRel will be vacuously true, but this is fine.
geq :: Value -> Value -> Bool
geq = (Integer -> Integer -> Bool) -> Value -> Value -> Bool
checkBinRel Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
(>=)

{-# INLINABLE leq #-}
-- | Check whether one 'Value' is less than or equal to another. See 'Value' for an explanation of
-- how operations on 'Value's work.
leq :: Value -> Value -> Bool
-- If both are zero then checkBinRel will be vacuously true, but this is fine.
leq :: Value -> Value -> Bool
leq = (Integer -> Integer -> Bool) -> Value -> Value -> Bool
checkBinRel Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
(<=)

{-# INLINABLE gt #-}
-- | Check whether one 'Value' is strictly greater than another.
-- This is *not* a pointwise operation. @gt l r@ means @geq l r && not (eq l r)@.
gt :: Value -> Value -> Bool
gt :: Value -> Value -> Bool
gt Value
l Value
r = Value -> Value -> Bool
geq Value
l Value
r Bool -> Bool -> Bool
&& Bool -> Bool
not (Value -> Value -> Bool
eq Value
l Value
r)

{-# INLINABLE lt #-}
-- | Check whether one 'Value' is strictly less than another.
-- This is *not* a pointwise operation. @lt l r@ means @leq l r && not (eq l r)@.
lt :: Value -> Value -> Bool
lt :: Value -> Value -> Bool
lt Value
l Value
r = Value -> Value -> Bool
leq Value
l Value
r Bool -> Bool -> Bool
&& Bool -> Bool
not (Value -> Value -> Bool
eq Value
l Value
r)

-- | Split a 'Value' into its positive and negative parts. The first element of
--   the tuple contains the negative parts of the 'Value', the second element
--   contains the positive parts.
--
--   @negate (fst (split a)) `plus` (snd (split a)) == a@
--
{-# INLINABLE split #-}
split :: Value -> (Value, Value)
split :: Value -> (Value, Value)
split (Value Map CurrencySymbol (Map TokenName Integer)
mp) = (Value -> Value
forall a. AdditiveGroup a => a -> a
negate (Map CurrencySymbol (Map TokenName Integer) -> Value
Value Map CurrencySymbol (Map TokenName Integer)
neg), Map CurrencySymbol (Map TokenName Integer) -> Value
Value Map CurrencySymbol (Map TokenName Integer)
pos) where
  (Map CurrencySymbol (Map TokenName Integer)
neg, Map CurrencySymbol (Map TokenName Integer)
pos) = (Map TokenName Integer
 -> These (Map TokenName Integer) (Map TokenName Integer))
-> Map CurrencySymbol (Map TokenName Integer)
-> (Map CurrencySymbol (Map TokenName Integer),
    Map CurrencySymbol (Map TokenName Integer))
forall v k a b.
(ToData a, ToData b, UnsafeFromData v) =>
(v -> These a b) -> Map k v -> (Map k a, Map k b)
Map.mapThese Map TokenName Integer
-> These (Map TokenName Integer) (Map TokenName Integer)
splitIntl Map CurrencySymbol (Map TokenName Integer)
mp

  splitIntl :: Map.Map TokenName Integer -> These (Map.Map TokenName Integer) (Map.Map TokenName Integer)
  splitIntl :: Map TokenName Integer
-> These (Map TokenName Integer) (Map TokenName Integer)
splitIntl Map TokenName Integer
mp' = Map TokenName Integer
-> Map TokenName Integer
-> These (Map TokenName Integer) (Map TokenName Integer)
forall a b. a -> b -> These a b
These Map TokenName Integer
l Map TokenName Integer
r where
    (Map TokenName Integer
l, Map TokenName Integer
r) = (Integer -> These Integer Integer)
-> Map TokenName Integer
-> (Map TokenName Integer, Map TokenName Integer)
forall v k a b.
(ToData a, ToData b, UnsafeFromData v) =>
(v -> These a b) -> Map k v -> (Map k a, Map k b)
Map.mapThese (\Integer
i -> if Integer
i Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
<= Integer
0 then Integer -> These Integer Integer
forall a b. a -> These a b
This Integer
i else Integer -> These Integer Integer
forall a b. b -> These a b
That Integer
i) Map TokenName Integer
mp'

{-# INLINABLE unordEqWith #-}
{- | Check equality of two lists of distinct key-value pairs, each value being uniquely
identified by a key, given a function checking whether a 'Value' is zero and a function
checking equality of values. Note that the caller must ensure that the two lists are
well-defined in this sense. This is not checked or enforced in `unordEqWith`, and therefore
it might yield undefined results for ill-defined input.

This function recurses on both the lists in parallel and checks whether the key-value pairs are
equal pointwise. If there is a mismatch, then it tries to find the left key-value pair in the right
list. If that succeeds then the pair is removed from both the lists and recursion proceeds pointwise
as before until there's another mismatch. If at some point a key-value pair from the left list is
not found in the right one, then the function returns 'False'. If the left list is exhausted, but
the right one still has some non-zero elements, the function returns 'False' as well.

We check equality of values of two key-value pairs right after ensuring that the keys match. This is
disadvantageous if the values are big and there's a key that is present in one of the lists but not
in the other, since in that case computing equality of values was expensive and pointless. However

1. we've checked and on the chain 'Value's very rarely contain 'CurrencySymbol's with more than 3
   'TokenName's associated with them, so we optimize for the most common use case
2. computing equality of values before ensuring equality of all the keys certainly does help when we
   check equality of 'TokenName'-value pairs, since the value of a 'TokenName' is an 'Integer' and
   @(==) :: Integer -> Integer -> Bool@ is generally much faster than repeatedly searching for keys
   in a list
3. having some clever logic for computing equality of values right away in some cases, but not in
   others would not only complicate the algorithm, but also increase the size of the function and
   this resource is quite scarce as the size of a program growing beyond what's acceptable by the
   network can be a real deal breaker, while general performance concerns don't seem to be as
   pressing

The algorithm we use here is very similar, if not identical, to @valueEqualsValue4@ from
https://github.com/IntersectMBO/plutus/issues/5135
-}
unordEqWith
    :: (BuiltinData -> Bool)
    -> (BuiltinData -> BuiltinData -> Bool)
    -> BuiltinList (BuiltinPair BuiltinData BuiltinData)
    -> BuiltinList (BuiltinPair BuiltinData BuiltinData)
    -> Bool
unordEqWith :: (BuiltinData -> Bool)
-> (BuiltinData -> BuiltinData -> Bool)
-> BuiltinList (BuiltinPair BuiltinData BuiltinData)
-> BuiltinList (BuiltinPair BuiltinData BuiltinData)
-> Bool
unordEqWith BuiltinData -> Bool
is0 BuiltinData -> BuiltinData -> Bool
eqV = BuiltinList (BuiltinPair BuiltinData BuiltinData)
-> BuiltinList (BuiltinPair BuiltinData BuiltinData) -> Bool
goBoth where
    goBoth
        :: BuiltinList (BuiltinPair BuiltinData BuiltinData)
        -> BuiltinList (BuiltinPair BuiltinData BuiltinData)
        -> Bool
    goBoth :: BuiltinList (BuiltinPair BuiltinData BuiltinData)
-> BuiltinList (BuiltinPair BuiltinData BuiltinData) -> Bool
goBoth BuiltinList (BuiltinPair BuiltinData BuiltinData)
l1 BuiltinList (BuiltinPair BuiltinData BuiltinData)
l2 =
        BuiltinList (BuiltinPair BuiltinData BuiltinData)
-> (() -> Bool)
-> (BuiltinPair BuiltinData BuiltinData
    -> BuiltinList (BuiltinPair BuiltinData BuiltinData) -> Bool)
-> Bool
forall a r.
BuiltinList a -> (() -> r) -> (a -> BuiltinList a -> r) -> r
B.matchList
            BuiltinList (BuiltinPair BuiltinData BuiltinData)
l1
            -- null l1 case
            ( \() ->
                BuiltinList (BuiltinPair BuiltinData BuiltinData)
-> (() -> Bool)
-> (BuiltinPair BuiltinData BuiltinData
    -> BuiltinList (BuiltinPair BuiltinData BuiltinData) -> Bool)
-> Bool
forall a r.
BuiltinList a -> (() -> r) -> (a -> BuiltinList a -> r) -> r
B.matchList
                    BuiltinList (BuiltinPair BuiltinData BuiltinData)
l2
                    -- null l2 case
                    (\() -> Bool
True)
                    -- non-null l2 case
                    (\ BuiltinPair BuiltinData BuiltinData
_ BuiltinList (BuiltinPair BuiltinData BuiltinData)
_ -> (BuiltinData -> Bool) -> Map BuiltinData BuiltinData -> Bool
forall k a. UnsafeFromData a => (a -> Bool) -> Map k a -> Bool
Map.all BuiltinData -> Bool
is0 (BuiltinList (BuiltinPair BuiltinData BuiltinData)
-> Map BuiltinData BuiltinData
forall k a.
BuiltinList (BuiltinPair BuiltinData BuiltinData) -> Map k a
Map.unsafeFromBuiltinList BuiltinList (BuiltinPair BuiltinData BuiltinData)
l2 :: Map.Map BuiltinData BuiltinData))
            )
            -- non-null l1 case
            ( \BuiltinPair BuiltinData BuiltinData
hd1 BuiltinList (BuiltinPair BuiltinData BuiltinData)
tl1 ->
                BuiltinList (BuiltinPair BuiltinData BuiltinData)
-> (() -> Bool)
-> (BuiltinPair BuiltinData BuiltinData
    -> BuiltinList (BuiltinPair BuiltinData BuiltinData) -> Bool)
-> Bool
forall a r.
BuiltinList a -> (() -> r) -> (a -> BuiltinList a -> r) -> r
B.matchList
                    BuiltinList (BuiltinPair BuiltinData BuiltinData)
l2
                    -- null l2 case
                    (\() -> (BuiltinData -> Bool) -> Map BuiltinData BuiltinData -> Bool
forall k a. UnsafeFromData a => (a -> Bool) -> Map k a -> Bool
Map.all BuiltinData -> Bool
is0 (BuiltinList (BuiltinPair BuiltinData BuiltinData)
-> Map BuiltinData BuiltinData
forall k a.
BuiltinList (BuiltinPair BuiltinData BuiltinData) -> Map k a
Map.unsafeFromBuiltinList BuiltinList (BuiltinPair BuiltinData BuiltinData)
l1 :: Map.Map BuiltinData BuiltinData))
                    -- non-null l2 case
                    ( \BuiltinPair BuiltinData BuiltinData
hd2 BuiltinList (BuiltinPair BuiltinData BuiltinData)
tl2 ->
                        let
                            k1 :: BuiltinData
k1 = BuiltinPair BuiltinData BuiltinData -> BuiltinData
forall a b. BuiltinPair a b -> a
BI.fst BuiltinPair BuiltinData BuiltinData
hd1
                            v1 :: BuiltinData
v1 = BuiltinPair BuiltinData BuiltinData -> BuiltinData
forall a b. BuiltinPair a b -> b
BI.snd BuiltinPair BuiltinData BuiltinData
hd1
                            k2 :: BuiltinData
k2 = BuiltinPair BuiltinData BuiltinData -> BuiltinData
forall a b. BuiltinPair a b -> a
BI.fst BuiltinPair BuiltinData BuiltinData
hd2
                            v2 :: BuiltinData
v2 = BuiltinPair BuiltinData BuiltinData -> BuiltinData
forall a b. BuiltinPair a b -> b
BI.snd BuiltinPair BuiltinData BuiltinData
hd2
                        in
                            if BuiltinData
k1 BuiltinData -> BuiltinData -> Bool
forall a. Eq a => a -> a -> Bool
== BuiltinData
k2
                            then
                                if BuiltinData -> BuiltinData -> Bool
eqV BuiltinData
v1 BuiltinData
v2
                                then BuiltinList (BuiltinPair BuiltinData BuiltinData)
-> BuiltinList (BuiltinPair BuiltinData BuiltinData) -> Bool
goBoth BuiltinList (BuiltinPair BuiltinData BuiltinData)
tl1 BuiltinList (BuiltinPair BuiltinData BuiltinData)
tl2
                                else Bool
False
                            else
                                if BuiltinData -> Bool
is0 BuiltinData
v1
                                then BuiltinList (BuiltinPair BuiltinData BuiltinData)
-> BuiltinList (BuiltinPair BuiltinData BuiltinData) -> Bool
goBoth BuiltinList (BuiltinPair BuiltinData BuiltinData)
tl1 BuiltinList (BuiltinPair BuiltinData BuiltinData)
l2
                                else
                                    let
                                        goRight
                                            :: BuiltinList (BuiltinPair BuiltinData BuiltinData)
                                            -> BuiltinList (BuiltinPair BuiltinData BuiltinData)
                                            -> Bool
                                        goRight :: BuiltinList (BuiltinPair BuiltinData BuiltinData)
-> BuiltinList (BuiltinPair BuiltinData BuiltinData) -> Bool
goRight BuiltinList (BuiltinPair BuiltinData BuiltinData)
acc BuiltinList (BuiltinPair BuiltinData BuiltinData)
l =
                                            BuiltinList (BuiltinPair BuiltinData BuiltinData)
-> (() -> Bool)
-> (BuiltinPair BuiltinData BuiltinData
    -> BuiltinList (BuiltinPair BuiltinData BuiltinData) -> Bool)
-> Bool
forall a r.
BuiltinList a -> (() -> r) -> (a -> BuiltinList a -> r) -> r
B.matchList
                                                BuiltinList (BuiltinPair BuiltinData BuiltinData)
l
                                                -- null l case
                                                (\() -> Bool
False)
                                                -- non-null l case
                                                ( \BuiltinPair BuiltinData BuiltinData
hd BuiltinList (BuiltinPair BuiltinData BuiltinData)
tl ->
                                                    let
                                                        k :: BuiltinData
k = BuiltinPair BuiltinData BuiltinData -> BuiltinData
forall a b. BuiltinPair a b -> a
BI.fst BuiltinPair BuiltinData BuiltinData
hd
                                                        v :: BuiltinData
v = BuiltinPair BuiltinData BuiltinData -> BuiltinData
forall a b. BuiltinPair a b -> b
BI.snd BuiltinPair BuiltinData BuiltinData
hd
                                                    in
                                                        if BuiltinData -> Bool
is0 BuiltinData
v
                                                        then BuiltinList (BuiltinPair BuiltinData BuiltinData)
-> BuiltinList (BuiltinPair BuiltinData BuiltinData) -> Bool
goRight BuiltinList (BuiltinPair BuiltinData BuiltinData)
acc BuiltinList (BuiltinPair BuiltinData BuiltinData)
tl
                                                        else
                                                            if BuiltinData
k BuiltinData -> BuiltinData -> Bool
forall a. Eq a => a -> a -> Bool
== BuiltinData
k1
                                                            then
                                                                if BuiltinData -> BuiltinData -> Bool
eqV BuiltinData
v1 BuiltinData
v
                                                                then BuiltinList (BuiltinPair BuiltinData BuiltinData)
-> BuiltinList (BuiltinPair BuiltinData BuiltinData) -> Bool
goBoth BuiltinList (BuiltinPair BuiltinData BuiltinData)
tl1 (BuiltinList (BuiltinPair BuiltinData BuiltinData)
-> BuiltinList (BuiltinPair BuiltinData BuiltinData)
-> BuiltinList (BuiltinPair BuiltinData BuiltinData)
forall {a}. BuiltinList a -> BuiltinList a -> BuiltinList a
revAppend' BuiltinList (BuiltinPair BuiltinData BuiltinData)
acc BuiltinList (BuiltinPair BuiltinData BuiltinData)
tl)
                                                                else Bool
False
                                                            else BuiltinList (BuiltinPair BuiltinData BuiltinData)
-> BuiltinList (BuiltinPair BuiltinData BuiltinData) -> Bool
goRight (BuiltinPair BuiltinData BuiltinData
hd BuiltinPair BuiltinData BuiltinData
-> BuiltinList (BuiltinPair BuiltinData BuiltinData)
-> BuiltinList (BuiltinPair BuiltinData BuiltinData)
forall a. a -> BuiltinList a -> BuiltinList a
`BI.mkCons` BuiltinList (BuiltinPair BuiltinData BuiltinData)
acc) BuiltinList (BuiltinPair BuiltinData BuiltinData)
tl
                                                )
                                    in
                                        BuiltinList (BuiltinPair BuiltinData BuiltinData)
-> BuiltinList (BuiltinPair BuiltinData BuiltinData) -> Bool
goRight
                                            ( if BuiltinData -> Bool
is0 BuiltinData
v2
                                                then BuiltinUnit -> BuiltinList (BuiltinPair BuiltinData BuiltinData)
BI.mkNilPairData BuiltinUnit
BI.unitval
                                                else BuiltinPair BuiltinData BuiltinData
hd2 BuiltinPair BuiltinData BuiltinData
-> BuiltinList (BuiltinPair BuiltinData BuiltinData)
-> BuiltinList (BuiltinPair BuiltinData BuiltinData)
forall a. a -> BuiltinList a -> BuiltinList a
`BI.mkCons` BuiltinUnit -> BuiltinList (BuiltinPair BuiltinData BuiltinData)
BI.mkNilPairData BuiltinUnit
BI.unitval
                                            )
                                            BuiltinList (BuiltinPair BuiltinData BuiltinData)
tl2
                    )
            )

    revAppend' :: BuiltinList a -> BuiltinList a -> BuiltinList a
revAppend' = BuiltinList a -> BuiltinList a -> BuiltinList a
forall {a}. BuiltinList a -> BuiltinList a -> BuiltinList a
rev
      where
        rev :: BuiltinList a -> BuiltinList a -> BuiltinList a
rev BuiltinList a
l BuiltinList a
acc =
            BuiltinList a
-> (() -> BuiltinList a)
-> (a -> BuiltinList a -> BuiltinList a)
-> BuiltinList a
forall a r.
BuiltinList a -> (() -> r) -> (a -> BuiltinList a -> r) -> r
B.matchList
                BuiltinList a
l
                (\() -> BuiltinList a
acc)
                ( \a
hd BuiltinList a
tl ->
                    BuiltinList a -> BuiltinList a -> BuiltinList a
rev BuiltinList a
tl (a
hd a -> BuiltinList a -> BuiltinList a
forall a. a -> BuiltinList a -> BuiltinList a
`BI.mkCons` BuiltinList a
acc)
                )


{-# INLINABLE eqMapOfMapsWith #-}
-- | Check equality of two maps of maps indexed by 'CurrencySymbol's,
--- given a function checking whether a value is zero and a function
-- checking equality of values.
eqMapOfMapsWith
    :: (Map.Map TokenName Integer -> Bool)
    -> (Map.Map TokenName Integer -> Map.Map TokenName Integer -> Bool)
    -> Map.Map CurrencySymbol (Map.Map TokenName Integer)
    -> Map.Map CurrencySymbol (Map.Map TokenName Integer)
    -> Bool
eqMapOfMapsWith :: (Map TokenName Integer -> Bool)
-> (Map TokenName Integer -> Map TokenName Integer -> Bool)
-> Map CurrencySymbol (Map TokenName Integer)
-> Map CurrencySymbol (Map TokenName Integer)
-> Bool
eqMapOfMapsWith Map TokenName Integer -> Bool
is0 Map TokenName Integer -> Map TokenName Integer -> Bool
eqV Map CurrencySymbol (Map TokenName Integer)
map1 Map CurrencySymbol (Map TokenName Integer)
map2 =
    let xs1 :: BuiltinList (BuiltinPair BuiltinData BuiltinData)
xs1 = Map CurrencySymbol (Map TokenName Integer)
-> BuiltinList (BuiltinPair BuiltinData BuiltinData)
forall k a.
Map k a -> BuiltinList (BuiltinPair BuiltinData BuiltinData)
Map.toBuiltinList Map CurrencySymbol (Map TokenName Integer)
map1
        xs2 :: BuiltinList (BuiltinPair BuiltinData BuiltinData)
xs2 = Map CurrencySymbol (Map TokenName Integer)
-> BuiltinList (BuiltinPair BuiltinData BuiltinData)
forall k a.
Map k a -> BuiltinList (BuiltinPair BuiltinData BuiltinData)
Map.toBuiltinList Map CurrencySymbol (Map TokenName Integer)
map2
        is0' :: BuiltinData -> Bool
is0' BuiltinData
v = Map TokenName Integer -> Bool
is0 (BuiltinData -> Map TokenName Integer
forall a. UnsafeFromData a => BuiltinData -> a
unsafeFromBuiltinData BuiltinData
v)
        eqV' :: BuiltinData -> BuiltinData -> Bool
eqV' BuiltinData
v1 BuiltinData
v2 = Map TokenName Integer -> Map TokenName Integer -> Bool
eqV (BuiltinData -> Map TokenName Integer
forall a. UnsafeFromData a => BuiltinData -> a
unsafeFromBuiltinData BuiltinData
v1) (BuiltinData -> Map TokenName Integer
forall a. UnsafeFromData a => BuiltinData -> a
unsafeFromBuiltinData BuiltinData
v2)
     in (BuiltinData -> Bool)
-> (BuiltinData -> BuiltinData -> Bool)
-> BuiltinList (BuiltinPair BuiltinData BuiltinData)
-> BuiltinList (BuiltinPair BuiltinData BuiltinData)
-> Bool
unordEqWith BuiltinData -> Bool
is0' BuiltinData -> BuiltinData -> Bool
eqV' BuiltinList (BuiltinPair BuiltinData BuiltinData)
xs1 BuiltinList (BuiltinPair BuiltinData BuiltinData)
xs2

{-# INLINABLE eqMapWith #-}
-- | Check equality of two 'Map Token Integer's given a function checking whether a value is zero and a function
-- checking equality of values.
eqMapWith
    :: (Integer -> Bool)
    -> (Integer -> Integer -> Bool)
    -> Map.Map TokenName Integer
    -> Map.Map TokenName Integer
    -> Bool
eqMapWith :: (Integer -> Bool)
-> (Integer -> Integer -> Bool)
-> Map TokenName Integer
-> Map TokenName Integer
-> Bool
eqMapWith Integer -> Bool
is0 Integer -> Integer -> Bool
eqV Map TokenName Integer
map1 Map TokenName Integer
map2 =
    let xs1 :: BuiltinList (BuiltinPair BuiltinData BuiltinData)
xs1 = Map TokenName Integer
-> BuiltinList (BuiltinPair BuiltinData BuiltinData)
forall k a.
Map k a -> BuiltinList (BuiltinPair BuiltinData BuiltinData)
Map.toBuiltinList Map TokenName Integer
map1
        xs2 :: BuiltinList (BuiltinPair BuiltinData BuiltinData)
xs2 = Map TokenName Integer
-> BuiltinList (BuiltinPair BuiltinData BuiltinData)
forall k a.
Map k a -> BuiltinList (BuiltinPair BuiltinData BuiltinData)
Map.toBuiltinList Map TokenName Integer
map2
        is0' :: BuiltinData -> Bool
is0' BuiltinData
v = Integer -> Bool
is0 (BuiltinData -> Integer
forall a. UnsafeFromData a => BuiltinData -> a
unsafeFromBuiltinData BuiltinData
v)
        eqV' :: BuiltinData -> BuiltinData -> Bool
eqV' BuiltinData
v1 BuiltinData
v2 = Integer -> Integer -> Bool
eqV (BuiltinData -> Integer
forall a. UnsafeFromData a => BuiltinData -> a
unsafeFromBuiltinData BuiltinData
v1) (BuiltinData -> Integer
forall a. UnsafeFromData a => BuiltinData -> a
unsafeFromBuiltinData BuiltinData
v2)
     in (BuiltinData -> Bool)
-> (BuiltinData -> BuiltinData -> Bool)
-> BuiltinList (BuiltinPair BuiltinData BuiltinData)
-> BuiltinList (BuiltinPair BuiltinData BuiltinData)
-> Bool
unordEqWith BuiltinData -> Bool
is0' BuiltinData -> BuiltinData -> Bool
eqV' BuiltinList (BuiltinPair BuiltinData BuiltinData)
xs1 BuiltinList (BuiltinPair BuiltinData BuiltinData)
xs2

{-# INLINABLE eq #-}
-- | Check equality of two 'Value's. Does not assume orderness of lists within a 'Value' or a lack
-- of empty values (such as a token whose quantity is zero or a currency that has a bunch of such
-- tokens or no tokens at all), but does assume that no currencies or tokens within a single
-- currency have multiple entries.
eq :: Value -> Value -> Bool
eq :: Value -> Value -> Bool
eq (Value Map CurrencySymbol (Map TokenName Integer)
currs1) (Value Map CurrencySymbol (Map TokenName Integer)
currs2) =
    (Map TokenName Integer -> Bool)
-> (Map TokenName Integer -> Map TokenName Integer -> Bool)
-> Map CurrencySymbol (Map TokenName Integer)
-> Map CurrencySymbol (Map TokenName Integer)
-> Bool
eqMapOfMapsWith ((Integer -> Bool) -> Map TokenName Integer -> Bool
forall k a. UnsafeFromData a => (a -> Bool) -> Map k a -> Bool
Map.all (Integer
0 Integer -> Integer -> Bool
forall a. Eq a => a -> a -> Bool
==)) ((Integer -> Bool)
-> (Integer -> Integer -> Bool)
-> Map TokenName Integer
-> Map TokenName Integer
-> Bool
eqMapWith (Integer
0 Integer -> Integer -> Bool
forall a. Eq a => a -> a -> Bool
==) Integer -> Integer -> Bool
forall a. Eq a => a -> a -> Bool
(==)) Map CurrencySymbol (Map TokenName Integer)
currs1 Map CurrencySymbol (Map TokenName Integer)
currs2

newtype Lovelace = Lovelace { Lovelace -> Integer
getLovelace :: Integer }
  deriving stock ((forall x. Lovelace -> Rep Lovelace x)
-> (forall x. Rep Lovelace x -> Lovelace) -> Generic Lovelace
forall x. Rep Lovelace x -> Lovelace
forall x. Lovelace -> Rep Lovelace x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. Lovelace -> Rep Lovelace x
from :: forall x. Lovelace -> Rep Lovelace x
$cto :: forall x. Rep Lovelace x -> Lovelace
to :: forall x. Rep Lovelace x -> Lovelace
Generic, Typeable)
  deriving ((forall ann. Lovelace -> Doc ann)
-> (forall ann. [Lovelace] -> Doc ann) -> Pretty Lovelace
forall ann. [Lovelace] -> Doc ann
forall ann. Lovelace -> Doc ann
forall a.
(forall ann. a -> Doc ann)
-> (forall ann. [a] -> Doc ann) -> Pretty a
$cpretty :: forall ann. Lovelace -> Doc ann
pretty :: forall ann. Lovelace -> Doc ann
$cprettyList :: forall ann. [Lovelace] -> Doc ann
prettyList :: forall ann. [Lovelace] -> Doc ann
Pretty) via (PrettyShow Lovelace)
  deriving anyclass (DefinitionId
DefinitionId -> HasBlueprintDefinition Lovelace
forall t. DefinitionId -> HasBlueprintDefinition t
$cdefinitionId :: DefinitionId
definitionId :: DefinitionId
HasBlueprintDefinition)
  deriving newtype
    ( Lovelace -> Lovelace -> Bool
(Lovelace -> Lovelace -> Bool)
-> (Lovelace -> Lovelace -> Bool) -> Eq Lovelace
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Lovelace -> Lovelace -> Bool
== :: Lovelace -> Lovelace -> Bool
$c/= :: Lovelace -> Lovelace -> Bool
/= :: Lovelace -> Lovelace -> Bool
Haskell.Eq
    , Eq Lovelace
Eq Lovelace =>
(Lovelace -> Lovelace -> Ordering)
-> (Lovelace -> Lovelace -> Bool)
-> (Lovelace -> Lovelace -> Bool)
-> (Lovelace -> Lovelace -> Bool)
-> (Lovelace -> Lovelace -> Bool)
-> (Lovelace -> Lovelace -> Lovelace)
-> (Lovelace -> Lovelace -> Lovelace)
-> Ord Lovelace
Lovelace -> Lovelace -> Bool
Lovelace -> Lovelace -> Ordering
Lovelace -> Lovelace -> Lovelace
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: Lovelace -> Lovelace -> Ordering
compare :: Lovelace -> Lovelace -> Ordering
$c< :: Lovelace -> Lovelace -> Bool
< :: Lovelace -> Lovelace -> Bool
$c<= :: Lovelace -> Lovelace -> Bool
<= :: Lovelace -> Lovelace -> Bool
$c> :: Lovelace -> Lovelace -> Bool
> :: Lovelace -> Lovelace -> Bool
$c>= :: Lovelace -> Lovelace -> Bool
>= :: Lovelace -> Lovelace -> Bool
$cmax :: Lovelace -> Lovelace -> Lovelace
max :: Lovelace -> Lovelace -> Lovelace
$cmin :: Lovelace -> Lovelace -> Lovelace
min :: Lovelace -> Lovelace -> Lovelace
Haskell.Ord
    , Int -> Lovelace -> ShowS
[Lovelace] -> ShowS
Lovelace -> String
(Int -> Lovelace -> ShowS)
-> (Lovelace -> String) -> ([Lovelace] -> ShowS) -> Show Lovelace
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Lovelace -> ShowS
showsPrec :: Int -> Lovelace -> ShowS
$cshow :: Lovelace -> String
show :: Lovelace -> String
$cshowList :: [Lovelace] -> ShowS
showList :: [Lovelace] -> ShowS
Haskell.Show
    , Integer -> Lovelace
Lovelace -> Lovelace
Lovelace -> Lovelace -> Lovelace
(Lovelace -> Lovelace -> Lovelace)
-> (Lovelace -> Lovelace -> Lovelace)
-> (Lovelace -> Lovelace -> Lovelace)
-> (Lovelace -> Lovelace)
-> (Lovelace -> Lovelace)
-> (Lovelace -> Lovelace)
-> (Integer -> Lovelace)
-> Num Lovelace
forall a.
(a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (Integer -> a)
-> Num a
$c+ :: Lovelace -> Lovelace -> Lovelace
+ :: Lovelace -> Lovelace -> Lovelace
$c- :: Lovelace -> Lovelace -> Lovelace
- :: Lovelace -> Lovelace -> Lovelace
$c* :: Lovelace -> Lovelace -> Lovelace
* :: Lovelace -> Lovelace -> Lovelace
$cnegate :: Lovelace -> Lovelace
negate :: Lovelace -> Lovelace
$cabs :: Lovelace -> Lovelace
abs :: Lovelace -> Lovelace
$csignum :: Lovelace -> Lovelace
signum :: Lovelace -> Lovelace
$cfromInteger :: Integer -> Lovelace
fromInteger :: Integer -> Lovelace
Haskell.Num
    , Num Lovelace
Ord Lovelace
(Num Lovelace, Ord Lovelace) =>
(Lovelace -> Rational) -> Real Lovelace
Lovelace -> Rational
forall a. (Num a, Ord a) => (a -> Rational) -> Real a
$ctoRational :: Lovelace -> Rational
toRational :: Lovelace -> Rational
Haskell.Real
    , Int -> Lovelace
Lovelace -> Int
Lovelace -> [Lovelace]
Lovelace -> Lovelace
Lovelace -> Lovelace -> [Lovelace]
Lovelace -> Lovelace -> Lovelace -> [Lovelace]
(Lovelace -> Lovelace)
-> (Lovelace -> Lovelace)
-> (Int -> Lovelace)
-> (Lovelace -> Int)
-> (Lovelace -> [Lovelace])
-> (Lovelace -> Lovelace -> [Lovelace])
-> (Lovelace -> Lovelace -> [Lovelace])
-> (Lovelace -> Lovelace -> Lovelace -> [Lovelace])
-> Enum Lovelace
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
$csucc :: Lovelace -> Lovelace
succ :: Lovelace -> Lovelace
$cpred :: Lovelace -> Lovelace
pred :: Lovelace -> Lovelace
$ctoEnum :: Int -> Lovelace
toEnum :: Int -> Lovelace
$cfromEnum :: Lovelace -> Int
fromEnum :: Lovelace -> Int
$cenumFrom :: Lovelace -> [Lovelace]
enumFrom :: Lovelace -> [Lovelace]
$cenumFromThen :: Lovelace -> Lovelace -> [Lovelace]
enumFromThen :: Lovelace -> Lovelace -> [Lovelace]
$cenumFromTo :: Lovelace -> Lovelace -> [Lovelace]
enumFromTo :: Lovelace -> Lovelace -> [Lovelace]
$cenumFromThenTo :: Lovelace -> Lovelace -> Lovelace -> [Lovelace]
enumFromThenTo :: Lovelace -> Lovelace -> Lovelace -> [Lovelace]
Haskell.Enum
    , Lovelace -> Lovelace -> Bool
(Lovelace -> Lovelace -> Bool) -> Eq Lovelace
forall a. (a -> a -> Bool) -> Eq a
$c== :: Lovelace -> Lovelace -> Bool
== :: Lovelace -> Lovelace -> Bool
PlutusTx.Eq
    , Eq Lovelace
Eq Lovelace =>
(Lovelace -> Lovelace -> Ordering)
-> (Lovelace -> Lovelace -> Bool)
-> (Lovelace -> Lovelace -> Bool)
-> (Lovelace -> Lovelace -> Bool)
-> (Lovelace -> Lovelace -> Bool)
-> (Lovelace -> Lovelace -> Lovelace)
-> (Lovelace -> Lovelace -> Lovelace)
-> Ord Lovelace
Lovelace -> Lovelace -> Bool
Lovelace -> Lovelace -> Ordering
Lovelace -> Lovelace -> Lovelace
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: Lovelace -> Lovelace -> Ordering
compare :: Lovelace -> Lovelace -> Ordering
$c< :: Lovelace -> Lovelace -> Bool
< :: Lovelace -> Lovelace -> Bool
$c<= :: Lovelace -> Lovelace -> Bool
<= :: Lovelace -> Lovelace -> Bool
$c> :: Lovelace -> Lovelace -> Bool
> :: Lovelace -> Lovelace -> Bool
$c>= :: Lovelace -> Lovelace -> Bool
>= :: Lovelace -> Lovelace -> Bool
$cmax :: Lovelace -> Lovelace -> Lovelace
max :: Lovelace -> Lovelace -> Lovelace
$cmin :: Lovelace -> Lovelace -> Lovelace
min :: Lovelace -> Lovelace -> Lovelace
PlutusTx.Ord
    , Lovelace -> BuiltinData
(Lovelace -> BuiltinData) -> ToData Lovelace
forall a. (a -> BuiltinData) -> ToData a
$ctoBuiltinData :: Lovelace -> BuiltinData
toBuiltinData :: Lovelace -> BuiltinData
PlutusTx.ToData
    , BuiltinData -> Maybe Lovelace
(BuiltinData -> Maybe Lovelace) -> FromData Lovelace
forall a. (BuiltinData -> Maybe a) -> FromData a
$cfromBuiltinData :: BuiltinData -> Maybe Lovelace
fromBuiltinData :: BuiltinData -> Maybe Lovelace
PlutusTx.FromData
    , BuiltinData -> Lovelace
(BuiltinData -> Lovelace) -> UnsafeFromData Lovelace
forall a. (BuiltinData -> a) -> UnsafeFromData a
$cunsafeFromBuiltinData :: BuiltinData -> Lovelace
unsafeFromBuiltinData :: BuiltinData -> Lovelace
PlutusTx.UnsafeFromData
    , Lovelace -> Lovelace -> Lovelace
(Lovelace -> Lovelace -> Lovelace) -> AdditiveSemigroup Lovelace
forall a. (a -> a -> a) -> AdditiveSemigroup a
$c+ :: Lovelace -> Lovelace -> Lovelace
+ :: Lovelace -> Lovelace -> Lovelace
PlutusTx.AdditiveSemigroup
    , AdditiveSemigroup Lovelace
Lovelace
AdditiveSemigroup Lovelace => Lovelace -> AdditiveMonoid Lovelace
forall a. AdditiveSemigroup a => a -> AdditiveMonoid a
$czero :: Lovelace
zero :: Lovelace
PlutusTx.AdditiveMonoid
    , AdditiveMonoid Lovelace
AdditiveMonoid Lovelace =>
(Lovelace -> Lovelace -> Lovelace) -> AdditiveGroup Lovelace
Lovelace -> Lovelace -> Lovelace
forall a. AdditiveMonoid a => (a -> a -> a) -> AdditiveGroup a
$c- :: Lovelace -> Lovelace -> Lovelace
- :: Lovelace -> Lovelace -> Lovelace
PlutusTx.AdditiveGroup
    , Integer -> Lovelace -> ShowS
Lovelace -> BuiltinString
(Integer -> Lovelace -> ShowS)
-> (Lovelace -> BuiltinString) -> Show Lovelace
forall a. (Integer -> a -> ShowS) -> (a -> BuiltinString) -> Show a
$cshowsPrec :: Integer -> Lovelace -> ShowS
showsPrec :: Integer -> Lovelace -> ShowS
$cshow :: Lovelace -> BuiltinString
show :: Lovelace -> BuiltinString
PlutusTx.Show
    )

----------------------------------------------------------------------------------------------------
-- TH Splices --------------------------------------------------------------------------------------

$(makeLift ''CurrencySymbol)
$(makeLift ''TokenName)
$(makeLift ''AssetClass)
$(makeLift ''Value)
$(makeLift ''Lovelace)