Copyright | © 2018-2020 IOHK |
---|---|
License | Apache-2.0 |
Safe Haskell | None |
Language | Haskell2010 |
Provides wallet layer functions that are used by API layer. Uses both Cardano.Wallet.DB and Cardano.Wallet.Network to realize its role as being intermediary between the three.
Functions of the wallet layer are often parameterized with variables following the convention below:
-
s
: A s tate used to keep track of known addresses. Typically, possible values for this parameter are described inAddressDiscovery
sub-modules. For instanceSeqState
orRnd State
. -
k
: A k ey derivation scheme intrinsically connected to the underlying discovery states
. This describes how the hierarchical structure of a wallet is defined as well as the relationship between secret keys and public addresses.
Synopsis
- data WalletLayer m s (k :: Depth -> Type -> Type ) = WalletLayer ( Tracer m WalletWorkerLog ) ( Block , NetworkParameters ) ( NetworkLayer m Block ) ( TransactionLayer k SealedTx ) ( DBLayer m s k)
- type HasDBLayer m s k = HasType ( DBLayer m s k)
- dbLayer :: forall m s k ctx. HasDBLayer m s k ctx => Lens' ctx ( DBLayer m s k)
- type HasLogger m msg = HasType ( Tracer m msg)
- logger :: forall m msg ctx. HasLogger m msg ctx => Lens' ctx ( Tracer m msg)
- type HasNetworkLayer m = HasType ( NetworkLayer m Block )
- networkLayer :: forall m ctx. HasNetworkLayer m ctx => Lens' ctx ( NetworkLayer m Block )
- type HasTransactionLayer k = HasType ( TransactionLayer k SealedTx )
- transactionLayer :: forall k ctx. HasTransactionLayer k ctx => Lens' ctx ( TransactionLayer k SealedTx )
- type HasGenesisData = HasType ( Block , NetworkParameters )
- genesisData :: forall ctx. HasGenesisData ctx => Lens' ctx ( Block , NetworkParameters )
- createWallet :: forall ctx m s k. ( MonadUnliftIO m, MonadTime m, HasGenesisData ctx, HasDBLayer m s k ctx, IsOurs s Address , IsOurs s RewardAccount ) => ctx -> WalletId -> WalletName -> s -> ExceptT ErrWalletAlreadyExists m WalletId
- createIcarusWallet :: forall ctx s k n. ( HasGenesisData ctx, HasDBLayer IO s k ctx, PaymentAddress n k, k ~ IcarusKey , s ~ SeqState n k, Typeable n) => ctx -> WalletId -> WalletName -> (k ' RootK XPrv , Passphrase "encryption") -> ExceptT ErrWalletAlreadyExists IO WalletId
- attachPrivateKeyFromPwd :: forall ctx s k. HasDBLayer IO s k ctx => ctx -> WalletId -> (k ' RootK XPrv , Passphrase "user") -> ExceptT ErrNoSuchWallet IO ()
- attachPrivateKeyFromPwdHash :: forall ctx s k. HasDBLayer IO s k ctx => ctx -> WalletId -> (k ' RootK XPrv , PassphraseHash ) -> ExceptT ErrNoSuchWallet IO ()
- getWalletUtxoSnapshot :: forall ctx s k. ( HasDBLayer IO s k ctx, HasNetworkLayer IO ctx, HasTransactionLayer k ctx) => ctx -> WalletId -> ExceptT ErrNoSuchWallet IO [( TokenBundle , Coin )]
- listUtxoStatistics :: forall ctx s k. HasDBLayer IO s k ctx => ctx -> WalletId -> ExceptT ErrListUTxOStatistics IO UTxOStatistics
- readWallet :: forall ctx s k. HasDBLayer IO s k ctx => ctx -> WalletId -> ExceptT ErrNoSuchWallet IO ( Wallet s, WalletMetadata , Set Tx )
- deleteWallet :: forall ctx s k. HasDBLayer IO s k ctx => ctx -> WalletId -> ExceptT ErrNoSuchWallet IO ()
- restoreWallet :: forall ctx s k. ( HasNetworkLayer IO ctx, HasDBLayer IO s k ctx, HasLogger IO WalletWorkerLog ctx, IsOurs s Address , IsOurs s RewardAccount , AddressBookIso s, MaybeLight s) => ctx -> WalletId -> ExceptT ErrNoSuchWallet IO ()
- updateWallet :: forall ctx s k. HasDBLayer IO s k ctx => ctx -> WalletId -> ( WalletMetadata -> WalletMetadata ) -> ExceptT ErrNoSuchWallet IO ()
- updateWalletPassphraseWithOldPassphrase :: forall ctx s k. ( HasDBLayer IO s k ctx, WalletKey k) => ctx -> WalletId -> ( Passphrase "user", Passphrase "user") -> ExceptT ErrUpdatePassphrase IO ()
- updateWalletPassphraseWithMnemonic :: forall ctx s k. HasDBLayer IO s k ctx => ctx -> WalletId -> (k ' RootK XPrv , Passphrase "user") -> ExceptT ErrUpdatePassphrase IO ()
- walletSyncProgress :: forall ctx s. HasNetworkLayer IO ctx => ctx -> Wallet s -> IO SyncProgress
- fetchRewardBalance :: forall ctx s k. HasDBLayer IO s k ctx => ctx -> WalletId -> IO Coin
- manageRewardBalance :: forall ctx s k (n :: NetworkDiscriminant ). ( HasLogger IO WalletWorkerLog ctx, HasNetworkLayer IO ctx, HasDBLayer IO s k ctx, Typeable s, Typeable n) => Proxy n -> ctx -> WalletId -> IO ()
- rollbackBlocks :: forall ctx s k. HasDBLayer IO s k ctx => ctx -> WalletId -> Slot -> ExceptT ErrNoSuchWallet IO ChainPoint
- checkWalletIntegrity :: forall ctx s k. HasDBLayer IO s k ctx => ctx -> WalletId -> GenesisParameters -> ExceptT ErrCheckWalletIntegrity IO ()
- readNextWithdrawal :: forall ctx k. ( HasTransactionLayer k ctx, HasNetworkLayer IO ctx) => ctx -> AnyCardanoEra -> Coin -> IO Coin
- readRewardAccount :: forall ctx s k (n :: NetworkDiscriminant ) shelley. ( HasDBLayer IO s k ctx, shelley ~ SeqState n ShelleyKey , Typeable n, Typeable s) => ctx -> WalletId -> ExceptT ErrReadRewardAccount IO ( RewardAccount , XPub , NonEmpty DerivationIndex )
- someRewardAccount :: ToRewardAccount k => SomeMnemonic -> ( XPrv , RewardAccount , NonEmpty DerivationIndex )
- readPolicyPublicKey :: forall ctx s k (n :: NetworkDiscriminant ) shelley. ( HasDBLayer IO s k ctx, shelley ~ SeqState n ShelleyKey , Typeable n, Typeable s) => ctx -> WalletId -> ExceptT ErrReadPolicyPublicKey IO ( XPub , NonEmpty DerivationIndex )
- writePolicyPublicKey :: forall ctx s (n :: NetworkDiscriminant ). ( HasDBLayer IO s ShelleyKey ctx, s ~ SeqState n ShelleyKey ) => ctx -> WalletId -> Passphrase "user" -> ExceptT ErrWritePolicyPublicKey IO ( ShelleyKey ' PolicyK XPub )
- queryRewardBalance :: forall ctx. HasNetworkLayer IO ctx => ctx -> RewardAccount -> ExceptT ErrFetchRewards IO Coin
- newtype ErrWalletAlreadyExists = ErrWalletAlreadyExists WalletId
- newtype ErrNoSuchWallet = ErrNoSuchWallet WalletId
- newtype ErrListUTxOStatistics = ErrListUTxOStatisticsNoSuchWallet ErrNoSuchWallet
- data ErrUpdatePassphrase
- newtype ErrFetchRewards = ErrFetchRewardsReadRewardAccount ErrReadRewardAccount
-
data
ErrCheckWalletIntegrity
- = ErrCheckWalletIntegrityNoSuchWallet ErrNoSuchWallet
- | ErrCheckIntegrityDifferentGenesis ( Hash "Genesis") ( Hash "Genesis")
- newtype ErrWalletNotResponding = ErrWalletNotResponding WalletId
- data ErrReadRewardAccount
- data ErrReadPolicyPublicKey
- data ErrWritePolicyPublicKey
- data ErrGetPolicyId
- updateCosigner :: forall ctx s k n. (s ~ SharedState n k, MkKeyFingerprint k Address , SoftDerivation k, Typeable n, WalletKey k, HasDBLayer IO s k ctx, k ~ SharedKey ) => ctx -> WalletId -> k ' AccountK XPub -> Cosigner -> CredentialType -> ExceptT ErrAddCosignerKey IO ()
- data ErrAddCosignerKey
- data ErrConstructSharedWallet
- normalizeSharedAddress :: forall n k. ( SupportsDiscovery n k, k ~ SharedKey ) => SharedState n k -> Address -> Maybe Address
- constructSharedTransaction :: forall ctx s k (n :: NetworkDiscriminant ). ( HasTransactionLayer k ctx, HasDBLayer IO s k ctx, HasNetworkLayer IO ctx, k ~ SharedKey , s ~ SharedState n k) => ctx -> WalletId -> AnyCardanoEra -> TransactionCtx -> SelectionOf TxOut -> ExceptT ErrConstructTx IO SealedTx
- createRandomAddress :: forall ctx s k n. ( HasDBLayer IO s k ctx, PaymentAddress n k, RndStateLike s, k ~ ByronKey , AddressBookIso s) => ctx -> WalletId -> Passphrase "user" -> Maybe ( Index ' Hardened ' AddressK ) -> ExceptT ErrCreateRandomAddress IO ( Address , NonEmpty DerivationIndex )
- importRandomAddresses :: forall ctx s k. ( HasDBLayer IO s k ctx, RndStateLike s, k ~ ByronKey , AddressBookIso s) => ctx -> WalletId -> [ Address ] -> ExceptT ErrImportRandomAddress IO ()
- listAddresses :: forall ctx s k. ( HasDBLayer IO s k ctx, CompareDiscovery s, KnownAddresses s) => ctx -> WalletId -> (s -> Address -> Maybe Address ) -> ExceptT ErrNoSuchWallet IO [( Address , AddressState , NonEmpty DerivationIndex )]
- normalizeDelegationAddress :: forall s k n. ( DelegationAddress n k, s ~ SeqState n k) => s -> Address -> Maybe Address
- lookupTxIns :: forall ctx s k. ( HasDBLayer IO s k ctx, IsOurs s Address ) => ctx -> WalletId -> [ TxIn ] -> ExceptT ErrDecodeTx IO [( TxIn , Maybe ( TxOut , NonEmpty DerivationIndex ))]
- lookupTxOuts :: forall ctx s k. ( HasDBLayer IO s k ctx, IsOurs s Address ) => ctx -> WalletId -> [ TxOut ] -> ExceptT ErrDecodeTx IO [( TxOut , Maybe ( NonEmpty DerivationIndex ))]
- data ErrCreateRandomAddress
- data ErrImportRandomAddress
- newtype ErrImportAddress = ErrAddrDoesNotBelong Address
- newtype ErrDecodeTx = ErrDecodeTxNoSuchWallet ErrNoSuchWallet
- getTxExpiry :: TimeInterpreter ( ExceptT PastHorizonException IO ) -> Maybe NominalDiffTime -> IO SlotNo
- data SelectAssetsParams s result = SelectAssetsParams { }
- selectAssets :: forall ctx m s k result. ( BoundedAddressLength k, HasTransactionLayer k ctx, HasLogger m WalletWorkerLog ctx, MonadRandom m) => ctx -> AnyCardanoEra -> ProtocolParameters -> SelectAssetsParams s result -> (s -> Selection -> result) -> ExceptT ErrSelectAssets m result
- readWalletUTxOIndex :: forall ctx s k. HasDBLayer IO s k ctx => ctx -> WalletId -> ExceptT ErrNoSuchWallet IO ( UTxOIndex WalletUTxO , Wallet s, Set Tx )
- assignChangeAddresses :: forall s. GenChange s => ArgGenChange s -> Selection -> s -> ( SelectionOf TxOut , s)
- assignChangeAddressesAndUpdateDb :: forall ctx s k. ( GenChange s, HasDBLayer IO s k ctx, AddressBookIso s) => ctx -> WalletId -> ArgGenChange s -> Selection -> ExceptT ErrSignPayment IO ( SelectionOf TxOut )
- assignChangeAddressesWithoutDbUpdate :: forall ctx s k. ( GenChange s, HasDBLayer IO s k ctx) => ctx -> WalletId -> ArgGenChange s -> Selection -> ExceptT ErrConstructTx IO ( SelectionOf TxOut )
- selectionToUnsignedTx :: forall s input output change withdrawal. ( IsOurs s Address , input ~ ( TxIn , TxOut , NonEmpty DerivationIndex ), output ~ TxOut , change ~ TxChange ( NonEmpty DerivationIndex ), withdrawal ~ ( RewardAccount , Coin , NonEmpty DerivationIndex )) => Withdrawal -> SelectionOf TxOut -> s -> UnsignedTx input output change withdrawal
- buildAndSignTransaction :: forall ctx s k. ( HasTransactionLayer k ctx, HasDBLayer IO s k ctx, HasNetworkLayer IO ctx, IsOwned s k) => ctx -> WalletId -> AnyCardanoEra -> ((k ' RootK XPrv , Passphrase "encryption") -> ( XPrv , Passphrase "encryption")) -> Passphrase "user" -> TransactionCtx -> SelectionOf TxOut -> ExceptT ErrSignPayment IO ( Tx , TxMeta , UTCTime , SealedTx )
- signTransaction :: forall k. ( WalletKey k, HardDerivation k, Bounded ( Index ( AddressIndexDerivationType k) ' AddressK )) => TransactionLayer k SealedTx -> AnyCardanoEra -> ( Address -> Maybe (k ' AddressK XPrv , Passphrase "encryption")) -> (k ' RootK XPrv , Passphrase "encryption") -> UTxO -> SealedTx -> SealedTx
- constructTransaction :: forall ctx s k (n :: NetworkDiscriminant ). ( HasTransactionLayer k ctx, HasDBLayer IO s k ctx, HasNetworkLayer IO ctx, Typeable s, Typeable n) => ctx -> WalletId -> AnyCardanoEra -> TransactionCtx -> SelectionOf TxOut -> ExceptT ErrConstructTx IO SealedTx
- constructTxMeta :: forall ctx s k. HasDBLayer IO s k ctx => ctx -> WalletId -> TransactionCtx -> [( TxIn , Coin )] -> [ TxOut ] -> ExceptT ErrSubmitTransaction IO TxMeta
- data ErrSelectAssets
- data ErrSignPayment
- data ErrNotASequentialWallet = ErrNotASequentialWallet
- data ErrWithdrawalNotWorth = ErrWithdrawalNotWorth
-
data
ErrConstructTx
- = ErrConstructTxWrongPayload
- | ErrConstructTxBody ErrMkTransaction
- | ErrConstructTxNoSuchWallet ErrNoSuchWallet
- | ErrConstructTxReadRewardAccount ErrReadRewardAccount
- | ErrConstructTxIncorrectTTL PastHorizonException
- | ErrConstructTxMultidelegationNotSupported
- | ErrConstructTxMultiaccountNotSupported
- | ErrConstructTxWrongMintingBurningTemplate
- | ErrConstructTxAssetNameTooLong
- | ErrConstructTxMintOrBurnAssetQuantityOutOfBounds
- | ErrConstructTxWrongValidityBounds
- | ErrConstructTxValidityIntervalNotWithinScriptTimelock
- | ErrConstructTxSharedWalletPending
- | ErrConstructTxNotImplemented String
- newtype ErrMintBurnAssets = ErrMintBurnNotImplemented Text
-
data
ErrBalanceTx
- = ErrBalanceTxUpdateError ErrUpdateSealedTx
- | ErrBalanceTxSelectAssets ErrSelectAssets
- | ErrBalanceTxMaxSizeLimitExceeded
- | ErrBalanceTxExistingCollateral
- | ErrBalanceTxExistingTotalCollateral
- | ErrBalanceTxExistingReturnCollateral
- | ErrBalanceTxConflictingNetworks
- | ErrBalanceTxAssignRedeemers ErrAssignRedeemers
- | ErrBalanceTxInternalError ErrBalanceTxInternalError
- | ErrBalanceTxZeroAdaOutput
- | ErrByronTxNotSupported
- data ErrBalanceTxInternalError
- newtype ErrUpdateSealedTx = ErrExistingKeyWitnesses Int
- data ErrCannotJoin
- data ErrCannotQuit
- data ErrSubmitTransaction
- createMigrationPlan :: forall ctx k s. ( HasDBLayer IO s k ctx, HasNetworkLayer IO ctx, HasTransactionLayer k ctx) => ctx -> AnyCardanoEra -> WalletId -> Withdrawal -> ExceptT ErrCreateMigrationPlan IO MigrationPlan
- migrationPlanToSelectionWithdrawals :: MigrationPlan -> Withdrawal -> NonEmpty Address -> Maybe ( NonEmpty ( SelectionWithoutChange , Withdrawal ))
- type SelectionWithoutChange = SelectionOf Void
- data ErrCreateMigrationPlan
- data PoolRetirementEpochInfo = PoolRetirementEpochInfo { }
- joinStakePool :: forall ctx s k. ( HasDBLayer IO s k ctx, HasNetworkLayer IO ctx, HasLogger IO WalletWorkerLog ctx) => ctx -> EpochNo -> Set PoolId -> PoolId -> PoolLifeCycleStatus -> WalletId -> ExceptT ErrStakePoolDelegation IO ( DelegationAction , Maybe Coin )
- quitStakePool :: forall ctx s k. HasDBLayer IO s k ctx => ctx -> WalletId -> Withdrawal -> ExceptT ErrStakePoolDelegation IO DelegationAction
- guardJoin :: Set PoolId -> WalletDelegation -> PoolId -> Maybe PoolRetirementEpochInfo -> Either ErrCannotJoin ()
- guardQuit :: WalletDelegation -> Withdrawal -> Coin -> Either ErrCannotQuit ()
- data ErrStakePoolDelegation
- data FeeEstimation = FeeEstimation { }
- estimateFee :: forall m. Monad m => ExceptT ErrSelectAssets m Coin -> ExceptT ErrSelectAssets m FeeEstimation
- calcMinimumDeposit :: forall ctx s k. ( HasDBLayer IO s k ctx, HasNetworkLayer IO ctx) => ctx -> WalletId -> ExceptT ErrSelectAssets IO Coin
- calcMinimumCoinValues :: forall ctx k f. ( HasTransactionLayer k ctx, HasNetworkLayer IO ctx, Applicative f) => ctx -> AnyCardanoEra -> f TxOut -> IO (f Coin )
- forgetTx :: forall ctx s k. HasDBLayer IO s k ctx => ctx -> WalletId -> Hash "Tx" -> ExceptT ErrRemoveTx IO ()
- listTransactions :: forall ctx s k. ( HasDBLayer IO s k ctx, HasNetworkLayer IO ctx) => ctx -> WalletId -> Maybe Coin -> Maybe UTCTime -> Maybe UTCTime -> SortOrder -> ExceptT ErrListTransactions IO [ TransactionInfo ]
- listAssets :: forall s k ctx. ( HasDBLayer IO s k ctx, IsOurs s Address ) => ctx -> WalletId -> ExceptT ErrNoSuchWallet IO ( Set AssetId )
- getTransaction :: forall ctx s k. HasDBLayer IO s k ctx => ctx -> WalletId -> Hash "Tx" -> ExceptT ErrGetTransaction IO TransactionInfo
- submitExternalTx :: forall ctx k. ( HasNetworkLayer IO ctx, HasTransactionLayer k ctx, HasLogger IO TxSubmitLog ctx) => ctx -> SealedTx -> ExceptT ErrPostTx IO Tx
- submitTx :: forall ctx s k. ( HasNetworkLayer IO ctx, HasDBLayer IO s k ctx, HasLogger IO WalletWorkerLog ctx) => ctx -> WalletId -> ( Tx , TxMeta , SealedTx ) -> ExceptT ErrSubmitTx IO ()
- balanceTransaction :: forall era m s k ctx. ( HasTransactionLayer k ctx, GenChange s, MonadRandom m, HasLogger m WalletWorkerLog ctx, IsShelleyBasedEra era, BoundedAddressLength k) => ctx -> ArgGenChange s -> ( ProtocolParameters , ProtocolParameters ) -> TimeInterpreter ( Either PastHorizonException ) -> ( UTxOIndex WalletUTxO , Wallet s, Set Tx ) -> PartialTx era -> ExceptT ErrBalanceTx m ( Tx era)
- data PartialTx era = PartialTx { }
-
data
LocalTxSubmissionConfig
=
LocalTxSubmissionConfig
{
- rateLimit :: DiffTime
- blockInterval :: Word64
- defaultLocalTxSubmissionConfig :: LocalTxSubmissionConfig
- runLocalTxSubmissionPool :: forall ctx s k m. ( MonadUnliftIO m, MonadMonotonicTime m, HasLogger IO WalletWorkerLog ctx, HasNetworkLayer m ctx, HasDBLayer m s k ctx) => LocalTxSubmissionConfig -> ctx -> WalletId -> m ()
- data ErrMkTransaction
- data ErrSubmitTx
- data ErrRemoveTx
- newtype ErrPostTx = ErrPostTxValidationError Text
- data ErrListTransactions
- data ErrGetTransaction
- data ErrNoSuchTransaction = ErrNoSuchTransaction WalletId ( Hash "Tx")
-
data
ErrStartTimeLaterThanEndTime
=
ErrStartTimeLaterThanEndTime
{
- errStartTime :: UTCTime
- errEndTime :: UTCTime
- data ErrWitnessTx
- withRootKey :: forall ctx s k e a. HasDBLayer IO s k ctx => ctx -> WalletId -> Passphrase "user" -> ( ErrWithRootKey -> e) -> (k ' RootK XPrv -> PassphraseScheme -> ExceptT e IO a) -> ExceptT e IO a
- derivePublicKey :: forall ctx s k. ( HasDBLayer IO s k ctx, SoftDerivation k, GetAccount s k) => ctx -> WalletId -> Role -> DerivationIndex -> ExceptT ErrDerivePublicKey IO (k ' AddressK XPub )
- getAccountPublicKeyAtIndex :: forall ctx s k. ( HasDBLayer IO s k ctx, WalletKey k, GetPurpose k) => ctx -> WalletId -> Passphrase "user" -> DerivationIndex -> Maybe DerivationIndex -> ExceptT ErrReadAccountPublicKey IO (k ' AccountK XPub )
- readAccountPublicKey :: forall ctx s k. ( HasDBLayer IO s k ctx, GetAccount s k) => ctx -> WalletId -> ExceptT ErrReadAccountPublicKey IO (k ' AccountK XPub )
- signMetadataWith :: forall ctx s k n. ( HasDBLayer IO s k ctx, HardDerivation k, AddressIndexDerivationType k ~ ' Soft , WalletKey k, s ~ SeqState n k) => ctx -> WalletId -> Passphrase "user" -> ( Role , DerivationIndex ) -> TxMetadata -> ExceptT ErrSignMetadataWith IO ( Signature TxMetadata )
- data ErrWithRootKey
- data ErrWrongPassphrase
- data ErrSignMetadataWith
- data ErrDerivePublicKey
- data ErrReadAccountPublicKey
- data ErrInvalidDerivationIndex derivation level = ErrIndexOutOfBound ( Index derivation level) ( Index derivation level) DerivationIndex
- throttle :: ( MonadUnliftIO m, MonadMonotonicTime m) => DiffTime -> ( Time -> a -> m ()) -> m (a -> m ())
- guardHardIndex :: Monad m => DerivationIndex -> ExceptT ( ErrInvalidDerivationIndex ' Hardened level) m ( Index ' Hardened whatever)
- withNoSuchWallet :: Monad m => WalletId -> m ( Maybe a) -> ExceptT ErrNoSuchWallet m a
- posAndNegFromCardanoValue :: Value -> ( TokenBundle , TokenBundle )
- data WalletWorkerLog
-
data
WalletFollowLog
- = MsgDiscoveredDelegationCert SlotNo DelegationCertificate
- | MsgCheckpoint BlockHeader
- | MsgDiscoveredTxs [( Tx , TxMeta )]
- | MsgDiscoveredTxsContent [( Tx , TxMeta )]
-
data
WalletLog
- = MsgSelectionStart Int [ TxOut ]
- | MsgSelectionForBalancingStart Int (BuildableInAnyEra PartialTx )
- | MsgSelectionError ( SelectionError WalletSelectionContext )
- | MsgSelectionReportSummarized SelectionReportSummarized
- | MsgSelectionReportDetailed SelectionReportDetailed
- | MsgMigrationUTxOBefore UTxOStatistics
- | MsgMigrationUTxOAfter UTxOStatistics
- | MsgRewardBalanceQuery BlockHeader
- | MsgRewardBalanceResult ( Either ErrFetchRewards Coin )
- | MsgRewardBalanceNoSuchWallet ErrNoSuchWallet
- | MsgRewardBalanceExited
- | MsgTxSubmit TxSubmitLog
- | MsgIsStakeKeyRegistered Bool
-
data
TxSubmitLog
- = MsgSubmitTx Tx TxMeta SealedTx ( BracketLog' ( Either ErrSubmitTx ()))
- | MsgSubmitExternalTx ( Hash "Tx") ( BracketLog' ( Either ErrPostTx Tx ))
- | MsgRetryPostTx ( Hash "Tx") ( BracketLog' ( Either ErrPostTx ()))
- | MsgProcessPendingPool BracketLog
Development
Naming Conventions
Components inside a particular context
ctx
can be called via dedicated
lenses (see Cardano.Wallet#Capabilities). These components are extracted from the context
in a
where
clause according to the following naming convention:
-
db = ctx ^. dbLayer @s \
k@ for theDBLayer
. -
tr = ctx ^. logger
for the Logger. -
nw = ctx ^. networkLayer
for theNetworkLayer
. -
tl = ctx ^. transactionLayer \
k@ for theTransactionLayer
. -
re = ctx ^. workerRegistry
for theWorkerRegistry
.
TroubleShooting
• Overlapping instances for HasType (DBLayer IO s k) ctx arising from a use of ‘myFunction’ Matching instances:
Occurs when a particular function is missing a top-level constraint
(because it uses another function that demands such constraint). Here,
myFunction
needs its surrounding context
ctx
to have a
DBLayer
but
the constraint is missing from its host function.
Fix
: Add "
HasDBLayer s k
" as a class-constraint to the surrounding function.
• Overlapping instances for HasType (DBLayer IO s t0 k0) ctx arising from a use of ‘myFunction’ Matching givens (or their superclasses):
Occurs when a function is called in a context where type-level parameters
can be inferred. Here,
myFunction
is called but it is unclear
whether the parameter
t0
and
k0
of its context are the same as the ones
from the function at the call-site.
Fix
: Add type-applications at the call-site "
myFunction @ctx @s \
k@"
WalletLayer
data WalletLayer m s (k :: Depth -> Type -> Type ) Source #
WalletLayer ( Tracer m WalletWorkerLog ) ( Block , NetworkParameters ) ( NetworkLayer m Block ) ( TransactionLayer k SealedTx ) ( DBLayer m s k) |
Instances
Capabilities
Each function in the wallet layer is defined in function of a non-specialized
context
ctx
. That context may require some extra capabilities via
class-constraints in the function signature. Capabilities are expressed in the
form of a "
HasXXX
" class-constraints sometimes with extra type parameters.
For example:
listWallets :: forall ctx s k. ( HasDBLayer s k ctx ) => ctx -> IO [WalletId]
Requires that the given context has an access to a database layer
DBLayer
parameterized over the wallet state, a network target and a key derivation
scheme. Components are pulled from the context generically (i.e. the concrete
ctx
must derive
Generic
) using their associated type. The concrete
ctx
is therefore expected to be a product-type of all the necessary components.
One can build an interface using only a subset of the wallet layer capabilities and functions, for instance, something to fiddle with wallets and their metadata does not require any networking layer.
type HasDBLayer m s k = HasType ( DBLayer m s k) Source #
type HasNetworkLayer m = HasType ( NetworkLayer m Block ) Source #
This module is only interested in one block-, and tx-type. This constraint hides that choice, for some ease of use.
networkLayer :: forall m ctx. HasNetworkLayer m ctx => Lens' ctx ( NetworkLayer m Block ) Source #
type HasTransactionLayer k = HasType ( TransactionLayer k SealedTx ) Source #
transactionLayer :: forall k ctx. HasTransactionLayer k ctx => Lens' ctx ( TransactionLayer k SealedTx ) Source #
type HasGenesisData = HasType ( Block , NetworkParameters ) Source #
genesisData :: forall ctx. HasGenesisData ctx => Lens' ctx ( Block , NetworkParameters ) Source #
Interface
Wallet
createWallet :: forall ctx m s k. ( MonadUnliftIO m, MonadTime m, HasGenesisData ctx, HasDBLayer m s k ctx, IsOurs s Address , IsOurs s RewardAccount ) => ctx -> WalletId -> WalletName -> s -> ExceptT ErrWalletAlreadyExists m WalletId Source #
Initialise and store a new wallet, returning its ID.
createIcarusWallet :: forall ctx s k n. ( HasGenesisData ctx, HasDBLayer IO s k ctx, PaymentAddress n k, k ~ IcarusKey , s ~ SeqState n k, Typeable n) => ctx -> WalletId -> WalletName -> (k ' RootK XPrv , Passphrase "encryption") -> ExceptT ErrWalletAlreadyExists IO WalletId Source #
Initialise and store a new legacy Icarus wallet. These wallets are intrinsically sequential, but, in the incentivized testnet, we only have access to the a snapshot of the MainNet.
To work-around this, we scan the genesis block with an arbitrary big gap and resort to a default gap afterwards.
attachPrivateKeyFromPwd :: forall ctx s k. HasDBLayer IO s k ctx => ctx -> WalletId -> (k ' RootK XPrv , Passphrase "user") -> ExceptT ErrNoSuchWallet IO () Source #
attachPrivateKeyFromPwdHash :: forall ctx s k. HasDBLayer IO s k ctx => ctx -> WalletId -> (k ' RootK XPrv , PassphraseHash ) -> ExceptT ErrNoSuchWallet IO () Source #
The hash here is the output of Scrypt function with the following parameters: - logN = 14 - r = 8 - p = 1 - bytesNumber = 64
getWalletUtxoSnapshot :: forall ctx s k. ( HasDBLayer IO s k ctx, HasNetworkLayer IO ctx, HasTransactionLayer k ctx) => ctx -> WalletId -> ExceptT ErrNoSuchWallet IO [( TokenBundle , Coin )] Source #
listUtxoStatistics :: forall ctx s k. HasDBLayer IO s k ctx => ctx -> WalletId -> ExceptT ErrListUTxOStatistics IO UTxOStatistics Source #
List the wallet's UTxO statistics.
readWallet :: forall ctx s k. HasDBLayer IO s k ctx => ctx -> WalletId -> ExceptT ErrNoSuchWallet IO ( Wallet s, WalletMetadata , Set Tx ) Source #
Retrieve the wallet state for the wallet with the given ID.
deleteWallet :: forall ctx s k. HasDBLayer IO s k ctx => ctx -> WalletId -> ExceptT ErrNoSuchWallet IO () Source #
Remove an existing wallet. Note that there's no particular work to be done regarding the restoration worker as it will simply terminate on the next tick when noticing that the corresponding wallet is gone.
restoreWallet :: forall ctx s k. ( HasNetworkLayer IO ctx, HasDBLayer IO s k ctx, HasLogger IO WalletWorkerLog ctx, IsOurs s Address , IsOurs s RewardAccount , AddressBookIso s, MaybeLight s) => ctx -> WalletId -> ExceptT ErrNoSuchWallet IO () Source #
Restore a wallet from its current tip.
After the wallet has been restored, this action will continue to fetch newly created blocks and apply them, or roll back to a previous point whenever the chain switches.
updateWallet :: forall ctx s k. HasDBLayer IO s k ctx => ctx -> WalletId -> ( WalletMetadata -> WalletMetadata ) -> ExceptT ErrNoSuchWallet IO () Source #
Update a wallet's metadata with the given update function.
updateWalletPassphraseWithOldPassphrase :: forall ctx s k. ( HasDBLayer IO s k ctx, WalletKey k) => ctx -> WalletId -> ( Passphrase "user", Passphrase "user") -> ExceptT ErrUpdatePassphrase IO () Source #
Change a wallet's passphrase to the given passphrase.
updateWalletPassphraseWithMnemonic :: forall ctx s k. HasDBLayer IO s k ctx => ctx -> WalletId -> (k ' RootK XPrv , Passphrase "user") -> ExceptT ErrUpdatePassphrase IO () Source #
walletSyncProgress :: forall ctx s. HasNetworkLayer IO ctx => ctx -> Wallet s -> IO SyncProgress Source #
fetchRewardBalance :: forall ctx s k. HasDBLayer IO s k ctx => ctx -> WalletId -> IO Coin Source #
Fetch the cached reward balance of a given wallet from the database.
manageRewardBalance :: forall ctx s k (n :: NetworkDiscriminant ). ( HasLogger IO WalletWorkerLog ctx, HasNetworkLayer IO ctx, HasDBLayer IO s k ctx, Typeable s, Typeable n) => Proxy n -> ctx -> WalletId -> IO () Source #
rollbackBlocks :: forall ctx s k. HasDBLayer IO s k ctx => ctx -> WalletId -> Slot -> ExceptT ErrNoSuchWallet IO ChainPoint Source #
Rewind the UTxO snapshots, transaction history and other information to a the earliest point in the past that is before or is the point of rollback.
checkWalletIntegrity :: forall ctx s k. HasDBLayer IO s k ctx => ctx -> WalletId -> GenesisParameters -> ExceptT ErrCheckWalletIntegrity IO () Source #
Check whether a wallet is in good shape when restarting a worker.
readNextWithdrawal :: forall ctx k. ( HasTransactionLayer k ctx, HasNetworkLayer IO ctx) => ctx -> AnyCardanoEra -> Coin -> IO Coin Source #
Read the current withdrawal capacity of a wallet. Note that, this simply returns 0 if:
a) There's no reward account for this type of wallet. b) The current reward value is too small to be considered (adding it would cost more than its value).
readRewardAccount :: forall ctx s k (n :: NetworkDiscriminant ) shelley. ( HasDBLayer IO s k ctx, shelley ~ SeqState n ShelleyKey , Typeable n, Typeable s) => ctx -> WalletId -> ExceptT ErrReadRewardAccount IO ( RewardAccount , XPub , NonEmpty DerivationIndex ) Source #
someRewardAccount :: ToRewardAccount k => SomeMnemonic -> ( XPrv , RewardAccount , NonEmpty DerivationIndex ) Source #
readPolicyPublicKey :: forall ctx s k (n :: NetworkDiscriminant ) shelley. ( HasDBLayer IO s k ctx, shelley ~ SeqState n ShelleyKey , Typeable n, Typeable s) => ctx -> WalletId -> ExceptT ErrReadPolicyPublicKey IO ( XPub , NonEmpty DerivationIndex ) Source #
writePolicyPublicKey :: forall ctx s (n :: NetworkDiscriminant ). ( HasDBLayer IO s ShelleyKey ctx, s ~ SeqState n ShelleyKey ) => ctx -> WalletId -> Passphrase "user" -> ExceptT ErrWritePolicyPublicKey IO ( ShelleyKey ' PolicyK XPub ) Source #
queryRewardBalance :: forall ctx. HasNetworkLayer IO ctx => ctx -> RewardAccount -> ExceptT ErrFetchRewards IO Coin Source #
Query the node for the reward balance of a given wallet.
Rather than force all callers of
readWallet
to wait for fetching the
account balance (via the
NetworkLayer
), we expose this function for it.
newtype ErrWalletAlreadyExists Source #
Forbidden operation was executed on an already existing wallet
Instances
Eq ErrWalletAlreadyExists Source # | |
Defined in Cardano.Wallet.DB |
|
Show ErrWalletAlreadyExists Source # | |
Defined in Cardano.Wallet.DB |
|
IsServerError ErrWalletAlreadyExists Source # | |
Defined in Cardano.Wallet.Api.Server |
newtype ErrNoSuchWallet Source #
Can't perform given operation because there's no wallet
Instances
Eq ErrNoSuchWallet Source # | |
Defined in Cardano.Wallet.DB.WalletState (==) :: ErrNoSuchWallet -> ErrNoSuchWallet -> Bool Source # (/=) :: ErrNoSuchWallet -> ErrNoSuchWallet -> Bool Source # |
|
Show ErrNoSuchWallet Source # | |
Defined in Cardano.Wallet.DB.WalletState |
|
IsServerError ErrNoSuchWallet Source # | |
Defined in Cardano.Wallet.Api.Server |
newtype ErrListUTxOStatistics Source #
Errors that can occur when listing UTxO statistics.
Instances
Eq ErrListUTxOStatistics Source # | |
Defined in Cardano.Wallet (==) :: ErrListUTxOStatistics -> ErrListUTxOStatistics -> Bool Source # (/=) :: ErrListUTxOStatistics -> ErrListUTxOStatistics -> Bool Source # |
|
Show ErrListUTxOStatistics Source # | |
Defined in Cardano.Wallet |
|
IsServerError ErrListUTxOStatistics Source # | |
Defined in Cardano.Wallet.Api.Server |
data ErrUpdatePassphrase Source #
Errors that can occur when trying to change a wallet's passphrase.
Instances
Eq ErrUpdatePassphrase Source # | |
Defined in Cardano.Wallet (==) :: ErrUpdatePassphrase -> ErrUpdatePassphrase -> Bool Source # (/=) :: ErrUpdatePassphrase -> ErrUpdatePassphrase -> Bool Source # |
|
Show ErrUpdatePassphrase Source # | |
Defined in Cardano.Wallet |
|
IsServerError ErrUpdatePassphrase Source # | |
Defined in Cardano.Wallet.Api.Server |
newtype ErrFetchRewards Source #
Errors that can occur when fetching the reward balance of a wallet
Instances
Eq ErrFetchRewards Source # | |
Defined in Cardano.Wallet (==) :: ErrFetchRewards -> ErrFetchRewards -> Bool Source # (/=) :: ErrFetchRewards -> ErrFetchRewards -> Bool Source # |
|
Show ErrFetchRewards Source # | |
Defined in Cardano.Wallet |
|
Generic ErrFetchRewards Source # | |
Defined in Cardano.Wallet from :: ErrFetchRewards -> Rep ErrFetchRewards x Source # to :: Rep ErrFetchRewards x -> ErrFetchRewards Source # |
|
IsServerError ErrFetchRewards Source # | |
Defined in Cardano.Wallet.Api.Server |
|
type Rep ErrFetchRewards Source # | |
Defined in Cardano.Wallet
type
Rep
ErrFetchRewards
=
D1
('
MetaData
"ErrFetchRewards" "Cardano.Wallet" "cardano-wallet-core-2022.7.1-AGKhlyz9liLKN3QqZD1gj" '
True
) (
C1
('
MetaCons
"ErrFetchRewardsReadRewardAccount" '
PrefixI
'
False
) (
S1
('
MetaSel
('
Nothing
::
Maybe
Symbol
) '
NoSourceUnpackedness
'
NoSourceStrictness
'
DecidedLazy
) (
Rec0
ErrReadRewardAccount
)))
|
data ErrCheckWalletIntegrity Source #
ErrCheckWalletIntegrityNoSuchWallet ErrNoSuchWallet | |
ErrCheckIntegrityDifferentGenesis ( Hash "Genesis") ( Hash "Genesis") |
Instances
Eq ErrCheckWalletIntegrity Source # | |
Defined in Cardano.Wallet |
|
Show ErrCheckWalletIntegrity Source # | |
Defined in Cardano.Wallet |
|
Exception ErrCheckWalletIntegrity Source # | |
newtype ErrWalletNotResponding Source #
Can't perform given operation because the wallet died.
Instances
Eq ErrWalletNotResponding Source # | |
Defined in Cardano.Wallet |
|
Show ErrWalletNotResponding Source # | |
Defined in Cardano.Wallet |
|
IsServerError ErrWalletNotResponding Source # | |
Defined in Cardano.Wallet.Api.Server |
data ErrReadRewardAccount Source #
Instances
data ErrReadPolicyPublicKey Source #
ErrReadPolicyPublicKeyNotAShelleyWallet | |
ErrReadPolicyPublicKeyNoSuchWallet ErrNoSuchWallet | |
ErrReadPolicyPublicKeyAbsent |
Instances
Eq ErrReadPolicyPublicKey Source # | |
Defined in Cardano.Wallet |
|
Show ErrReadPolicyPublicKey Source # | |
Defined in Cardano.Wallet |
|
Generic ErrReadPolicyPublicKey Source # | |
Defined in Cardano.Wallet |
|
IsServerError ErrReadPolicyPublicKey Source # | |
Defined in Cardano.Wallet.Api.Server |
|
type Rep ErrReadPolicyPublicKey Source # | |
Defined in Cardano.Wallet
type
Rep
ErrReadPolicyPublicKey
=
D1
('
MetaData
"ErrReadPolicyPublicKey" "Cardano.Wallet" "cardano-wallet-core-2022.7.1-AGKhlyz9liLKN3QqZD1gj" '
False
) (
C1
('
MetaCons
"ErrReadPolicyPublicKeyNotAShelleyWallet" '
PrefixI
'
False
) (
U1
::
Type
->
Type
)
:+:
(
C1
('
MetaCons
"ErrReadPolicyPublicKeyNoSuchWallet" '
PrefixI
'
False
) (
S1
('
MetaSel
('
Nothing
::
Maybe
Symbol
) '
NoSourceUnpackedness
'
NoSourceStrictness
'
DecidedLazy
) (
Rec0
ErrNoSuchWallet
))
:+:
C1
('
MetaCons
"ErrReadPolicyPublicKeyAbsent" '
PrefixI
'
False
) (
U1
::
Type
->
Type
)))
|
data ErrWritePolicyPublicKey Source #
ErrWritePolicyPublicKeyNoSuchWallet ErrNoSuchWallet | |
ErrWritePolicyPublicKeyWithRootKey ErrWithRootKey |
Instances
Eq ErrWritePolicyPublicKey Source # | |
Defined in Cardano.Wallet |
|
Show ErrWritePolicyPublicKey Source # | |
Defined in Cardano.Wallet |
|
Generic ErrWritePolicyPublicKey Source # | |
Defined in Cardano.Wallet |
|
IsServerError ErrWritePolicyPublicKey Source # | |
Defined in Cardano.Wallet.Api.Server |
|
type Rep ErrWritePolicyPublicKey Source # | |
Defined in Cardano.Wallet
type
Rep
ErrWritePolicyPublicKey
=
D1
('
MetaData
"ErrWritePolicyPublicKey" "Cardano.Wallet" "cardano-wallet-core-2022.7.1-AGKhlyz9liLKN3QqZD1gj" '
False
) (
C1
('
MetaCons
"ErrWritePolicyPublicKeyNoSuchWallet" '
PrefixI
'
False
) (
S1
('
MetaSel
('
Nothing
::
Maybe
Symbol
) '
NoSourceUnpackedness
'
NoSourceStrictness
'
DecidedLazy
) (
Rec0
ErrNoSuchWallet
))
:+:
C1
('
MetaCons
"ErrWritePolicyPublicKeyWithRootKey" '
PrefixI
'
False
) (
S1
('
MetaSel
('
Nothing
::
Maybe
Symbol
) '
NoSourceUnpackedness
'
NoSourceStrictness
'
DecidedLazy
) (
Rec0
ErrWithRootKey
)))
|
data ErrGetPolicyId Source #
Errors that can occur when getting policy id.
Instances
Eq ErrGetPolicyId Source # | |
Defined in Cardano.Wallet (==) :: ErrGetPolicyId -> ErrGetPolicyId -> Bool Source # (/=) :: ErrGetPolicyId -> ErrGetPolicyId -> Bool Source # |
|
Show ErrGetPolicyId Source # | |
Defined in Cardano.Wallet |
|
IsServerError ErrGetPolicyId Source # | |
Defined in Cardano.Wallet.Api.Server |
Shared Wallet
updateCosigner :: forall ctx s k n. (s ~ SharedState n k, MkKeyFingerprint k Address , SoftDerivation k, Typeable n, WalletKey k, HasDBLayer IO s k ctx, k ~ SharedKey ) => ctx -> WalletId -> k ' AccountK XPub -> Cosigner -> CredentialType -> ExceptT ErrAddCosignerKey IO () Source #
data ErrAddCosignerKey Source #
ErrAddCosignerKeyNoSuchWallet ErrNoSuchWallet |
The shared wallet doesn't exist? |
ErrAddCosignerKey ErrAddCosigner |
Error adding this co-signer to the shared wallet. |
Instances
Eq ErrAddCosignerKey Source # | |
Defined in Cardano.Wallet (==) :: ErrAddCosignerKey -> ErrAddCosignerKey -> Bool Source # (/=) :: ErrAddCosignerKey -> ErrAddCosignerKey -> Bool Source # |
|
Show ErrAddCosignerKey Source # | |
Defined in Cardano.Wallet |
|
IsServerError ErrAddCosignerKey Source # | |
Defined in Cardano.Wallet.Api.Server |
data ErrConstructSharedWallet Source #
ErrConstructSharedWalletWrongScriptTemplate ErrScriptTemplate |
The shared wallet' script template doesn't pass validation |
ErrConstructSharedWalletInvalidIndex ( ErrInvalidDerivationIndex ' Hardened ' AccountK ) |
User provided a derivation index outside of the
|
Instances
normalizeSharedAddress :: forall n k. ( SupportsDiscovery n k, k ~ SharedKey ) => SharedState n k -> Address -> Maybe Address Source #
constructSharedTransaction :: forall ctx s k (n :: NetworkDiscriminant ). ( HasTransactionLayer k ctx, HasDBLayer IO s k ctx, HasNetworkLayer IO ctx, k ~ SharedKey , s ~ SharedState n k) => ctx -> WalletId -> AnyCardanoEra -> TransactionCtx -> SelectionOf TxOut -> ExceptT ErrConstructTx IO SealedTx Source #
Construct an unsigned transaction from a given selection for a shared wallet.
Address
createRandomAddress :: forall ctx s k n. ( HasDBLayer IO s k ctx, PaymentAddress n k, RndStateLike s, k ~ ByronKey , AddressBookIso s) => ctx -> WalletId -> Passphrase "user" -> Maybe ( Index ' Hardened ' AddressK ) -> ExceptT ErrCreateRandomAddress IO ( Address , NonEmpty DerivationIndex ) Source #
importRandomAddresses :: forall ctx s k. ( HasDBLayer IO s k ctx, RndStateLike s, k ~ ByronKey , AddressBookIso s) => ctx -> WalletId -> [ Address ] -> ExceptT ErrImportRandomAddress IO () Source #
:: forall ctx s k. ( HasDBLayer IO s k ctx, CompareDiscovery s, KnownAddresses s) | |
=> ctx | |
-> WalletId | |
-> (s -> Address -> Maybe Address ) |
A function to normalize address, so that delegated addresses
non-delegation addresses found in the transaction history are
shown with their delegation settings.
Use
|
-> ExceptT ErrNoSuchWallet IO [( Address , AddressState , NonEmpty DerivationIndex )] |
List all addresses of a wallet with their metadata. Addresses are ordered from the most-recently-discovered to the oldest known.
normalizeDelegationAddress :: forall s k n. ( DelegationAddress n k, s ~ SeqState n k) => s -> Address -> Maybe Address Source #
lookupTxIns :: forall ctx s k. ( HasDBLayer IO s k ctx, IsOurs s Address ) => ctx -> WalletId -> [ TxIn ] -> ExceptT ErrDecodeTx IO [( TxIn , Maybe ( TxOut , NonEmpty DerivationIndex ))] Source #
lookupTxOuts :: forall ctx s k. ( HasDBLayer IO s k ctx, IsOurs s Address ) => ctx -> WalletId -> [ TxOut ] -> ExceptT ErrDecodeTx IO [( TxOut , Maybe ( NonEmpty DerivationIndex ))] Source #
data ErrCreateRandomAddress Source #
ErrIndexAlreadyExists ( Index ' Hardened ' AddressK ) | |
ErrCreateAddrNoSuchWallet ErrNoSuchWallet | |
ErrCreateAddrWithRootKey ErrWithRootKey | |
ErrCreateAddressNotAByronWallet |
Instances
data ErrImportRandomAddress Source #
ErrImportAddrNoSuchWallet ErrNoSuchWallet | |
ErrImportAddr ErrImportAddress | |
ErrImportAddressNotAByronWallet |
Instances
Eq ErrImportRandomAddress Source # | |
Defined in Cardano.Wallet |
|
Show ErrImportRandomAddress Source # | |
Defined in Cardano.Wallet |
|
Generic ErrImportRandomAddress Source # | |
Defined in Cardano.Wallet |
|
IsServerError ErrImportRandomAddress Source # | |
Defined in Cardano.Wallet.Api.Server |
|
type Rep ErrImportRandomAddress Source # | |
Defined in Cardano.Wallet
type
Rep
ErrImportRandomAddress
=
D1
('
MetaData
"ErrImportRandomAddress" "Cardano.Wallet" "cardano-wallet-core-2022.7.1-AGKhlyz9liLKN3QqZD1gj" '
False
) (
C1
('
MetaCons
"ErrImportAddrNoSuchWallet" '
PrefixI
'
False
) (
S1
('
MetaSel
('
Nothing
::
Maybe
Symbol
) '
NoSourceUnpackedness
'
NoSourceStrictness
'
DecidedLazy
) (
Rec0
ErrNoSuchWallet
))
:+:
(
C1
('
MetaCons
"ErrImportAddr" '
PrefixI
'
False
) (
S1
('
MetaSel
('
Nothing
::
Maybe
Symbol
) '
NoSourceUnpackedness
'
NoSourceStrictness
'
DecidedLazy
) (
Rec0
ErrImportAddress
))
:+:
C1
('
MetaCons
"ErrImportAddressNotAByronWallet" '
PrefixI
'
False
) (
U1
::
Type
->
Type
)))
|
newtype ErrImportAddress Source #
Instances
Eq ErrImportAddress Source # | |
Defined in Cardano.Wallet.Primitive.AddressDiscovery.Random (==) :: ErrImportAddress -> ErrImportAddress -> Bool Source # (/=) :: ErrImportAddress -> ErrImportAddress -> Bool Source # |
|
Show ErrImportAddress Source # | |
|
|
Generic ErrImportAddress Source # | |
Defined in Cardano.Wallet.Primitive.AddressDiscovery.Random from :: ErrImportAddress -> Rep ErrImportAddress x Source # to :: Rep ErrImportAddress x -> ErrImportAddress Source # |
|
type Rep ErrImportAddress Source # | |
Defined in Cardano.Wallet.Primitive.AddressDiscovery.Random
type
Rep
ErrImportAddress
=
D1
('
MetaData
"ErrImportAddress" "Cardano.Wallet.Primitive.AddressDiscovery.Random" "cardano-wallet-core-2022.7.1-AGKhlyz9liLKN3QqZD1gj" '
True
) (
C1
('
MetaCons
"ErrAddrDoesNotBelong" '
PrefixI
'
False
) (
S1
('
MetaSel
('
Nothing
::
Maybe
Symbol
) '
NoSourceUnpackedness
'
NoSourceStrictness
'
DecidedLazy
) (
Rec0
Address
)))
|
newtype ErrDecodeTx Source #
Errors that can occur when decoding a transaction.
Instances
Eq ErrDecodeTx Source # | |
Defined in Cardano.Wallet (==) :: ErrDecodeTx -> ErrDecodeTx -> Bool Source # (/=) :: ErrDecodeTx -> ErrDecodeTx -> Bool Source # |
|
Show ErrDecodeTx Source # | |
Defined in Cardano.Wallet |
|
IsServerError ErrDecodeTx Source # | |
Defined in Cardano.Wallet.Api.Server |
Payment
:: TimeInterpreter ( ExceptT PastHorizonException IO ) |
Context for time to slot calculation. |
-> Maybe NominalDiffTime |
Time to live (TTL) in seconds from now. |
-> IO SlotNo |
Calculate the transaction expiry slot, given a
TimeInterpreter
, and an
optional TTL in seconds.
If no TTL is provided, a default of 2 hours is used (note: there is no particular reason why we chose that duration).
data SelectAssetsParams s result Source #
Parameters for the
selectAssets
function.
SelectAssetsParams | |
|
Instances
selectAssets :: forall ctx m s k result. ( BoundedAddressLength k, HasTransactionLayer k ctx, HasLogger m WalletWorkerLog ctx, MonadRandom m) => ctx -> AnyCardanoEra -> ProtocolParameters -> SelectAssetsParams s result -> (s -> Selection -> result) -> ExceptT ErrSelectAssets m result Source #
Selects assets from a wallet.
This function has the following responsibilities:
- selecting inputs from the UTxO set to pay for user-specified outputs;
- selecting inputs from the UTxO set to pay for collateral;
- producing change outputs to return excess value to the wallet;
- balancing a selection to pay for the transaction fee.
When selecting inputs to pay for user-specified outputs, inputs are selected randomly.
By default, the seed used for random selection is derived automatically,
from the given
MonadRandom
context.
However, if a concrete value is specified for the optional
$sel:randomSeed:SelectAssetsParams
parameter, then that value will be used instead as the seed for random
selection.
readWalletUTxOIndex :: forall ctx s k. HasDBLayer IO s k ctx => ctx -> WalletId -> ExceptT ErrNoSuchWallet IO ( UTxOIndex WalletUTxO , Wallet s, Set Tx ) Source #
Read a wallet checkpoint and index its UTxO, for
selectAssets
and
selectAssetsNoOutputs
.
assignChangeAddresses :: forall s. GenChange s => ArgGenChange s -> Selection -> s -> ( SelectionOf TxOut , s) Source #
Augments the given outputs with new outputs. These new outputs correspond to change outputs to which new addresses have been assigned. This updates the wallet state as it needs to keep track of new pending change addresses.
assignChangeAddressesAndUpdateDb :: forall ctx s k. ( GenChange s, HasDBLayer IO s k ctx, AddressBookIso s) => ctx -> WalletId -> ArgGenChange s -> Selection -> ExceptT ErrSignPayment IO ( SelectionOf TxOut ) Source #
assignChangeAddressesWithoutDbUpdate :: forall ctx s k. ( GenChange s, HasDBLayer IO s k ctx) => ctx -> WalletId -> ArgGenChange s -> Selection -> ExceptT ErrConstructTx IO ( SelectionOf TxOut ) Source #
selectionToUnsignedTx :: forall s input output change withdrawal. ( IsOurs s Address , input ~ ( TxIn , TxOut , NonEmpty DerivationIndex ), output ~ TxOut , change ~ TxChange ( NonEmpty DerivationIndex ), withdrawal ~ ( RewardAccount , Coin , NonEmpty DerivationIndex )) => Withdrawal -> SelectionOf TxOut -> s -> UnsignedTx input output change withdrawal Source #
buildAndSignTransaction Source #
:: forall ctx s k. ( HasTransactionLayer k ctx, HasDBLayer IO s k ctx, HasNetworkLayer IO ctx, IsOwned s k) | |
=> ctx | |
-> WalletId | |
-> AnyCardanoEra | |
-> ((k ' RootK XPrv , Passphrase "encryption") -> ( XPrv , Passphrase "encryption")) |
Reward account derived from the root key (or somewhere else). |
-> Passphrase "user" | |
-> TransactionCtx | |
-> SelectionOf TxOut | |
-> ExceptT ErrSignPayment IO ( Tx , TxMeta , UTCTime , SealedTx ) |
Produce witnesses and construct a transaction from a given selection.
Requires the encryption passphrase in order to decrypt the root private key.
Note that this doesn't broadcast the transaction to the network. In order to
do so, use
submitTx
.
:: forall k. ( WalletKey k, HardDerivation k, Bounded ( Index ( AddressIndexDerivationType k) ' AddressK )) | |
=> TransactionLayer k SealedTx |
The way to interact with the wallet backend |
-> AnyCardanoEra |
Preferred latest era |
-> ( Address -> Maybe (k ' AddressK XPrv , Passphrase "encryption")) |
The wallets address-key lookup function |
-> (k ' RootK XPrv , Passphrase "encryption") |
The root key of the wallet |
-> UTxO |
The total UTxO set of the wallet (i.e. if pending transactions all applied). |
-> SealedTx |
The transaction to sign |
-> SealedTx |
The original transaction, with additional signatures added where necessary |
constructTransaction :: forall ctx s k (n :: NetworkDiscriminant ). ( HasTransactionLayer k ctx, HasDBLayer IO s k ctx, HasNetworkLayer IO ctx, Typeable s, Typeable n) => ctx -> WalletId -> AnyCardanoEra -> TransactionCtx -> SelectionOf TxOut -> ExceptT ErrConstructTx IO SealedTx Source #
Construct an unsigned transaction from a given selection.
constructTxMeta :: forall ctx s k. HasDBLayer IO s k ctx => ctx -> WalletId -> TransactionCtx -> [( TxIn , Coin )] -> [ TxOut ] -> ExceptT ErrSubmitTransaction IO TxMeta Source #
data ErrSelectAssets Source #
Instances
data ErrSignPayment Source #
Errors that can occur when signing a transaction.
ErrSignPaymentMkTx ErrMkTransaction | |
ErrSignPaymentNoSuchWallet ErrNoSuchWallet | |
ErrSignPaymentWithRootKey ErrWithRootKey | |
ErrSignPaymentIncorrectTTL PastHorizonException |
Instances
Eq ErrSignPayment Source # | |
Defined in Cardano.Wallet (==) :: ErrSignPayment -> ErrSignPayment -> Bool Source # (/=) :: ErrSignPayment -> ErrSignPayment -> Bool Source # |
|
Show ErrSignPayment Source # | |
Defined in Cardano.Wallet |
|
IsServerError ErrSignPayment Source # | |
Defined in Cardano.Wallet.Api.Server |
data ErrNotASequentialWallet Source #
Instances
Eq ErrNotASequentialWallet Source # | |
Defined in Cardano.Wallet |
|
Show ErrNotASequentialWallet Source # | |
Defined in Cardano.Wallet |
|
Generic ErrNotASequentialWallet Source # | |
Defined in Cardano.Wallet |
|
IsServerError ErrNotASequentialWallet Source # | |
Defined in Cardano.Wallet.Api.Server |
|
type Rep ErrNotASequentialWallet Source # | |
data ErrWithdrawalNotWorth Source #
Instances
Eq ErrWithdrawalNotWorth Source # | |
Defined in Cardano.Wallet (==) :: ErrWithdrawalNotWorth -> ErrWithdrawalNotWorth -> Bool Source # (/=) :: ErrWithdrawalNotWorth -> ErrWithdrawalNotWorth -> Bool Source # |
|
Show ErrWithdrawalNotWorth Source # | |
Defined in Cardano.Wallet |
|
Generic ErrWithdrawalNotWorth Source # | |
Defined in Cardano.Wallet |
|
IsServerError ErrWithdrawalNotWorth Source # | |
Defined in Cardano.Wallet.Api.Server |
|
type Rep ErrWithdrawalNotWorth Source # | |
data ErrConstructTx Source #
Errors that can occur when constructing an unsigned transaction.
Instances
Eq ErrConstructTx Source # | |
Defined in Cardano.Wallet (==) :: ErrConstructTx -> ErrConstructTx -> Bool Source # (/=) :: ErrConstructTx -> ErrConstructTx -> Bool Source # |
|
Show ErrConstructTx Source # | |
Defined in Cardano.Wallet |
|
IsServerError ErrConstructTx Source # | |
Defined in Cardano.Wallet.Api.Server |
newtype ErrMintBurnAssets Source #
ErrMintBurnNotImplemented Text |
Temporary error constructor. |
Instances
Eq ErrMintBurnAssets Source # | |
Defined in Cardano.Wallet (==) :: ErrMintBurnAssets -> ErrMintBurnAssets -> Bool Source # (/=) :: ErrMintBurnAssets -> ErrMintBurnAssets -> Bool Source # |
|
Show ErrMintBurnAssets Source # | |
Defined in Cardano.Wallet |
data ErrBalanceTx Source #
Errors that can occur when balancing transaction.
Instances
Eq ErrBalanceTx Source # | |
Defined in Cardano.Wallet (==) :: ErrBalanceTx -> ErrBalanceTx -> Bool Source # (/=) :: ErrBalanceTx -> ErrBalanceTx -> Bool Source # |
|
Show ErrBalanceTx Source # | |
Defined in Cardano.Wallet |
|
IsServerError ErrBalanceTx Source # | |
Defined in Cardano.Wallet.Api.Server |
data ErrBalanceTxInternalError Source #
Instances
Eq ErrBalanceTxInternalError Source # | |
Defined in Cardano.Wallet |
|
Show ErrBalanceTxInternalError Source # | |
Defined in Cardano.Wallet |
newtype ErrUpdateSealedTx Source #
ErrExistingKeyWitnesses Int |
The
|
Instances
Eq ErrUpdateSealedTx Source # | |
Defined in Cardano.Wallet.Transaction (==) :: ErrUpdateSealedTx -> ErrUpdateSealedTx -> Bool Source # (/=) :: ErrUpdateSealedTx -> ErrUpdateSealedTx -> Bool Source # |
|
Show ErrUpdateSealedTx Source # | |
Defined in Cardano.Wallet.Transaction |
|
Generic ErrUpdateSealedTx Source # | |
Defined in Cardano.Wallet.Transaction from :: ErrUpdateSealedTx -> Rep ErrUpdateSealedTx x Source # to :: Rep ErrUpdateSealedTx x -> ErrUpdateSealedTx Source # |
|
IsServerError ErrUpdateSealedTx Source # | |
Defined in Cardano.Wallet.Api.Server |
|
type Rep ErrUpdateSealedTx Source # | |
Defined in Cardano.Wallet.Transaction
type
Rep
ErrUpdateSealedTx
=
D1
('
MetaData
"ErrUpdateSealedTx" "Cardano.Wallet.Transaction" "cardano-wallet-core-2022.7.1-AGKhlyz9liLKN3QqZD1gj" '
True
) (
C1
('
MetaCons
"ErrExistingKeyWitnesses" '
PrefixI
'
False
) (
S1
('
MetaSel
('
Nothing
::
Maybe
Symbol
) '
NoSourceUnpackedness
'
NoSourceStrictness
'
DecidedLazy
) (
Rec0
Int
)))
|
data ErrCannotJoin Source #
Instances
data ErrCannotQuit Source #
Instances
Eq ErrCannotQuit Source # | |
Defined in Cardano.Wallet.Transaction (==) :: ErrCannotQuit -> ErrCannotQuit -> Bool Source # (/=) :: ErrCannotQuit -> ErrCannotQuit -> Bool Source # |
|
Show ErrCannotQuit Source # | |
Defined in Cardano.Wallet.Transaction |
|
IsServerError ErrCannotQuit Source # | |
Defined in Cardano.Wallet.Api.Server |
data ErrSubmitTransaction Source #
Errors that can occur when submitting a transaction.
ErrSubmitTransactionNoSuchWallet ErrNoSuchWallet | |
ErrSubmitTransactionForeignWallet | |
ErrSubmitTransactionPartiallySignedOrNoSignedTx Int Int | |
ErrSubmitTransactionMultidelegationNotSupported |
Instances
Eq ErrSubmitTransaction Source # | |
Defined in Cardano.Wallet (==) :: ErrSubmitTransaction -> ErrSubmitTransaction -> Bool Source # (/=) :: ErrSubmitTransaction -> ErrSubmitTransaction -> Bool Source # |
|
Show ErrSubmitTransaction Source # | |
Defined in Cardano.Wallet |
|
IsServerError ErrSubmitTransaction Source # | |
Defined in Cardano.Wallet.Api.Server |
Migration
createMigrationPlan :: forall ctx k s. ( HasDBLayer IO s k ctx, HasNetworkLayer IO ctx, HasTransactionLayer k ctx) => ctx -> AnyCardanoEra -> WalletId -> Withdrawal -> ExceptT ErrCreateMigrationPlan IO MigrationPlan Source #
migrationPlanToSelectionWithdrawals :: MigrationPlan -> Withdrawal -> NonEmpty Address -> Maybe ( NonEmpty ( SelectionWithoutChange , Withdrawal )) Source #
type SelectionWithoutChange = SelectionOf Void Source #
data ErrCreateMigrationPlan Source #
Instances
Eq ErrCreateMigrationPlan Source # | |
Defined in Cardano.Wallet |
|
Show ErrCreateMigrationPlan Source # | |
Defined in Cardano.Wallet |
|
Generic ErrCreateMigrationPlan Source # | |
Defined in Cardano.Wallet |
|
IsServerError ErrCreateMigrationPlan Source # | |
Defined in Cardano.Wallet.Api.Server |
|
type Rep ErrCreateMigrationPlan Source # | |
Defined in Cardano.Wallet
type
Rep
ErrCreateMigrationPlan
=
D1
('
MetaData
"ErrCreateMigrationPlan" "Cardano.Wallet" "cardano-wallet-core-2022.7.1-AGKhlyz9liLKN3QqZD1gj" '
False
) (
C1
('
MetaCons
"ErrCreateMigrationPlanEmpty" '
PrefixI
'
False
) (
U1
::
Type
->
Type
)
:+:
C1
('
MetaCons
"ErrCreateMigrationPlanNoSuchWallet" '
PrefixI
'
False
) (
S1
('
MetaSel
('
Nothing
::
Maybe
Symbol
) '
NoSourceUnpackedness
'
NoSourceStrictness
'
DecidedLazy
) (
Rec0
ErrNoSuchWallet
)))
|
Delegation
data PoolRetirementEpochInfo Source #
PoolRetirementEpochInfo | |
|
Instances
Eq PoolRetirementEpochInfo Source # | |
Defined in Cardano.Wallet |
|
Show PoolRetirementEpochInfo Source # | |
Defined in Cardano.Wallet |
|
Generic PoolRetirementEpochInfo Source # | |
Defined in Cardano.Wallet |
|
type Rep PoolRetirementEpochInfo Source # | |
Defined in Cardano.Wallet
type
Rep
PoolRetirementEpochInfo
=
D1
('
MetaData
"PoolRetirementEpochInfo" "Cardano.Wallet" "cardano-wallet-core-2022.7.1-AGKhlyz9liLKN3QqZD1gj" '
False
) (
C1
('
MetaCons
"PoolRetirementEpochInfo" '
PrefixI
'
True
) (
S1
('
MetaSel
('
Just
"currentEpoch") '
NoSourceUnpackedness
'
NoSourceStrictness
'
DecidedLazy
) (
Rec0
EpochNo
)
:*:
S1
('
MetaSel
('
Just
"retirementEpoch") '
NoSourceUnpackedness
'
NoSourceStrictness
'
DecidedLazy
) (
Rec0
EpochNo
)))
|
:: forall ctx s k. ( HasDBLayer IO s k ctx, HasNetworkLayer IO ctx, HasLogger IO WalletWorkerLog ctx) | |
=> ctx | |
-> EpochNo | |
-> Set PoolId | |
-> PoolId | |
-> PoolLifeCycleStatus | |
-> WalletId | |
-> ExceptT ErrStakePoolDelegation IO ( DelegationAction , Maybe Coin ) |
snd is the deposit |
quitStakePool :: forall ctx s k. HasDBLayer IO s k ctx => ctx -> WalletId -> Withdrawal -> ExceptT ErrStakePoolDelegation IO DelegationAction Source #
Helper function to factor necessary logic for quitting a stake pool.
guardJoin :: Set PoolId -> WalletDelegation -> PoolId -> Maybe PoolRetirementEpochInfo -> Either ErrCannotJoin () Source #
guardQuit :: WalletDelegation -> Withdrawal -> Coin -> Either ErrCannotQuit () Source #
data ErrStakePoolDelegation Source #
ErrStakePoolDelegationNoSuchWallet ErrNoSuchWallet | |
ErrStakePoolJoin ErrCannotJoin | |
ErrStakePoolQuit ErrCannotQuit |
Instances
Fee Estimation
data FeeEstimation Source #
Result of a fee estimation process given a wallet and payment order.
Instances
Eq FeeEstimation Source # | |
Defined in Cardano.Wallet (==) :: FeeEstimation -> FeeEstimation -> Bool Source # (/=) :: FeeEstimation -> FeeEstimation -> Bool Source # |
|
Show FeeEstimation Source # | |
Defined in Cardano.Wallet |
|
Generic FeeEstimation Source # | |
Defined in Cardano.Wallet from :: FeeEstimation -> Rep FeeEstimation x Source # to :: Rep FeeEstimation x -> FeeEstimation Source # |
|
NFData FeeEstimation Source # | |
Defined in Cardano.Wallet rnf :: FeeEstimation -> () Source # |
|
type Rep FeeEstimation Source # | |
Defined in Cardano.Wallet
type
Rep
FeeEstimation
=
D1
('
MetaData
"FeeEstimation" "Cardano.Wallet" "cardano-wallet-core-2022.7.1-AGKhlyz9liLKN3QqZD1gj" '
False
) (
C1
('
MetaCons
"FeeEstimation" '
PrefixI
'
True
) (
S1
('
MetaSel
('
Just
"estMinFee") '
NoSourceUnpackedness
'
NoSourceStrictness
'
DecidedLazy
) (
Rec0
Word64
)
:*:
S1
('
MetaSel
('
Just
"estMaxFee") '
NoSourceUnpackedness
'
NoSourceStrictness
'
DecidedLazy
) (
Rec0
Word64
)))
|
estimateFee :: forall m. Monad m => ExceptT ErrSelectAssets m Coin -> ExceptT ErrSelectAssets m FeeEstimation Source #
Estimate the transaction fee for a given coin selection algorithm by
repeatedly running it (100 times) and collecting the results. In the returned
FeeEstimation
, the minimum fee is that which 90% of the sampled fees are
greater than. The maximum fee is the highest fee observed in the samples.
calcMinimumDeposit :: forall ctx s k. ( HasDBLayer IO s k ctx, HasNetworkLayer IO ctx) => ctx -> WalletId -> ExceptT ErrSelectAssets IO Coin Source #
Calculate the minimum deposit necessary if a given wallet wanted to delegate to a pool. Said differently, this return either 0, or the value of the key deposit protocol parameters if the wallet has no registered stake key.
calcMinimumCoinValues :: forall ctx k f. ( HasTransactionLayer k ctx, HasNetworkLayer IO ctx, Applicative f) => ctx -> AnyCardanoEra -> f TxOut -> IO (f Coin ) Source #
Calculate the minimum coin values required for a bunch of specified outputs.
Transaction
forgetTx :: forall ctx s k. HasDBLayer IO s k ctx => ctx -> WalletId -> Hash "Tx" -> ExceptT ErrRemoveTx IO () Source #
Remove a pending or expired transaction from the transaction history. This happens at the request of the user. If the transaction is already on chain, or is missing from the transaction history, an error will be returned.
If a
Pending
transaction is removed, but later appears in a block, it will
be added back to the transaction history.
listTransactions :: forall ctx s k. ( HasDBLayer IO s k ctx, HasNetworkLayer IO ctx) => ctx -> WalletId -> Maybe Coin -> Maybe UTCTime -> Maybe UTCTime -> SortOrder -> ExceptT ErrListTransactions IO [ TransactionInfo ] Source #
List all transactions and metadata from history for a given wallet.
listAssets :: forall s k ctx. ( HasDBLayer IO s k ctx, IsOurs s Address ) => ctx -> WalletId -> ExceptT ErrNoSuchWallet IO ( Set AssetId ) Source #
Extract assets associated with a given wallet from its transaction history.
getTransaction :: forall ctx s k. HasDBLayer IO s k ctx => ctx -> WalletId -> Hash "Tx" -> ExceptT ErrGetTransaction IO TransactionInfo Source #
Get transaction and metadata from history for a given wallet.
submitExternalTx :: forall ctx k. ( HasNetworkLayer IO ctx, HasTransactionLayer k ctx, HasLogger IO TxSubmitLog ctx) => ctx -> SealedTx -> ExceptT ErrPostTx IO Tx Source #
Broadcast an externally-signed transaction to the network.
NOTE: external transactions will not be added to the LocalTxSubmission pool, so the user must retry submission themselves.
submitTx :: forall ctx s k. ( HasNetworkLayer IO ctx, HasDBLayer IO s k ctx, HasLogger IO WalletWorkerLog ctx) => ctx -> WalletId -> ( Tx , TxMeta , SealedTx ) -> ExceptT ErrSubmitTx IO () Source #
Broadcast a (signed) transaction to the network.
balanceTransaction :: forall era m s k ctx. ( HasTransactionLayer k ctx, GenChange s, MonadRandom m, HasLogger m WalletWorkerLog ctx, IsShelleyBasedEra era, BoundedAddressLength k) => ctx -> ArgGenChange s -> ( ProtocolParameters , ProtocolParameters ) -> TimeInterpreter ( Either PastHorizonException ) -> ( UTxOIndex WalletUTxO , Wallet s, Set Tx ) -> PartialTx era -> ExceptT ErrBalanceTx m ( Tx era) Source #
A
PartialTx
is an an unbalanced
SealedTx
along with the necessary
information to balance it.
The
$sel:inputs:PartialTx
and
$sel:redeemers:PartialTx
must match the binary transaction contained in
the
sealedTx
.
Instances
Eq ( PartialTx era) Source # | |
Show ( PartialTx era) Source # | |
Generic ( PartialTx era) Source # | |
Buildable ( PartialTx era) Source # | |
type Rep ( PartialTx era) Source # | |
Defined in Cardano.Wallet
type
Rep
(
PartialTx
era) =
D1
('
MetaData
"PartialTx" "Cardano.Wallet" "cardano-wallet-core-2022.7.1-AGKhlyz9liLKN3QqZD1gj" '
False
) (
C1
('
MetaCons
"PartialTx" '
PrefixI
'
True
) (
S1
('
MetaSel
('
Just
"tx") '
NoSourceUnpackedness
'
NoSourceStrictness
'
DecidedLazy
) (
Rec0
(
Tx
era))
:*:
(
S1
('
MetaSel
('
Just
"inputs") '
NoSourceUnpackedness
'
NoSourceStrictness
'
DecidedLazy
) (
Rec0
[(
TxIn
,
TxOut
,
Maybe
(
Hash
"Datum"))])
:*:
S1
('
MetaSel
('
Just
"redeemers") '
NoSourceUnpackedness
'
NoSourceStrictness
'
DecidedLazy
) (
Rec0
[
Redeemer
]))))
|
data LocalTxSubmissionConfig Source #
Parameters for
runLocalTxSubmissionPool
LocalTxSubmissionConfig | |
|
Instances
Eq LocalTxSubmissionConfig Source # | |
Defined in Cardano.Wallet |
|
Show LocalTxSubmissionConfig Source # | |
Defined in Cardano.Wallet |
|
Generic LocalTxSubmissionConfig Source # | |
Defined in Cardano.Wallet |
|
type Rep LocalTxSubmissionConfig Source # | |
Defined in Cardano.Wallet
type
Rep
LocalTxSubmissionConfig
=
D1
('
MetaData
"LocalTxSubmissionConfig" "Cardano.Wallet" "cardano-wallet-core-2022.7.1-AGKhlyz9liLKN3QqZD1gj" '
False
) (
C1
('
MetaCons
"LocalTxSubmissionConfig" '
PrefixI
'
True
) (
S1
('
MetaSel
('
Just
"rateLimit") '
NoSourceUnpackedness
'
NoSourceStrictness
'
DecidedLazy
) (
Rec0
DiffTime
)
:*:
S1
('
MetaSel
('
Just
"blockInterval") '
NoSourceUnpackedness
'
NoSourceStrictness
'
DecidedLazy
) (
Rec0
Word64
)))
|
defaultLocalTxSubmissionConfig :: LocalTxSubmissionConfig Source #
The current default is to resubmit any pending transaction about once every 10 blocks.
The default rate limit for checking the pending list is 1000ms.
runLocalTxSubmissionPool :: forall ctx s k m. ( MonadUnliftIO m, MonadMonotonicTime m, HasLogger IO WalletWorkerLog ctx, HasNetworkLayer m ctx, HasDBLayer m s k ctx) => LocalTxSubmissionConfig -> ctx -> WalletId -> m () Source #
Continuous process which monitors the chain tip and retries submission of pending transactions as the chain lengthens.
Regardless of the frequency of chain updates, this function won't re-query
the database faster than the configured
$sel:rateLimit:LocalTxSubmissionConfig
.
This only exits if the network layer
watchNodeTip
function exits.
data ErrMkTransaction Source #
ErrMkTransactionNoSuchWallet WalletId | |
ErrMkTransactionTxBodyError Text |
We failed to construct a transaction for some reasons. |
ErrMkTransactionInvalidEra AnyCardanoEra |
Should never happen, means that that we have programmatically provided an invalid era. |
ErrMkTransactionJoinStakePool ErrCannotJoin | |
ErrMkTransactionQuitStakePool ErrCannotQuit | |
ErrMkTransactionIncorrectTTL PastHorizonException |
Instances
data ErrSubmitTx Source #
Errors that can occur when submitting a signed transaction to the network.
ErrSubmitTxNetwork ErrPostTx | |
ErrSubmitTxNoSuchWallet ErrNoSuchWallet | |
ErrSubmitTxImpossible ErrNoSuchTransaction |
Instances
Eq ErrSubmitTx Source # | |
Defined in Cardano.Wallet (==) :: ErrSubmitTx -> ErrSubmitTx -> Bool Source # (/=) :: ErrSubmitTx -> ErrSubmitTx -> Bool Source # |
|
Show ErrSubmitTx Source # | |
Defined in Cardano.Wallet |
|
IsServerError ErrSubmitTx Source # | |
Defined in Cardano.Wallet.Api.Server |
data ErrRemoveTx Source #
Can't remove pending or expired transaction.
ErrRemoveTxNoSuchWallet ErrNoSuchWallet | |
ErrRemoveTxNoSuchTransaction ErrNoSuchTransaction | |
ErrRemoveTxAlreadyInLedger ( Hash "Tx") |
Instances
Eq ErrRemoveTx Source # | |
Defined in Cardano.Wallet.DB (==) :: ErrRemoveTx -> ErrRemoveTx -> Bool Source # (/=) :: ErrRemoveTx -> ErrRemoveTx -> Bool Source # |
|
Show ErrRemoveTx Source # | |
Defined in Cardano.Wallet.DB |
|
IsServerError ErrRemoveTx Source # | |
Defined in Cardano.Wallet.Api.Server |
Error while trying to send a transaction
Instances
Eq ErrPostTx Source # | |
Show ErrPostTx Source # | |
Generic ErrPostTx Source # | |
ToText ErrPostTx Source # | |
IsServerError ErrPostTx Source # | |
Defined in Cardano.Wallet.Api.Server toServerError :: ErrPostTx -> ServerError Source # |
|
type Rep ErrPostTx Source # | |
Defined in Cardano.Wallet.Network
type
Rep
ErrPostTx
=
D1
('
MetaData
"ErrPostTx" "Cardano.Wallet.Network" "cardano-wallet-core-2022.7.1-AGKhlyz9liLKN3QqZD1gj" '
True
) (
C1
('
MetaCons
"ErrPostTxValidationError" '
PrefixI
'
False
) (
S1
('
MetaSel
('
Nothing
::
Maybe
Symbol
) '
NoSourceUnpackedness
'
NoSourceStrictness
'
DecidedLazy
) (
Rec0
Text
)))
|
data ErrListTransactions Source #
Errors that can occur when trying to list transactions.
Instances
Show ErrListTransactions Source # | |
Defined in Cardano.Wallet |
|
IsServerError ErrListTransactions Source # | |
Defined in Cardano.Wallet.Api.Server |
data ErrGetTransaction Source #
Errors that can occur when trying to get transaction.
ErrGetTransactionNoSuchWallet ErrNoSuchWallet | |
ErrGetTransactionNoSuchTransaction ErrNoSuchTransaction |
Instances
Eq ErrGetTransaction Source # | |
Defined in Cardano.Wallet (==) :: ErrGetTransaction -> ErrGetTransaction -> Bool Source # (/=) :: ErrGetTransaction -> ErrGetTransaction -> Bool Source # |
|
Show ErrGetTransaction Source # | |
Defined in Cardano.Wallet |
|
IsServerError ErrGetTransaction Source # | |
Defined in Cardano.Wallet.Api.Server |
data ErrNoSuchTransaction Source #
Indicates that the specified transaction hash is not found in the transaction history of the given wallet.
ErrNoSuchTransaction WalletId ( Hash "Tx") |
Instances
Eq ErrNoSuchTransaction Source # | |
Defined in Cardano.Wallet.DB (==) :: ErrNoSuchTransaction -> ErrNoSuchTransaction -> Bool Source # (/=) :: ErrNoSuchTransaction -> ErrNoSuchTransaction -> Bool Source # |
|
Show ErrNoSuchTransaction Source # | |
Defined in Cardano.Wallet.DB |
|
IsServerError ErrNoSuchTransaction Source # | |
Defined in Cardano.Wallet.Api.Server |
data ErrStartTimeLaterThanEndTime Source #
Indicates that the specified start time is later than the specified end time.
Instances
Eq ErrStartTimeLaterThanEndTime Source # | |
Defined in Cardano.Wallet |
|
Show ErrStartTimeLaterThanEndTime Source # | |
Defined in Cardano.Wallet |
|
IsServerError ErrStartTimeLaterThanEndTime Source # | |
Defined in Cardano.Wallet.Api.Server |
data ErrWitnessTx Source #
Errors that can occur when signing a transaction.
ErrWitnessTxSignTx ErrSignTx | |
ErrWitnessTxNoSuchWallet ErrNoSuchWallet | |
ErrWitnessTxWithRootKey ErrWithRootKey | |
ErrWitnessTxIncorrectTTL PastHorizonException |
Instances
Eq ErrWitnessTx Source # | |
Defined in Cardano.Wallet (==) :: ErrWitnessTx -> ErrWitnessTx -> Bool Source # (/=) :: ErrWitnessTx -> ErrWitnessTx -> Bool Source # |
|
Show ErrWitnessTx Source # | |
Defined in Cardano.Wallet |
|
IsServerError ErrWitnessTx Source # | |
Defined in Cardano.Wallet.Api.Server |
Root Key
withRootKey :: forall ctx s k e a. HasDBLayer IO s k ctx => ctx -> WalletId -> Passphrase "user" -> ( ErrWithRootKey -> e) -> (k ' RootK XPrv -> PassphraseScheme -> ExceptT e IO a) -> ExceptT e IO a Source #
Execute an action which requires holding a root XPrv.
withRootKey
takes a callback function with two arguments:
- The encrypted root private key itself
- The underlying passphrase scheme (legacy or new)
Caller are then expected to use
preparePassphrase
with the given scheme in
order to "prepare" the passphrase to be used by other function. This does
nothing for the new encryption, but for the legacy encryption with Scrypt,
passphrases needed to first be CBOR serialized and blake2b_256 hashed.
@@
withRootKey
ctx
s
k ctx wid pwd OnError $ xprv scheme ->
changePassphrase (preparePassphrase scheme pwd) newPwd xprv
@@@
derivePublicKey :: forall ctx s k. ( HasDBLayer IO s k ctx, SoftDerivation k, GetAccount s k) => ctx -> WalletId -> Role -> DerivationIndex -> ExceptT ErrDerivePublicKey IO (k ' AddressK XPub ) Source #
getAccountPublicKeyAtIndex :: forall ctx s k. ( HasDBLayer IO s k ctx, WalletKey k, GetPurpose k) => ctx -> WalletId -> Passphrase "user" -> DerivationIndex -> Maybe DerivationIndex -> ExceptT ErrReadAccountPublicKey IO (k ' AccountK XPub ) Source #
Retrieve any public account key of a wallet.
readAccountPublicKey :: forall ctx s k. ( HasDBLayer IO s k ctx, GetAccount s k) => ctx -> WalletId -> ExceptT ErrReadAccountPublicKey IO (k ' AccountK XPub ) Source #
Retrieve current public account key of a wallet.
signMetadataWith :: forall ctx s k n. ( HasDBLayer IO s k ctx, HardDerivation k, AddressIndexDerivationType k ~ ' Soft , WalletKey k, s ~ SeqState n k) => ctx -> WalletId -> Passphrase "user" -> ( Role , DerivationIndex ) -> TxMetadata -> ExceptT ErrSignMetadataWith IO ( Signature TxMetadata ) Source #
Sign an arbitrary transaction metadata object with a private key belonging to the wallet's account.
This is experimental, and will likely be replaced by a more robust to arbitrary message signing using COSE, or a subset of it.
data ErrWithRootKey Source #
Errors that can occur when trying to perform an operation on a wallet that requires a private key, but where none is attached to the wallet.
ErrWithRootKeyNoRootKey WalletId | |
ErrWithRootKeyWrongPassphrase WalletId ErrWrongPassphrase | |
ErrWithRootKeyWrongMnemonic WalletId |
Instances
Eq ErrWithRootKey Source # | |
Defined in Cardano.Wallet (==) :: ErrWithRootKey -> ErrWithRootKey -> Bool Source # (/=) :: ErrWithRootKey -> ErrWithRootKey -> Bool Source # |
|
Show ErrWithRootKey Source # | |
Defined in Cardano.Wallet |
|
IsServerError ErrWithRootKey Source # | |
Defined in Cardano.Wallet.Api.Server |
data ErrWrongPassphrase Source #
Indicate a failure when checking for a given
Passphrase
match
Instances
data ErrSignMetadataWith Source #
ErrSignMetadataWithRootKey ErrWithRootKey |
The wallet exists, but there's no root key attached to it |
ErrSignMetadataWithNoSuchWallet ErrNoSuchWallet |
The wallet doesn't exist? |
ErrSignMetadataWithInvalidIndex ( ErrInvalidDerivationIndex ' Soft ' AddressK ) |
User provided a derivation index outside of the
|
Instances
Eq ErrSignMetadataWith Source # | |
Defined in Cardano.Wallet (==) :: ErrSignMetadataWith -> ErrSignMetadataWith -> Bool Source # (/=) :: ErrSignMetadataWith -> ErrSignMetadataWith -> Bool Source # |
|
Show ErrSignMetadataWith Source # | |
Defined in Cardano.Wallet |
|
IsServerError ErrSignMetadataWith Source # | |
Defined in Cardano.Wallet.Api.Server |
data ErrDerivePublicKey Source #
ErrDerivePublicKeyNoSuchWallet ErrNoSuchWallet |
The wallet doesn't exist? |
ErrDerivePublicKeyInvalidIndex ( ErrInvalidDerivationIndex ' Soft ' AddressK ) |
User provided a derivation index outside of the
|
Instances
Eq ErrDerivePublicKey Source # | |
Defined in Cardano.Wallet (==) :: ErrDerivePublicKey -> ErrDerivePublicKey -> Bool Source # (/=) :: ErrDerivePublicKey -> ErrDerivePublicKey -> Bool Source # |
|
Show ErrDerivePublicKey Source # | |
Defined in Cardano.Wallet |
|
IsServerError ErrDerivePublicKey Source # | |
Defined in Cardano.Wallet.Api.Server |
data ErrReadAccountPublicKey Source #
ErrReadAccountPublicKeyNoSuchWallet ErrNoSuchWallet |
The wallet doesn't exist? |
ErrReadAccountPublicKeyInvalidAccountIndex ( ErrInvalidDerivationIndex ' Hardened ' AccountK ) |
User provided a derivation index for account outside of the
|
ErrReadAccountPublicKeyInvalidPurposeIndex ( ErrInvalidDerivationIndex ' Hardened ' PurposeK ) |
User provided a derivation index for purpose outside of the
|
ErrReadAccountPublicKeyRootKey ErrWithRootKey |
The wallet exists, but there's no root key attached to it |
Instances
Eq ErrReadAccountPublicKey Source # | |
Defined in Cardano.Wallet |
|
Show ErrReadAccountPublicKey Source # | |
Defined in Cardano.Wallet |
|
IsServerError ErrReadAccountPublicKey Source # | |
Defined in Cardano.Wallet.Api.Server |
data ErrInvalidDerivationIndex derivation level Source #
ErrIndexOutOfBound ( Index derivation level) ( Index derivation level) DerivationIndex |
Instances
Eq ( ErrInvalidDerivationIndex derivation level) Source # | |
Defined in Cardano.Wallet (==) :: ErrInvalidDerivationIndex derivation level -> ErrInvalidDerivationIndex derivation level -> Bool Source # (/=) :: ErrInvalidDerivationIndex derivation level -> ErrInvalidDerivationIndex derivation level -> Bool Source # |
|
Show ( ErrInvalidDerivationIndex derivation level) Source # | |
Defined in Cardano.Wallet |
|
IsServerError ( ErrInvalidDerivationIndex ' Hardened level) Source # | |
Defined in Cardano.Wallet.Api.Server toServerError :: ErrInvalidDerivationIndex ' Hardened level -> ServerError Source # |
|
IsServerError ( ErrInvalidDerivationIndex ' Soft level) Source # | |
Defined in Cardano.Wallet.Api.Server toServerError :: ErrInvalidDerivationIndex ' Soft level -> ServerError Source # |
Utilities
throttle :: ( MonadUnliftIO m, MonadMonotonicTime m) => DiffTime -> ( Time -> a -> m ()) -> m (a -> m ()) Source #
Return a function to run an action at most once every _interval_.
guardHardIndex :: Monad m => DerivationIndex -> ExceptT ( ErrInvalidDerivationIndex ' Hardened level) m ( Index ' Hardened whatever) Source #
withNoSuchWallet :: Monad m => WalletId -> m ( Maybe a) -> ExceptT ErrNoSuchWallet m a Source #
posAndNegFromCardanoValue :: Value -> ( TokenBundle , TokenBundle ) Source #
Convert a
Value
into a positive and negative component. Useful
to convert the potentially negative balance of a partial tx into
TokenBundles.
Logging
data WalletWorkerLog Source #
Log messages for actions running within a wallet worker context.
Instances
Eq WalletWorkerLog Source # | |
Defined in Cardano.Wallet (==) :: WalletWorkerLog -> WalletWorkerLog -> Bool Source # (/=) :: WalletWorkerLog -> WalletWorkerLog -> Bool Source # |
|
Show WalletWorkerLog Source # | |
Defined in Cardano.Wallet |
|
ToText WalletWorkerLog Source # | |
Defined in Cardano.Wallet toText :: WalletWorkerLog -> Text Source # |
|
HasPrivacyAnnotation WalletWorkerLog Source # | |
Defined in Cardano.Wallet getPrivacyAnnotation :: WalletWorkerLog -> PrivacyAnnotation |
|
HasSeverityAnnotation WalletWorkerLog Source # | |
Defined in Cardano.Wallet getSeverityAnnotation :: WalletWorkerLog -> Severity |
data WalletFollowLog Source #
Log messages arising from the restore and follow process.
MsgDiscoveredDelegationCert SlotNo DelegationCertificate | |
MsgCheckpoint BlockHeader | |
MsgDiscoveredTxs [( Tx , TxMeta )] | |
MsgDiscoveredTxsContent [( Tx , TxMeta )] |
Instances
Eq WalletFollowLog Source # | |
Defined in Cardano.Wallet (==) :: WalletFollowLog -> WalletFollowLog -> Bool Source # (/=) :: WalletFollowLog -> WalletFollowLog -> Bool Source # |
|
Show WalletFollowLog Source # | |
Defined in Cardano.Wallet |
|
ToText WalletFollowLog Source # | |
Defined in Cardano.Wallet toText :: WalletFollowLog -> Text Source # |
|
HasPrivacyAnnotation WalletFollowLog Source # | |
Defined in Cardano.Wallet getPrivacyAnnotation :: WalletFollowLog -> PrivacyAnnotation |
|
HasSeverityAnnotation WalletFollowLog Source # | |
Defined in Cardano.Wallet getSeverityAnnotation :: WalletFollowLog -> Severity |
Log messages from API server actions running in a wallet worker context.
Instances
Eq WalletLog Source # | |
Show WalletLog Source # | |
ToText WalletLog Source # | |
HasPrivacyAnnotation WalletLog Source # | |
Defined in Cardano.Wallet getPrivacyAnnotation :: WalletLog -> PrivacyAnnotation |
|
HasSeverityAnnotation WalletLog Source # | |
Defined in Cardano.Wallet getSeverityAnnotation :: WalletLog -> Severity |
data TxSubmitLog Source #
MsgSubmitTx Tx TxMeta SealedTx ( BracketLog' ( Either ErrSubmitTx ())) | |
MsgSubmitExternalTx ( Hash "Tx") ( BracketLog' ( Either ErrPostTx Tx )) | |
MsgRetryPostTx ( Hash "Tx") ( BracketLog' ( Either ErrPostTx ())) | |
MsgProcessPendingPool BracketLog |
Instances
Eq TxSubmitLog Source # | |
Defined in Cardano.Wallet (==) :: TxSubmitLog -> TxSubmitLog -> Bool Source # (/=) :: TxSubmitLog -> TxSubmitLog -> Bool Source # |
|
Show TxSubmitLog Source # | |
Defined in Cardano.Wallet |
|
Buildable TxSubmitLog Source # | |
Defined in Cardano.Wallet build :: TxSubmitLog -> Builder Source # |
|
ToText TxSubmitLog Source # | |
Defined in Cardano.Wallet toText :: TxSubmitLog -> Text Source # |
|
HasPrivacyAnnotation TxSubmitLog Source # | |
Defined in Cardano.Wallet getPrivacyAnnotation :: TxSubmitLog -> PrivacyAnnotation |
|
HasSeverityAnnotation TxSubmitLog Source # | |
Defined in Cardano.Wallet getSeverityAnnotation :: TxSubmitLog -> Severity |