plutus-contract-1.2.0.0
Safe HaskellNone
LanguageHaskell2010

Wallet.Emulator.Types

Synopsis

Wallets

data Wallet Source #

A wallet identifier

Instances

Instances details
Eq Wallet Source # 
Instance details

Defined in Wallet.Emulator.Wallet

Data Wallet Source # 
Instance details

Defined in Wallet.Emulator.Wallet

Methods

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

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

toConstr :: Wallet -> Constr Source #

dataTypeOf :: Wallet -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Ord Wallet Source # 
Instance details

Defined in Wallet.Emulator.Wallet

Show Wallet Source # 
Instance details

Defined in Wallet.Emulator.Wallet

Generic Wallet Source # 
Instance details

Defined in Wallet.Emulator.Wallet

Associated Types

type Rep Wallet :: Type -> Type Source #

FromJSON Wallet Source # 
Instance details

Defined in Wallet.Emulator.Wallet

Methods

parseJSON :: Value -> Parser Wallet

parseJSONList :: Value -> Parser [Wallet]

ToJSON Wallet Source # 
Instance details

Defined in Wallet.Emulator.Wallet

Methods

toJSON :: Wallet -> Value

toEncoding :: Wallet -> Encoding

toJSONList :: [Wallet] -> Value

toEncodingList :: [Wallet] -> Encoding

ToJSONKey Wallet Source # 
Instance details

Defined in Wallet.Emulator.Wallet

Methods

toJSONKey :: ToJSONKeyFunction Wallet

toJSONKeyList :: ToJSONKeyFunction [Wallet]

Pretty Wallet Source # 
Instance details

Defined in Wallet.Emulator.Wallet

Methods

pretty :: Wallet -> Doc ann

prettyList :: [Wallet] -> Doc ann

FromHttpApiData Wallet Source # 
Instance details

Defined in Wallet.Emulator.Wallet

Methods

parseUrlPiece :: Text -> Either Text Wallet

parseHeader :: ByteString -> Either Text Wallet

parseQueryParam :: Text -> Either Text Wallet

ToHttpApiData Wallet Source # 
Instance details

Defined in Wallet.Emulator.Wallet

Methods

toUrlPiece :: Wallet -> Text

toEncodedUrlPiece :: Wallet -> Builder

toHeader :: Wallet -> ByteString

toQueryParam :: Wallet -> Text

type Rep Wallet Source # 
Instance details

Defined in Wallet.Emulator.Wallet

type Rep Wallet = D1 ('MetaData "Wallet" "Wallet.Emulator.Wallet" "plutus-contract-1.2.0.0-FH8LC9wh7UV4Nmv68NHXrC" 'False) (C1 ('MetaCons "Wallet" 'PrefixI 'True) (S1 ('MetaSel ('Just "prettyWalletName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe String)) :*: S1 ('MetaSel ('Just "getWalletId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 WalletId)))

newtype WalletId Source #

Constructors

WalletId 

Fields

Instances

Instances details
Eq WalletId Source # 
Instance details

Defined in Wallet.Emulator.Wallet

Data WalletId Source # 
Instance details

Defined in Wallet.Emulator.Wallet

Methods

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

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

toConstr :: WalletId -> Constr Source #

dataTypeOf :: WalletId -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Ord WalletId Source # 
Instance details

Defined in Wallet.Emulator.Wallet

Show WalletId Source # 
Instance details

Defined in Wallet.Emulator.Wallet

Generic WalletId Source # 
Instance details

Defined in Wallet.Emulator.Wallet

Associated Types

type Rep WalletId :: Type -> Type Source #

FromJSON WalletId Source # 
Instance details

Defined in Wallet.Emulator.Wallet

Methods

parseJSON :: Value -> Parser WalletId

parseJSONList :: Value -> Parser [WalletId]

ToJSON WalletId Source # 
Instance details

Defined in Wallet.Emulator.Wallet

Methods

toJSON :: WalletId -> Value

toEncoding :: WalletId -> Encoding

toJSONList :: [WalletId] -> Value

toEncodingList :: [WalletId] -> Encoding

ToJSONKey WalletId Source # 
Instance details

Defined in Wallet.Emulator.Wallet

Methods

toJSONKey :: ToJSONKeyFunction WalletId

toJSONKeyList :: ToJSONKeyFunction [WalletId]

FromHttpApiData WalletId Source # 
Instance details

Defined in Wallet.Emulator.Wallet

Methods

parseUrlPiece :: Text -> Either Text WalletId

parseHeader :: ByteString -> Either Text WalletId

parseQueryParam :: Text -> Either Text WalletId

ToHttpApiData WalletId Source # 
Instance details

Defined in Wallet.Emulator.Wallet

Methods

toUrlPiece :: WalletId -> Text

toEncodedUrlPiece :: WalletId -> Builder

toHeader :: WalletId -> ByteString

toQueryParam :: WalletId -> Text

type Rep WalletId Source # 
Instance details

Defined in Wallet.Emulator.Wallet

type Rep WalletId = D1 ('MetaData "WalletId" "Wallet.Emulator.Wallet" "plutus-contract-1.2.0.0-FH8LC9wh7UV4Nmv68NHXrC" 'True) (C1 ('MetaCons "WalletId" 'PrefixI 'True) (S1 ('MetaSel ('Just "unWalletId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Digest Blake2b_160))))

data XPrv #

Instances

Instances details
NFData XPrv 
Instance details

Defined in Cardano.Crypto.Wallet

Methods

rnf :: XPrv -> () Source #

ByteArrayAccess XPrv 
Instance details

Defined in Cardano.Crypto.Wallet

Methods

length :: XPrv -> Int

withByteArray :: XPrv -> (Ptr p -> IO a) -> IO a

copyByteArrayToPtr :: XPrv -> Ptr p -> IO ()

data XPub #

Instances

Instances details
Eq XPub 
Instance details

Defined in Cardano.Crypto.Wallet

Methods

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

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

Ord XPub 
Instance details

Defined in Cardano.Crypto.Wallet

Show XPub 
Instance details

Defined in Cardano.Crypto.Wallet

Generic XPub 
Instance details

Defined in Cardano.Crypto.Wallet

Associated Types

type Rep XPub :: Type -> Type Source #

Methods

from :: XPub -> Rep XPub x Source #

to :: Rep XPub x -> XPub Source #

NFData XPub 
Instance details

Defined in Cardano.Crypto.Wallet

Methods

rnf :: XPub -> () Source #

Hashable XPub 
Instance details

Defined in Cardano.Crypto.Wallet

Methods

hashWithSalt :: Int -> XPub -> Int

hash :: XPub -> Int

type Rep XPub 
Instance details

Defined in Cardano.Crypto.Wallet

type Rep XPub = D1 ('MetaData "XPub" "Cardano.Crypto.Wallet" "cardano-crypto-1.1.1-AR10YQhE07qCYnMgL8MnSo" 'False) (C1 ('MetaCons "XPub" 'PrefixI 'True) (S1 ('MetaSel ('Just "xpubPublicKey") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 ByteString) :*: S1 ('MetaSel ('Just "xpubChaincode") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 ChainCode)))

mockWalletAddress :: Wallet -> CardanoAddress Source #

Get the cardano address of a mock wallet. (Fails if the wallet is not a mock wallet).

mockWalletPaymentPubKey :: Wallet -> PaymentPubKey Source #

The public key of a mock wallet. (Fails if the wallet is not a mock wallet).

mockWalletPaymentPubKeyHash :: Wallet -> PaymentPubKeyHash Source #

The payment public key hash of a mock wallet. (Fails if the wallet is not a mock wallet).

newtype WalletNumber #

Constructors

WalletNumber 

Fields

Instances

Instances details
Enum WalletNumber 
Instance details

Defined in Ledger.CardanoWallet

Eq WalletNumber 
Instance details

Defined in Ledger.CardanoWallet

Integral WalletNumber 
Instance details

Defined in Ledger.CardanoWallet

Num WalletNumber 
Instance details

Defined in Ledger.CardanoWallet

Ord WalletNumber 
Instance details

Defined in Ledger.CardanoWallet

Real WalletNumber 
Instance details

Defined in Ledger.CardanoWallet

Show WalletNumber 
Instance details

Defined in Ledger.CardanoWallet

Generic WalletNumber 
Instance details

Defined in Ledger.CardanoWallet

Associated Types

type Rep WalletNumber :: Type -> Type Source #

FromJSON WalletNumber 
Instance details

Defined in Ledger.CardanoWallet

Methods

parseJSON :: Value -> Parser WalletNumber

parseJSONList :: Value -> Parser [WalletNumber]

ToJSON WalletNumber 
Instance details

Defined in Ledger.CardanoWallet

Methods

toJSON :: WalletNumber -> Value

toEncoding :: WalletNumber -> Encoding

toJSONList :: [WalletNumber] -> Value

toEncodingList :: [WalletNumber] -> Encoding

FromHttpApiData WalletNumber 
Instance details

Defined in Ledger.CardanoWallet

Methods

parseUrlPiece :: Text -> Either Text WalletNumber

parseHeader :: ByteString -> Either Text WalletNumber

parseQueryParam :: Text -> Either Text WalletNumber

ToHttpApiData WalletNumber 
Instance details

Defined in Ledger.CardanoWallet

Methods

toUrlPiece :: WalletNumber -> Text

toEncodedUrlPiece :: WalletNumber -> Builder

toHeader :: WalletNumber -> ByteString

toQueryParam :: WalletNumber -> Text

type Rep WalletNumber 
Instance details

Defined in Ledger.CardanoWallet

type Rep WalletNumber = D1 ('MetaData "WalletNumber" "Ledger.CardanoWallet" "plutus-ledger-1.2.0.0-8dOSOspdVv7Hd909lHBnfn" 'True) (C1 ('MetaCons "WalletNumber" 'PrefixI 'True) (S1 ('MetaSel ('Just "getWallet") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Integer)))

data MockWallet #

Constructors

MockWallet 

Fields

Instances

Instances details
Show MockWallet 
Instance details

Defined in Ledger.CardanoWallet

type TxPool = [CardanoTx] #

Emulator

type EmulatorEffs = '[MultiAgentEffect, ChainEffect, ChainControlEffect] Source #

newtype AssertionError Source #

An error emitted when an Assertion fails.

Constructors

GenericAssertion 

Fields

Instances

Instances details
Eq AssertionError Source # 
Instance details

Defined in Plutus.Contract.Error

Show AssertionError Source # 
Instance details

Defined in Plutus.Contract.Error

Generic AssertionError Source # 
Instance details

Defined in Plutus.Contract.Error

Associated Types

type Rep AssertionError :: Type -> Type Source #

FromJSON AssertionError Source # 
Instance details

Defined in Plutus.Contract.Error

Methods

parseJSON :: Value -> Parser AssertionError

parseJSONList :: Value -> Parser [AssertionError]

ToJSON AssertionError Source # 
Instance details

Defined in Plutus.Contract.Error

Methods

toJSON :: AssertionError -> Value

toEncoding :: AssertionError -> Encoding

toJSONList :: [AssertionError] -> Value

toEncodingList :: [AssertionError] -> Encoding

Pretty AssertionError Source # 
Instance details

Defined in Plutus.Contract.Error

Methods

pretty :: AssertionError -> Doc ann

prettyList :: [AssertionError] -> Doc ann

AsAssertionError AssertionError Source # 
Instance details

Defined in Plutus.Contract.Error

type Rep AssertionError Source # 
Instance details

Defined in Plutus.Contract.Error

type Rep AssertionError = D1 ('MetaData "AssertionError" "Plutus.Contract.Error" "plutus-contract-1.2.0.0-FH8LC9wh7UV4Nmv68NHXrC" 'True) (C1 ('MetaCons "GenericAssertion" 'PrefixI 'True) (S1 ('MetaSel ('Just "unAssertionError") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)))

class AsAssertionError r where Source #

Minimal complete definition

_AssertionError

Methods

_AssertionError :: Prism' r AssertionError Source #

_GenericAssertion :: Prism' r Text Source #

Instances

Instances details
AsAssertionError Text Source #

This lets people use Text as their error type.

Instance details

Defined in Plutus.Contract.Error

Methods

_AssertionError :: Prism' Text AssertionError Source #

_GenericAssertion :: Prism' Text Text Source #

AsAssertionError AssertionError Source # 
Instance details

Defined in Plutus.Contract.Error

AsAssertionError (TraceError e) Source # 
Instance details

Defined in Plutus.Contract.Trace

data EmulatorEvent' Source #

Events produced by the blockchain emulator.

Instances

Instances details
Eq EmulatorEvent' Source # 
Instance details

Defined in Wallet.Emulator.MultiAgent

Show EmulatorEvent' Source # 
Instance details

Defined in Wallet.Emulator.MultiAgent

Generic EmulatorEvent' Source # 
Instance details

Defined in Wallet.Emulator.MultiAgent

Associated Types

type Rep EmulatorEvent' :: Type -> Type Source #

FromJSON EmulatorEvent' Source # 
Instance details

Defined in Wallet.Emulator.MultiAgent

Methods

parseJSON :: Value -> Parser EmulatorEvent'

parseJSONList :: Value -> Parser [EmulatorEvent']

ToJSON EmulatorEvent' Source # 
Instance details

Defined in Wallet.Emulator.MultiAgent

Methods

toJSON :: EmulatorEvent' -> Value

toEncoding :: EmulatorEvent' -> Encoding

toJSONList :: [EmulatorEvent'] -> Value

toEncodingList :: [EmulatorEvent'] -> Encoding

Pretty EmulatorEvent' Source # 
Instance details

Defined in Wallet.Emulator.MultiAgent

Methods

pretty :: EmulatorEvent' -> Doc ann

prettyList :: [EmulatorEvent'] -> Doc ann

type Rep EmulatorEvent' Source # 
Instance details

Defined in Wallet.Emulator.MultiAgent

type Rep EmulatorEvent' = D1 ('MetaData "EmulatorEvent'" "Wallet.Emulator.MultiAgent" "plutus-contract-1.2.0.0-FH8LC9wh7UV4Nmv68NHXrC" 'False) ((C1 ('MetaCons "ChainEvent" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ChainEvent)) :+: (C1 ('MetaCons "ClientEvent" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Wallet) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 NodeClientEvent)) :+: C1 ('MetaCons "WalletEvent" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Wallet) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 WalletEvent)))) :+: ((C1 ('MetaCons "ChainIndexEvent" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Wallet) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ChainIndexLog)) :+: C1 ('MetaCons "SchedulerEvent" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SchedulerLog))) :+: (C1 ('MetaCons "InstanceEvent" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ContractInstanceLog)) :+: C1 ('MetaCons "UserThreadEvent" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 UserThreadMsg)))))

data EmulatorTimeEvent e Source #

An event with a timestamp measured in emulator time (currently: Slot)

Constructors

EmulatorTimeEvent 

Instances

Instances details
Functor EmulatorTimeEvent Source # 
Instance details

Defined in Wallet.Emulator.MultiAgent

Foldable EmulatorTimeEvent Source # 
Instance details

Defined in Wallet.Emulator.MultiAgent

Methods

fold :: Monoid m => EmulatorTimeEvent m -> m Source #

foldMap :: Monoid m => (a -> m) -> EmulatorTimeEvent a -> m Source #

foldMap' :: Monoid m => (a -> m) -> EmulatorTimeEvent a -> m Source #

foldr :: (a -> b -> b) -> b -> EmulatorTimeEvent a -> b Source #

foldr' :: (a -> b -> b) -> b -> EmulatorTimeEvent a -> b Source #

foldl :: (b -> a -> b) -> b -> EmulatorTimeEvent a -> b Source #

foldl' :: (b -> a -> b) -> b -> EmulatorTimeEvent a -> b Source #

foldr1 :: (a -> a -> a) -> EmulatorTimeEvent a -> a Source #

foldl1 :: (a -> a -> a) -> EmulatorTimeEvent a -> a Source #

toList :: EmulatorTimeEvent a -> [a] Source #

null :: EmulatorTimeEvent a -> Bool Source #

length :: EmulatorTimeEvent a -> Int Source #

elem :: Eq a => a -> EmulatorTimeEvent a -> Bool Source #

maximum :: Ord a => EmulatorTimeEvent a -> a Source #

minimum :: Ord a => EmulatorTimeEvent a -> a Source #

sum :: Num a => EmulatorTimeEvent a -> a Source #

product :: Num a => EmulatorTimeEvent a -> a Source #

Traversable EmulatorTimeEvent Source # 
Instance details

Defined in Wallet.Emulator.MultiAgent

Eq e => Eq (EmulatorTimeEvent e) Source # 
Instance details

Defined in Wallet.Emulator.MultiAgent

Show e => Show (EmulatorTimeEvent e) Source # 
Instance details

Defined in Wallet.Emulator.MultiAgent

Generic (EmulatorTimeEvent e) Source # 
Instance details

Defined in Wallet.Emulator.MultiAgent

Associated Types

type Rep (EmulatorTimeEvent e) :: Type -> Type Source #

FromJSON e => FromJSON (EmulatorTimeEvent e) Source # 
Instance details

Defined in Wallet.Emulator.MultiAgent

Methods

parseJSON :: Value -> Parser (EmulatorTimeEvent e)

parseJSONList :: Value -> Parser [EmulatorTimeEvent e]

ToJSON e => ToJSON (EmulatorTimeEvent e) Source # 
Instance details

Defined in Wallet.Emulator.MultiAgent

Methods

toJSON :: EmulatorTimeEvent e -> Value

toEncoding :: EmulatorTimeEvent e -> Encoding

toJSONList :: [EmulatorTimeEvent e] -> Value

toEncodingList :: [EmulatorTimeEvent e] -> Encoding

Pretty e => Pretty (EmulatorTimeEvent e) Source # 
Instance details

Defined in Wallet.Emulator.MultiAgent

Methods

pretty :: EmulatorTimeEvent e -> Doc ann

prettyList :: [EmulatorTimeEvent e] -> Doc ann

type Rep (EmulatorTimeEvent e) Source # 
Instance details

Defined in Wallet.Emulator.MultiAgent

type Rep (EmulatorTimeEvent e) = D1 ('MetaData "EmulatorTimeEvent" "Wallet.Emulator.MultiAgent" "plutus-contract-1.2.0.0-FH8LC9wh7UV4Nmv68NHXrC" 'False) (C1 ('MetaCons "EmulatorTimeEvent" 'PrefixI 'True) (S1 ('MetaSel ('Just "_eteEmulatorTime") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Slot) :*: S1 ('MetaSel ('Just "_eteEvent") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 e)))

Wallet state

data WalletState Source #

The state used by the mock wallet environment.

Constructors

WalletState 

Fields

Instances

Instances details
Show WalletState Source # 
Instance details

Defined in Wallet.Emulator.Wallet

emptyWalletState :: Wallet -> Maybe WalletState Source #

Empty wallet state for an emulator Wallet. Returns Nothing if the wallet is not known in the emulator.

ownPaymentPrivateKey :: WalletState -> PaymentPrivateKey Source #

ownAddress :: WalletState -> CardanoAddress Source #

Get the user's own payment public-key address.

Traces

walletAction :: Member MultiAgentEffect effs => Wallet -> Eff EmulatedWalletEffects r -> Eff effs r Source #

Run an action in the context of a wallet (ie. agent)

Emulator internals

data EmulatorState Source #

The state of the emulator itself.

Constructors

EmulatorState 

Fields

Instances

Instances details
Show EmulatorState Source # 
Instance details

Defined in Wallet.Emulator.MultiAgent

emulatorState :: Blockchain -> EmulatorState Source #

Initialise the emulator state with a blockchain.

emulatorStatePool :: TxPool -> EmulatorState Source #

Initialise the emulator state with a pool of pending transactions.

emulatorStateInitialDist :: Params -> Map PaymentPubKeyHash Value -> Either ToCardanoError EmulatorState Source #

Initialise the emulator state with a single pending transaction that creates the initial distribution of funds to public key addresses.

txPool :: Lens' ChainState TxPool #

index :: Lens' ChainState UtxoIndex #

chainState :: Lens' EmulatorState ChainState Source #

chainCurrentSlot :: Lens' ChainState Slot #

processEmulated :: forall effs. (Member (Error WalletAPIError) effs, Member (Error ChainIndexError) effs, Member (State EmulatorState) effs, Member (LogMsg EmulatorEvent') effs) => Params -> Eff (MultiAgentEffect ': (MultiAgentControlEffect ': (ChainEffect ': (ChainControlEffect ': effs)))) ~> Eff effs Source #

fundsDistribution :: EmulatorState -> Map Wallet Value Source #

Get a map with the total value of each wallet's "own funds".

emLog :: EmulatorState -> [LogMessage EmulatorEvent] Source #

Get the emulator log.