plutus-ledger-api-1.0.0.1: Interface to the Plutus ledger for the Cardano ledger.
Safe HaskellNone
LanguageHaskell2010

Plutus.V1.Ledger.Value

Description

Functions for working with Value.

Synopsis

Currency symbols

newtype CurrencySymbol Source #

Instances

Instances details
Eq CurrencySymbol Source # 
Instance details

Defined in Plutus.V1.Ledger.Value

Data CurrencySymbol Source # 
Instance details

Defined in Plutus.V1.Ledger.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 #

Ord CurrencySymbol Source # 
Instance details

Defined in Plutus.V1.Ledger.Value

Show CurrencySymbol Source # 
Instance details

Defined in Plutus.V1.Ledger.Value

IsString CurrencySymbol Source # 
Instance details

Defined in Plutus.V1.Ledger.Value

Generic CurrencySymbol Source # 
Instance details

Defined in Plutus.V1.Ledger.Value

Associated Types

type Rep CurrencySymbol :: Type -> Type Source #

NFData CurrencySymbol Source # 
Instance details

Defined in Plutus.V1.Ledger.Value

Methods

rnf :: CurrencySymbol -> () Source #

Pretty CurrencySymbol Source # 
Instance details

Defined in Plutus.V1.Ledger.Value

Methods

pretty :: CurrencySymbol -> Doc ann

prettyList :: [CurrencySymbol] -> Doc ann

FromData CurrencySymbol Source # 
Instance details

Defined in Plutus.V1.Ledger.Value

ToData CurrencySymbol Source # 
Instance details

Defined in Plutus.V1.Ledger.Value

UnsafeFromData CurrencySymbol Source # 
Instance details

Defined in Plutus.V1.Ledger.Value

Eq CurrencySymbol Source # 
Instance details

Defined in Plutus.V1.Ledger.Value

Ord CurrencySymbol Source # 
Instance details

Defined in Plutus.V1.Ledger.Value

Lift DefaultUni CurrencySymbol Source # 
Instance details

Defined in Plutus.V1.Ledger.Value

Methods

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

Typeable DefaultUni CurrencySymbol Source # 
Instance details

Defined in Plutus.V1.Ledger.Value

Methods

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

type Rep CurrencySymbol Source # 
Instance details

Defined in Plutus.V1.Ledger.Value

type Rep CurrencySymbol = D1 ('MetaData "CurrencySymbol" "Plutus.V1.Ledger.Value" "plutus-ledger-api-1.0.0.1-6EvbyJiK8IAAVEtnIJDu5Z" 'True) (C1 ('MetaCons "CurrencySymbol" 'PrefixI 'True) (S1 ('MetaSel ('Just "unCurrencySymbol") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 BuiltinByteString)))

currencySymbol :: ByteString -> CurrencySymbol Source #

Creates CurrencySymbol from raw ByteString.

mpsSymbol :: MintingPolicyHash -> CurrencySymbol Source #

The currency symbol of a monetay policy hash

currencyMPSHash :: CurrencySymbol -> MintingPolicyHash Source #

The minting policy hash of a currency symbol

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

Constructors

TokenName 

Instances

Instances details
Eq TokenName Source # 
Instance details

Defined in Plutus.V1.Ledger.Value

Data TokenName Source # 
Instance details

Defined in Plutus.V1.Ledger.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 #

Ord TokenName Source # 
Instance details

Defined in Plutus.V1.Ledger.Value

Show TokenName Source # 
Instance details

Defined in Plutus.V1.Ledger.Value

IsString TokenName Source # 
Instance details

Defined in Plutus.V1.Ledger.Value

Generic TokenName Source # 
Instance details

Defined in Plutus.V1.Ledger.Value

Associated Types

type Rep TokenName :: Type -> Type Source #

NFData TokenName Source # 
Instance details

Defined in Plutus.V1.Ledger.Value

Methods

rnf :: TokenName -> () Source #

Pretty TokenName Source # 
Instance details

Defined in Plutus.V1.Ledger.Value

Methods

pretty :: TokenName -> Doc ann

prettyList :: [TokenName] -> Doc ann

FromData TokenName Source # 
Instance details

Defined in Plutus.V1.Ledger.Value

ToData TokenName Source # 
Instance details

Defined in Plutus.V1.Ledger.Value

UnsafeFromData TokenName Source # 
Instance details

Defined in Plutus.V1.Ledger.Value

Eq TokenName Source # 
Instance details

Defined in Plutus.V1.Ledger.Value

Methods

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

Ord TokenName Source # 
Instance details

Defined in Plutus.V1.Ledger.Value

Lift DefaultUni TokenName Source # 
Instance details

Defined in Plutus.V1.Ledger.Value

Methods

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

Typeable DefaultUni TokenName Source # 
Instance details

Defined in Plutus.V1.Ledger.Value

Methods

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

type Rep TokenName Source # 
Instance details

Defined in Plutus.V1.Ledger.Value

type Rep TokenName = D1 ('MetaData "TokenName" "Plutus.V1.Ledger.Value" "plutus-ledger-api-1.0.0.1-6EvbyJiK8IAAVEtnIJDu5Z" 'True) (C1 ('MetaCons "TokenName" 'PrefixI 'True) (S1 ('MetaSel ('Just "unTokenName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 BuiltinByteString)))

tokenName :: ByteString -> TokenName Source #

Creates TokenName from raw ByteString.

adaToken :: TokenName Source #

The TokenName of the Ada currency.

Asset classes

newtype AssetClass Source #

An asset class, identified by currency symbol and token name.

Constructors

AssetClass 

Instances

Instances details
Eq AssetClass Source # 
Instance details

Defined in Plutus.V1.Ledger.Value

Data AssetClass Source # 
Instance details

Defined in Plutus.V1.Ledger.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 #

Ord AssetClass Source # 
Instance details

Defined in Plutus.V1.Ledger.Value

Show AssetClass Source # 
Instance details

Defined in Plutus.V1.Ledger.Value

Generic AssetClass Source # 
Instance details

Defined in Plutus.V1.Ledger.Value

Associated Types

type Rep AssetClass :: Type -> Type Source #

NFData AssetClass Source # 
Instance details

Defined in Plutus.V1.Ledger.Value

Methods

rnf :: AssetClass -> () Source #

Pretty AssetClass Source # 
Instance details

Defined in Plutus.V1.Ledger.Value

Methods

pretty :: AssetClass -> Doc ann

prettyList :: [AssetClass] -> Doc ann

FromData AssetClass Source # 
Instance details

Defined in Plutus.V1.Ledger.Value

ToData AssetClass Source # 
Instance details

Defined in Plutus.V1.Ledger.Value

UnsafeFromData AssetClass Source # 
Instance details

Defined in Plutus.V1.Ledger.Value

Eq AssetClass Source # 
Instance details

Defined in Plutus.V1.Ledger.Value

Methods

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

Ord AssetClass Source # 
Instance details

Defined in Plutus.V1.Ledger.Value

Lift DefaultUni AssetClass Source # 
Instance details

Defined in Plutus.V1.Ledger.Value

Methods

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

Typeable DefaultUni AssetClass Source # 
Instance details

Defined in Plutus.V1.Ledger.Value

Methods

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

type Rep AssetClass Source # 
Instance details

Defined in Plutus.V1.Ledger.Value

type Rep AssetClass = D1 ('MetaData "AssetClass" "Plutus.V1.Ledger.Value" "plutus-ledger-api-1.0.0.1-6EvbyJiK8IAAVEtnIJDu5Z" 'True) (C1 ('MetaCons "AssetClass" 'PrefixI 'True) (S1 ('MetaSel ('Just "unAssetClass") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (CurrencySymbol, TokenName))))

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 #

A cryptocurrency value. This is a map from CurrencySymbols to a quantity of that currency.

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.

See note [Currencies] for more details.

Instances

Instances details
Eq Value Source # 
Instance details

Defined in Plutus.V1.Ledger.Value

Methods

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

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

Data Value Source # 
Instance details

Defined in Plutus.V1.Ledger.Value

Methods

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

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

toConstr :: Value -> Constr Source #

dataTypeOf :: Value -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Show Value Source # 
Instance details

Defined in Plutus.V1.Ledger.Value

Generic Value Source # 
Instance details

Defined in Plutus.V1.Ledger.Value

Associated Types

type Rep Value :: Type -> Type Source #

Methods

from :: Value -> Rep Value x Source #

to :: Rep Value x -> Value Source #

Semigroup Value Source # 
Instance details

Defined in Plutus.V1.Ledger.Value

Monoid Value Source # 
Instance details

Defined in Plutus.V1.Ledger.Value

NFData Value Source # 
Instance details

Defined in Plutus.V1.Ledger.Value

Methods

rnf :: Value -> () Source #

Pretty Value Source # 
Instance details

Defined in Plutus.V1.Ledger.Value

Methods

pretty :: Value -> Doc ann

prettyList :: [Value] -> Doc ann

FromData Value Source # 
Instance details

Defined in Plutus.V1.Ledger.Value

ToData Value Source # 
Instance details

Defined in Plutus.V1.Ledger.Value

UnsafeFromData Value Source # 
Instance details

Defined in Plutus.V1.Ledger.Value

Eq Value Source # 
Instance details

Defined in Plutus.V1.Ledger.Value

Methods

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

JoinSemiLattice Value Source # 
Instance details

Defined in Plutus.V1.Ledger.Value

Methods

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

MeetSemiLattice Value Source # 
Instance details

Defined in Plutus.V1.Ledger.Value

Methods

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

Group Value Source # 
Instance details

Defined in Plutus.V1.Ledger.Value

Methods

inv :: Value -> Value

Monoid Value Source # 
Instance details

Defined in Plutus.V1.Ledger.Value

Methods

mempty :: Value

AdditiveGroup Value Source # 
Instance details

Defined in Plutus.V1.Ledger.Value

Methods

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

AdditiveMonoid Value Source # 
Instance details

Defined in Plutus.V1.Ledger.Value

Methods

zero :: Value

AdditiveSemigroup Value Source # 
Instance details

Defined in Plutus.V1.Ledger.Value

Methods

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

Semigroup Value Source # 
Instance details

Defined in Plutus.V1.Ledger.Value

Methods

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

Lift DefaultUni Value Source # 
Instance details

Defined in Plutus.V1.Ledger.Value

Methods

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

Module Integer Value Source # 
Instance details

Defined in Plutus.V1.Ledger.Value

Methods

scale :: Integer -> Value -> Value #

Typeable DefaultUni Value Source # 
Instance details

Defined in Plutus.V1.Ledger.Value

Methods

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

type Rep Value Source # 
Instance details

Defined in Plutus.V1.Ledger.Value

type Rep Value = D1 ('MetaData "Value" "Plutus.V1.Ledger.Value" "plutus-ledger-api-1.0.0.1-6EvbyJiK8IAAVEtnIJDu5Z" '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.

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

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

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

Convert a value to a simple list, keeping only the non-zero amounts.