plutus-ledger-api-1.30.0.0: Interface to the Plutus ledger for the Cardano ledger.
Safe HaskellSafe-Inferred
LanguageHaskell2010

PlutusLedgerApi.V1.Data.Value

Description

Functions for working with Value.

Synopsis

Currency symbols

newtype CurrencySymbol Source #

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.

Instances

Instances details
Data CurrencySymbol Source # 
Instance details

Defined in PlutusLedgerApi.V1.Data.Value

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> CurrencySymbol -> c CurrencySymbol Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c CurrencySymbol Source #

toConstr :: CurrencySymbol -> Constr Source #

dataTypeOf :: CurrencySymbol -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c CurrencySymbol) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c CurrencySymbol) Source #

gmapT :: (forall b. Data b => b -> b) -> CurrencySymbol -> CurrencySymbol Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> CurrencySymbol -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> CurrencySymbol -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> CurrencySymbol -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> CurrencySymbol -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> CurrencySymbol -> m CurrencySymbol Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> CurrencySymbol -> m CurrencySymbol Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> CurrencySymbol -> m CurrencySymbol Source #

IsString CurrencySymbol Source #

from hex encoding

Instance details

Defined in PlutusLedgerApi.V1.Data.Value

Generic CurrencySymbol Source # 
Instance details

Defined in PlutusLedgerApi.V1.Data.Value

Associated Types

type Rep CurrencySymbol :: Type -> Type Source #

Show CurrencySymbol Source #

using hex encoding

Instance details

Defined in PlutusLedgerApi.V1.Data.Value

NFData CurrencySymbol Source # 
Instance details

Defined in PlutusLedgerApi.V1.Data.Value

Methods

rnf :: CurrencySymbol -> () Source #

Eq CurrencySymbol Source # 
Instance details

Defined in PlutusLedgerApi.V1.Data.Value

Ord CurrencySymbol Source # 
Instance details

Defined in PlutusLedgerApi.V1.Data.Value

Eq CurrencySymbol Source # 
Instance details

Defined in PlutusLedgerApi.V1.Data.Value

FromData CurrencySymbol Source # 
Instance details

Defined in PlutusLedgerApi.V1.Data.Value

ToData CurrencySymbol Source # 
Instance details

Defined in PlutusLedgerApi.V1.Data.Value

UnsafeFromData CurrencySymbol Source # 
Instance details

Defined in PlutusLedgerApi.V1.Data.Value

Ord CurrencySymbol Source # 
Instance details

Defined in PlutusLedgerApi.V1.Data.Value

Pretty CurrencySymbol Source #

using hex encoding

Instance details

Defined in PlutusLedgerApi.V1.Data.Value

Methods

pretty :: CurrencySymbol -> Doc ann

prettyList :: [CurrencySymbol] -> Doc ann

Lift DefaultUni CurrencySymbol Source # 
Instance details

Defined in PlutusLedgerApi.V1.Data.Value

Methods

lift :: CurrencySymbol -> RTCompile DefaultUni fun (Term TyName Name DefaultUni fun ())

Typeable DefaultUni CurrencySymbol Source # 
Instance details

Defined in PlutusLedgerApi.V1.Data.Value

Methods

typeRep :: Proxy CurrencySymbol -> RTCompile DefaultUni fun (Type TyName DefaultUni ())

type Rep CurrencySymbol Source # 
Instance details

Defined in PlutusLedgerApi.V1.Data.Value

type Rep CurrencySymbol = D1 ('MetaData "CurrencySymbol" "PlutusLedgerApi.V1.Data.Value" "plutus-ledger-api-1.30.0.0-AeqdHlc23KHCP4Mgl3sbFx" 'True) (C1 ('MetaCons "CurrencySymbol" 'PrefixI 'True) (S1 ('MetaSel ('Just "unCurrencySymbol") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 BuiltinByteString)))

currencySymbol :: ByteString -> CurrencySymbol Source #

Creates CurrencySymbol from raw ByteString.

adaSymbol :: CurrencySymbol Source #

The CurrencySymbol of the Ada currency.

Token names

newtype TokenName Source #

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.

Constructors

TokenName 

Instances

Instances details
Data TokenName Source # 
Instance details

Defined in PlutusLedgerApi.V1.Data.Value

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> TokenName -> c TokenName Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c TokenName Source #

toConstr :: TokenName -> Constr Source #

dataTypeOf :: TokenName -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c TokenName) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TokenName) Source #

gmapT :: (forall b. Data b => b -> b) -> TokenName -> TokenName Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TokenName -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TokenName -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> TokenName -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> TokenName -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> TokenName -> m TokenName Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> TokenName -> m TokenName Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> TokenName -> m TokenName Source #

IsString TokenName Source #

UTF-8 encoding. Doesn't verify length.

Instance details

Defined in PlutusLedgerApi.V1.Data.Value

Generic TokenName Source # 
Instance details

Defined in PlutusLedgerApi.V1.Data.Value

Associated Types

type Rep TokenName :: Type -> Type Source #

Show TokenName Source # 
Instance details

Defined in PlutusLedgerApi.V1.Data.Value

NFData TokenName Source # 
Instance details

Defined in PlutusLedgerApi.V1.Data.Value

Methods

rnf :: TokenName -> () Source #

Eq TokenName Source # 
Instance details

Defined in PlutusLedgerApi.V1.Data.Value

Ord TokenName Source # 
Instance details

Defined in PlutusLedgerApi.V1.Data.Value

Eq TokenName Source # 
Instance details

Defined in PlutusLedgerApi.V1.Data.Value

Methods

(==) :: TokenName -> TokenName -> Bool

FromData TokenName Source # 
Instance details

Defined in PlutusLedgerApi.V1.Data.Value

ToData TokenName Source # 
Instance details

Defined in PlutusLedgerApi.V1.Data.Value

UnsafeFromData TokenName Source # 
Instance details

Defined in PlutusLedgerApi.V1.Data.Value

Ord TokenName Source # 
Instance details

Defined in PlutusLedgerApi.V1.Data.Value

Pretty TokenName Source # 
Instance details

Defined in PlutusLedgerApi.V1.Data.Value

Methods

pretty :: TokenName -> Doc ann

prettyList :: [TokenName] -> Doc ann

Lift DefaultUni TokenName Source # 
Instance details

Defined in PlutusLedgerApi.V1.Data.Value

Methods

lift :: TokenName -> RTCompile DefaultUni fun (Term TyName Name DefaultUni fun ())

Typeable DefaultUni TokenName Source # 
Instance details

Defined in PlutusLedgerApi.V1.Data.Value

Methods

typeRep :: Proxy TokenName -> RTCompile DefaultUni fun (Type TyName DefaultUni ())

type Rep TokenName Source # 
Instance details

Defined in PlutusLedgerApi.V1.Data.Value

type Rep TokenName = D1 ('MetaData "TokenName" "PlutusLedgerApi.V1.Data.Value" "plutus-ledger-api-1.30.0.0-AeqdHlc23KHCP4Mgl3sbFx" 'True) (C1 ('MetaCons "TokenName" 'PrefixI 'True) (S1 ('MetaSel ('Just "unTokenName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 BuiltinByteString)))

tokenName :: ByteString -> TokenName Source #

Creates TokenName from raw ByteString.

toString :: TokenName -> String Source #

Turn a TokenName to a hex-encoded String

Compared to show , it will not surround the string with double-quotes.

adaToken :: TokenName Source #

The TokenName of the Ada currency.

Asset classes

newtype AssetClass Source #

An asset class, identified by a CurrencySymbol and a TokenName.

Constructors

AssetClass 

Instances

Instances details
Data AssetClass Source # 
Instance details

Defined in PlutusLedgerApi.V1.Data.Value

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> AssetClass -> c AssetClass Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c AssetClass Source #

toConstr :: AssetClass -> Constr Source #

dataTypeOf :: AssetClass -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c AssetClass) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c AssetClass) Source #

gmapT :: (forall b. Data b => b -> b) -> AssetClass -> AssetClass Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> AssetClass -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> AssetClass -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> AssetClass -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> AssetClass -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> AssetClass -> m AssetClass Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> AssetClass -> m AssetClass Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> AssetClass -> m AssetClass Source #

Generic AssetClass Source # 
Instance details

Defined in PlutusLedgerApi.V1.Data.Value

Associated Types

type Rep AssetClass :: Type -> Type Source #

Show AssetClass Source # 
Instance details

Defined in PlutusLedgerApi.V1.Data.Value

NFData AssetClass Source # 
Instance details

Defined in PlutusLedgerApi.V1.Data.Value

Methods

rnf :: AssetClass -> () Source #

Eq AssetClass Source # 
Instance details

Defined in PlutusLedgerApi.V1.Data.Value

Ord AssetClass Source # 
Instance details

Defined in PlutusLedgerApi.V1.Data.Value

Eq AssetClass Source # 
Instance details

Defined in PlutusLedgerApi.V1.Data.Value

Methods

(==) :: AssetClass -> AssetClass -> Bool

FromData AssetClass Source # 
Instance details

Defined in PlutusLedgerApi.V1.Data.Value

ToData AssetClass Source # 
Instance details

Defined in PlutusLedgerApi.V1.Data.Value

UnsafeFromData AssetClass Source # 
Instance details

Defined in PlutusLedgerApi.V1.Data.Value

Ord AssetClass Source # 
Instance details

Defined in PlutusLedgerApi.V1.Data.Value

Pretty AssetClass Source # 
Instance details

Defined in PlutusLedgerApi.V1.Data.Value

Methods

pretty :: AssetClass -> Doc ann

prettyList :: [AssetClass] -> Doc ann

Lift DefaultUni AssetClass Source # 
Instance details

Defined in PlutusLedgerApi.V1.Data.Value

Methods

lift :: AssetClass -> RTCompile DefaultUni fun (Term TyName Name DefaultUni fun ())

Typeable DefaultUni AssetClass Source # 
Instance details

Defined in PlutusLedgerApi.V1.Data.Value

Methods

typeRep :: Proxy AssetClass -> RTCompile DefaultUni fun (Type TyName DefaultUni ())

type Rep AssetClass Source # 
Instance details

Defined in PlutusLedgerApi.V1.Data.Value

type Rep AssetClass = D1 ('MetaData "AssetClass" "PlutusLedgerApi.V1.Data.Value" "plutus-ledger-api-1.30.0.0-AeqdHlc23KHCP4Mgl3sbFx" 'True) (C1 ('MetaCons "AssetClass" 'PrefixI 'True) (S1 ('MetaSel ('Just "unAssetClass") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (CurrencySymbol, TokenName))))

assetClass :: CurrencySymbol -> TokenName -> AssetClass Source #

The curried version of AssetClass constructor

assetClassValue :: AssetClass -> Integer -> Value Source #

A Value containing the given amount of the asset class.

assetClassValueOf :: Value -> AssetClass -> Integer Source #

Get the quantity of the given AssetClass class in the Value.

Value

newtype Value Source #

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 Values 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.

Constructors

Value 

Instances

Instances details
Monoid Value Source # 
Instance details

Defined in PlutusLedgerApi.V1.Data.Value

Semigroup Value Source # 
Instance details

Defined in PlutusLedgerApi.V1.Data.Value

Generic Value Source # 
Instance details

Defined in PlutusLedgerApi.V1.Data.Value

Associated Types

type Rep Value :: Type -> Type Source #

Methods

from :: Value -> Rep Value x Source #

to :: Rep Value x -> Value Source #

Show Value Source # 
Instance details

Defined in PlutusLedgerApi.V1.Data.Value

Eq Value Source # 
Instance details

Defined in PlutusLedgerApi.V1.Data.Value

Methods

(==) :: Value -> Value -> Bool Source #

(/=) :: Value -> Value -> Bool Source #

Eq Value Source # 
Instance details

Defined in PlutusLedgerApi.V1.Data.Value

Methods

(==) :: Value -> Value -> Bool

FromData Value Source # 
Instance details

Defined in PlutusLedgerApi.V1.Data.Value

ToData Value Source # 
Instance details

Defined in PlutusLedgerApi.V1.Data.Value

UnsafeFromData Value Source # 
Instance details

Defined in PlutusLedgerApi.V1.Data.Value

JoinSemiLattice Value Source # 
Instance details

Defined in PlutusLedgerApi.V1.Data.Value

Methods

(\/) :: Value -> Value -> Value

MeetSemiLattice Value Source # 
Instance details

Defined in PlutusLedgerApi.V1.Data.Value

Methods

(/\) :: Value -> Value -> Value

Group Value Source # 
Instance details

Defined in PlutusLedgerApi.V1.Data.Value

Methods

inv :: Value -> Value

Monoid Value Source # 
Instance details

Defined in PlutusLedgerApi.V1.Data.Value

Methods

mempty :: Value

AdditiveGroup Value Source # 
Instance details

Defined in PlutusLedgerApi.V1.Data.Value

Methods

(-) :: Value -> Value -> Value

AdditiveMonoid Value Source # 
Instance details

Defined in PlutusLedgerApi.V1.Data.Value

Methods

zero :: Value

AdditiveSemigroup Value Source # 
Instance details

Defined in PlutusLedgerApi.V1.Data.Value

Methods

(+) :: Value -> Value -> Value

Semigroup Value Source # 
Instance details

Defined in PlutusLedgerApi.V1.Data.Value

Methods

(<>) :: Value -> Value -> Value

Pretty Value Source # 
Instance details

Defined in PlutusLedgerApi.V1.Data.Value

Methods

pretty :: Value -> Doc ann

prettyList :: [Value] -> Doc ann

Lift DefaultUni Value Source # 
Instance details

Defined in PlutusLedgerApi.V1.Data.Value

Methods

lift :: Value -> RTCompile DefaultUni fun (Term TyName Name DefaultUni fun ())

Module Integer Value Source # 
Instance details

Defined in PlutusLedgerApi.V1.Data.Value

Methods

scale :: Integer -> Value -> Value #

Typeable DefaultUni Value Source # 
Instance details

Defined in PlutusLedgerApi.V1.Data.Value

Methods

typeRep :: Proxy Value -> RTCompile DefaultUni fun (Type TyName DefaultUni ())

type Rep Value Source # 
Instance details

Defined in PlutusLedgerApi.V1.Data.Value

type Rep Value = D1 ('MetaData "Value" "PlutusLedgerApi.V1.Data.Value" "plutus-ledger-api-1.30.0.0-AeqdHlc23KHCP4Mgl3sbFx" 'True) (C1 ('MetaCons "Value" 'PrefixI 'True) (S1 ('MetaSel ('Just "getValue") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Map CurrencySymbol (Map TokenName Integer)))))

singleton :: CurrencySymbol -> TokenName -> Integer -> Value Source #

Make a Value containing only the given quantity of the given currency.

valueOf :: Value -> CurrencySymbol -> TokenName -> Integer Source #

Get the quantity of the given currency in the Value. Assumes that the underlying map doesn't contain duplicate keys.

currencySymbolValueOf :: Value -> CurrencySymbol -> Integer Source #

Get the total value of the currency symbol in the Value map. Assumes that the underlying map doesn't contain duplicate keys.

lovelaceValue :: Lovelace -> Value Source #

A Value containing the given quantity of Lovelace.

lovelaceValueOf :: Value -> Lovelace Source #

Get the quantity of Lovelace in the Value.

scale :: Module s v => s -> v -> v #

symbols :: Value -> BuiltinList BuiltinData Source #

The list of CurrencySymbols of a Value.

Partial order operations

geq :: Value -> Value -> Bool Source #

Check whether one Value is greater than or equal to another. See Value for an explanation of how operations on Values work.

gt :: Value -> Value -> Bool Source #

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).

leq :: Value -> Value -> Bool Source #

Check whether one Value is less than or equal to another. See Value for an explanation of how operations on Values work.

lt :: Value -> Value -> Bool Source #

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).

Etc.

isZero :: Value -> Bool Source #

Check whether a Value is zero.

split :: Value -> (Value, Value) Source #

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

unionWith :: (Integer -> Integer -> Integer) -> Value -> Value -> Value Source #

Combine two Value maps with the argument function. Assumes the well-definedness of the two maps.

flattenValue :: Value -> [(CurrencySymbol, TokenName, Integer)] Source #

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.

newtype Lovelace Source #

Constructors

Lovelace 

Fields

Instances

Instances details
Enum Lovelace Source # 
Instance details

Defined in PlutusLedgerApi.V1.Data.Value

Generic Lovelace Source # 
Instance details

Defined in PlutusLedgerApi.V1.Data.Value

Associated Types

type Rep Lovelace :: Type -> Type Source #

Num Lovelace Source # 
Instance details

Defined in PlutusLedgerApi.V1.Data.Value

Real Lovelace Source # 
Instance details

Defined in PlutusLedgerApi.V1.Data.Value

Show Lovelace Source # 
Instance details

Defined in PlutusLedgerApi.V1.Data.Value

Eq Lovelace Source # 
Instance details

Defined in PlutusLedgerApi.V1.Data.Value

Ord Lovelace Source # 
Instance details

Defined in PlutusLedgerApi.V1.Data.Value

Eq Lovelace Source # 
Instance details

Defined in PlutusLedgerApi.V1.Data.Value

Methods

(==) :: Lovelace -> Lovelace -> Bool

FromData Lovelace Source # 
Instance details

Defined in PlutusLedgerApi.V1.Data.Value

ToData Lovelace Source # 
Instance details

Defined in PlutusLedgerApi.V1.Data.Value

UnsafeFromData Lovelace Source # 
Instance details

Defined in PlutusLedgerApi.V1.Data.Value

AdditiveGroup Lovelace Source # 
Instance details

Defined in PlutusLedgerApi.V1.Data.Value

Methods

(-) :: Lovelace -> Lovelace -> Lovelace

AdditiveMonoid Lovelace Source # 
Instance details

Defined in PlutusLedgerApi.V1.Data.Value

Methods

zero :: Lovelace

AdditiveSemigroup Lovelace Source # 
Instance details

Defined in PlutusLedgerApi.V1.Data.Value

Methods

(+) :: Lovelace -> Lovelace -> Lovelace

Ord Lovelace Source # 
Instance details

Defined in PlutusLedgerApi.V1.Data.Value

Show Lovelace Source # 
Instance details

Defined in PlutusLedgerApi.V1.Data.Value

Methods

showsPrec :: Integer -> Lovelace -> ShowS

show :: Lovelace -> BuiltinString

Pretty Lovelace Source # 
Instance details

Defined in PlutusLedgerApi.V1.Data.Value

Methods

pretty :: Lovelace -> Doc ann

prettyList :: [Lovelace] -> Doc ann

Lift DefaultUni Lovelace Source # 
Instance details

Defined in PlutusLedgerApi.V1.Data.Value

Methods

lift :: Lovelace -> RTCompile DefaultUni fun (Term TyName Name DefaultUni fun ())

Typeable DefaultUni Lovelace Source # 
Instance details

Defined in PlutusLedgerApi.V1.Data.Value

Methods

typeRep :: Proxy Lovelace -> RTCompile DefaultUni fun (Type TyName DefaultUni ())

type Rep Lovelace Source # 
Instance details

Defined in PlutusLedgerApi.V1.Data.Value

type Rep Lovelace = D1 ('MetaData "Lovelace" "PlutusLedgerApi.V1.Data.Value" "plutus-ledger-api-1.30.0.0-AeqdHlc23KHCP4Mgl3sbFx" 'True) (C1 ('MetaCons "Lovelace" 'PrefixI 'True) (S1 ('MetaSel ('Just "getLovelace") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Integer)))