plutus-script-utils-1.2.0.0: Helper/utility functions for writing Plutus scripts.
Safe HaskellNone
LanguageHaskell2010

Plutus.Script.Utils.Value

Synopsis

Documentation

geq :: Value -> Value -> Bool #

gt :: Value -> Value -> Bool #

leq :: Value -> Value -> Bool #

lt :: Value -> Value -> Bool #

tokenName :: ByteString -> TokenName #

newtype AssetClass #

Constructors

AssetClass 

Instances

Instances details
Eq AssetClass 
Instance details

Defined in Plutus.V1.Ledger.Value

Data AssetClass 
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 
Instance details

Defined in Plutus.V1.Ledger.Value

Show AssetClass 
Instance details

Defined in Plutus.V1.Ledger.Value

Generic AssetClass 
Instance details

Defined in Plutus.V1.Ledger.Value

Associated Types

type Rep AssetClass :: Type -> Type Source #

NFData AssetClass 
Instance details

Defined in Plutus.V1.Ledger.Value

Methods

rnf :: AssetClass -> () Source #

Eq AssetClass 
Instance details

Defined in Plutus.V1.Ledger.Value

Methods

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

FromData AssetClass 
Instance details

Defined in Plutus.V1.Ledger.Value

Methods

fromBuiltinData :: BuiltinData -> Maybe AssetClass

Ord AssetClass 
Instance details

Defined in Plutus.V1.Ledger.Value

Pretty AssetClass 
Instance details

Defined in Plutus.V1.Ledger.Value

Methods

pretty :: AssetClass -> Doc ann

prettyList :: [AssetClass] -> Doc ann

ToData AssetClass 
Instance details

Defined in Plutus.V1.Ledger.Value

Methods

toBuiltinData :: AssetClass -> BuiltinData

UnsafeFromData AssetClass 
Instance details

Defined in Plutus.V1.Ledger.Value

Methods

unsafeFromBuiltinData :: BuiltinData -> AssetClass

Lift DefaultUni AssetClass 
Instance details

Defined in Plutus.V1.Ledger.Value

Methods

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

Typeable DefaultUni AssetClass 
Instance details

Defined in Plutus.V1.Ledger.Value

Methods

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

type Rep AssetClass 
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))))

newtype CurrencySymbol #

Constructors

CurrencySymbol 

Fields

Instances

Instances details
Eq CurrencySymbol 
Instance details

Defined in Plutus.V1.Ledger.Value

Data CurrencySymbol 
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 
Instance details

Defined in Plutus.V1.Ledger.Value

Show CurrencySymbol 
Instance details

Defined in Plutus.V1.Ledger.Value

IsString CurrencySymbol 
Instance details

Defined in Plutus.V1.Ledger.Value

Generic CurrencySymbol 
Instance details

Defined in Plutus.V1.Ledger.Value

Associated Types

type Rep CurrencySymbol :: Type -> Type Source #

NFData CurrencySymbol 
Instance details

Defined in Plutus.V1.Ledger.Value

Methods

rnf :: CurrencySymbol -> () Source #

Eq CurrencySymbol 
Instance details

Defined in Plutus.V1.Ledger.Value

FromData CurrencySymbol 
Instance details

Defined in Plutus.V1.Ledger.Value

Methods

fromBuiltinData :: BuiltinData -> Maybe CurrencySymbol

Ord CurrencySymbol 
Instance details

Defined in Plutus.V1.Ledger.Value

Pretty CurrencySymbol 
Instance details

Defined in Plutus.V1.Ledger.Value

Methods

pretty :: CurrencySymbol -> Doc ann

prettyList :: [CurrencySymbol] -> Doc ann

ToData CurrencySymbol 
Instance details

Defined in Plutus.V1.Ledger.Value

Methods

toBuiltinData :: CurrencySymbol -> BuiltinData

UnsafeFromData CurrencySymbol 
Instance details

Defined in Plutus.V1.Ledger.Value

Methods

unsafeFromBuiltinData :: BuiltinData -> CurrencySymbol

Lift DefaultUni CurrencySymbol 
Instance details

Defined in Plutus.V1.Ledger.Value

Methods

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

Typeable DefaultUni CurrencySymbol 
Instance details

Defined in Plutus.V1.Ledger.Value

Methods

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

type Rep CurrencySymbol 
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)))

newtype TokenName #

Constructors

TokenName 

Fields

Instances

Instances details
Eq TokenName 
Instance details

Defined in Plutus.V1.Ledger.Value

Data TokenName 
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 
Instance details

Defined in Plutus.V1.Ledger.Value

Show TokenName 
Instance details

Defined in Plutus.V1.Ledger.Value

IsString TokenName 
Instance details

Defined in Plutus.V1.Ledger.Value

Generic TokenName 
Instance details

Defined in Plutus.V1.Ledger.Value

Associated Types

type Rep TokenName :: Type -> Type Source #

NFData TokenName 
Instance details

Defined in Plutus.V1.Ledger.Value

Methods

rnf :: TokenName -> () Source #

Eq TokenName 
Instance details

Defined in Plutus.V1.Ledger.Value

Methods

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

FromData TokenName 
Instance details

Defined in Plutus.V1.Ledger.Value

Methods

fromBuiltinData :: BuiltinData -> Maybe TokenName

Ord TokenName 
Instance details

Defined in Plutus.V1.Ledger.Value

Pretty TokenName 
Instance details

Defined in Plutus.V1.Ledger.Value

Methods

pretty :: TokenName -> Doc ann

prettyList :: [TokenName] -> Doc ann

ToData TokenName 
Instance details

Defined in Plutus.V1.Ledger.Value

Methods

toBuiltinData :: TokenName -> BuiltinData

UnsafeFromData TokenName 
Instance details

Defined in Plutus.V1.Ledger.Value

Methods

unsafeFromBuiltinData :: BuiltinData -> TokenName

Lift DefaultUni TokenName 
Instance details

Defined in Plutus.V1.Ledger.Value

Methods

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

Typeable DefaultUni TokenName 
Instance details

Defined in Plutus.V1.Ledger.Value

Methods

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

type Rep TokenName 
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)))

newtype Value #

Constructors

Value 

Instances

Instances details
Eq Value 
Instance details

Defined in Plutus.V1.Ledger.Value

Methods

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

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

Data Value 
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 
Instance details

Defined in Plutus.V1.Ledger.Value

Generic Value 
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 
Instance details

Defined in Plutus.V1.Ledger.Value

Monoid Value 
Instance details

Defined in Plutus.V1.Ledger.Value

NFData Value 
Instance details

Defined in Plutus.V1.Ledger.Value

Methods

rnf :: Value -> () Source #

AdditiveGroup Value 
Instance details

Defined in Plutus.V1.Ledger.Value

Methods

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

AdditiveMonoid Value 
Instance details

Defined in Plutus.V1.Ledger.Value

Methods

zero :: Value

AdditiveSemigroup Value 
Instance details

Defined in Plutus.V1.Ledger.Value

Methods

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

Eq Value 
Instance details

Defined in Plutus.V1.Ledger.Value

Methods

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

FromData Value 
Instance details

Defined in Plutus.V1.Ledger.Value

Methods

fromBuiltinData :: BuiltinData -> Maybe Value

Group Value 
Instance details

Defined in Plutus.V1.Ledger.Value

Methods

inv :: Value -> Value

JoinSemiLattice Value 
Instance details

Defined in Plutus.V1.Ledger.Value

Methods

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

MeetSemiLattice Value 
Instance details

Defined in Plutus.V1.Ledger.Value

Methods

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

Monoid Value 
Instance details

Defined in Plutus.V1.Ledger.Value

Methods

mempty :: Value

Pretty Value 
Instance details

Defined in Plutus.V1.Ledger.Value

Methods

pretty :: Value -> Doc ann

prettyList :: [Value] -> Doc ann

Semigroup Value 
Instance details

Defined in Plutus.V1.Ledger.Value

Methods

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

ToData Value 
Instance details

Defined in Plutus.V1.Ledger.Value

Methods

toBuiltinData :: Value -> BuiltinData

UnsafeFromData Value 
Instance details

Defined in Plutus.V1.Ledger.Value

Methods

unsafeFromBuiltinData :: BuiltinData -> Value

Module Integer Value 
Instance details

Defined in Plutus.V1.Ledger.Value

Methods

scale :: Integer -> Value -> Value #

Lift DefaultUni Value 
Instance details

Defined in Plutus.V1.Ledger.Value

Methods

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

Typeable DefaultUni Value 
Instance details

Defined in Plutus.V1.Ledger.Value

Methods

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

type Rep Value 
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)))))

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

noAdaValue :: Value -> Value Source #

Value without any Ada.

adaOnlyValue :: Value -> Value Source #

Value without any non-Ada.

currencyValueOf :: Value -> CurrencySymbol -> Value Source #

Get the quantities of just the given CurrencySymbol in the Value. This is useful when implementing minting policies as they are responsible for checking all minted/burnt tokens of their own CurrencySymbol.