atlas-cardano-0.4.0: Application backend for Plutus smart contracts on Cardano
Copyright(c) 2023 GYELD GMBH
LicenseApache 2.0
Maintainer[email protected]
Stabilitydevelop
Safe HaskellSafe-Inferred
LanguageGHC2021

GeniusYield.TxBuilder.Class

Description

 
Synopsis

Documentation

class Monad m ⇒ MonadError e (m ∷ TypeType) | m → e where Source #

The strategy of combining computations that can throw exceptions by bypassing bound functions from the point an exception is thrown to the point that it is handled.

Is parameterized over the type of error information and the monad type constructor. It is common to use Either String as the monad type constructor for an error monad in which error descriptions take the form of strings. In that case and many other common cases the resulting monad is already defined as an instance of the MonadError class. You can also define your own error type and/or use a monad type constructor other than Either String or Either IOError. In these cases you will have to explicitly define instances of the MonadError class. (If you are using the deprecated Control.Monad.Error or Control.Monad.Trans.Error, you may also have to define an Error instance.)

Methods

throwError ∷ e → m a Source #

Is used within a monadic computation to begin exception processing.

catchError ∷ m a → (e → m a) → m a Source #

A handler function to handle previous errors and return to normal execution. A common idiom is:

do { action1; action2; action3 } `catchError` handler

where the action functions can call throwError. Note that handler and the do-block must have the same return type.

Instances

Instances details
MonadError GYTxMonadException GYTxMonadNode # 
Instance details

Defined in GeniusYield.TxBuilder.Node

MonadError GYTxMonadException GYTxQueryMonadNode # 
Instance details

Defined in GeniusYield.TxBuilder.NodeQuery

MonadError GYTxMonadException GYTxMonadRun # 
Instance details

Defined in GeniusYield.TxBuilder.Run

MonadError IOException IO 
Instance details

Defined in Control.Monad.Error.Class

Methods

throwErrorIOExceptionIO a Source #

catchErrorIO a → (IOExceptionIO a) → IO a Source #

MonadError FailReason Validate 
Instance details

Defined in Plutus.Model.Mock

Methods

throwErrorFailReason → Validate a Source #

catchError ∷ Validate a → (FailReason → Validate a) → Validate a Source #

MonadError ClientError ClientM 
Instance details

Defined in Servant.Client.Internal.HttpClient

MonadError () EvaluationResult 
Instance details

Defined in PlutusCore.Evaluation.Result

MonadError () Maybe

Since: mtl-2.2.2

Instance details

Defined in Control.Monad.Error.Class

Methods

throwError ∷ () → Maybe a Source #

catchErrorMaybe a → (() → Maybe a) → Maybe a Source #

Monad m ⇒ MonadError BlockfrostError (BlockfrostClientT m) 
Instance details

Defined in Blockfrost.Client.Types

MonadError e (Either e) 
Instance details

Defined in Control.Monad.Error.Class

Methods

throwError ∷ e → Either e a Source #

catchErrorEither e a → (e → Either e a) → Either e a Source #

(Functor m, MonadError e m) ⇒ MonadError e (Free m) 
Instance details

Defined in Control.Monad.Free

Methods

throwError ∷ e → Free m a Source #

catchErrorFree m a → (e → Free m a) → Free m a Source #

MonadError e m ⇒ MonadError e (GenT m) 
Instance details

Defined in Hedgehog.Internal.Gen

Methods

throwError ∷ e → GenT m a Source #

catchErrorGenT m a → (e → GenT m a) → GenT m a Source #

MonadError e m ⇒ MonadError e (PropertyT m) 
Instance details

Defined in Hedgehog.Internal.Property

Methods

throwError ∷ e → PropertyT m a Source #

catchErrorPropertyT m a → (e → PropertyT m a) → PropertyT m a Source #

MonadError e m ⇒ MonadError e (TestT m) 
Instance details

Defined in Hedgehog.Internal.Property

Methods

throwError ∷ e → TestT m a Source #

catchErrorTestT m a → (e → TestT m a) → TestT m a Source #

MonadError e m ⇒ MonadError e (TreeT m) 
Instance details

Defined in Hedgehog.Internal.Tree

Methods

throwError ∷ e → TreeT m a Source #

catchErrorTreeT m a → (e → TreeT m a) → TreeT m a Source #

MonadError e m ⇒ MonadError e (KatipContextT m) 
Instance details

Defined in Katip.Monadic

Methods

throwError ∷ e → KatipContextT m a Source #

catchErrorKatipContextT m a → (e → KatipContextT m a) → KatipContextT m a Source #

MonadError e m ⇒ MonadError e (NoLoggingT m) 
Instance details

Defined in Katip.Monadic

Methods

throwError ∷ e → NoLoggingT m a Source #

catchErrorNoLoggingT m a → (e → NoLoggingT m a) → NoLoggingT m a Source #

MonadError e m ⇒ MonadError e (ListT m) 
Instance details

Defined in ListT

Methods

throwError ∷ e → ListT m a Source #

catchErrorListT m a → (e → ListT m a) → ListT m a Source #

MonadError e m ⇒ MonadError e (ResourceT m) 
Instance details

Defined in Control.Monad.Trans.Resource.Internal

Methods

throwError ∷ e → ResourceT m a Source #

catchErrorResourceT m a → (e → ResourceT m a) → ResourceT m a Source #

MonadError e m ⇒ MonadError e (ListT m) 
Instance details

Defined in Control.Monad.Error.Class

Methods

throwError ∷ e → ListT m a Source #

catchErrorListT m a → (e → ListT m a) → ListT m a Source #

MonadError e m ⇒ MonadError e (MaybeT m) 
Instance details

Defined in Control.Monad.Error.Class

Methods

throwError ∷ e → MaybeT m a Source #

catchErrorMaybeT m a → (e → MaybeT m a) → MaybeT m a Source #

MonadError e m ⇒ MonadError e (RandT g m) 
Instance details

Defined in Control.Monad.Trans.Random.Lazy

Methods

throwError ∷ e → RandT g m a Source #

catchErrorRandT g m a → (e → RandT g m a) → RandT g m a Source #

MonadError e m ⇒ MonadError e (RandT g m) 
Instance details

Defined in Control.Monad.Trans.Random.Strict

Methods

throwError ∷ e → RandT g m a Source #

catchErrorRandT g m a → (e → RandT g m a) → RandT g m a Source #

(Functor f, MonadError e m) ⇒ MonadError e (FreeT f m) 
Instance details

Defined in Control.Monad.Trans.Free

Methods

throwError ∷ e → FreeT f m a Source #

catchErrorFreeT f m a → (e → FreeT f m a) → FreeT f m a Source #

(Monad m, Error e) ⇒ MonadError e (ErrorT e m) 
Instance details

Defined in Control.Monad.Error.Class

Methods

throwError ∷ e → ErrorT e m a Source #

catchErrorErrorT e m a → (e → ErrorT e m a) → ErrorT e m a Source #

Monad m ⇒ MonadError e (ExceptT e m)

Since: mtl-2.2

Instance details

Defined in Control.Monad.Error.Class

Methods

throwError ∷ e → ExceptT e m a Source #

catchErrorExceptT e m a → (e → ExceptT e m a) → ExceptT e m a Source #

MonadError e m ⇒ MonadError e (IdentityT m) 
Instance details

Defined in Control.Monad.Error.Class

Methods

throwError ∷ e → IdentityT m a Source #

catchErrorIdentityT m a → (e → IdentityT m a) → IdentityT m a Source #

MonadError e m ⇒ MonadError e (ReaderT r m) 
Instance details

Defined in Control.Monad.Error.Class

Methods

throwError ∷ e → ReaderT r m a Source #

catchErrorReaderT r m a → (e → ReaderT r m a) → ReaderT r m a Source #

MonadError e m ⇒ MonadError e (StateT s m) 
Instance details

Defined in Control.Monad.Error.Class

Methods

throwError ∷ e → StateT s m a Source #

catchErrorStateT s m a → (e → StateT s m a) → StateT s m a Source #

MonadError e m ⇒ MonadError e (StateT s m) 
Instance details

Defined in Control.Monad.Error.Class

Methods

throwError ∷ e → StateT s m a Source #

catchErrorStateT s m a → (e → StateT s m a) → StateT s m a Source #

(Monoid w, MonadError e m) ⇒ MonadError e (WriterT w m) 
Instance details

Defined in Control.Monad.Error.Class

Methods

throwError ∷ e → WriterT w m a Source #

catchErrorWriterT w m a → (e → WriterT w m a) → WriterT w m a Source #

(Monoid w, MonadError e m) ⇒ MonadError e (WriterT w m) 
Instance details

Defined in Control.Monad.Error.Class

Methods

throwError ∷ e → WriterT w m a Source #

catchErrorWriterT w m a → (e → WriterT w m a) → WriterT w m a Source #

MonadError e m ⇒ MonadError e (ConduitT i o m) 
Instance details

Defined in Data.Conduit.Internal.Conduit

Methods

throwError ∷ e → ConduitT i o m a Source #

catchErrorConduitT i o m a → (e → ConduitT i o m a) → ConduitT i o m a Source #

(Monoid w, MonadError e m) ⇒ MonadError e (RWST r w s m) 
Instance details

Defined in Control.Monad.Error.Class

Methods

throwError ∷ e → RWST r w s m a Source #

catchErrorRWST r w s m a → (e → RWST r w s m a) → RWST r w s m a Source #

(Monoid w, MonadError e m) ⇒ MonadError e (RWST r w s m) 
Instance details

Defined in Control.Monad.Error.Class

Methods

throwError ∷ e → RWST r w s m a Source #

catchErrorRWST r w s m a → (e → RWST r w s m a) → RWST r w s m a Source #

MonadError e m ⇒ MonadError e (Pipe l i o u m) 
Instance details

Defined in Data.Conduit.Internal.Pipe

Methods

throwError ∷ e → Pipe l i o u m a Source #

catchErrorPipe l i o u m a → (e → Pipe l i o u m a) → Pipe l i o u m a Source #

PrettyUni uni fun ⇒ MonadError (CekEvaluationException NamedDeBruijn uni fun) (CekM uni fun s) 
Instance details

Defined in UntypedPlutusCore.Evaluation.Machine.Cek.Internal

Methods

throwErrorCekEvaluationException NamedDeBruijn uni fun → CekM uni fun s a Source #

catchErrorCekM uni fun s a → (CekEvaluationException NamedDeBruijn uni fun → CekM uni fun s a) → CekM uni fun s a Source #

class Monad m ⇒ MonadRandom (m ∷ TypeType) where Source #

With a source of random number supply in hand, the MonadRandom class allows the programmer to extract random values of a variety of types.

Methods

getRandomRRandom a ⇒ (a, a) → m a Source #

Takes a range (lo,hi) and a random number generator g, and returns a computation that returns a random value uniformly distributed in the closed interval [lo,hi], together with a new generator. It is unspecified what happens if lo>hi. For continuous types there is no requirement that the values lo and hi are ever produced, but they may be, depending on the implementation and the interval.

See randomR for details.

getRandomRandom a ⇒ m a Source #

The same as getRandomR, but using a default range determined by the type:

  • For bounded types (instances of Bounded, such as Char), the range is normally the whole type.
  • For fractional types, the range is normally the semi-closed interval [0,1).
  • For Integer, the range is (arbitrarily) the range of Int.

See random for details.

getRandomRsRandom a ⇒ (a, a) → m [a] Source #

Plural variant of getRandomR, producing an infinite list of random values instead of returning a new generator.

See randomRs for details.

getRandomsRandom a ⇒ m [a] Source #

Plural variant of getRandom, producing an infinite list of random values instead of returning a new generator.

See randoms for details.

Instances

Instances details
MonadRandom GYTxMonadNode # 
Instance details

Defined in GeniusYield.TxBuilder.Node

Methods

getRandomRRandom a ⇒ (a, a) → GYTxMonadNode a Source #

getRandomRandom a ⇒ GYTxMonadNode a Source #

getRandomRsRandom a ⇒ (a, a) → GYTxMonadNode [a] Source #

getRandomsRandom a ⇒ GYTxMonadNode [a] Source #

MonadRandom GYTxMonadRun # 
Instance details

Defined in GeniusYield.TxBuilder.Run

Methods

getRandomRRandom a ⇒ (a, a) → GYTxMonadRun a Source #

getRandomRandom a ⇒ GYTxMonadRun a Source #

getRandomRsRandom a ⇒ (a, a) → GYTxMonadRun [a] Source #

getRandomsRandom a ⇒ GYTxMonadRun [a] Source #

MonadRandom NonRandom 
Instance details

Defined in Control.Monad.Random.NonRandom

Methods

getRandomRRandom a ⇒ (a, a) → NonRandom a Source #

getRandomRandom a ⇒ NonRandom a Source #

getRandomRsRandom a ⇒ (a, a) → NonRandom [a] Source #

getRandomsRandom a ⇒ NonRandom [a] Source #

MonadRandom IO 
Instance details

Defined in Control.Monad.Random.Class

Methods

getRandomRRandom a ⇒ (a, a) → IO a Source #

getRandomRandom a ⇒ IO a Source #

getRandomRsRandom a ⇒ (a, a) → IO [a] Source #

getRandomsRandom a ⇒ IO [a] Source #

MonadRandom m ⇒ MonadRandom (MaybeT m) 
Instance details

Defined in Control.Monad.Random.Class

Methods

getRandomRRandom a ⇒ (a, a) → MaybeT m a Source #

getRandomRandom a ⇒ MaybeT m a Source #

getRandomRsRandom a ⇒ (a, a) → MaybeT m [a] Source #

getRandomsRandom a ⇒ MaybeT m [a] Source #

(RandomGen g, Monad m) ⇒ MonadRandom (RandT g m) 
Instance details

Defined in Control.Monad.Trans.Random.Lazy

Methods

getRandomRRandom a ⇒ (a, a) → RandT g m a Source #

getRandomRandom a ⇒ RandT g m a Source #

getRandomRsRandom a ⇒ (a, a) → RandT g m [a] Source #

getRandomsRandom a ⇒ RandT g m [a] Source #

(RandomGen g, Monad m) ⇒ MonadRandom (RandT g m) 
Instance details

Defined in Control.Monad.Trans.Random.Strict

Methods

getRandomRRandom a ⇒ (a, a) → RandT g m a Source #

getRandomRandom a ⇒ RandT g m a Source #

getRandomRsRandom a ⇒ (a, a) → RandT g m [a] Source #

getRandomsRandom a ⇒ RandT g m [a] Source #

MonadRandom m ⇒ MonadRandom (ExceptT e m) 
Instance details

Defined in Control.Monad.Random.Class

Methods

getRandomRRandom a ⇒ (a, a) → ExceptT e m a Source #

getRandomRandom a ⇒ ExceptT e m a Source #

getRandomRsRandom a ⇒ (a, a) → ExceptT e m [a] Source #

getRandomsRandom a ⇒ ExceptT e m [a] Source #

MonadRandom m ⇒ MonadRandom (IdentityT m) 
Instance details

Defined in Control.Monad.Random.Class

Methods

getRandomRRandom a ⇒ (a, a) → IdentityT m a Source #

getRandomRandom a ⇒ IdentityT m a Source #

getRandomRsRandom a ⇒ (a, a) → IdentityT m [a] Source #

getRandomsRandom a ⇒ IdentityT m [a] Source #

MonadRandom m ⇒ MonadRandom (ReaderT r m) 
Instance details

Defined in Control.Monad.Random.Class

Methods

getRandomRRandom a ⇒ (a, a) → ReaderT r m a Source #

getRandomRandom a ⇒ ReaderT r m a Source #

getRandomRsRandom a ⇒ (a, a) → ReaderT r m [a] Source #

getRandomsRandom a ⇒ ReaderT r m [a] Source #

MonadRandom m ⇒ MonadRandom (StateT s m) 
Instance details

Defined in Control.Monad.Random.Class

Methods

getRandomRRandom a ⇒ (a, a) → StateT s m a Source #

getRandomRandom a ⇒ StateT s m a Source #

getRandomRsRandom a ⇒ (a, a) → StateT s m [a] Source #

getRandomsRandom a ⇒ StateT s m [a] Source #

MonadRandom m ⇒ MonadRandom (StateT s m) 
Instance details

Defined in Control.Monad.Random.Class

Methods

getRandomRRandom a ⇒ (a, a) → StateT s m a Source #

getRandomRandom a ⇒ StateT s m a Source #

getRandomRsRandom a ⇒ (a, a) → StateT s m [a] Source #

getRandomsRandom a ⇒ StateT s m [a] Source #

(MonadRandom m, Monoid w) ⇒ MonadRandom (WriterT w m) 
Instance details

Defined in Control.Monad.Random.Class

Methods

getRandomRRandom a ⇒ (a, a) → WriterT w m a Source #

getRandomRandom a ⇒ WriterT w m a Source #

getRandomRsRandom a ⇒ (a, a) → WriterT w m [a] Source #

getRandomsRandom a ⇒ WriterT w m [a] Source #

(MonadRandom m, Monoid w) ⇒ MonadRandom (WriterT w m) 
Instance details

Defined in Control.Monad.Random.Class

Methods

getRandomRRandom a ⇒ (a, a) → WriterT w m a Source #

getRandomRandom a ⇒ WriterT w m a Source #

getRandomRsRandom a ⇒ (a, a) → WriterT w m [a] Source #

getRandomsRandom a ⇒ WriterT w m [a] Source #

MonadRandom m ⇒ MonadRandom (ContT r m) 
Instance details

Defined in Control.Monad.Random.Class

Methods

getRandomRRandom a ⇒ (a, a) → ContT r m a Source #

getRandomRandom a ⇒ ContT r m a Source #

getRandomRsRandom a ⇒ (a, a) → ContT r m [a] Source #

getRandomsRandom a ⇒ ContT r m [a] Source #

(Monoid w, MonadRandom m) ⇒ MonadRandom (RWST r w s m) 
Instance details

Defined in Control.Monad.Random.Class

Methods

getRandomRRandom a ⇒ (a, a) → RWST r w s m a Source #

getRandomRandom a ⇒ RWST r w s m a Source #

getRandomRsRandom a ⇒ (a, a) → RWST r w s m [a] Source #

getRandomsRandom a ⇒ RWST r w s m [a] Source #

(Monoid w, MonadRandom m) ⇒ MonadRandom (RWST r w s m) 
Instance details

Defined in Control.Monad.Random.Class

Methods

getRandomRRandom a ⇒ (a, a) → RWST r w s m a Source #

getRandomRandom a ⇒ RWST r w s m a Source #

getRandomRsRandom a ⇒ (a, a) → RWST r w s m [a] Source #

getRandomsRandom a ⇒ RWST r w s m [a] Source #

class GYTxQueryMonad m ⇒ GYTxMonad m where #

Class of monads for querying monads as a user.

Methods

ownAddresses ∷ m [GYAddress] #

Get your own address(es).

availableUTxOs ∷ m GYUTxOs #

Get available UTxOs that can be operated upon.

someUTxOPlutusVersion → m GYTxOutRef #

Return some unspend transaction output translatable to the given language corresponding to the script in question.

Note: may or may not return the same value

randSeed ∷ m Int #

A seed to inject non-determinism.

class MonadError GYTxMonadException m ⇒ GYTxQueryMonad m where #

Class of monads for querying chain data.

Methods

networkId ∷ m GYNetworkId #

Get the network id

lookupDatumGYDatumHash → m (Maybe GYDatum) #

Lookup datum by its hash.

utxoAtTxOutRefGYTxOutRef → m (Maybe GYUTxO) #

Lookup GYUTxO at GYTxOutRef.

utxoAtTxOutRefWithDatumGYTxOutRef → m (Maybe (GYUTxO, Maybe GYDatum)) #

Lookup UTxO at GYTxOutRef with an attempt to resolve for datum.

utxosAtTxOutRefs ∷ [GYTxOutRef] → m GYUTxOs #

Lookup GYUTxOs at multiple GYTxOutRefs at once

utxosAtTxOutRefsWithDatums ∷ [GYTxOutRef] → m [(GYUTxO, Maybe GYDatum)] #

Lookup UTxOs at zero or more GYTxOutRef with their datums. This has a default implementation using utxosAtTxOutRefs and lookupDatum but should be overridden for efficiency if provider provides suitable option.

utxosAtAddressGYAddressMaybe GYAssetClass → m GYUTxOs #

Lookup GYUTxOs at GYAddress.

utxosAtAddressWithDatumsGYAddressMaybe GYAssetClass → m [(GYUTxO, Maybe GYDatum)] #

Lookup GYUTxO at given GYAddress with their datums. This has a default implementation using utxosAtAddress and lookupDatum but should be overridden for efficiency if provider provides suitable option.

utxosAtAddresses ∷ [GYAddress] → m GYUTxOs #

Lookup GYUTxOs at zero or more GYAddress.

utxosAtAddressesWithDatums ∷ [GYAddress] → m [(GYUTxO, Maybe GYDatum)] #

Lookup UTxOs at zero or more GYAddress with their datums. This has a default implementation using utxosAtAddresses and lookupDatum but should be overridden for efficiency if provider provides suitable option.

utxoRefsAtAddressGYAddress → m [GYTxOutRef] #

Lookup the `[GYTxOutRef]`s at a GYAddress

utxosAtPaymentCredentialGYPaymentCredential → m GYUTxOs #

utxosAtPaymentCredentialWithDatumsGYPaymentCredential → m [(GYUTxO, Maybe GYDatum)] #

Lookup UTxOs at given GYPaymentCredential with their datums. This has a default implementation using utxosAtPaymentCredential and lookupDatum but should be overridden for efficiency if provider provides suitable option.

slotConfig ∷ m GYSlotConfig #

Obtain the slot config for the network.

Implementations using era history to create slot config may raise GYEraSummariesToSlotConfigError.

slotOfCurrentBlock ∷ m GYSlot #

This is expected to give the slot of the latest block. We say "expected" as we cache the result for 5 seconds, that is to say, suppose slot was cached at time T, now if query for current block's slot comes within time duration (T, T + 5), then we'll return the cached slot but if say, query happened at time (T + 5, T + 21) where 21 was taken as an arbitrary number above 5, then we'll query the chain tip and get the slot of the latest block seen by the provider and then store it in our cache, thus new cached value would be served for requests coming within time interval of (T + 21, T + 26).

NOTE: It's behaviour is slightly different, solely for our plutus simple model provider where it actually returns the value of the currentSlot variable maintained inside plutus simple model library.

logMsgHasCallStackGYLogNamespaceGYLogSeverityString → m () #

Log a message with specified namespace and severity.

Instances

Instances details
GYTxQueryMonad GYTxMonadNode # 
Instance details

Defined in GeniusYield.TxBuilder.Node

GYTxQueryMonad GYTxQueryMonadNode # 
Instance details

Defined in GeniusYield.TxBuilder.NodeQuery

GYTxQueryMonad GYTxMonadRun # 
Instance details

Defined in GeniusYield.TxBuilder.Run

GYTxQueryMonad m ⇒ GYTxQueryMonad (RandT g m) # 
Instance details

Defined in GeniusYield.TxBuilder.Class

GYTxQueryMonad m ⇒ GYTxQueryMonad (ExceptT GYTxMonadException m) # 
Instance details

Defined in GeniusYield.TxBuilder.Class

GYTxQueryMonad m ⇒ GYTxQueryMonad (ReaderT env m) # 
Instance details

Defined in GeniusYield.TxBuilder.Class

data GYTxSkeleton (v ∷ PlutusVersion) #

Transaction skeleton

Note: let's add fields as we need them.

The parameter v indicates the minimum version of scripts allowed as inputs.

Instances

Instances details
Monoid (GYTxSkeleton v) # 
Instance details

Defined in GeniusYield.TxBuilder.Class

Semigroup (GYTxSkeleton v) # 
Instance details

Defined in GeniusYield.TxBuilder.Class

Show (GYTxSkeleton v) # 
Instance details

Defined in GeniusYield.TxBuilder.Class

data RandT g (m ∷ TypeType) a Source #

A random transformer monad parameterized by:

  • g - The generator.
  • m - The inner monad.

The return function leaves the generator unchanged, while >>= uses the final generator of the first computation as the initial generator of the second.

Instances

Instances details
(MonadReader r m, MonadWriter w m, MonadState s m) ⇒ MonadRWS r w s (RandT g m) 
Instance details

Defined in Control.Monad.Trans.Random.Lazy

(RandomGen g, Monad m) ⇒ MonadSplit g (RandT g m) 
Instance details

Defined in Control.Monad.Trans.Random.Lazy

Methods

getSplitRandT g m g Source #

MonadError e m ⇒ MonadError e (RandT g m) 
Instance details

Defined in Control.Monad.Trans.Random.Lazy

Methods

throwError ∷ e → RandT g m a Source #

catchErrorRandT g m a → (e → RandT g m a) → RandT g m a Source #

MonadReader r m ⇒ MonadReader r (RandT g m) 
Instance details

Defined in Control.Monad.Trans.Random.Lazy

Methods

askRandT g m r Source #

local ∷ (r → r) → RandT g m a → RandT g m a Source #

reader ∷ (r → a) → RandT g m a Source #

MonadState s m ⇒ MonadState s (RandT g m) 
Instance details

Defined in Control.Monad.Trans.Random.Lazy

Methods

getRandT g m s Source #

put ∷ s → RandT g m () Source #

state ∷ (s → (a, s)) → RandT g m a Source #

MonadWriter w m ⇒ MonadWriter w (RandT g m) 
Instance details

Defined in Control.Monad.Trans.Random.Lazy

Methods

writer ∷ (a, w) → RandT g m a Source #

tell ∷ w → RandT g m () Source #

listenRandT g m a → RandT g m (a, w) Source #

passRandT g m (a, w → w) → RandT g m a Source #

MonadTrans (RandT g) 
Instance details

Defined in Control.Monad.Trans.Random.Lazy

Methods

liftMonad m ⇒ m a → RandT g m a Source #

(Monad m, RandomGen g) ⇒ RandomGenM (RandGen g) g (RandT g m)

Since: MonadRandom-0.5.3

Instance details

Defined in Control.Monad.Trans.Random.Lazy

Methods

applyRandomGenM ∷ (g → (a, g)) → RandGen g → RandT g m a Source #

(Monad m, RandomGen g) ⇒ StatefulGen (RandGen g) (RandT g m)

Since: MonadRandom-0.5.3

Instance details

Defined in Control.Monad.Trans.Random.Lazy

(Monad m, RandomGen g) ⇒ MonadInterleave (RandT g m) 
Instance details

Defined in Control.Monad.Trans.Random.Lazy

Methods

interleaveRandT g m a → RandT g m a Source #

(RandomGen g, Monad m) ⇒ MonadRandom (RandT g m) 
Instance details

Defined in Control.Monad.Trans.Random.Lazy

Methods

getRandomRRandom a ⇒ (a, a) → RandT g m a Source #

getRandomRandom a ⇒ RandT g m a Source #

getRandomRsRandom a ⇒ (a, a) → RandT g m [a] Source #

getRandomsRandom a ⇒ RandT g m [a] Source #

GYTxMonad m ⇒ GYTxMonad (RandT g m) # 
Instance details

Defined in GeniusYield.TxBuilder.Class

GYTxQueryMonad m ⇒ GYTxQueryMonad (RandT g m) # 
Instance details

Defined in GeniusYield.TxBuilder.Class

MonadFail m ⇒ MonadFail (RandT g m) 
Instance details

Defined in Control.Monad.Trans.Random.Lazy

Methods

failStringRandT g m a Source #

MonadFix m ⇒ MonadFix (RandT g m) 
Instance details

Defined in Control.Monad.Trans.Random.Lazy

Methods

mfix ∷ (a → RandT g m a) → RandT g m a Source #

MonadIO m ⇒ MonadIO (RandT g m) 
Instance details

Defined in Control.Monad.Trans.Random.Lazy

Methods

liftIOIO a → RandT g m a Source #

MonadPlus m ⇒ Alternative (RandT g m) 
Instance details

Defined in Control.Monad.Trans.Random.Lazy

Methods

emptyRandT g m a Source #

(<|>)RandT g m a → RandT g m a → RandT g m a Source #

someRandT g m a → RandT g m [a] Source #

manyRandT g m a → RandT g m [a] Source #

Monad m ⇒ Applicative (RandT g m) 
Instance details

Defined in Control.Monad.Trans.Random.Lazy

Methods

pure ∷ a → RandT g m a Source #

(<*>)RandT g m (a → b) → RandT g m a → RandT g m b Source #

liftA2 ∷ (a → b → c) → RandT g m a → RandT g m b → RandT g m c Source #

(*>)RandT g m a → RandT g m b → RandT g m b Source #

(<*)RandT g m a → RandT g m b → RandT g m a Source #

Functor m ⇒ Functor (RandT g m) 
Instance details

Defined in Control.Monad.Trans.Random.Lazy

Methods

fmap ∷ (a → b) → RandT g m a → RandT g m b Source #

(<$) ∷ a → RandT g m b → RandT g m a Source #

Monad m ⇒ Monad (RandT g m) 
Instance details

Defined in Control.Monad.Trans.Random.Lazy

Methods

(>>=)RandT g m a → (a → RandT g m b) → RandT g m b Source #

(>>)RandT g m a → RandT g m b → RandT g m b Source #

return ∷ a → RandT g m a Source #

MonadPlus m ⇒ MonadPlus (RandT g m) 
Instance details

Defined in Control.Monad.Trans.Random.Lazy

Methods

mzeroRandT g m a Source #

mplusRandT g m a → RandT g m a → RandT g m a Source #

MonadCont m ⇒ MonadCont (RandT g m) 
Instance details

Defined in Control.Monad.Trans.Random.Lazy

Methods

callCC ∷ ((a → RandT g m b) → RandT g m a) → RandT g m a Source #

PrimMonad m ⇒ PrimMonad (RandT s m) 
Instance details

Defined in Control.Monad.Trans.Random.Lazy

Associated Types

type PrimState (RandT s m) Source #

Methods

primitive ∷ (State# (PrimState (RandT s m)) → (# State# (PrimState (RandT s m)), a #)) → RandT s m a Source #

type PrimState (RandT s m) 
Instance details

Defined in Control.Monad.Trans.Random.Lazy

type PrimState (RandT s m) = PrimState m

lookupDatum'GYTxQueryMonad m ⇒ GYDatumHash → m GYDatum #

A version of lookupDatum that raises GYNoDatumForHash if the datum is not found.

utxoAtTxOutRef'GYTxQueryMonad m ⇒ GYTxOutRef → m GYUTxO #

A version of utxoAtTxOutRef that raises GYNoUtxoAtRef if the utxo is not found.

utxoAtTxOutRefWithDatum'GYTxQueryMonad m ⇒ GYTxOutRef → m (GYUTxO, Maybe GYDatum) #

A version of utxoAtTxOutRefWithDatum that raises GYNoUtxoAtRef if the utxo is not found.

someUTxOWithoutRefScriptGYTxMonad m ⇒ m GYTxOutRef #

Returns some UTxO present in wallet which doesn't have reference script.

slotToBeginTimeGYTxQueryMonad f ⇒ GYSlot → f GYTime #

Get the starting GYTime of a GYSlot in GYTxMonad.

slotToEndTimeGYTxQueryMonad f ⇒ GYSlot → f GYTime #

Get the ending GYTime of a GYSlot (inclusive) in GYTxMonad.

enclosingSlotFromTimeGYTxQueryMonad f ⇒ GYTime → f (Maybe GYSlot) #

Get the GYSlot of a GYTime in GYTxMonad.

Returns Nothing if given time is before known system start.

enclosingSlotFromTime'GYTxQueryMonad m ⇒ GYTime → m GYSlot #

Partial version of enclosingSlotFromTime.

Raises GYTimeUnderflowException if given time is before known system start.

scriptAddressGYTxQueryMonad m ⇒ GYValidator v → m GYAddress #

Calculate script's address.

scriptAddress'GYTxQueryMonad m ⇒ GYValidatorHash → m GYAddress #

Calculate script's address.

addressFromText'MonadError GYTxMonadException m ⇒ Text → m GYAddress #

Parse the bech32 representation of an address into GYAddress in GYTxMonad.

Throw GYConversionException if parsing fails.

addressFromPlutusMGYTxQueryMonad m ⇒ Address → m (Either PlutusToCardanoError GYAddress) #

Convert a Address to GYAddress in GYTxMonad.

Explicitly returns an error rather than throwing it.

addressFromPlutus'GYTxQueryMonad m ⇒ Address → m GYAddress #

Convert a Address to GYAddress in GYTxMonad.

Throw GYConversionException if conversion fails.

valueFromPlutus'MonadError GYTxMonadException m ⇒ Value → m GYValue #

Convert a Value to GYValue in GYTxMonad.

Throw GYConversionException if conversion fails.

valueFromPlutusIOValueIO GYValue #

Convert a Value to GYValue in IO.

Throw GYConversionException if conversion fails.

makeAssetClass'MonadError GYTxMonadException m ⇒ TextText → m GYAssetClass #

Create a GYAssetClass from the textual representation of currency symbol and token name in GYTxMonad.

Throw GYConversionException if conversion fails.

makeAssetClassIOTextTextIO GYAssetClass #

makeAssetClass' in the IO monad.

Throw GYConversionException if conversion fails.

advanceSlot'MonadError GYTxMonadException m ⇒ GYSlotNatural → m GYSlot #

Advance GYSlot forward in GYTxMonad. If slot value overflows, throw GYSlotOverflowException.

utxoDatumPureHushedFromData a ⇒ (GYUTxO, Maybe GYDatum) → Maybe (GYTxOutRef, (GYAddress, GYValue, a)) #

Obtain original datum representation of an UTxO.

utxoDatum' ∷ (GYTxQueryMonad m, FromData a) ⇒ GYUTxO → m (GYAddress, GYValue, a) #

Version of utxoDatum that throws GYTxMonadException.

skeletonToRefScriptsORefsGYTxSkeleton v → [GYTxOutRef] #

Given a skeleton, returns a list of reference to reference script UTxOs which are present as witness.