{-# LANGUAGE AllowAmbiguousTypes #-}
{-# LANGUAGE ConstraintKinds #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE PolyKinds #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeOperators #-}
module Cardano.Wallet.Api
(
Api
, ApiV2
, PostData
, Wallets
, DeleteWallet
, GetWallet
, ListWallets
, PostWallet
, PutWallet
, PutWalletPassphrase
, GetUTxOsStatistics
, GetWalletUtxoSnapshot
, WalletKeys
, GetWalletKey
, SignMetadata
, PostAccountKey
, GetAccountKey
, GetPolicyKey
, PostPolicyKey
, PostPolicyId
, Assets
, ListAssets
, GetAsset
, GetAssetDefault
, Addresses
, ListAddresses
, InspectAddress
, PostAnyAddress
, CoinSelections
, SelectCoins
, ShelleyTransactions
, ConstructTransaction
, SignTransaction
, ListTransactions
, GetTransaction
, DeleteTransaction
, CreateTransactionOld
, PostTransactionFeeOld
, BalanceTransaction
, DecodeTransaction
, SubmitTransaction
, StakePools
, ListStakePools
, JoinStakePool
, QuitStakePool
, DelegationFee
, ListStakeKeys
, PostPoolMaintenance
, GetPoolMaintenance
, ShelleyMigrations
, MigrateShelleyWallet
, CreateShelleyWalletMigrationPlan
, Settings
, PutSettings
, GetSettings
, ByronWallets
, DeleteByronWallet
, GetByronWallet
, ListByronWallets
, PostByronWallet
, PutByronWallet
, GetByronUTxOsStatistics
, GetByronWalletUtxoSnapshot
, PutByronWalletPassphrase
, ByronAssets
, ListByronAssets
, GetByronAsset
, GetByronAssetDefault
, ByronAddresses
, PostByronAddress
, PutByronAddress
, PutByronAddresses
, ListByronAddresses
, ByronCoinSelections
, ByronSelectCoins
, ByronTransactions
, ConstructByronTransaction
, SignByronTransaction
, ListByronTransactions
, GetByronTransaction
, DeleteByronTransaction
, CreateByronTransactionOld
, PostByronTransactionFeeOld
, ByronMigrations
, MigrateByronWallet
, CreateByronWalletMigrationPlan
, Network
, GetNetworkInformation
, GetNetworkParameters
, GetNetworkClock
, SMASH
, GetCurrentSMASHHealth
, SharedWallets
, PostSharedWallet
, GetSharedWallet
, ListSharedWallets
, PatchSharedWalletInPayment
, PatchSharedWalletInDelegation
, DeleteSharedWallet
, SharedWalletKeys
, GetSharedWalletKey
, PostAccountKeyShared
, GetAccountKeyShared
, SharedAddresses
, ListSharedAddresses
, SharedTransactions
, ConstructSharedTransaction
, DecodeSharedTransaction
, Proxy_
, PostExternalTransaction
, ApiLayer (..)
, HasWorkerRegistry
, workerRegistry
, WalletLock (..)
, walletLocks
, HasDBFactory
, dbFactory
, tokenMetadataClient
, HasTokenMetadataClient
) where
import Prelude
import Cardano.Wallet
( TxSubmitLog, WalletLayer (..), WalletWorkerLog )
import Cardano.Wallet.Api.Types
( AnyAddress
, ApiAccountKey
, ApiAccountKeyShared
, ApiAddressData
, ApiAddressIdT
, ApiAddressInspect
, ApiAddressInspectData
, ApiAddressT
, ApiAsset
, ApiBalanceTransactionPostDataT
, ApiByronWallet
, ApiCoinSelectionT
, ApiConstructTransactionDataT
, ApiConstructTransactionT
, ApiDecodedTransactionT
, ApiFee
, ApiHealthCheck
, ApiMaintenanceAction
, ApiMaintenanceActionPostData
, ApiNetworkClock
, ApiNetworkInformation
, ApiNetworkParameters
, ApiPolicyId
, ApiPolicyKey
, ApiPoolId
, ApiPostAccountKeyData
, ApiPostAccountKeyDataWithPurpose
, ApiPostPolicyIdData
, ApiPostPolicyKeyData
, ApiPostRandomAddressData
, ApiPutAddressesDataT
, ApiSelectCoinsDataT
, ApiSerialisedTransaction
, ApiSharedWallet
, ApiSharedWalletPatchData
, ApiSharedWalletPostData
, ApiSignTransactionPostData
, ApiStakeKeysT
, ApiT
, ApiTransactionT
, ApiTxId
, ApiUtxoStatistics
, ApiVerificationKeyShared
, ApiVerificationKeyShelley
, ApiWallet
, ApiWalletMigrationPlan
, ApiWalletMigrationPlanPostDataT
, ApiWalletMigrationPostDataT
, ApiWalletPassphrase
, ApiWalletSignData
, ApiWalletUtxoSnapshot
, ByronWalletPutPassphraseData
, Iso8601Time
, KeyFormat
, MinWithdrawal
, PostTransactionFeeOldDataT
, PostTransactionOldDataT
, SettingsPutData
, SomeByronWalletPostData
, WalletOrAccountPostData
, WalletPutData
, WalletPutPassphraseData
)
import Cardano.Wallet.DB
( DBFactory, DBLayer )
import Cardano.Wallet.Network
( NetworkLayer )
import Cardano.Wallet.Primitive.AddressDerivation
( Depth, DerivationIndex, Role )
import Cardano.Wallet.Primitive.Types
( Block
, NetworkParameters
, SmashServer (..)
, SortOrder (..)
, WalletId (..)
)
import Cardano.Wallet.Primitive.Types.Address
( AddressState )
import Cardano.Wallet.Primitive.Types.Coin
( Coin (..) )
import Cardano.Wallet.Primitive.Types.TokenPolicy
( TokenName, TokenPolicyId )
import Cardano.Wallet.Primitive.Types.Tx
( SealedTx )
import Cardano.Wallet.Registry
( HasWorkerCtx (..), WorkerLog, WorkerRegistry )
import Cardano.Wallet.TokenMetadata
( TokenMetadataClient )
import Cardano.Wallet.Transaction
( TransactionLayer )
import Control.Concurrent.Concierge
( Concierge )
import Control.Tracer
( Tracer, contramap )
import Data.ByteString
( ByteString )
import Data.Generics.Internal.VL.Lens
( Lens' )
import Data.Generics.Labels
()
import Data.Generics.Product.Typed
( HasType, typed )
import Data.Kind
( Type )
import Data.List.NonEmpty
( NonEmpty )
import GHC.Generics
( Generic )
import Servant.API
( (:<|>)
, (:>)
, Capture
, JSON
, OctetStream
, QueryFlag
, QueryParam
, ReqBody
)
import Servant.API.Verbs
( DeleteAccepted
, DeleteNoContent
, Get
, Patch
, Post
, PostAccepted
, PostCreated
, PostNoContent
, Put
, PutAccepted
, PutNoContent
)
import qualified Cardano.Wallet.Primitive.Types as W
type ApiV2 n apiPool = "v2" :> Api n apiPool
type Api n apiPool =
Wallets
:<|> WalletKeys
:<|> Assets
:<|> Addresses n
:<|> CoinSelections n
:<|> ShelleyTransactions n
:<|> ShelleyMigrations n
:<|> StakePools n apiPool
:<|> ByronWallets
:<|> ByronAssets
:<|> ByronAddresses n
:<|> ByronCoinSelections n
:<|> ByronTransactions n
:<|> ByronMigrations n
:<|> Network
:<|> Proxy_
:<|> Settings
:<|> SMASH
:<|> SharedWallets
:<|> SharedWalletKeys
:<|> SharedAddresses n
:<|> SharedTransactions n
type Wallets =
DeleteWallet
:<|> GetWallet
:<|> ListWallets
:<|> PostWallet
:<|> PutWallet
:<|> PutWalletPassphrase
:<|> GetWalletUtxoSnapshot
:<|> GetUTxOsStatistics
type DeleteWallet = "wallets"
:> Capture "walletId" (ApiT WalletId)
:> DeleteNoContent
type GetWallet = "wallets"
:> Capture "walletId" (ApiT WalletId)
:> Get '[JSON] ApiWallet
type ListWallets = "wallets"
:> Get '[JSON] [ApiWallet]
type PostWallet = "wallets"
:> ReqBody '[JSON] (PostData ApiWallet)
:> PostCreated '[JSON] ApiWallet
type PutWallet = "wallets"
:> Capture "walletId" (ApiT WalletId)
:> ReqBody '[JSON] WalletPutData
:> Put '[JSON] ApiWallet
type PutWalletPassphrase = "wallets"
:> Capture "walletId" (ApiT WalletId)
:> "passphrase"
:> ReqBody '[JSON] WalletPutPassphraseData
:> PutNoContent
type GetWalletUtxoSnapshot = "wallets"
:> Capture "walletId" (ApiT WalletId)
:> "utxo"
:> Get '[JSON] ApiWalletUtxoSnapshot
type GetUTxOsStatistics = "wallets"
:> Capture "walletId" (ApiT WalletId)
:> "statistics"
:> "utxos"
:> Get '[JSON] ApiUtxoStatistics
type WalletKeys =
GetWalletKey
:<|> SignMetadata
:<|> PostAccountKey
:<|> GetAccountKey
:<|> GetPolicyKey
:<|> PostPolicyKey
:<|> PostPolicyId
type GetWalletKey = "wallets"
:> Capture "walletId" (ApiT WalletId)
:> "keys"
:> Capture "role" (ApiT Role)
:> Capture "index" (ApiT DerivationIndex)
:> QueryParam "hash" Bool
:> Get '[JSON] ApiVerificationKeyShelley
type SignMetadata = "wallets"
:> Capture "walletId" (ApiT WalletId)
:> "signatures"
:> Capture "role" (ApiT Role)
:> Capture "index" (ApiT DerivationIndex)
:> ReqBody '[JSON] ApiWalletSignData
:> Post '[OctetStream] ByteString
type PostAccountKey = "wallets"
:> Capture "walletId" (ApiT WalletId)
:> "keys"
:> Capture "index" (ApiT DerivationIndex)
:> ReqBody '[JSON] ApiPostAccountKeyDataWithPurpose
:> PostAccepted '[JSON] ApiAccountKey
type GetAccountKey = "wallets"
:> Capture "walletId" (ApiT WalletId)
:> "keys"
:> QueryParam "format" KeyFormat
:> Get '[JSON] ApiAccountKey
type GetPolicyKey = "wallets"
:> Capture "walletId" (ApiT WalletId)
:> "policy-key"
:> QueryParam "hash" Bool
:> Get '[JSON] ApiPolicyKey
type PostPolicyKey = "wallets"
:> Capture "walletId" (ApiT WalletId)
:> "policy-key"
:> QueryParam "hash" Bool
:> ReqBody '[JSON] ApiPostPolicyKeyData
:> PostAccepted '[JSON] ApiPolicyKey
type PostPolicyId = "wallets"
:> Capture "walletId" (ApiT WalletId)
:> "policy-id"
:> ReqBody '[JSON] ApiPostPolicyIdData
:> PostAccepted '[JSON] ApiPolicyId
type Assets =
ListAssets
:<|> GetAsset
:<|> GetAssetDefault
type ListAssets = "wallets"
:> Capture "walletId" (ApiT WalletId)
:> "assets"
:> Get '[JSON] [ApiAsset]
type GetAsset = "wallets"
:> Capture "walletId" (ApiT WalletId)
:> "assets"
:> Capture "policyId" (ApiT TokenPolicyId)
:> Capture "assetName" (ApiT TokenName)
:> Get '[JSON] ApiAsset
type GetAssetDefault = "wallets"
:> Capture "walletId" (ApiT WalletId)
:> "assets"
:> Capture "policyId" (ApiT TokenPolicyId)
:> Get '[JSON] ApiAsset
type Addresses n =
ListAddresses n
:<|> InspectAddress
:<|> PostAnyAddress n
type ListAddresses n = "wallets"
:> Capture "walletId" (ApiT WalletId)
:> "addresses"
:> QueryParam "state" (ApiT AddressState)
:> Get '[JSON] [ApiAddressT n]
type InspectAddress = "addresses"
:> Capture "addressId" ApiAddressInspectData
:> Get '[JSON] ApiAddressInspect
type PostAnyAddress n = "addresses"
:> ReqBody '[JSON] ApiAddressData
:> PostAccepted '[JSON] AnyAddress
type CoinSelections n =
SelectCoins n
type SelectCoins n = "wallets"
:> Capture "walletId" (ApiT WalletId)
:> "coin-selections"
:> "random"
:> ReqBody '[JSON] (ApiSelectCoinsDataT n)
:> Post '[JSON] (ApiCoinSelectionT n)
type ShelleyTransactions n =
ConstructTransaction n
:<|> SignTransaction n
:<|> ListTransactions n
:<|> GetTransaction n
:<|> DeleteTransaction
:<|> CreateTransactionOld n
:<|> PostTransactionFeeOld n
:<|> BalanceTransaction n
:<|> DecodeTransaction n
:<|> SubmitTransaction
type ConstructTransaction n = "wallets"
:> Capture "walletId" (ApiT WalletId)
:> "transactions-construct"
:> ReqBody '[JSON] (ApiConstructTransactionDataT n)
:> PostAccepted '[JSON] (ApiConstructTransactionT n)
type SignTransaction n = "wallets"
:> Capture "walletId" (ApiT WalletId)
:> "transactions-sign"
:> ReqBody '[JSON] ApiSignTransactionPostData
:> PostAccepted '[JSON] ApiSerialisedTransaction
type CreateTransactionOld n = "wallets"
:> Capture "walletId" (ApiT WalletId)
:> "transactions"
:> ReqBody '[JSON] (PostTransactionOldDataT n)
:> PostAccepted '[JSON] (ApiTransactionT n)
type ListTransactions n = "wallets"
:> Capture "walletId" (ApiT WalletId)
:> "transactions"
:> QueryParam "minWithdrawal" MinWithdrawal
:> QueryParam "start" Iso8601Time
:> QueryParam "end" Iso8601Time
:> QueryParam "order" (ApiT SortOrder)
:> QueryFlag "simple-metadata"
:> Get '[JSON] [ApiTransactionT n]
type GetTransaction n = "wallets"
:> Capture "walletId" (ApiT WalletId)
:> "transactions"
:> Capture "transactionId" ApiTxId
:> QueryFlag "simple-metadata"
:> Get '[JSON] (ApiTransactionT n)
type PostTransactionFeeOld n = "wallets"
:> Capture "walletId" (ApiT WalletId)
:> "payment-fees"
:> ReqBody '[JSON] (PostTransactionFeeOldDataT n)
:> PostAccepted '[JSON] ApiFee
type DeleteTransaction = "wallets"
:> Capture "walletId" (ApiT WalletId)
:> "transactions"
:> Capture "transactionId" ApiTxId
:> DeleteNoContent
type BalanceTransaction n = "wallets"
:> Capture "walletId" (ApiT WalletId)
:> "transactions-balance"
:> ReqBody '[JSON] (ApiBalanceTransactionPostDataT n)
:> PostAccepted '[JSON] ApiSerialisedTransaction
type DecodeTransaction n = "wallets"
:> Capture "walletId" (ApiT WalletId)
:> "transactions-decode"
:> ReqBody '[JSON] ApiSerialisedTransaction
:> PostAccepted '[JSON] (ApiDecodedTransactionT n)
type SubmitTransaction = "wallets"
:> Capture "walletId" (ApiT WalletId)
:> "transactions-submit"
:> ReqBody '[JSON] ApiSerialisedTransaction
:> PostAccepted '[JSON] ApiTxId
type ShelleyMigrations n =
CreateShelleyWalletMigrationPlan n
:<|> MigrateShelleyWallet n
type MigrateShelleyWallet n = "wallets"
:> Capture "walletId" (ApiT WalletId)
:> "migrations"
:> ReqBody '[JSON] (ApiWalletMigrationPostDataT n "user")
:> PostAccepted '[JSON] (NonEmpty (ApiTransactionT n))
type CreateShelleyWalletMigrationPlan n = "wallets"
:> Capture "walletId" (ApiT WalletId)
:> "migrations"
:> "plan"
:> ReqBody '[JSON] (ApiWalletMigrationPlanPostDataT n)
:> PostAccepted '[JSON] (ApiWalletMigrationPlan n)
type StakePools n apiPool =
ListStakePools apiPool
:<|> JoinStakePool n
:<|> QuitStakePool n
:<|> DelegationFee
:<|> ListStakeKeys n
:<|> PostPoolMaintenance
:<|> GetPoolMaintenance
type ListStakePools apiPool = "stake-pools"
:> QueryParam "stake" (ApiT Coin)
:> Get '[JSON] [apiPool]
type JoinStakePool n = "stake-pools"
:> Capture "stakePoolId" ApiPoolId
:> "wallets"
:> Capture "walletId" (ApiT WalletId)
:> ReqBody '[JSON] ApiWalletPassphrase
:> PutAccepted '[JSON] (ApiTransactionT n)
type QuitStakePool n = "stake-pools"
:> "*"
:> "wallets"
:> Capture "walletId" (ApiT WalletId)
:> ReqBody '[JSON] ApiWalletPassphrase
:> DeleteAccepted '[JSON] (ApiTransactionT n)
type ListStakeKeys n = "wallets"
:> Capture "walletId" (ApiT WalletId)
:> "stake-keys"
:> Get '[JSON] (ApiStakeKeysT n)
type DelegationFee = "wallets"
:> Capture "walletId" (ApiT WalletId)
:> "delegation-fees"
:> Get '[JSON] ApiFee
type PostPoolMaintenance = "stake-pools"
:> "maintenance-actions"
:> ReqBody '[JSON] ApiMaintenanceActionPostData
:> PostNoContent
type GetPoolMaintenance = "stake-pools"
:> "maintenance-actions"
:> Get '[JSON] ApiMaintenanceAction
type Settings = PutSettings :<|> GetSettings
type PutSettings = "settings"
:> ReqBody '[JSON] SettingsPutData
:> PutNoContent
type GetSettings = "settings"
:> Get '[JSON] (ApiT W.Settings)
type ByronWallets =
PostByronWallet
:<|> DeleteByronWallet
:<|> GetByronWallet
:<|> ListByronWallets
:<|> PutByronWallet
:<|> GetByronWalletUtxoSnapshot
:<|> GetByronUTxOsStatistics
:<|> PutByronWalletPassphrase
type PostByronWallet = "byron-wallets"
:> ReqBody '[JSON] (PostData ApiByronWallet)
:> PostCreated '[JSON] ApiByronWallet
type DeleteByronWallet = "byron-wallets"
:> Capture "walletId" (ApiT WalletId)
:> DeleteNoContent
type GetByronWallet = "byron-wallets"
:> Capture "walletId" (ApiT WalletId)
:> Get '[JSON] ApiByronWallet
type ListByronWallets = "byron-wallets"
:> Get '[JSON] [ApiByronWallet]
type PutByronWallet = "byron-wallets"
:> Capture "walletId" (ApiT WalletId)
:> ReqBody '[JSON] WalletPutData
:> Put '[JSON] ApiByronWallet
type GetByronWalletUtxoSnapshot = "byron-wallets"
:> Capture "walletId" (ApiT WalletId)
:> "utxo"
:> Get '[JSON] ApiWalletUtxoSnapshot
type GetByronUTxOsStatistics = "byron-wallets"
:> Capture "walletId" (ApiT WalletId)
:> "statistics"
:> "utxos"
:> Get '[JSON] ApiUtxoStatistics
type PutByronWalletPassphrase = "byron-wallets"
:> Capture "walletId" (ApiT WalletId)
:> "passphrase"
:> ReqBody '[JSON] ByronWalletPutPassphraseData
:> PutNoContent
type ByronAssets =
ListByronAssets
:<|> GetByronAsset
:<|> GetByronAssetDefault
type ListByronAssets = "byron-wallets"
:> Capture "walletId" (ApiT WalletId)
:> "assets"
:> Get '[JSON] [ApiAsset]
type GetByronAsset = "byron-wallets"
:> Capture "walletId" (ApiT WalletId)
:> "assets"
:> Capture "policyId" (ApiT TokenPolicyId)
:> Capture "assetName" (ApiT TokenName)
:> Get '[JSON] ApiAsset
type GetByronAssetDefault = "byron-wallets"
:> Capture "walletId" (ApiT WalletId)
:> "assets"
:> Capture "policyId" (ApiT TokenPolicyId)
:> Get '[JSON] ApiAsset
type ByronAddresses n =
PostByronAddress n
:<|> PutByronAddress n
:<|> PutByronAddresses n
:<|> ListByronAddresses n
type PostByronAddress n = "byron-wallets"
:> Capture "walletId" (ApiT WalletId)
:> "addresses"
:> ReqBody '[JSON] ApiPostRandomAddressData
:> PostCreated '[JSON] (ApiAddressT n)
type PutByronAddress n = "byron-wallets"
:> Capture "walletId" (ApiT WalletId)
:> "addresses"
:> Capture "addressId" (ApiAddressIdT n)
:> PutNoContent
type PutByronAddresses n = "byron-wallets"
:> Capture "walletId" (ApiT WalletId)
:> "addresses"
:> ReqBody '[JSON] (ApiPutAddressesDataT n)
:> PutNoContent
type ListByronAddresses n = "byron-wallets"
:> Capture "walletId" (ApiT WalletId)
:> "addresses"
:> QueryParam "state" (ApiT AddressState)
:> Get '[JSON] [ApiAddressT n]
type ByronCoinSelections n =
ByronSelectCoins n
type ByronSelectCoins n = "byron-wallets"
:> Capture "walletId" (ApiT WalletId)
:> "coin-selections"
:> "random"
:> ReqBody '[JSON] (ApiSelectCoinsDataT n)
:> Post '[JSON] (ApiCoinSelectionT n)
type ByronTransactions n =
ConstructByronTransaction n
:<|> SignByronTransaction n
:<|> ListByronTransactions n
:<|> GetByronTransaction n
:<|> DeleteByronTransaction
:<|> CreateByronTransactionOld n
:<|> PostByronTransactionFeeOld n
type ConstructByronTransaction n = "byron-wallets"
:> Capture "walletId" (ApiT WalletId)
:> "transactions-construct"
:> ReqBody '[JSON] (ApiConstructTransactionDataT n)
:> PostAccepted '[JSON] (ApiConstructTransactionT n)
type SignByronTransaction n = "byron-wallets"
:> Capture "walletId" (ApiT WalletId)
:> "transactions-sign"
:> ReqBody '[JSON] ApiSignTransactionPostData
:> PostAccepted '[JSON] ApiSerialisedTransaction
type CreateByronTransactionOld n = "byron-wallets"
:> Capture "walletId" (ApiT WalletId)
:> "transactions"
:> ReqBody '[JSON] (PostTransactionOldDataT n)
:> PostAccepted '[JSON] (ApiTransactionT n)
type ListByronTransactions n = "byron-wallets"
:> Capture "walletId" (ApiT WalletId)
:> "transactions"
:> QueryParam "start" Iso8601Time
:> QueryParam "end" Iso8601Time
:> QueryParam "order" (ApiT SortOrder)
:> Get '[JSON] [ApiTransactionT n]
type GetByronTransaction n = "byron-wallets"
:> Capture "walletId" (ApiT WalletId)
:> "transactions"
:> Capture "transactionId" ApiTxId
:> Get '[JSON] (ApiTransactionT n)
type PostByronTransactionFeeOld n = "byron-wallets"
:> Capture "walletId" (ApiT WalletId)
:> "payment-fees"
:> ReqBody '[JSON] (PostTransactionFeeOldDataT n)
:> PostAccepted '[JSON] ApiFee
type DeleteByronTransaction = "byron-wallets"
:> Capture "walletId" (ApiT WalletId)
:> "transactions"
:> Capture "transactionId" ApiTxId
:> DeleteNoContent
type ByronMigrations n =
CreateByronWalletMigrationPlan n
:<|> MigrateByronWallet n
type MigrateByronWallet n = "byron-wallets"
:> Capture "walletId" (ApiT WalletId)
:> "migrations"
:> ReqBody '[JSON] (ApiWalletMigrationPostDataT n "lenient")
:> PostAccepted '[JSON] (NonEmpty (ApiTransactionT n))
type CreateByronWalletMigrationPlan n = "byron-wallets"
:> Capture "walletId" (ApiT WalletId)
:> "migrations"
:> "plan"
:> ReqBody '[JSON] (ApiWalletMigrationPlanPostDataT n)
:> PostAccepted '[JSON] (ApiWalletMigrationPlan n)
type Network =
GetNetworkInformation
:<|> GetNetworkParameters
:<|> GetNetworkClock
type GetNetworkInformation = "network"
:> "information"
:> Get '[JSON] ApiNetworkInformation
type GetNetworkParameters = "network"
:> "parameters"
:> Get '[JSON] ApiNetworkParameters
type GetNetworkClock = "network"
:> "clock"
:> QueryFlag "forceNtpCheck"
:> Get '[JSON] ApiNetworkClock
type SMASH = GetCurrentSMASHHealth
type GetCurrentSMASHHealth = "smash"
:> "health"
:> QueryParam "url" (ApiT SmashServer)
:> Get '[JSON] ApiHealthCheck
type SharedWallets =
PostSharedWallet
:<|> GetSharedWallet
:<|> ListSharedWallets
:<|> PatchSharedWalletInPayment
:<|> PatchSharedWalletInDelegation
:<|> DeleteSharedWallet
type PostSharedWallet = "shared-wallets"
:> ReqBody '[JSON] ApiSharedWalletPostData
:> PostCreated '[JSON] ApiSharedWallet
type GetSharedWallet = "shared-wallets"
:> Capture "walletId" (ApiT WalletId)
:> Get '[JSON] ApiSharedWallet
type ListSharedWallets = "shared-wallets"
:> Get '[JSON] [ApiSharedWallet]
type PatchSharedWalletInPayment = "shared-wallets"
:> Capture "walletId" (ApiT WalletId)
:> "payment-script-template"
:> ReqBody '[JSON] ApiSharedWalletPatchData
:> Patch '[JSON] ApiSharedWallet
type PatchSharedWalletInDelegation = "shared-wallets"
:> Capture "walletId" (ApiT WalletId)
:> "delegation-script-template"
:> ReqBody '[JSON] ApiSharedWalletPatchData
:> Patch '[JSON] ApiSharedWallet
type DeleteSharedWallet = "shared-wallets"
:> Capture "walletId" (ApiT WalletId)
:> DeleteNoContent
type SharedWalletKeys =
GetSharedWalletKey
:<|> PostAccountKeyShared
:<|> GetAccountKeyShared
type GetSharedWalletKey = "shared-wallets"
:> Capture "walletId" (ApiT WalletId)
:> "keys"
:> Capture "role" (ApiT Role)
:> Capture "index" (ApiT DerivationIndex)
:> QueryParam "hash" Bool
:> Get '[JSON] ApiVerificationKeyShared
type PostAccountKeyShared = "shared-wallets"
:> Capture "walletId" (ApiT WalletId)
:> "keys"
:> Capture "index" (ApiT DerivationIndex)
:> ReqBody '[JSON] ApiPostAccountKeyData
:> PostAccepted '[JSON] ApiAccountKeyShared
type GetAccountKeyShared = "shared-wallets"
:> Capture "walletId" (ApiT WalletId)
:> "keys"
:> QueryParam "format" KeyFormat
:> Get '[JSON] ApiAccountKeyShared
type SharedAddresses n =
ListSharedAddresses n
type ListSharedAddresses n = "shared-wallets"
:> Capture "walletId" (ApiT WalletId)
:> "addresses"
:> QueryParam "state" (ApiT AddressState)
:> Get '[JSON] [ApiAddressT n]
type SharedTransactions n =
ConstructSharedTransaction n
:<|> DecodeSharedTransaction n
type ConstructSharedTransaction n = "shared-wallets"
:> Capture "walletId" (ApiT WalletId)
:> "transactions-construct"
:> ReqBody '[JSON] (ApiConstructTransactionDataT n)
:> PostAccepted '[JSON] (ApiConstructTransactionT n)
type DecodeSharedTransaction n = "shared-wallets"
:> Capture "walletId" (ApiT WalletId)
:> "transactions-decode"
:> ReqBody '[JSON] ApiSerialisedTransaction
:> PostAccepted '[JSON] (ApiDecodedTransactionT n)
type Proxy_ =
PostExternalTransaction
type PostExternalTransaction = "proxy"
:> "transactions"
:> ReqBody '[OctetStream] (ApiT SealedTx)
:> PostAccepted '[JSON] ApiTxId
data ApiLayer s (k :: Depth -> Type -> Type)
= ApiLayer
(Tracer IO TxSubmitLog)
(Tracer IO (WorkerLog WalletId WalletWorkerLog))
(Block, NetworkParameters)
(NetworkLayer IO Block)
(TransactionLayer k SealedTx)
(DBFactory IO s k)
(WorkerRegistry WalletId (DBLayer IO s k))
(Concierge IO WalletLock)
(TokenMetadataClient IO)
deriving ((forall x. ApiLayer s k -> Rep (ApiLayer s k) x)
-> (forall x. Rep (ApiLayer s k) x -> ApiLayer s k)
-> Generic (ApiLayer s k)
forall x. Rep (ApiLayer s k) x -> ApiLayer s k
forall x. ApiLayer s k -> Rep (ApiLayer s k) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall s (k :: Depth -> * -> *) x.
Rep (ApiLayer s k) x -> ApiLayer s k
forall s (k :: Depth -> * -> *) x.
ApiLayer s k -> Rep (ApiLayer s k) x
$cto :: forall s (k :: Depth -> * -> *) x.
Rep (ApiLayer s k) x -> ApiLayer s k
$cfrom :: forall s (k :: Depth -> * -> *) x.
ApiLayer s k -> Rep (ApiLayer s k) x
Generic)
data WalletLock = PostTransactionOld WalletId
deriving (WalletLock -> WalletLock -> Bool
(WalletLock -> WalletLock -> Bool)
-> (WalletLock -> WalletLock -> Bool) -> Eq WalletLock
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: WalletLock -> WalletLock -> Bool
$c/= :: WalletLock -> WalletLock -> Bool
== :: WalletLock -> WalletLock -> Bool
$c== :: WalletLock -> WalletLock -> Bool
Eq, Eq WalletLock
Eq WalletLock
-> (WalletLock -> WalletLock -> Ordering)
-> (WalletLock -> WalletLock -> Bool)
-> (WalletLock -> WalletLock -> Bool)
-> (WalletLock -> WalletLock -> Bool)
-> (WalletLock -> WalletLock -> Bool)
-> (WalletLock -> WalletLock -> WalletLock)
-> (WalletLock -> WalletLock -> WalletLock)
-> Ord WalletLock
WalletLock -> WalletLock -> Bool
WalletLock -> WalletLock -> Ordering
WalletLock -> WalletLock -> WalletLock
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: WalletLock -> WalletLock -> WalletLock
$cmin :: WalletLock -> WalletLock -> WalletLock
max :: WalletLock -> WalletLock -> WalletLock
$cmax :: WalletLock -> WalletLock -> WalletLock
>= :: WalletLock -> WalletLock -> Bool
$c>= :: WalletLock -> WalletLock -> Bool
> :: WalletLock -> WalletLock -> Bool
$c> :: WalletLock -> WalletLock -> Bool
<= :: WalletLock -> WalletLock -> Bool
$c<= :: WalletLock -> WalletLock -> Bool
< :: WalletLock -> WalletLock -> Bool
$c< :: WalletLock -> WalletLock -> Bool
compare :: WalletLock -> WalletLock -> Ordering
$ccompare :: WalletLock -> WalletLock -> Ordering
$cp1Ord :: Eq WalletLock
Ord, Int -> WalletLock -> ShowS
[WalletLock] -> ShowS
WalletLock -> String
(Int -> WalletLock -> ShowS)
-> (WalletLock -> String)
-> ([WalletLock] -> ShowS)
-> Show WalletLock
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [WalletLock] -> ShowS
$cshowList :: [WalletLock] -> ShowS
show :: WalletLock -> String
$cshow :: WalletLock -> String
showsPrec :: Int -> WalletLock -> ShowS
$cshowsPrec :: Int -> WalletLock -> ShowS
Show)
instance HasWorkerCtx (DBLayer IO s k) (ApiLayer s k) where
type WorkerCtx (ApiLayer s k) = WalletLayer IO s k
type WorkerMsg (ApiLayer s k) = WalletWorkerLog
type WorkerKey (ApiLayer s k) = WalletId
hoistResource :: DBLayer IO s k
-> (WorkerMsg (ApiLayer s k)
-> WorkerLog (WorkerKey (ApiLayer s k)) (WorkerMsg (ApiLayer s k)))
-> ApiLayer s k
-> WorkerCtx (ApiLayer s k)
hoistResource DBLayer IO s k
db WorkerMsg (ApiLayer s k)
-> WorkerLog (WorkerKey (ApiLayer s k)) (WorkerMsg (ApiLayer s k))
transform (ApiLayer Tracer IO TxSubmitLog
_ Tracer IO (WorkerLog WalletId WalletWorkerLog)
tr (Block, NetworkParameters)
gp NetworkLayer IO Block
nw TransactionLayer k SealedTx
tl DBFactory IO s k
_ WorkerRegistry WalletId (DBLayer IO s k)
_ Concierge IO WalletLock
_ TokenMetadataClient IO
_) =
Tracer IO WalletWorkerLog
-> (Block, NetworkParameters)
-> NetworkLayer IO Block
-> TransactionLayer k SealedTx
-> DBLayer IO s k
-> WalletLayer IO s k
forall (m :: * -> *) s (k :: Depth -> * -> *).
Tracer m WalletWorkerLog
-> (Block, NetworkParameters)
-> NetworkLayer m Block
-> TransactionLayer k SealedTx
-> DBLayer m s k
-> WalletLayer m s k
WalletLayer ((WalletWorkerLog -> WorkerLog WalletId WalletWorkerLog)
-> Tracer IO (WorkerLog WalletId WalletWorkerLog)
-> Tracer IO WalletWorkerLog
forall (f :: * -> *) a b. Contravariant f => (a -> b) -> f b -> f a
contramap WalletWorkerLog -> WorkerLog WalletId WalletWorkerLog
WorkerMsg (ApiLayer s k)
-> WorkerLog (WorkerKey (ApiLayer s k)) (WorkerMsg (ApiLayer s k))
transform Tracer IO (WorkerLog WalletId WalletWorkerLog)
tr) (Block, NetworkParameters)
gp NetworkLayer IO Block
nw TransactionLayer k SealedTx
tl DBLayer IO s k
db
type HasWorkerRegistry s k ctx =
( HasType (WorkerRegistry WalletId (DBLayer IO s k)) ctx
, HasWorkerCtx (DBLayer IO s k) ctx
, WorkerKey ctx ~ WalletId
, WorkerMsg ctx ~ WalletWorkerLog
)
workerRegistry
:: forall s k ctx. (HasWorkerRegistry s k ctx)
=> Lens' ctx (WorkerRegistry WalletId (DBLayer IO s k))
workerRegistry :: Lens' ctx (WorkerRegistry WalletId (DBLayer IO s k))
workerRegistry =
forall s.
HasType (WorkerRegistry WalletId (DBLayer IO s k)) s =>
Lens
s
s
(WorkerRegistry WalletId (DBLayer IO s k))
(WorkerRegistry WalletId (DBLayer IO s k))
forall a s. HasType a s => Lens s s a a
typed @(WorkerRegistry WalletId (DBLayer IO s k))
type HasDBFactory s k = HasType (DBFactory IO s k)
type HasTokenMetadataClient = HasType (TokenMetadataClient IO)
dbFactory
:: forall s k ctx. (HasDBFactory s k ctx)
=> Lens' ctx (DBFactory IO s k)
dbFactory :: Lens' ctx (DBFactory IO s k)
dbFactory =
forall s.
HasType (DBFactory IO s k) s =>
Lens s s (DBFactory IO s k) (DBFactory IO s k)
forall a s. HasType a s => Lens s s a a
typed @(DBFactory IO s k)
tokenMetadataClient
:: forall ctx. (HasTokenMetadataClient ctx)
=> Lens' ctx (TokenMetadataClient IO)
tokenMetadataClient :: Lens' ctx (TokenMetadataClient IO)
tokenMetadataClient =
forall s.
HasType (TokenMetadataClient IO) s =>
Lens s s (TokenMetadataClient IO) (TokenMetadataClient IO)
forall a s. HasType a s => Lens s s a a
typed @(TokenMetadataClient IO)
walletLocks
:: forall ctx. (HasType (Concierge IO WalletLock) ctx)
=> Lens' ctx (Concierge IO WalletLock)
walletLocks :: Lens' ctx (Concierge IO WalletLock)
walletLocks =
forall s.
HasType (Concierge IO WalletLock) s =>
Lens s s (Concierge IO WalletLock) (Concierge IO WalletLock)
forall a s. HasType a s => Lens s s a a
typed @(Concierge IO WalletLock)
type family PostData wallet :: Type where
PostData ApiWallet = WalletOrAccountPostData
PostData ApiByronWallet = SomeByronWalletPostData