Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- data Wallet = Wallet {}
- newtype WalletId = WalletId {
- unWalletId :: Digest Blake2b_160
- data XPrv
- data XPub
- mockWalletAddress :: Wallet -> CardanoAddress
- mockWalletPaymentPubKey :: Wallet -> PaymentPubKey
- mockWalletPaymentPubKeyHash :: Wallet -> PaymentPubKeyHash
- knownWallets :: [Wallet]
- knownWallet :: Integer -> Wallet
- newtype WalletNumber = WalletNumber {}
- toWalletNumber :: MockWallet -> WalletNumber
- fromWalletNumber :: WalletNumber -> Wallet
- data MockWallet = MockWallet {
- mwWalletId :: Digest Blake2b_160
- mwPaymentKey :: MockPrivateKey
- mwStakeKey :: Maybe MockPrivateKey
- mwPrintAs :: Maybe String
- type TxPool = [CardanoTx]
- type EmulatorEffs = '[MultiAgentEffect, ChainEffect, ChainControlEffect]
- newtype AssertionError = GenericAssertion {
- unAssertionError :: Text
- class AsAssertionError r where
- _AssertionError :: Prism' r AssertionError
- _GenericAssertion :: Prism' r Text
- data ChainClientNotification
- = BlockValidated Block
- | SlotChanged Slot
- type EmulatorEvent = EmulatorTimeEvent EmulatorEvent'
- data EmulatorEvent'
- data EmulatorTimeEvent e = EmulatorTimeEvent {
- _eteEmulatorTime :: Slot
- _eteEvent :: e
- data WalletState = WalletState {
- _mockWallet :: MockWallet
- _nodeClient :: NodeClientState
- _chainIndexEmulatorState :: ChainIndexEmulatorState
- _signingProcess :: Maybe SigningProcess
- emptyWalletState :: Wallet -> Maybe WalletState
- ownPaymentPrivateKey :: WalletState -> PaymentPrivateKey
- ownAddress :: WalletState -> CardanoAddress
- walletAction :: Member MultiAgentEffect effs => Wallet -> Eff EmulatedWalletEffects r -> Eff effs r
- data EmulatorState = EmulatorState {
- _chainState :: ChainState
- _walletStates :: Map Wallet WalletState
- _emulatorLog :: [LogMessage EmulatorEvent]
- emptyEmulatorState :: EmulatorState
- emulatorState :: Blockchain -> EmulatorState
- emulatorStatePool :: TxPool -> EmulatorState
- emulatorStateInitialDist :: Params -> Map PaymentPubKeyHash Value -> Either ToCardanoError EmulatorState
- txPool :: Lens' ChainState TxPool
- walletStates :: Lens' EmulatorState (Map Wallet WalletState)
- index :: Lens' ChainState UtxoIndex
- chainState :: Lens' EmulatorState ChainState
- 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
- fundsDistribution :: EmulatorState -> Map Wallet Value
- emLog :: EmulatorState -> [LogMessage EmulatorEvent]
Wallets
A wallet identifier
Instances
Eq Wallet Source # | |
Data Wallet Source # | |
Defined in Wallet.Emulator.Wallet 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 # | |
Defined in Wallet.Emulator.Wallet | |
Show Wallet Source # | |
Generic Wallet Source # | |
FromJSON Wallet Source # | |
Defined in Wallet.Emulator.Wallet parseJSON :: Value -> Parser Wallet parseJSONList :: Value -> Parser [Wallet] | |
ToJSON Wallet Source # | |
Defined in Wallet.Emulator.Wallet toEncoding :: Wallet -> Encoding toJSONList :: [Wallet] -> Value toEncodingList :: [Wallet] -> Encoding | |
ToJSONKey Wallet Source # | |
Defined in Wallet.Emulator.Wallet toJSONKey :: ToJSONKeyFunction Wallet toJSONKeyList :: ToJSONKeyFunction [Wallet] | |
Pretty Wallet Source # | |
Defined in Wallet.Emulator.Wallet prettyList :: [Wallet] -> Doc ann | |
FromHttpApiData Wallet Source # | |
Defined in Wallet.Emulator.Wallet parseUrlPiece :: Text -> Either Text Wallet parseHeader :: ByteString -> Either Text Wallet parseQueryParam :: Text -> Either Text Wallet | |
ToHttpApiData Wallet Source # | |
Defined in Wallet.Emulator.Wallet toUrlPiece :: Wallet -> Text toEncodedUrlPiece :: Wallet -> Builder toHeader :: Wallet -> ByteString toQueryParam :: Wallet -> Text | |
type Rep Wallet Source # | |
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))) |
WalletId | |
|
Instances
Eq WalletId Source # | |
Data WalletId Source # | |
Defined in Wallet.Emulator.Wallet 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 # | |
Defined in Wallet.Emulator.Wallet | |
Show WalletId Source # | |
Generic WalletId Source # | |
FromJSON WalletId Source # | |
Defined in Wallet.Emulator.Wallet parseJSON :: Value -> Parser WalletId parseJSONList :: Value -> Parser [WalletId] | |
ToJSON WalletId Source # | |
Defined in Wallet.Emulator.Wallet toEncoding :: WalletId -> Encoding toJSONList :: [WalletId] -> Value toEncodingList :: [WalletId] -> Encoding | |
ToJSONKey WalletId Source # | |
Defined in Wallet.Emulator.Wallet toJSONKey :: ToJSONKeyFunction WalletId toJSONKeyList :: ToJSONKeyFunction [WalletId] | |
FromHttpApiData WalletId Source # | |
Defined in Wallet.Emulator.Wallet parseUrlPiece :: Text -> Either Text WalletId parseHeader :: ByteString -> Either Text WalletId parseQueryParam :: Text -> Either Text WalletId | |
ToHttpApiData WalletId Source # | |
Defined in Wallet.Emulator.Wallet toUrlPiece :: WalletId -> Text toEncodedUrlPiece :: WalletId -> Builder toHeader :: WalletId -> ByteString toQueryParam :: WalletId -> Text | |
type Rep WalletId Source # | |
Defined in Wallet.Emulator.Wallet |
Instances
Eq XPub | |
Ord XPub | |
Show XPub | |
Generic XPub | |
NFData XPub | |
Defined in Cardano.Crypto.Wallet | |
Hashable XPub | |
Defined in Cardano.Crypto.Wallet | |
type Rep XPub | |
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).
knownWallets :: [Wallet] Source #
knownWallet :: Integer -> Wallet Source #
newtype WalletNumber #
Instances
data MockWallet #
MockWallet | |
|
Instances
Show MockWallet | |
Defined in Ledger.CardanoWallet |
Emulator
type EmulatorEffs = '[MultiAgentEffect, ChainEffect, ChainControlEffect] Source #
newtype AssertionError Source #
An error emitted when an Assertion
fails.
GenericAssertion | |
|
Instances
class AsAssertionError r where Source #
_AssertionError :: Prism' r AssertionError Source #
_GenericAssertion :: Prism' r Text Source #
Instances
AsAssertionError Text Source # | This lets people use |
Defined in Plutus.Contract.Error _AssertionError :: Prism' Text AssertionError Source # _GenericAssertion :: Prism' Text Text Source # | |
AsAssertionError AssertionError Source # | |
Defined in Plutus.Contract.Error _AssertionError :: Prism' AssertionError AssertionError Source # _GenericAssertion :: Prism' AssertionError Text Source # | |
AsAssertionError (TraceError e) Source # | |
Defined in Plutus.Contract.Trace _AssertionError :: Prism' (TraceError e) AssertionError Source # _GenericAssertion :: Prism' (TraceError e) Text Source # |
data ChainClientNotification Source #
BlockValidated Block | |
SlotChanged Slot |
Instances
Eq ChainClientNotification Source # | |
Defined in Wallet.Emulator.NodeClient | |
Show ChainClientNotification Source # | |
Defined in Wallet.Emulator.NodeClient |
data EmulatorEvent' Source #
Events produced by the blockchain emulator.
Instances
data EmulatorTimeEvent e Source #
An event with a timestamp measured in emulator time
(currently: Slot
)
Instances
Wallet state
data WalletState Source #
The state used by the mock wallet environment.
WalletState | |
|
Instances
Show WalletState Source # | |
Defined in Wallet.Emulator.Wallet |
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.
EmulatorState | |
|
Instances
Show EmulatorState Source # | |
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.
walletStates :: Lens' EmulatorState (Map Wallet WalletState) Source #
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.