{-# LANGUAGE AllowAmbiguousTypes #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE PolyKinds #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE UndecidableInstances #-}
module Cardano.Wallet.Api.Link
(
deleteWallet
, getWallet
, listWallets
, postWallet
, putWallet
, putWalletPassphrase
, getWalletUtxoSnapshot
, getUTxOsStatistics
, createMigrationPlan
, migrateWallet
, getWalletKey
, signMetadata
, postAccountKey
, getAccountKey
, getPolicyKey
, postPolicyKey
, postPolicyId
, postRandomAddress
, putRandomAddresses
, listAddresses
, listAddresses'
, inspectAddress
, postAnyAddress
, selectCoins
, listAssets
, getAsset
, listByronAssets
, getByronAsset
, createTransactionOld
, listTransactions
, listTransactions'
, getTransactionFeeOld
, deleteTransaction
, getTransaction
, createUnsignedTransaction
, signTransaction
, balanceTransaction
, decodeTransaction
, submitTransaction
, listStakePools
, listStakeKeys
, joinStakePool
, quitStakePool
, getDelegationFee
, postPoolMaintenance
, getPoolMaintenance
, getNetworkInfo
, getNetworkParams
, getNetworkClock
, getNetworkClock'
, postExternalTransaction
, putSettings
, getSettings
, getCurrentSMASHHealth
, patchSharedWallet
, PostWallet
, Discriminate
) where
import Prelude
import Cardano.Wallet.Api.Types
( ApiAddressInspectData (..)
, ApiPoolId (..)
, ApiT (..)
, ApiTxId (ApiTxId)
, Iso8601Time
, KeyFormat
, MinWithdrawal (..)
, WalletStyle (..)
)
import Cardano.Wallet.Api.Types.SchemaMetadata
( TxMetadataSchema (..), toSimpleMetadataFlag )
import Cardano.Wallet.Primitive.AddressDerivation
( DerivationIndex, NetworkDiscriminant (..), Role )
import Cardano.Wallet.Primitive.AddressDiscovery.Shared
( CredentialType (..) )
import Cardano.Wallet.Primitive.Types
( PoolId, SmashServer, SortOrder, WalletId (..) )
import Cardano.Wallet.Primitive.Types.Address
( AddressState )
import Cardano.Wallet.Primitive.Types.Coin
( Coin (..) )
import Cardano.Wallet.Primitive.Types.Hash
( Hash )
import Cardano.Wallet.Primitive.Types.TokenPolicy
( TokenName, TokenPolicyId, nullTokenName )
import Data.Function
( (&) )
import Data.Generics.Internal.VL.Lens
( (^.) )
import Data.Generics.Product.Typed
( HasType, typed )
import Data.Proxy
( Proxy (..) )
import Data.Text
( Text )
import GHC.Stack
( HasCallStack )
import GHC.TypeLits
( Symbol )
import Network.HTTP.Types.Method
( Method )
import Numeric.Natural
( Natural )
import Servant.API
( (:>)
, Capture
, Header'
, IsElem
, NoContentVerb
, QueryFlag
, QueryParam
, ReflectMethod (..)
, ReqBody
, Verb
)
import Servant.Links
( HasLink (..), safeLink' )
import Web.HttpApiData
( ToHttpApiData (..) )
import qualified Cardano.Wallet.Api as Api
class PostWallet (style :: WalletStyle) where
postWallet :: (Method, Text)
instance PostWallet 'Shelley where
postWallet :: (Method, Text)
postWallet = (MkLink PostWallet Text -> Text) -> (Method, Text)
forall endpoint.
(HasLink endpoint, IsElem endpoint endpoint, HasVerb endpoint) =>
(MkLink endpoint Text -> Text) -> (Method, Text)
endpoint @Api.PostWallet MkLink PostWallet Text -> Text
forall a. a -> a
id
instance PostWallet 'Byron where
postWallet :: (Method, Text)
postWallet = (MkLink PostByronWallet Text -> Text) -> (Method, Text)
forall endpoint.
(HasLink endpoint, IsElem endpoint endpoint, HasVerb endpoint) =>
(MkLink endpoint Text -> Text) -> (Method, Text)
endpoint @Api.PostByronWallet MkLink PostByronWallet Text -> Text
forall a. a -> a
id
instance PostWallet 'Shared where
postWallet :: (Method, Text)
postWallet = (MkLink PostSharedWallet Text -> Text) -> (Method, Text)
forall endpoint.
(HasLink endpoint, IsElem endpoint endpoint, HasVerb endpoint) =>
(MkLink endpoint Text -> Text) -> (Method, Text)
endpoint @Api.PostSharedWallet MkLink PostSharedWallet Text -> Text
forall a. a -> a
id
deleteWallet
:: forall (style :: WalletStyle) w.
( Discriminate style
, HasType (ApiT WalletId) w
)
=> w
-> (Method, Text)
deleteWallet :: w -> (Method, Text)
deleteWallet w
w = (Method, Text)
-> (Method, Text) -> (Method, Text) -> (Method, Text)
forall (style :: WalletStyle) a.
Discriminate style =>
a -> a -> a -> a
discriminate @style
((MkLink DeleteWallet Text -> Text) -> (Method, Text)
forall endpoint.
(HasLink endpoint, IsElem endpoint endpoint, HasVerb endpoint) =>
(MkLink endpoint Text -> Text) -> (Method, Text)
endpoint @Api.DeleteWallet (ApiT WalletId
wid ApiT WalletId -> (ApiT WalletId -> Text) -> Text
forall a b. a -> (a -> b) -> b
&))
((MkLink DeleteByronWallet Text -> Text) -> (Method, Text)
forall endpoint.
(HasLink endpoint, IsElem endpoint endpoint, HasVerb endpoint) =>
(MkLink endpoint Text -> Text) -> (Method, Text)
endpoint @Api.DeleteByronWallet (ApiT WalletId
wid ApiT WalletId -> (ApiT WalletId -> Text) -> Text
forall a b. a -> (a -> b) -> b
&))
((MkLink DeleteSharedWallet Text -> Text) -> (Method, Text)
forall endpoint.
(HasLink endpoint, IsElem endpoint endpoint, HasVerb endpoint) =>
(MkLink endpoint Text -> Text) -> (Method, Text)
endpoint @Api.DeleteSharedWallet (ApiT WalletId
wid ApiT WalletId -> (ApiT WalletId -> Text) -> Text
forall a b. a -> (a -> b) -> b
&))
where
wid :: ApiT WalletId
wid = w
w w
-> ((ApiT WalletId -> Const (ApiT WalletId) (ApiT WalletId))
-> w -> Const (ApiT WalletId) w)
-> ApiT WalletId
forall s a. s -> ((a -> Const a a) -> s -> Const a s) -> a
^. forall s.
HasType (ApiT WalletId) s =>
Lens s s (ApiT WalletId) (ApiT WalletId)
forall a s. HasType a s => Lens s s a a
typed @(ApiT WalletId)
getWallet
:: forall (style :: WalletStyle) w.
( Discriminate style
, HasType (ApiT WalletId) w
)
=> w
-> (Method, Text)
getWallet :: w -> (Method, Text)
getWallet w
w = (Method, Text)
-> (Method, Text) -> (Method, Text) -> (Method, Text)
forall (style :: WalletStyle) a.
Discriminate style =>
a -> a -> a -> a
discriminate @style
((MkLink GetWallet Text -> Text) -> (Method, Text)
forall endpoint.
(HasLink endpoint, IsElem endpoint endpoint, HasVerb endpoint) =>
(MkLink endpoint Text -> Text) -> (Method, Text)
endpoint @Api.GetWallet (ApiT WalletId
wid ApiT WalletId -> (ApiT WalletId -> Text) -> Text
forall a b. a -> (a -> b) -> b
&))
((MkLink GetByronWallet Text -> Text) -> (Method, Text)
forall endpoint.
(HasLink endpoint, IsElem endpoint endpoint, HasVerb endpoint) =>
(MkLink endpoint Text -> Text) -> (Method, Text)
endpoint @Api.GetByronWallet (ApiT WalletId
wid ApiT WalletId -> (ApiT WalletId -> Text) -> Text
forall a b. a -> (a -> b) -> b
&))
((MkLink GetSharedWallet Text -> Text) -> (Method, Text)
forall endpoint.
(HasLink endpoint, IsElem endpoint endpoint, HasVerb endpoint) =>
(MkLink endpoint Text -> Text) -> (Method, Text)
endpoint @Api.GetSharedWallet (ApiT WalletId
wid ApiT WalletId -> (ApiT WalletId -> Text) -> Text
forall a b. a -> (a -> b) -> b
&))
where
wid :: ApiT WalletId
wid = w
w w
-> ((ApiT WalletId -> Const (ApiT WalletId) (ApiT WalletId))
-> w -> Const (ApiT WalletId) w)
-> ApiT WalletId
forall s a. s -> ((a -> Const a a) -> s -> Const a s) -> a
^. forall s.
HasType (ApiT WalletId) s =>
Lens s s (ApiT WalletId) (ApiT WalletId)
forall a s. HasType a s => Lens s s a a
typed @(ApiT WalletId)
getUTxOsStatistics
:: forall (style :: WalletStyle) w.
( HasCallStack
, Discriminate style
, HasType (ApiT WalletId) w
)
=> w
-> (Method, Text)
getUTxOsStatistics :: w -> (Method, Text)
getUTxOsStatistics w
w = (Method, Text)
-> (Method, Text) -> (Method, Text) -> (Method, Text)
forall (style :: WalletStyle) a.
Discriminate style =>
a -> a -> a -> a
discriminate @style
((MkLink GetUTxOsStatistics Text -> Text) -> (Method, Text)
forall endpoint.
(HasLink endpoint, IsElem endpoint endpoint, HasVerb endpoint) =>
(MkLink endpoint Text -> Text) -> (Method, Text)
endpoint @Api.GetUTxOsStatistics (ApiT WalletId
wid ApiT WalletId -> (ApiT WalletId -> Text) -> Text
forall a b. a -> (a -> b) -> b
&))
((MkLink GetByronUTxOsStatistics Text -> Text) -> (Method, Text)
forall endpoint.
(HasLink endpoint, IsElem endpoint endpoint, HasVerb endpoint) =>
(MkLink endpoint Text -> Text) -> (Method, Text)
endpoint @Api.GetByronUTxOsStatistics (ApiT WalletId
wid ApiT WalletId -> (ApiT WalletId -> Text) -> Text
forall a b. a -> (a -> b) -> b
&))
(String -> (Method, Text)
forall a. HasCallStack => String -> a
notSupported String
"Shared")
where
wid :: ApiT WalletId
wid = w
w w
-> ((ApiT WalletId -> Const (ApiT WalletId) (ApiT WalletId))
-> w -> Const (ApiT WalletId) w)
-> ApiT WalletId
forall s a. s -> ((a -> Const a a) -> s -> Const a s) -> a
^. forall s.
HasType (ApiT WalletId) s =>
Lens s s (ApiT WalletId) (ApiT WalletId)
forall a s. HasType a s => Lens s s a a
typed @(ApiT WalletId)
getWalletUtxoSnapshot
:: forall (style :: WalletStyle) w.
( HasCallStack
, Discriminate style
, HasType (ApiT WalletId) w
)
=> w
-> (Method, Text)
getWalletUtxoSnapshot :: w -> (Method, Text)
getWalletUtxoSnapshot w
w = (Method, Text)
-> (Method, Text) -> (Method, Text) -> (Method, Text)
forall (style :: WalletStyle) a.
Discriminate style =>
a -> a -> a -> a
discriminate @style
((MkLink GetWalletUtxoSnapshot Text -> Text) -> (Method, Text)
forall endpoint.
(HasLink endpoint, IsElem endpoint endpoint, HasVerb endpoint) =>
(MkLink endpoint Text -> Text) -> (Method, Text)
endpoint @Api.GetWalletUtxoSnapshot (ApiT WalletId
wid ApiT WalletId -> (ApiT WalletId -> Text) -> Text
forall a b. a -> (a -> b) -> b
&))
((MkLink GetByronWalletUtxoSnapshot Text -> Text) -> (Method, Text)
forall endpoint.
(HasLink endpoint, IsElem endpoint endpoint, HasVerb endpoint) =>
(MkLink endpoint Text -> Text) -> (Method, Text)
endpoint @Api.GetByronWalletUtxoSnapshot (ApiT WalletId
wid ApiT WalletId -> (ApiT WalletId -> Text) -> Text
forall a b. a -> (a -> b) -> b
&))
(String -> (Method, Text)
forall a. HasCallStack => String -> a
notSupported String
"Shared")
where
wid :: ApiT WalletId
wid = w
w w
-> ((ApiT WalletId -> Const (ApiT WalletId) (ApiT WalletId))
-> w -> Const (ApiT WalletId) w)
-> ApiT WalletId
forall s a. s -> ((a -> Const a a) -> s -> Const a s) -> a
^. forall s.
HasType (ApiT WalletId) s =>
Lens s s (ApiT WalletId) (ApiT WalletId)
forall a s. HasType a s => Lens s s a a
typed @(ApiT WalletId)
listWallets
:: forall (style :: WalletStyle).
( Discriminate style
)
=> (Method, Text)
listWallets :: (Method, Text)
listWallets = (Method, Text)
-> (Method, Text) -> (Method, Text) -> (Method, Text)
forall (style :: WalletStyle) a.
Discriminate style =>
a -> a -> a -> a
discriminate @style
((MkLink ListWallets Text -> Text) -> (Method, Text)
forall endpoint.
(HasLink endpoint, IsElem endpoint endpoint, HasVerb endpoint) =>
(MkLink endpoint Text -> Text) -> (Method, Text)
endpoint @Api.ListWallets MkLink ListWallets Text -> Text
forall a. a -> a
id)
((MkLink ListByronWallets Text -> Text) -> (Method, Text)
forall endpoint.
(HasLink endpoint, IsElem endpoint endpoint, HasVerb endpoint) =>
(MkLink endpoint Text -> Text) -> (Method, Text)
endpoint @Api.ListByronWallets MkLink ListByronWallets Text -> Text
forall a. a -> a
id)
((MkLink ListSharedWallets Text -> Text) -> (Method, Text)
forall endpoint.
(HasLink endpoint, IsElem endpoint endpoint, HasVerb endpoint) =>
(MkLink endpoint Text -> Text) -> (Method, Text)
endpoint @Api.ListSharedWallets MkLink ListSharedWallets Text -> Text
forall a. a -> a
id)
putWallet
:: forall (style :: WalletStyle) w.
( HasCallStack
, Discriminate style
, HasType (ApiT WalletId) w
)
=> w
-> (Method, Text)
putWallet :: w -> (Method, Text)
putWallet w
w = (Method, Text)
-> (Method, Text) -> (Method, Text) -> (Method, Text)
forall (style :: WalletStyle) a.
Discriminate style =>
a -> a -> a -> a
discriminate @style
((MkLink PutWallet Text -> Text) -> (Method, Text)
forall endpoint.
(HasLink endpoint, IsElem endpoint endpoint, HasVerb endpoint) =>
(MkLink endpoint Text -> Text) -> (Method, Text)
endpoint @Api.PutWallet (ApiT WalletId
wid ApiT WalletId -> (ApiT WalletId -> Text) -> Text
forall a b. a -> (a -> b) -> b
&))
((MkLink PutByronWallet Text -> Text) -> (Method, Text)
forall endpoint.
(HasLink endpoint, IsElem endpoint endpoint, HasVerb endpoint) =>
(MkLink endpoint Text -> Text) -> (Method, Text)
endpoint @Api.PutByronWallet (ApiT WalletId
wid ApiT WalletId -> (ApiT WalletId -> Text) -> Text
forall a b. a -> (a -> b) -> b
&))
(String -> (Method, Text)
forall a. HasCallStack => String -> a
notSupported String
"Shared")
where
wid :: ApiT WalletId
wid = w
w w
-> ((ApiT WalletId -> Const (ApiT WalletId) (ApiT WalletId))
-> w -> Const (ApiT WalletId) w)
-> ApiT WalletId
forall s a. s -> ((a -> Const a a) -> s -> Const a s) -> a
^. forall s.
HasType (ApiT WalletId) s =>
Lens s s (ApiT WalletId) (ApiT WalletId)
forall a s. HasType a s => Lens s s a a
typed @(ApiT WalletId)
putWalletPassphrase
:: forall (style :: WalletStyle) w.
( HasCallStack
, Discriminate style
, HasType (ApiT WalletId) w
)
=> w
-> (Method, Text)
putWalletPassphrase :: w -> (Method, Text)
putWalletPassphrase w
w = (Method, Text)
-> (Method, Text) -> (Method, Text) -> (Method, Text)
forall (style :: WalletStyle) a.
Discriminate style =>
a -> a -> a -> a
discriminate @style
((MkLink PutWalletPassphrase Text -> Text) -> (Method, Text)
forall endpoint.
(HasLink endpoint, IsElem endpoint endpoint, HasVerb endpoint) =>
(MkLink endpoint Text -> Text) -> (Method, Text)
endpoint @Api.PutWalletPassphrase (ApiT WalletId
wid ApiT WalletId -> (ApiT WalletId -> Text) -> Text
forall a b. a -> (a -> b) -> b
&))
((MkLink PutByronWalletPassphrase Text -> Text) -> (Method, Text)
forall endpoint.
(HasLink endpoint, IsElem endpoint endpoint, HasVerb endpoint) =>
(MkLink endpoint Text -> Text) -> (Method, Text)
endpoint @Api.PutByronWalletPassphrase (ApiT WalletId
wid ApiT WalletId -> (ApiT WalletId -> Text) -> Text
forall a b. a -> (a -> b) -> b
&))
(String -> (Method, Text)
forall a. HasCallStack => String -> a
notSupported String
"Shared")
where
wid :: ApiT WalletId
wid = w
w w
-> ((ApiT WalletId -> Const (ApiT WalletId) (ApiT WalletId))
-> w -> Const (ApiT WalletId) w)
-> ApiT WalletId
forall s a. s -> ((a -> Const a a) -> s -> Const a s) -> a
^. forall s.
HasType (ApiT WalletId) s =>
Lens s s (ApiT WalletId) (ApiT WalletId)
forall a s. HasType a s => Lens s s a a
typed @(ApiT WalletId)
migrateWallet
:: forall (style :: WalletStyle) w.
( HasCallStack
, Discriminate style
, HasType (ApiT WalletId) w
)
=> w
-> (Method, Text)
migrateWallet :: w -> (Method, Text)
migrateWallet w
w = (Method, Text)
-> (Method, Text) -> (Method, Text) -> (Method, Text)
forall (style :: WalletStyle) a.
Discriminate style =>
a -> a -> a -> a
discriminate @style
((MkLink (MigrateShelleyWallet Net) Text -> Text) -> (Method, Text)
forall endpoint.
(HasLink endpoint, IsElem endpoint endpoint, HasVerb endpoint) =>
(MkLink endpoint Text -> Text) -> (Method, Text)
endpoint @(Api.MigrateShelleyWallet Net) (ApiT WalletId
wid ApiT WalletId -> (ApiT WalletId -> Text) -> Text
forall a b. a -> (a -> b) -> b
&))
((MkLink (MigrateByronWallet Net) Text -> Text) -> (Method, Text)
forall endpoint.
(HasLink endpoint, IsElem endpoint endpoint, HasVerb endpoint) =>
(MkLink endpoint Text -> Text) -> (Method, Text)
endpoint @(Api.MigrateByronWallet Net) (ApiT WalletId
wid ApiT WalletId -> (ApiT WalletId -> Text) -> Text
forall a b. a -> (a -> b) -> b
&))
(String -> (Method, Text)
forall a. HasCallStack => String -> a
notSupported String
"Shared")
where
wid :: ApiT WalletId
wid = w
w w
-> ((ApiT WalletId -> Const (ApiT WalletId) (ApiT WalletId))
-> w -> Const (ApiT WalletId) w)
-> ApiT WalletId
forall s a. s -> ((a -> Const a a) -> s -> Const a s) -> a
^. forall s.
HasType (ApiT WalletId) s =>
Lens s s (ApiT WalletId) (ApiT WalletId)
forall a s. HasType a s => Lens s s a a
typed @(ApiT WalletId)
createMigrationPlan
:: forall (style :: WalletStyle) w.
( HasCallStack
, Discriminate style
, HasType (ApiT WalletId) w
)
=> w
-> (Method, Text)
createMigrationPlan :: w -> (Method, Text)
createMigrationPlan w
w = (Method, Text)
-> (Method, Text) -> (Method, Text) -> (Method, Text)
forall (style :: WalletStyle) a.
Discriminate style =>
a -> a -> a -> a
discriminate @style
((MkLink (CreateShelleyWalletMigrationPlan Net) Text -> Text)
-> (Method, Text)
forall endpoint.
(HasLink endpoint, IsElem endpoint endpoint, HasVerb endpoint) =>
(MkLink endpoint Text -> Text) -> (Method, Text)
endpoint @(Api.CreateShelleyWalletMigrationPlan Net) (ApiT WalletId
wid ApiT WalletId -> (ApiT WalletId -> Text) -> Text
forall a b. a -> (a -> b) -> b
&))
((MkLink (CreateByronWalletMigrationPlan Net) Text -> Text)
-> (Method, Text)
forall endpoint.
(HasLink endpoint, IsElem endpoint endpoint, HasVerb endpoint) =>
(MkLink endpoint Text -> Text) -> (Method, Text)
endpoint @(Api.CreateByronWalletMigrationPlan Net) (ApiT WalletId
wid ApiT WalletId -> (ApiT WalletId -> Text) -> Text
forall a b. a -> (a -> b) -> b
&))
(String -> (Method, Text)
forall a. HasCallStack => String -> a
notSupported String
"Shared")
where
wid :: ApiT WalletId
wid = w
w w
-> ((ApiT WalletId -> Const (ApiT WalletId) (ApiT WalletId))
-> w -> Const (ApiT WalletId) w)
-> ApiT WalletId
forall s a. s -> ((a -> Const a a) -> s -> Const a s) -> a
^. forall s.
HasType (ApiT WalletId) s =>
Lens s s (ApiT WalletId) (ApiT WalletId)
forall a s. HasType a s => Lens s s a a
typed @(ApiT WalletId)
getWalletKey
:: forall style w.
( HasCallStack
, HasType (ApiT WalletId) w
, Discriminate style
)
=> w
-> Role
-> DerivationIndex
-> Maybe Bool
-> (Method, Text)
getWalletKey :: w -> Role -> DerivationIndex -> Maybe Bool -> (Method, Text)
getWalletKey w
w Role
role_ DerivationIndex
index Maybe Bool
hashed = (Method, Text)
-> (Method, Text) -> (Method, Text) -> (Method, Text)
forall (style :: WalletStyle) a.
Discriminate style =>
a -> a -> a -> a
discriminate @style
((MkLink GetWalletKey Text -> Text) -> (Method, Text)
forall endpoint.
(HasLink endpoint, IsElem endpoint endpoint, HasVerb endpoint) =>
(MkLink endpoint Text -> Text) -> (Method, Text)
endpoint @Api.GetWalletKey (\MkLink GetWalletKey Text
mk -> MkLink GetWalletKey Text
ApiT WalletId
-> ApiT Role -> ApiT DerivationIndex -> Maybe Bool -> Text
mk ApiT WalletId
wid (Role -> ApiT Role
forall a. a -> ApiT a
ApiT Role
role_) (DerivationIndex -> ApiT DerivationIndex
forall a. a -> ApiT a
ApiT DerivationIndex
index) Maybe Bool
hashed))
(String -> (Method, Text)
forall a. HasCallStack => String -> a
notSupported String
"Byron")
((MkLink GetSharedWalletKey Text -> Text) -> (Method, Text)
forall endpoint.
(HasLink endpoint, IsElem endpoint endpoint, HasVerb endpoint) =>
(MkLink endpoint Text -> Text) -> (Method, Text)
endpoint @Api.GetSharedWalletKey (\MkLink GetSharedWalletKey Text
mk -> MkLink GetSharedWalletKey Text
ApiT WalletId
-> ApiT Role -> ApiT DerivationIndex -> Maybe Bool -> Text
mk ApiT WalletId
wid (Role -> ApiT Role
forall a. a -> ApiT a
ApiT Role
role_) (DerivationIndex -> ApiT DerivationIndex
forall a. a -> ApiT a
ApiT DerivationIndex
index) Maybe Bool
hashed))
where
wid :: ApiT WalletId
wid = w
w w
-> ((ApiT WalletId -> Const (ApiT WalletId) (ApiT WalletId))
-> w -> Const (ApiT WalletId) w)
-> ApiT WalletId
forall s a. s -> ((a -> Const a a) -> s -> Const a s) -> a
^. forall s.
HasType (ApiT WalletId) s =>
Lens s s (ApiT WalletId) (ApiT WalletId)
forall a s. HasType a s => Lens s s a a
typed @(ApiT WalletId)
signMetadata
:: forall w.
( HasType (ApiT WalletId) w
)
=> w
-> Role
-> DerivationIndex
-> (Method, Text)
signMetadata :: w -> Role -> DerivationIndex -> (Method, Text)
signMetadata w
w Role
role_ DerivationIndex
index =
(MkLink SignMetadata Text -> Text) -> (Method, Text)
forall endpoint.
(HasLink endpoint, IsElem endpoint endpoint, HasVerb endpoint) =>
(MkLink endpoint Text -> Text) -> (Method, Text)
endpoint @Api.SignMetadata (\MkLink SignMetadata Text
mk -> MkLink SignMetadata Text
ApiT WalletId -> ApiT Role -> ApiT DerivationIndex -> Text
mk ApiT WalletId
wid (Role -> ApiT Role
forall a. a -> ApiT a
ApiT Role
role_) (DerivationIndex -> ApiT DerivationIndex
forall a. a -> ApiT a
ApiT DerivationIndex
index))
where
wid :: ApiT WalletId
wid = w
w w
-> ((ApiT WalletId -> Const (ApiT WalletId) (ApiT WalletId))
-> w -> Const (ApiT WalletId) w)
-> ApiT WalletId
forall s a. s -> ((a -> Const a a) -> s -> Const a s) -> a
^. forall s.
HasType (ApiT WalletId) s =>
Lens s s (ApiT WalletId) (ApiT WalletId)
forall a s. HasType a s => Lens s s a a
typed @(ApiT WalletId)
postAccountKey
:: forall style w.
( HasCallStack
, HasType (ApiT WalletId) w
, Discriminate style
)
=> w
-> DerivationIndex
-> (Method, Text)
postAccountKey :: w -> DerivationIndex -> (Method, Text)
postAccountKey w
w DerivationIndex
index = (Method, Text)
-> (Method, Text) -> (Method, Text) -> (Method, Text)
forall (style :: WalletStyle) a.
Discriminate style =>
a -> a -> a -> a
discriminate @style
((MkLink PostAccountKey Text -> Text) -> (Method, Text)
forall endpoint.
(HasLink endpoint, IsElem endpoint endpoint, HasVerb endpoint) =>
(MkLink endpoint Text -> Text) -> (Method, Text)
endpoint @Api.PostAccountKey (\MkLink PostAccountKey Text
mk -> MkLink PostAccountKey Text
ApiT WalletId -> ApiT DerivationIndex -> Text
mk ApiT WalletId
wid (DerivationIndex -> ApiT DerivationIndex
forall a. a -> ApiT a
ApiT DerivationIndex
index)))
(String -> (Method, Text)
forall a. HasCallStack => String -> a
notSupported String
"Byron")
((MkLink PostAccountKeyShared Text -> Text) -> (Method, Text)
forall endpoint.
(HasLink endpoint, IsElem endpoint endpoint, HasVerb endpoint) =>
(MkLink endpoint Text -> Text) -> (Method, Text)
endpoint @Api.PostAccountKeyShared (\MkLink PostAccountKeyShared Text
mk -> MkLink PostAccountKeyShared Text
ApiT WalletId -> ApiT DerivationIndex -> Text
mk ApiT WalletId
wid (DerivationIndex -> ApiT DerivationIndex
forall a. a -> ApiT a
ApiT DerivationIndex
index)))
where
wid :: ApiT WalletId
wid = w
w w
-> ((ApiT WalletId -> Const (ApiT WalletId) (ApiT WalletId))
-> w -> Const (ApiT WalletId) w)
-> ApiT WalletId
forall s a. s -> ((a -> Const a a) -> s -> Const a s) -> a
^. forall s.
HasType (ApiT WalletId) s =>
Lens s s (ApiT WalletId) (ApiT WalletId)
forall a s. HasType a s => Lens s s a a
typed @(ApiT WalletId)
getAccountKey
:: forall style w.
( HasCallStack
, HasType (ApiT WalletId) w
, Discriminate style
)
=> w
-> Maybe KeyFormat
-> (Method, Text)
getAccountKey :: w -> Maybe KeyFormat -> (Method, Text)
getAccountKey w
w Maybe KeyFormat
extended = (Method, Text)
-> (Method, Text) -> (Method, Text) -> (Method, Text)
forall (style :: WalletStyle) a.
Discriminate style =>
a -> a -> a -> a
discriminate @style
((MkLink GetAccountKey Text -> Text) -> (Method, Text)
forall endpoint.
(HasLink endpoint, IsElem endpoint endpoint, HasVerb endpoint) =>
(MkLink endpoint Text -> Text) -> (Method, Text)
endpoint @Api.GetAccountKey (\MkLink GetAccountKey Text
mk -> MkLink GetAccountKey Text
ApiT WalletId -> Maybe KeyFormat -> Text
mk ApiT WalletId
wid Maybe KeyFormat
extended))
(String -> (Method, Text)
forall a. HasCallStack => String -> a
notSupported String
"Byron")
((MkLink GetAccountKeyShared Text -> Text) -> (Method, Text)
forall endpoint.
(HasLink endpoint, IsElem endpoint endpoint, HasVerb endpoint) =>
(MkLink endpoint Text -> Text) -> (Method, Text)
endpoint @Api.GetAccountKeyShared (\MkLink GetAccountKeyShared Text
mk -> MkLink GetAccountKeyShared Text
ApiT WalletId -> Maybe KeyFormat -> Text
mk ApiT WalletId
wid Maybe KeyFormat
extended))
where
wid :: ApiT WalletId
wid = w
w w
-> ((ApiT WalletId -> Const (ApiT WalletId) (ApiT WalletId))
-> w -> Const (ApiT WalletId) w)
-> ApiT WalletId
forall s a. s -> ((a -> Const a a) -> s -> Const a s) -> a
^. forall s.
HasType (ApiT WalletId) s =>
Lens s s (ApiT WalletId) (ApiT WalletId)
forall a s. HasType a s => Lens s s a a
typed @(ApiT WalletId)
getPolicyKey
:: forall style w.
( HasCallStack
, HasType (ApiT WalletId) w
, Discriminate style
)
=> w
-> Maybe Bool
-> (Method, Text)
getPolicyKey :: w -> Maybe Bool -> (Method, Text)
getPolicyKey w
w Maybe Bool
hashed = (Method, Text)
-> (Method, Text) -> (Method, Text) -> (Method, Text)
forall (style :: WalletStyle) a.
Discriminate style =>
a -> a -> a -> a
discriminate @style
((MkLink GetPolicyKey Text -> Text) -> (Method, Text)
forall endpoint.
(HasLink endpoint, IsElem endpoint endpoint, HasVerb endpoint) =>
(MkLink endpoint Text -> Text) -> (Method, Text)
endpoint @Api.GetPolicyKey (\MkLink GetPolicyKey Text
mk -> MkLink GetPolicyKey Text
ApiT WalletId -> Maybe Bool -> Text
mk ApiT WalletId
wid Maybe Bool
hashed))
(String -> (Method, Text)
forall a. HasCallStack => String -> a
notSupported String
"Byron")
(String -> (Method, Text)
forall a. HasCallStack => String -> a
notSupported String
"Shared")
where
wid :: ApiT WalletId
wid = w
w w
-> ((ApiT WalletId -> Const (ApiT WalletId) (ApiT WalletId))
-> w -> Const (ApiT WalletId) w)
-> ApiT WalletId
forall s a. s -> ((a -> Const a a) -> s -> Const a s) -> a
^. forall s.
HasType (ApiT WalletId) s =>
Lens s s (ApiT WalletId) (ApiT WalletId)
forall a s. HasType a s => Lens s s a a
typed @(ApiT WalletId)
postPolicyKey
:: forall (style :: WalletStyle) w.
( HasCallStack
, Discriminate style
, HasType (ApiT WalletId) w
)
=> w
-> Maybe Bool
-> (Method, Text)
postPolicyKey :: w -> Maybe Bool -> (Method, Text)
postPolicyKey w
w Maybe Bool
hashed = (Method, Text)
-> (Method, Text) -> (Method, Text) -> (Method, Text)
forall (style :: WalletStyle) a.
Discriminate style =>
a -> a -> a -> a
discriminate @style
((MkLink PostPolicyKey Text -> Text) -> (Method, Text)
forall endpoint.
(HasLink endpoint, IsElem endpoint endpoint, HasVerb endpoint) =>
(MkLink endpoint Text -> Text) -> (Method, Text)
endpoint @Api.PostPolicyKey (\MkLink PostPolicyKey Text
mk -> MkLink PostPolicyKey Text
ApiT WalletId -> Maybe Bool -> Text
mk ApiT WalletId
wid Maybe Bool
hashed))
(String -> (Method, Text)
forall a. HasCallStack => String -> a
notSupported String
"Byron")
(String -> (Method, Text)
forall a. HasCallStack => String -> a
notSupported String
"Shared")
where
wid :: ApiT WalletId
wid = w
w w
-> ((ApiT WalletId -> Const (ApiT WalletId) (ApiT WalletId))
-> w -> Const (ApiT WalletId) w)
-> ApiT WalletId
forall s a. s -> ((a -> Const a a) -> s -> Const a s) -> a
^. forall s.
HasType (ApiT WalletId) s =>
Lens s s (ApiT WalletId) (ApiT WalletId)
forall a s. HasType a s => Lens s s a a
typed @(ApiT WalletId)
postPolicyId
:: forall (style :: WalletStyle) w.
( HasCallStack
, Discriminate style
, HasType (ApiT WalletId) w
)
=> w
-> (Method, Text)
postPolicyId :: w -> (Method, Text)
postPolicyId w
w = (Method, Text)
-> (Method, Text) -> (Method, Text) -> (Method, Text)
forall (style :: WalletStyle) a.
Discriminate style =>
a -> a -> a -> a
discriminate @style
((MkLink PostPolicyId Text -> Text) -> (Method, Text)
forall endpoint.
(HasLink endpoint, IsElem endpoint endpoint, HasVerb endpoint) =>
(MkLink endpoint Text -> Text) -> (Method, Text)
endpoint @Api.PostPolicyId (ApiT WalletId
wid ApiT WalletId -> (ApiT WalletId -> Text) -> Text
forall a b. a -> (a -> b) -> b
&))
(String -> (Method, Text)
forall a. HasCallStack => String -> a
notSupported String
"Byron")
(String -> (Method, Text)
forall a. HasCallStack => String -> a
notSupported String
"Shared")
where
wid :: ApiT WalletId
wid = w
w w
-> ((ApiT WalletId -> Const (ApiT WalletId) (ApiT WalletId))
-> w -> Const (ApiT WalletId) w)
-> ApiT WalletId
forall s a. s -> ((a -> Const a a) -> s -> Const a s) -> a
^. forall s.
HasType (ApiT WalletId) s =>
Lens s s (ApiT WalletId) (ApiT WalletId)
forall a s. HasType a s => Lens s s a a
typed @(ApiT WalletId)
postRandomAddress
:: forall w.
( HasType (ApiT WalletId) w
)
=> w
-> (Method, Text)
postRandomAddress :: w -> (Method, Text)
postRandomAddress w
w =
(MkLink (PostByronAddress Net) Text -> Text) -> (Method, Text)
forall endpoint.
(HasLink endpoint, IsElem endpoint endpoint, HasVerb endpoint) =>
(MkLink endpoint Text -> Text) -> (Method, Text)
endpoint @(Api.PostByronAddress Net) (ApiT WalletId
wid ApiT WalletId -> (ApiT WalletId -> Text) -> Text
forall a b. a -> (a -> b) -> b
&)
where
wid :: ApiT WalletId
wid = w
w w
-> ((ApiT WalletId -> Const (ApiT WalletId) (ApiT WalletId))
-> w -> Const (ApiT WalletId) w)
-> ApiT WalletId
forall s a. s -> ((a -> Const a a) -> s -> Const a s) -> a
^. forall s.
HasType (ApiT WalletId) s =>
Lens s s (ApiT WalletId) (ApiT WalletId)
forall a s. HasType a s => Lens s s a a
typed @(ApiT WalletId)
putRandomAddresses
:: forall w.
( HasType (ApiT WalletId) w
)
=> w
-> (Method, Text)
putRandomAddresses :: w -> (Method, Text)
putRandomAddresses w
w =
(MkLink (PutByronAddresses Net) Text -> Text) -> (Method, Text)
forall endpoint.
(HasLink endpoint, IsElem endpoint endpoint, HasVerb endpoint) =>
(MkLink endpoint Text -> Text) -> (Method, Text)
endpoint @(Api.PutByronAddresses Net) (ApiT WalletId
wid ApiT WalletId -> (ApiT WalletId -> Text) -> Text
forall a b. a -> (a -> b) -> b
&)
where
wid :: ApiT WalletId
wid = w
w w
-> ((ApiT WalletId -> Const (ApiT WalletId) (ApiT WalletId))
-> w -> Const (ApiT WalletId) w)
-> ApiT WalletId
forall s a. s -> ((a -> Const a a) -> s -> Const a s) -> a
^. forall s.
HasType (ApiT WalletId) s =>
Lens s s (ApiT WalletId) (ApiT WalletId)
forall a s. HasType a s => Lens s s a a
typed @(ApiT WalletId)
listAddresses
:: forall style w.
( HasType (ApiT WalletId) w
, Discriminate style
)
=> w
-> (Method, Text)
listAddresses :: w -> (Method, Text)
listAddresses w
w =
w -> Maybe AddressState -> (Method, Text)
forall (style :: WalletStyle) w.
(HasType (ApiT WalletId) w, Discriminate style) =>
w -> Maybe AddressState -> (Method, Text)
listAddresses' @style w
w Maybe AddressState
forall a. Maybe a
Nothing
listAddresses'
:: forall style w.
( HasType (ApiT WalletId) w
, Discriminate style
)
=> w
-> Maybe AddressState
-> (Method, Text)
listAddresses' :: w -> Maybe AddressState -> (Method, Text)
listAddresses' w
w Maybe AddressState
mstate = (Method, Text)
-> (Method, Text) -> (Method, Text) -> (Method, Text)
forall (style :: WalletStyle) a.
Discriminate style =>
a -> a -> a -> a
discriminate @style
((MkLink (ListAddresses Net) Text -> Text) -> (Method, Text)
forall endpoint.
(HasLink endpoint, IsElem endpoint endpoint, HasVerb endpoint) =>
(MkLink endpoint Text -> Text) -> (Method, Text)
endpoint @(Api.ListAddresses Net) (\MkLink (ListAddresses Net) Text
mk -> MkLink (ListAddresses Net) Text
ApiT WalletId -> Maybe (ApiT AddressState) -> Text
mk ApiT WalletId
wid (AddressState -> ApiT AddressState
forall a. a -> ApiT a
ApiT (AddressState -> ApiT AddressState)
-> Maybe AddressState -> Maybe (ApiT AddressState)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe AddressState
mstate)))
((MkLink (ListByronAddresses Net) Text -> Text) -> (Method, Text)
forall endpoint.
(HasLink endpoint, IsElem endpoint endpoint, HasVerb endpoint) =>
(MkLink endpoint Text -> Text) -> (Method, Text)
endpoint @(Api.ListByronAddresses Net) (\MkLink (ListByronAddresses Net) Text
mk -> MkLink (ListByronAddresses Net) Text
ApiT WalletId -> Maybe (ApiT AddressState) -> Text
mk ApiT WalletId
wid (AddressState -> ApiT AddressState
forall a. a -> ApiT a
ApiT (AddressState -> ApiT AddressState)
-> Maybe AddressState -> Maybe (ApiT AddressState)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe AddressState
mstate)))
((MkLink (ListSharedAddresses Net) Text -> Text) -> (Method, Text)
forall endpoint.
(HasLink endpoint, IsElem endpoint endpoint, HasVerb endpoint) =>
(MkLink endpoint Text -> Text) -> (Method, Text)
endpoint @(Api.ListSharedAddresses Net) (\MkLink (ListSharedAddresses Net) Text
mk -> MkLink (ListSharedAddresses Net) Text
ApiT WalletId -> Maybe (ApiT AddressState) -> Text
mk ApiT WalletId
wid (AddressState -> ApiT AddressState
forall a. a -> ApiT a
ApiT (AddressState -> ApiT AddressState)
-> Maybe AddressState -> Maybe (ApiT AddressState)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe AddressState
mstate)))
where
wid :: ApiT WalletId
wid = w
w w
-> ((ApiT WalletId -> Const (ApiT WalletId) (ApiT WalletId))
-> w -> Const (ApiT WalletId) w)
-> ApiT WalletId
forall s a. s -> ((a -> Const a a) -> s -> Const a s) -> a
^. forall s.
HasType (ApiT WalletId) s =>
Lens s s (ApiT WalletId) (ApiT WalletId)
forall a s. HasType a s => Lens s s a a
typed @(ApiT WalletId)
inspectAddress
:: ApiAddressInspectData
-> (Method, Text)
inspectAddress :: ApiAddressInspectData -> (Method, Text)
inspectAddress ApiAddressInspectData
addr =
(MkLink InspectAddress Text -> Text) -> (Method, Text)
forall endpoint.
(HasLink endpoint, IsElem endpoint endpoint, HasVerb endpoint) =>
(MkLink endpoint Text -> Text) -> (Method, Text)
endpoint @Api.InspectAddress (ApiAddressInspectData
addr ApiAddressInspectData -> (ApiAddressInspectData -> Text) -> Text
forall a b. a -> (a -> b) -> b
&)
postAnyAddress
:: (Method, Text)
postAnyAddress :: (Method, Text)
postAnyAddress =
(MkLink (PostAnyAddress Net) Text -> Text) -> (Method, Text)
forall endpoint.
(HasLink endpoint, IsElem endpoint endpoint, HasVerb endpoint) =>
(MkLink endpoint Text -> Text) -> (Method, Text)
endpoint @(Api.PostAnyAddress Net) MkLink (PostAnyAddress Net) Text -> Text
forall a. a -> a
id
selectCoins
:: forall style w.
( HasCallStack
, HasType (ApiT WalletId) w
, Discriminate style
)
=> w
-> (Method, Text)
selectCoins :: w -> (Method, Text)
selectCoins w
w = (Method, Text)
-> (Method, Text) -> (Method, Text) -> (Method, Text)
forall (style :: WalletStyle) a.
Discriminate style =>
a -> a -> a -> a
discriminate @style
((MkLink (SelectCoins Net) Text -> Text) -> (Method, Text)
forall endpoint.
(HasLink endpoint, IsElem endpoint endpoint, HasVerb endpoint) =>
(MkLink endpoint Text -> Text) -> (Method, Text)
endpoint @(Api.SelectCoins Net) (ApiT WalletId
wid ApiT WalletId -> (ApiT WalletId -> Text) -> Text
forall a b. a -> (a -> b) -> b
&))
((MkLink (ByronSelectCoins Net) Text -> Text) -> (Method, Text)
forall endpoint.
(HasLink endpoint, IsElem endpoint endpoint, HasVerb endpoint) =>
(MkLink endpoint Text -> Text) -> (Method, Text)
endpoint @(Api.ByronSelectCoins Net) (ApiT WalletId
wid ApiT WalletId -> (ApiT WalletId -> Text) -> Text
forall a b. a -> (a -> b) -> b
&))
(String -> (Method, Text)
forall a. HasCallStack => String -> a
notSupported String
"Shared")
where
wid :: ApiT WalletId
wid = w
w w
-> ((ApiT WalletId -> Const (ApiT WalletId) (ApiT WalletId))
-> w -> Const (ApiT WalletId) w)
-> ApiT WalletId
forall s a. s -> ((a -> Const a a) -> s -> Const a s) -> a
^. forall s.
HasType (ApiT WalletId) s =>
Lens s s (ApiT WalletId) (ApiT WalletId)
forall a s. HasType a s => Lens s s a a
typed @(ApiT WalletId)
listAssets
:: forall w.
( HasType (ApiT WalletId) w
)
=> w
-> (Method, Text)
listAssets :: w -> (Method, Text)
listAssets w
w =
(MkLink ListAssets Text -> Text) -> (Method, Text)
forall endpoint.
(HasLink endpoint, IsElem endpoint endpoint, HasVerb endpoint) =>
(MkLink endpoint Text -> Text) -> (Method, Text)
endpoint @Api.ListAssets (ApiT WalletId
wid ApiT WalletId -> (ApiT WalletId -> Text) -> Text
forall a b. a -> (a -> b) -> b
&)
where
wid :: ApiT WalletId
wid = w
w w
-> ((ApiT WalletId -> Const (ApiT WalletId) (ApiT WalletId))
-> w -> Const (ApiT WalletId) w)
-> ApiT WalletId
forall s a. s -> ((a -> Const a a) -> s -> Const a s) -> a
^. forall s.
HasType (ApiT WalletId) s =>
Lens s s (ApiT WalletId) (ApiT WalletId)
forall a s. HasType a s => Lens s s a a
typed @(ApiT WalletId)
getAsset
:: forall w.
( HasType (ApiT WalletId) w
)
=> w
-> TokenPolicyId
-> TokenName
-> (Method, Text)
getAsset :: w -> TokenPolicyId -> TokenName -> (Method, Text)
getAsset w
w TokenPolicyId
pid TokenName
n
| TokenName
n TokenName -> TokenName -> Bool
forall a. Eq a => a -> a -> Bool
== TokenName
nullTokenName = (MkLink GetAssetDefault Text -> Text) -> (Method, Text)
forall endpoint.
(HasLink endpoint, IsElem endpoint endpoint, HasVerb endpoint) =>
(MkLink endpoint Text -> Text) -> (Method, Text)
endpoint @Api.GetAssetDefault MkLink GetAssetDefault Text -> Text
(ApiT WalletId -> ApiT TokenPolicyId -> Text) -> Text
mkURLDefault
| Bool
otherwise = (MkLink GetAsset Text -> Text) -> (Method, Text)
forall endpoint.
(HasLink endpoint, IsElem endpoint endpoint, HasVerb endpoint) =>
(MkLink endpoint Text -> Text) -> (Method, Text)
endpoint @Api.GetAsset MkLink GetAsset Text -> Text
(ApiT WalletId -> ApiT TokenPolicyId -> ApiT TokenName -> Text)
-> Text
mkURL
where
wid :: ApiT WalletId
wid = w
w w
-> ((ApiT WalletId -> Const (ApiT WalletId) (ApiT WalletId))
-> w -> Const (ApiT WalletId) w)
-> ApiT WalletId
forall s a. s -> ((a -> Const a a) -> s -> Const a s) -> a
^. forall s.
HasType (ApiT WalletId) s =>
Lens s s (ApiT WalletId) (ApiT WalletId)
forall a s. HasType a s => Lens s s a a
typed @(ApiT WalletId)
mkURL :: (ApiT WalletId -> ApiT TokenPolicyId -> ApiT TokenName -> Text)
-> Text
mkURL ApiT WalletId -> ApiT TokenPolicyId -> ApiT TokenName -> Text
mk = ApiT WalletId -> ApiT TokenPolicyId -> ApiT TokenName -> Text
mk ApiT WalletId
wid (TokenPolicyId -> ApiT TokenPolicyId
forall a. a -> ApiT a
ApiT TokenPolicyId
pid) (TokenName -> ApiT TokenName
forall a. a -> ApiT a
ApiT TokenName
n)
mkURLDefault :: (ApiT WalletId -> ApiT TokenPolicyId -> Text) -> Text
mkURLDefault ApiT WalletId -> ApiT TokenPolicyId -> Text
mk = ApiT WalletId -> ApiT TokenPolicyId -> Text
mk ApiT WalletId
wid (TokenPolicyId -> ApiT TokenPolicyId
forall a. a -> ApiT a
ApiT TokenPolicyId
pid)
listByronAssets
:: forall w.
( HasType (ApiT WalletId) w
)
=> w
-> (Method, Text)
listByronAssets :: w -> (Method, Text)
listByronAssets w
w =
(MkLink ListByronAssets Text -> Text) -> (Method, Text)
forall endpoint.
(HasLink endpoint, IsElem endpoint endpoint, HasVerb endpoint) =>
(MkLink endpoint Text -> Text) -> (Method, Text)
endpoint @Api.ListByronAssets (ApiT WalletId
wid ApiT WalletId -> (ApiT WalletId -> Text) -> Text
forall a b. a -> (a -> b) -> b
&)
where
wid :: ApiT WalletId
wid = w
w w
-> ((ApiT WalletId -> Const (ApiT WalletId) (ApiT WalletId))
-> w -> Const (ApiT WalletId) w)
-> ApiT WalletId
forall s a. s -> ((a -> Const a a) -> s -> Const a s) -> a
^. forall s.
HasType (ApiT WalletId) s =>
Lens s s (ApiT WalletId) (ApiT WalletId)
forall a s. HasType a s => Lens s s a a
typed @(ApiT WalletId)
getByronAsset
:: forall w.
( HasType (ApiT WalletId) w
)
=> w
-> TokenPolicyId
-> TokenName
-> (Method, Text)
getByronAsset :: w -> TokenPolicyId -> TokenName -> (Method, Text)
getByronAsset w
w TokenPolicyId
pid TokenName
n
| TokenName
n TokenName -> TokenName -> Bool
forall a. Eq a => a -> a -> Bool
== TokenName
nullTokenName = (MkLink GetByronAssetDefault Text -> Text) -> (Method, Text)
forall endpoint.
(HasLink endpoint, IsElem endpoint endpoint, HasVerb endpoint) =>
(MkLink endpoint Text -> Text) -> (Method, Text)
endpoint @Api.GetByronAssetDefault MkLink GetByronAssetDefault Text -> Text
(ApiT WalletId -> ApiT TokenPolicyId -> Text) -> Text
mkURLDefault
| Bool
otherwise = (MkLink GetByronAsset Text -> Text) -> (Method, Text)
forall endpoint.
(HasLink endpoint, IsElem endpoint endpoint, HasVerb endpoint) =>
(MkLink endpoint Text -> Text) -> (Method, Text)
endpoint @Api.GetByronAsset MkLink GetByronAsset Text -> Text
(ApiT WalletId -> ApiT TokenPolicyId -> ApiT TokenName -> Text)
-> Text
mkURL
where
wid :: ApiT WalletId
wid = w
w w
-> ((ApiT WalletId -> Const (ApiT WalletId) (ApiT WalletId))
-> w -> Const (ApiT WalletId) w)
-> ApiT WalletId
forall s a. s -> ((a -> Const a a) -> s -> Const a s) -> a
^. forall s.
HasType (ApiT WalletId) s =>
Lens s s (ApiT WalletId) (ApiT WalletId)
forall a s. HasType a s => Lens s s a a
typed @(ApiT WalletId)
mkURL :: (ApiT WalletId -> ApiT TokenPolicyId -> ApiT TokenName -> Text)
-> Text
mkURL ApiT WalletId -> ApiT TokenPolicyId -> ApiT TokenName -> Text
mk = ApiT WalletId -> ApiT TokenPolicyId -> ApiT TokenName -> Text
mk ApiT WalletId
wid (TokenPolicyId -> ApiT TokenPolicyId
forall a. a -> ApiT a
ApiT TokenPolicyId
pid) (TokenName -> ApiT TokenName
forall a. a -> ApiT a
ApiT TokenName
n)
mkURLDefault :: (ApiT WalletId -> ApiT TokenPolicyId -> Text) -> Text
mkURLDefault ApiT WalletId -> ApiT TokenPolicyId -> Text
mk = ApiT WalletId -> ApiT TokenPolicyId -> Text
mk ApiT WalletId
wid (TokenPolicyId -> ApiT TokenPolicyId
forall a. a -> ApiT a
ApiT TokenPolicyId
pid)
createTransactionOld
:: forall style w.
( HasCallStack
, HasType (ApiT WalletId) w
, Discriminate style
)
=> w
-> (Method, Text)
createTransactionOld :: w -> (Method, Text)
createTransactionOld w
w = (Method, Text)
-> (Method, Text) -> (Method, Text) -> (Method, Text)
forall (style :: WalletStyle) a.
Discriminate style =>
a -> a -> a -> a
discriminate @style
((MkLink (CreateTransactionOld Net) Text -> Text) -> (Method, Text)
forall endpoint.
(HasLink endpoint, IsElem endpoint endpoint, HasVerb endpoint) =>
(MkLink endpoint Text -> Text) -> (Method, Text)
endpoint @(Api.CreateTransactionOld Net) (ApiT WalletId
wid ApiT WalletId -> (ApiT WalletId -> Text) -> Text
forall a b. a -> (a -> b) -> b
&))
((MkLink (CreateByronTransactionOld Net) Text -> Text)
-> (Method, Text)
forall endpoint.
(HasLink endpoint, IsElem endpoint endpoint, HasVerb endpoint) =>
(MkLink endpoint Text -> Text) -> (Method, Text)
endpoint @(Api.CreateByronTransactionOld Net) (ApiT WalletId
wid ApiT WalletId -> (ApiT WalletId -> Text) -> Text
forall a b. a -> (a -> b) -> b
&))
(String -> (Method, Text)
forall a. HasCallStack => String -> a
notSupported String
"Shared")
where
wid :: ApiT WalletId
wid = w
w w
-> ((ApiT WalletId -> Const (ApiT WalletId) (ApiT WalletId))
-> w -> Const (ApiT WalletId) w)
-> ApiT WalletId
forall s a. s -> ((a -> Const a a) -> s -> Const a s) -> a
^. forall s.
HasType (ApiT WalletId) s =>
Lens s s (ApiT WalletId) (ApiT WalletId)
forall a s. HasType a s => Lens s s a a
typed @(ApiT WalletId)
listTransactions
:: forall (style :: WalletStyle) w.
( Discriminate style
, HasType (ApiT WalletId) w
)
=> w
-> (Method, Text)
listTransactions :: w -> (Method, Text)
listTransactions w
w =
w
-> Maybe Natural
-> Maybe Iso8601Time
-> Maybe Iso8601Time
-> Maybe SortOrder
-> (Method, Text)
forall (style :: WalletStyle) w.
(HasCallStack, Discriminate style, HasType (ApiT WalletId) w) =>
w
-> Maybe Natural
-> Maybe Iso8601Time
-> Maybe Iso8601Time
-> Maybe SortOrder
-> (Method, Text)
listTransactions' @style w
w Maybe Natural
forall a. Maybe a
Nothing Maybe Iso8601Time
forall a. Maybe a
Nothing Maybe Iso8601Time
forall a. Maybe a
Nothing Maybe SortOrder
forall a. Maybe a
Nothing
listTransactions'
:: forall (style :: WalletStyle) w.
( HasCallStack
, Discriminate style
, HasType (ApiT WalletId) w
)
=> w
-> Maybe Natural
-> Maybe Iso8601Time
-> Maybe Iso8601Time
-> Maybe SortOrder
-> (Method, Text)
listTransactions' :: w
-> Maybe Natural
-> Maybe Iso8601Time
-> Maybe Iso8601Time
-> Maybe SortOrder
-> (Method, Text)
listTransactions' w
w Maybe Natural
minWithdrawal Maybe Iso8601Time
inf Maybe Iso8601Time
sup Maybe SortOrder
order = (Method, Text)
-> (Method, Text) -> (Method, Text) -> (Method, Text)
forall (style :: WalletStyle) a.
Discriminate style =>
a -> a -> a -> a
discriminate @style
((MkLink (ListTransactions Net) Text -> Text) -> (Method, Text)
forall endpoint.
(HasLink endpoint, IsElem endpoint endpoint, HasVerb endpoint) =>
(MkLink endpoint Text -> Text) -> (Method, Text)
endpoint @(Api.ListTransactions Net)
(\MkLink (ListTransactions Net) Text
mk -> MkLink (ListTransactions Net) Text
ApiT WalletId
-> Maybe MinWithdrawal
-> Maybe Iso8601Time
-> Maybe Iso8601Time
-> Maybe (ApiT SortOrder)
-> Bool
-> Text
mk
ApiT WalletId
wid
(Natural -> MinWithdrawal
MinWithdrawal (Natural -> MinWithdrawal) -> Maybe Natural -> Maybe MinWithdrawal
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe Natural
minWithdrawal)
Maybe Iso8601Time
inf
Maybe Iso8601Time
sup
(SortOrder -> ApiT SortOrder
forall a. a -> ApiT a
ApiT (SortOrder -> ApiT SortOrder)
-> Maybe SortOrder -> Maybe (ApiT SortOrder)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe SortOrder
order)
(TxMetadataSchema -> Bool
toSimpleMetadataFlag TxMetadataSchema
TxMetadataDetailedSchema)
)
)
((MkLink (ListByronTransactions Net) Text -> Text) -> (Method, Text)
forall endpoint.
(HasLink endpoint, IsElem endpoint endpoint, HasVerb endpoint) =>
(MkLink endpoint Text -> Text) -> (Method, Text)
endpoint @(Api.ListByronTransactions Net)
(\MkLink (ListByronTransactions Net) Text
mk -> MkLink (ListByronTransactions Net) Text
ApiT WalletId
-> Maybe Iso8601Time
-> Maybe Iso8601Time
-> Maybe (ApiT SortOrder)
-> Text
mk ApiT WalletId
wid Maybe Iso8601Time
inf Maybe Iso8601Time
sup (SortOrder -> ApiT SortOrder
forall a. a -> ApiT a
ApiT (SortOrder -> ApiT SortOrder)
-> Maybe SortOrder -> Maybe (ApiT SortOrder)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe SortOrder
order)))
(String -> (Method, Text)
forall a. HasCallStack => String -> a
notSupported String
"Shared")
where
wid :: ApiT WalletId
wid = w
w w
-> ((ApiT WalletId -> Const (ApiT WalletId) (ApiT WalletId))
-> w -> Const (ApiT WalletId) w)
-> ApiT WalletId
forall s a. s -> ((a -> Const a a) -> s -> Const a s) -> a
^. forall s.
HasType (ApiT WalletId) s =>
Lens s s (ApiT WalletId) (ApiT WalletId)
forall a s. HasType a s => Lens s s a a
typed @(ApiT WalletId)
getTransactionFeeOld
:: forall style w.
( HasCallStack
, HasType (ApiT WalletId) w
, Discriminate style
)
=> w
-> (Method, Text)
getTransactionFeeOld :: w -> (Method, Text)
getTransactionFeeOld w
w = (Method, Text)
-> (Method, Text) -> (Method, Text) -> (Method, Text)
forall (style :: WalletStyle) a.
Discriminate style =>
a -> a -> a -> a
discriminate @style
((MkLink (PostTransactionFeeOld Net) Text -> Text) -> (Method, Text)
forall endpoint.
(HasLink endpoint, IsElem endpoint endpoint, HasVerb endpoint) =>
(MkLink endpoint Text -> Text) -> (Method, Text)
endpoint @(Api.PostTransactionFeeOld Net) (ApiT WalletId
wid ApiT WalletId -> (ApiT WalletId -> Text) -> Text
forall a b. a -> (a -> b) -> b
&))
((MkLink (PostByronTransactionFeeOld Net) Text -> Text)
-> (Method, Text)
forall endpoint.
(HasLink endpoint, IsElem endpoint endpoint, HasVerb endpoint) =>
(MkLink endpoint Text -> Text) -> (Method, Text)
endpoint @(Api.PostByronTransactionFeeOld Net) (ApiT WalletId
wid ApiT WalletId -> (ApiT WalletId -> Text) -> Text
forall a b. a -> (a -> b) -> b
&))
(String -> (Method, Text)
forall a. HasCallStack => String -> a
notSupported String
"Shared")
where
wid :: ApiT WalletId
wid = w
w w
-> ((ApiT WalletId -> Const (ApiT WalletId) (ApiT WalletId))
-> w -> Const (ApiT WalletId) w)
-> ApiT WalletId
forall s a. s -> ((a -> Const a a) -> s -> Const a s) -> a
^. forall s.
HasType (ApiT WalletId) s =>
Lens s s (ApiT WalletId) (ApiT WalletId)
forall a s. HasType a s => Lens s s a a
typed @(ApiT WalletId)
deleteTransaction
:: forall (style :: WalletStyle) w t.
( HasCallStack
, Discriminate style
, HasType (ApiT WalletId) w
, HasType (ApiT (Hash "Tx")) t
)
=> w
-> t
-> (Method, Text)
deleteTransaction :: w -> t -> (Method, Text)
deleteTransaction w
w t
t = (Method, Text)
-> (Method, Text) -> (Method, Text) -> (Method, Text)
forall (style :: WalletStyle) a.
Discriminate style =>
a -> a -> a -> a
discriminate @style
((MkLink DeleteTransaction Text -> Text) -> (Method, Text)
forall endpoint.
(HasLink endpoint, IsElem endpoint endpoint, HasVerb endpoint) =>
(MkLink endpoint Text -> Text) -> (Method, Text)
endpoint @Api.DeleteTransaction MkLink DeleteTransaction Text -> Text
(ApiT WalletId -> ApiTxId -> Text) -> Text
mkURL)
((MkLink DeleteByronTransaction Text -> Text) -> (Method, Text)
forall endpoint.
(HasLink endpoint, IsElem endpoint endpoint, HasVerb endpoint) =>
(MkLink endpoint Text -> Text) -> (Method, Text)
endpoint @Api.DeleteByronTransaction MkLink DeleteByronTransaction Text -> Text
(ApiT WalletId -> ApiTxId -> Text) -> Text
mkURL)
(String -> (Method, Text)
forall a. HasCallStack => String -> a
notSupported String
"Shared")
where
wid :: ApiT WalletId
wid = w
w w
-> ((ApiT WalletId -> Const (ApiT WalletId) (ApiT WalletId))
-> w -> Const (ApiT WalletId) w)
-> ApiT WalletId
forall s a. s -> ((a -> Const a a) -> s -> Const a s) -> a
^. forall s.
HasType (ApiT WalletId) s =>
Lens s s (ApiT WalletId) (ApiT WalletId)
forall a s. HasType a s => Lens s s a a
typed @(ApiT WalletId)
tid :: ApiTxId
tid = ApiT (Hash "Tx") -> ApiTxId
ApiTxId (t
t t
-> ((ApiT (Hash "Tx")
-> Const (ApiT (Hash "Tx")) (ApiT (Hash "Tx")))
-> t -> Const (ApiT (Hash "Tx")) t)
-> ApiT (Hash "Tx")
forall s a. s -> ((a -> Const a a) -> s -> Const a s) -> a
^. forall s.
HasType (ApiT (Hash "Tx")) s =>
Lens s s (ApiT (Hash "Tx")) (ApiT (Hash "Tx"))
forall a s. HasType a s => Lens s s a a
typed @(ApiT (Hash "Tx")))
mkURL :: (ApiT WalletId -> ApiTxId -> Text) -> Text
mkURL ApiT WalletId -> ApiTxId -> Text
mk = ApiT WalletId -> ApiTxId -> Text
mk ApiT WalletId
wid ApiTxId
tid
getTransaction
:: forall (style :: WalletStyle) w t.
( HasCallStack
, Discriminate style
, HasType (ApiT WalletId) w
, HasType (ApiT (Hash "Tx")) t
)
=> w
-> t
-> (Method, Text)
getTransaction :: w -> t -> (Method, Text)
getTransaction w
w t
t = (Method, Text)
-> (Method, Text) -> (Method, Text) -> (Method, Text)
forall (style :: WalletStyle) a.
Discriminate style =>
a -> a -> a -> a
discriminate @style
((MkLink (GetTransaction Net) Text -> Text) -> (Method, Text)
forall endpoint.
(HasLink endpoint, IsElem endpoint endpoint, HasVerb endpoint) =>
(MkLink endpoint Text -> Text) -> (Method, Text)
endpoint @(Api.GetTransaction Net) MkLink (GetTransaction Net) Text -> Text
(ApiT WalletId -> ApiTxId -> Bool -> Text) -> Text
mkShelleyURL)
((MkLink (GetByronTransaction Net) Text -> Text) -> (Method, Text)
forall endpoint.
(HasLink endpoint, IsElem endpoint endpoint, HasVerb endpoint) =>
(MkLink endpoint Text -> Text) -> (Method, Text)
endpoint @(Api.GetByronTransaction Net) MkLink (GetByronTransaction Net) Text -> Text
(ApiT WalletId -> ApiTxId -> Text) -> Text
mkByronURL)
(String -> (Method, Text)
forall a. HasCallStack => String -> a
notSupported String
"Shared")
where
wid :: ApiT WalletId
wid = w
w w
-> ((ApiT WalletId -> Const (ApiT WalletId) (ApiT WalletId))
-> w -> Const (ApiT WalletId) w)
-> ApiT WalletId
forall s a. s -> ((a -> Const a a) -> s -> Const a s) -> a
^. forall s.
HasType (ApiT WalletId) s =>
Lens s s (ApiT WalletId) (ApiT WalletId)
forall a s. HasType a s => Lens s s a a
typed @(ApiT WalletId)
tid :: ApiTxId
tid = ApiT (Hash "Tx") -> ApiTxId
ApiTxId (t
t t
-> ((ApiT (Hash "Tx")
-> Const (ApiT (Hash "Tx")) (ApiT (Hash "Tx")))
-> t -> Const (ApiT (Hash "Tx")) t)
-> ApiT (Hash "Tx")
forall s a. s -> ((a -> Const a a) -> s -> Const a s) -> a
^. forall s.
HasType (ApiT (Hash "Tx")) s =>
Lens s s (ApiT (Hash "Tx")) (ApiT (Hash "Tx"))
forall a s. HasType a s => Lens s s a a
typed @(ApiT (Hash "Tx")))
mkByronURL :: (ApiT WalletId -> ApiTxId -> Text) -> Text
mkByronURL ApiT WalletId -> ApiTxId -> Text
mk = ApiT WalletId -> ApiTxId -> Text
mk ApiT WalletId
wid ApiTxId
tid
mkShelleyURL :: (ApiT WalletId -> ApiTxId -> Bool -> Text) -> Text
mkShelleyURL :: (ApiT WalletId -> ApiTxId -> Bool -> Text) -> Text
mkShelleyURL ApiT WalletId -> ApiTxId -> Bool -> Text
mk =
ApiT WalletId -> ApiTxId -> Bool -> Text
mk ApiT WalletId
wid ApiTxId
tid (TxMetadataSchema -> Bool
toSimpleMetadataFlag TxMetadataSchema
TxMetadataDetailedSchema)
createUnsignedTransaction
:: forall style w.
( HasType (ApiT WalletId) w
, Discriminate style
)
=> w
-> (Method, Text)
createUnsignedTransaction :: w -> (Method, Text)
createUnsignedTransaction w
w = (Method, Text)
-> (Method, Text) -> (Method, Text) -> (Method, Text)
forall (style :: WalletStyle) a.
Discriminate style =>
a -> a -> a -> a
discriminate @style
((MkLink (ConstructTransaction Net) Text -> Text) -> (Method, Text)
forall endpoint.
(HasLink endpoint, IsElem endpoint endpoint, HasVerb endpoint) =>
(MkLink endpoint Text -> Text) -> (Method, Text)
endpoint @(Api.ConstructTransaction Net) (ApiT WalletId
wid ApiT WalletId -> (ApiT WalletId -> Text) -> Text
forall a b. a -> (a -> b) -> b
&))
((MkLink (ConstructByronTransaction Net) Text -> Text)
-> (Method, Text)
forall endpoint.
(HasLink endpoint, IsElem endpoint endpoint, HasVerb endpoint) =>
(MkLink endpoint Text -> Text) -> (Method, Text)
endpoint @(Api.ConstructByronTransaction Net) (ApiT WalletId
wid ApiT WalletId -> (ApiT WalletId -> Text) -> Text
forall a b. a -> (a -> b) -> b
&))
((MkLink (ConstructSharedTransaction Net) Text -> Text)
-> (Method, Text)
forall endpoint.
(HasLink endpoint, IsElem endpoint endpoint, HasVerb endpoint) =>
(MkLink endpoint Text -> Text) -> (Method, Text)
endpoint @(Api.ConstructSharedTransaction Net) (ApiT WalletId
wid ApiT WalletId -> (ApiT WalletId -> Text) -> Text
forall a b. a -> (a -> b) -> b
&))
where
wid :: ApiT WalletId
wid = w
w w
-> ((ApiT WalletId -> Const (ApiT WalletId) (ApiT WalletId))
-> w -> Const (ApiT WalletId) w)
-> ApiT WalletId
forall s a. s -> ((a -> Const a a) -> s -> Const a s) -> a
^. forall s.
HasType (ApiT WalletId) s =>
Lens s s (ApiT WalletId) (ApiT WalletId)
forall a s. HasType a s => Lens s s a a
typed @(ApiT WalletId)
signTransaction
:: forall style w.
( HasCallStack
, HasType (ApiT WalletId) w
, Discriminate style
)
=> w
-> (Method, Text)
signTransaction :: w -> (Method, Text)
signTransaction w
w = (Method, Text)
-> (Method, Text) -> (Method, Text) -> (Method, Text)
forall (style :: WalletStyle) a.
Discriminate style =>
a -> a -> a -> a
discriminate @style
((MkLink (SignTransaction Net) Text -> Text) -> (Method, Text)
forall endpoint.
(HasLink endpoint, IsElem endpoint endpoint, HasVerb endpoint) =>
(MkLink endpoint Text -> Text) -> (Method, Text)
endpoint @(Api.SignTransaction Net) (ApiT WalletId
wid ApiT WalletId -> (ApiT WalletId -> Text) -> Text
forall a b. a -> (a -> b) -> b
&))
((MkLink (SignByronTransaction Net) Text -> Text) -> (Method, Text)
forall endpoint.
(HasLink endpoint, IsElem endpoint endpoint, HasVerb endpoint) =>
(MkLink endpoint Text -> Text) -> (Method, Text)
endpoint @(Api.SignByronTransaction Net) (ApiT WalletId
wid ApiT WalletId -> (ApiT WalletId -> Text) -> Text
forall a b. a -> (a -> b) -> b
&))
(String -> (Method, Text)
forall a. HasCallStack => String -> a
notSupported String
"Shared")
where
wid :: ApiT WalletId
wid = w
w w
-> ((ApiT WalletId -> Const (ApiT WalletId) (ApiT WalletId))
-> w -> Const (ApiT WalletId) w)
-> ApiT WalletId
forall s a. s -> ((a -> Const a a) -> s -> Const a s) -> a
^. forall s.
HasType (ApiT WalletId) s =>
Lens s s (ApiT WalletId) (ApiT WalletId)
forall a s. HasType a s => Lens s s a a
typed @(ApiT WalletId)
balanceTransaction
:: forall style w.
( HasCallStack
, HasType (ApiT WalletId) w
, Discriminate style
)
=> w
-> (Method, Text)
balanceTransaction :: w -> (Method, Text)
balanceTransaction w
w = (Method, Text)
-> (Method, Text) -> (Method, Text) -> (Method, Text)
forall (style :: WalletStyle) a.
Discriminate style =>
a -> a -> a -> a
discriminate @style
((MkLink (BalanceTransaction Net) Text -> Text) -> (Method, Text)
forall endpoint.
(HasLink endpoint, IsElem endpoint endpoint, HasVerb endpoint) =>
(MkLink endpoint Text -> Text) -> (Method, Text)
endpoint @(Api.BalanceTransaction Net) (ApiT WalletId
wid ApiT WalletId -> (ApiT WalletId -> Text) -> Text
forall a b. a -> (a -> b) -> b
&))
(String -> (Method, Text)
forall a. HasCallStack => String -> a
notSupported String
"Byron")
(String -> (Method, Text)
forall a. HasCallStack => String -> a
notSupported String
"Shared")
where
wid :: ApiT WalletId
wid = w
w w
-> ((ApiT WalletId -> Const (ApiT WalletId) (ApiT WalletId))
-> w -> Const (ApiT WalletId) w)
-> ApiT WalletId
forall s a. s -> ((a -> Const a a) -> s -> Const a s) -> a
^. forall s.
HasType (ApiT WalletId) s =>
Lens s s (ApiT WalletId) (ApiT WalletId)
forall a s. HasType a s => Lens s s a a
typed @(ApiT WalletId)
decodeTransaction
:: forall style w.
( HasCallStack
, HasType (ApiT WalletId) w
, Discriminate style
)
=> w
-> (Method, Text)
decodeTransaction :: w -> (Method, Text)
decodeTransaction w
w = (Method, Text)
-> (Method, Text) -> (Method, Text) -> (Method, Text)
forall (style :: WalletStyle) a.
Discriminate style =>
a -> a -> a -> a
discriminate @style
((MkLink (DecodeTransaction Net) Text -> Text) -> (Method, Text)
forall endpoint.
(HasLink endpoint, IsElem endpoint endpoint, HasVerb endpoint) =>
(MkLink endpoint Text -> Text) -> (Method, Text)
endpoint @(Api.DecodeTransaction Net) (ApiT WalletId
wid ApiT WalletId -> (ApiT WalletId -> Text) -> Text
forall a b. a -> (a -> b) -> b
&))
(String -> (Method, Text)
forall a. HasCallStack => String -> a
notSupported String
"Byron")
((MkLink (DecodeSharedTransaction Net) Text -> Text)
-> (Method, Text)
forall endpoint.
(HasLink endpoint, IsElem endpoint endpoint, HasVerb endpoint) =>
(MkLink endpoint Text -> Text) -> (Method, Text)
endpoint @(Api.DecodeSharedTransaction Net) (ApiT WalletId
wid ApiT WalletId -> (ApiT WalletId -> Text) -> Text
forall a b. a -> (a -> b) -> b
&))
where
wid :: ApiT WalletId
wid = w
w w
-> ((ApiT WalletId -> Const (ApiT WalletId) (ApiT WalletId))
-> w -> Const (ApiT WalletId) w)
-> ApiT WalletId
forall s a. s -> ((a -> Const a a) -> s -> Const a s) -> a
^. forall s.
HasType (ApiT WalletId) s =>
Lens s s (ApiT WalletId) (ApiT WalletId)
forall a s. HasType a s => Lens s s a a
typed @(ApiT WalletId)
submitTransaction
:: forall style w.
( HasCallStack
, HasType (ApiT WalletId) w
, Discriminate style
)
=> w
-> (Method, Text)
submitTransaction :: w -> (Method, Text)
submitTransaction w
w = (Method, Text)
-> (Method, Text) -> (Method, Text) -> (Method, Text)
forall (style :: WalletStyle) a.
Discriminate style =>
a -> a -> a -> a
discriminate @style
((MkLink SubmitTransaction Text -> Text) -> (Method, Text)
forall endpoint.
(HasLink endpoint, IsElem endpoint endpoint, HasVerb endpoint) =>
(MkLink endpoint Text -> Text) -> (Method, Text)
endpoint @Api.SubmitTransaction (ApiT WalletId
wid ApiT WalletId -> (ApiT WalletId -> Text) -> Text
forall a b. a -> (a -> b) -> b
&))
(String -> (Method, Text)
forall a. HasCallStack => String -> a
notSupported String
"Byron")
(String -> (Method, Text)
forall a. HasCallStack => String -> a
notSupported String
"Shared")
where
wid :: ApiT WalletId
wid = w
w w
-> ((ApiT WalletId -> Const (ApiT WalletId) (ApiT WalletId))
-> w -> Const (ApiT WalletId) w)
-> ApiT WalletId
forall s a. s -> ((a -> Const a a) -> s -> Const a s) -> a
^. forall s.
HasType (ApiT WalletId) s =>
Lens s s (ApiT WalletId) (ApiT WalletId)
forall a s. HasType a s => Lens s s a a
typed @(ApiT WalletId)
postPoolMaintenance
:: (Method, Text)
postPoolMaintenance :: (Method, Text)
postPoolMaintenance =
(MkLink PostPoolMaintenance Text -> Text) -> (Method, Text)
forall endpoint.
(HasLink endpoint, IsElem endpoint endpoint, HasVerb endpoint) =>
(MkLink endpoint Text -> Text) -> (Method, Text)
endpoint @Api.PostPoolMaintenance MkLink PostPoolMaintenance Text -> Text
forall a. a -> a
id
getPoolMaintenance
:: (Method, Text)
getPoolMaintenance :: (Method, Text)
getPoolMaintenance =
(MkLink GetPoolMaintenance Text -> Text) -> (Method, Text)
forall endpoint.
(HasLink endpoint, IsElem endpoint endpoint, HasVerb endpoint) =>
(MkLink endpoint Text -> Text) -> (Method, Text)
endpoint @Api.GetPoolMaintenance MkLink GetPoolMaintenance Text -> Text
forall a. a -> a
id
listStakePools
:: Maybe Coin
-> (Method, Text)
listStakePools :: Maybe Coin -> (Method, Text)
listStakePools Maybe Coin
stake =
(MkLink (ListStakePools ()) Text -> Text) -> (Method, Text)
forall endpoint.
(HasLink endpoint, IsElem endpoint endpoint, HasVerb endpoint) =>
(MkLink endpoint Text -> Text) -> (Method, Text)
endpoint @(Api.ListStakePools ()) (\MkLink (ListStakePools ()) Text
mk -> MkLink (ListStakePools ()) Text
Maybe (ApiT Coin) -> Text
mk (Coin -> ApiT Coin
forall a. a -> ApiT a
ApiT (Coin -> ApiT Coin) -> Maybe Coin -> Maybe (ApiT Coin)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe Coin
stake))
listStakeKeys
:: forall w. (HasType (ApiT WalletId) w)
=> w
-> (Method, Text)
listStakeKeys :: w -> (Method, Text)
listStakeKeys w
w =
(MkLink (ListStakeKeys ()) Text -> Text) -> (Method, Text)
forall endpoint.
(HasLink endpoint, IsElem endpoint endpoint, HasVerb endpoint) =>
(MkLink endpoint Text -> Text) -> (Method, Text)
endpoint @(Api.ListStakeKeys ()) (\MkLink (ListStakeKeys ()) Text
mk -> MkLink (ListStakeKeys ()) Text
ApiT WalletId -> Text
mk ApiT WalletId
wid)
where
wid :: ApiT WalletId
wid = w
w w
-> ((ApiT WalletId -> Const (ApiT WalletId) (ApiT WalletId))
-> w -> Const (ApiT WalletId) w)
-> ApiT WalletId
forall s a. s -> ((a -> Const a a) -> s -> Const a s) -> a
^. forall s.
HasType (ApiT WalletId) s =>
Lens s s (ApiT WalletId) (ApiT WalletId)
forall a s. HasType a s => Lens s s a a
typed @(ApiT WalletId)
joinStakePool
:: forall s w.
( HasType (ApiT PoolId) s
, HasType (ApiT WalletId) w
)
=> s
-> w
-> (Method, Text)
joinStakePool :: s -> w -> (Method, Text)
joinStakePool s
s w
w =
(MkLink (JoinStakePool Net) Text -> Text) -> (Method, Text)
forall endpoint.
(HasLink endpoint, IsElem endpoint endpoint, HasVerb endpoint) =>
(MkLink endpoint Text -> Text) -> (Method, Text)
endpoint @(Api.JoinStakePool Net) (\MkLink (JoinStakePool Net) Text
mk -> MkLink (JoinStakePool Net) Text
ApiPoolId -> ApiT WalletId -> Text
mk ApiPoolId
sid ApiT WalletId
wid)
where
sid :: ApiPoolId
sid = PoolId -> ApiPoolId
ApiPoolId (PoolId -> ApiPoolId) -> PoolId -> ApiPoolId
forall a b. (a -> b) -> a -> b
$ ApiT PoolId -> PoolId
forall a. ApiT a -> a
getApiT (ApiT PoolId -> PoolId) -> ApiT PoolId -> PoolId
forall a b. (a -> b) -> a -> b
$ s
s s
-> ((ApiT PoolId -> Const (ApiT PoolId) (ApiT PoolId))
-> s -> Const (ApiT PoolId) s)
-> ApiT PoolId
forall s a. s -> ((a -> Const a a) -> s -> Const a s) -> a
^. forall s.
HasType (ApiT PoolId) s =>
Lens s s (ApiT PoolId) (ApiT PoolId)
forall a s. HasType a s => Lens s s a a
typed @(ApiT PoolId)
wid :: ApiT WalletId
wid = w
w w
-> ((ApiT WalletId -> Const (ApiT WalletId) (ApiT WalletId))
-> w -> Const (ApiT WalletId) w)
-> ApiT WalletId
forall s a. s -> ((a -> Const a a) -> s -> Const a s) -> a
^. forall s.
HasType (ApiT WalletId) s =>
Lens s s (ApiT WalletId) (ApiT WalletId)
forall a s. HasType a s => Lens s s a a
typed @(ApiT WalletId)
quitStakePool
:: forall w.
( HasType (ApiT WalletId) w
)
=> w
-> (Method, Text)
quitStakePool :: w -> (Method, Text)
quitStakePool w
w =
(MkLink (QuitStakePool Net) Text -> Text) -> (Method, Text)
forall endpoint.
(HasLink endpoint, IsElem endpoint endpoint, HasVerb endpoint) =>
(MkLink endpoint Text -> Text) -> (Method, Text)
endpoint @(Api.QuitStakePool Net) (ApiT WalletId
wid ApiT WalletId -> (ApiT WalletId -> Text) -> Text
forall a b. a -> (a -> b) -> b
&)
where
wid :: ApiT WalletId
wid = w
w w
-> ((ApiT WalletId -> Const (ApiT WalletId) (ApiT WalletId))
-> w -> Const (ApiT WalletId) w)
-> ApiT WalletId
forall s a. s -> ((a -> Const a a) -> s -> Const a s) -> a
^. forall s.
HasType (ApiT WalletId) s =>
Lens s s (ApiT WalletId) (ApiT WalletId)
forall a s. HasType a s => Lens s s a a
typed @(ApiT WalletId)
getDelegationFee
:: forall w.
( HasType (ApiT WalletId) w
)
=> w
-> (Method, Text)
getDelegationFee :: w -> (Method, Text)
getDelegationFee w
w =
(MkLink DelegationFee Text -> Text) -> (Method, Text)
forall endpoint.
(HasLink endpoint, IsElem endpoint endpoint, HasVerb endpoint) =>
(MkLink endpoint Text -> Text) -> (Method, Text)
endpoint @Api.DelegationFee (ApiT WalletId
wid ApiT WalletId -> (ApiT WalletId -> Text) -> Text
forall a b. a -> (a -> b) -> b
&)
where
wid :: ApiT WalletId
wid = w
w w
-> ((ApiT WalletId -> Const (ApiT WalletId) (ApiT WalletId))
-> w -> Const (ApiT WalletId) w)
-> ApiT WalletId
forall s a. s -> ((a -> Const a a) -> s -> Const a s) -> a
^. forall s.
HasType (ApiT WalletId) s =>
Lens s s (ApiT WalletId) (ApiT WalletId)
forall a s. HasType a s => Lens s s a a
typed @(ApiT WalletId)
getNetworkInfo
:: (Method, Text)
getNetworkInfo :: (Method, Text)
getNetworkInfo =
(MkLink GetNetworkInformation Text -> Text) -> (Method, Text)
forall endpoint.
(HasLink endpoint, IsElem endpoint endpoint, HasVerb endpoint) =>
(MkLink endpoint Text -> Text) -> (Method, Text)
endpoint @Api.GetNetworkInformation MkLink GetNetworkInformation Text -> Text
forall a. a -> a
id
getNetworkParams
:: (Method, Text)
getNetworkParams :: (Method, Text)
getNetworkParams =
(MkLink GetNetworkParameters Text -> Text) -> (Method, Text)
forall endpoint.
(HasLink endpoint, IsElem endpoint endpoint, HasVerb endpoint) =>
(MkLink endpoint Text -> Text) -> (Method, Text)
endpoint @Api.GetNetworkParameters MkLink GetNetworkParameters Text -> Text
forall a. a -> a
id
getNetworkClock
:: (Method, Text)
getNetworkClock :: (Method, Text)
getNetworkClock =
(MkLink GetNetworkClock Text -> Text) -> (Method, Text)
forall endpoint.
(HasLink endpoint, IsElem endpoint endpoint, HasVerb endpoint) =>
(MkLink endpoint Text -> Text) -> (Method, Text)
endpoint @Api.GetNetworkClock (Bool
False Bool -> (Bool -> Text) -> Text
forall a b. a -> (a -> b) -> b
&)
getNetworkClock'
:: Bool
-> (Method, Text)
getNetworkClock' :: Bool -> (Method, Text)
getNetworkClock' Bool
forceNtpCheck =
(MkLink GetNetworkClock Text -> Text) -> (Method, Text)
forall endpoint.
(HasLink endpoint, IsElem endpoint endpoint, HasVerb endpoint) =>
(MkLink endpoint Text -> Text) -> (Method, Text)
endpoint @Api.GetNetworkClock (Bool
forceNtpCheck Bool -> (Bool -> Text) -> Text
forall a b. a -> (a -> b) -> b
&)
postExternalTransaction
:: (Method, Text)
postExternalTransaction :: (Method, Text)
postExternalTransaction =
(MkLink PostExternalTransaction Text -> Text) -> (Method, Text)
forall endpoint.
(HasLink endpoint, IsElem endpoint endpoint, HasVerb endpoint) =>
(MkLink endpoint Text -> Text) -> (Method, Text)
endpoint @Api.PostExternalTransaction MkLink PostExternalTransaction Text -> Text
forall a. a -> a
id
putSettings
:: (Method, Text)
putSettings :: (Method, Text)
putSettings =
(MkLink PutSettings Text -> Text) -> (Method, Text)
forall endpoint.
(HasLink endpoint, IsElem endpoint endpoint, HasVerb endpoint) =>
(MkLink endpoint Text -> Text) -> (Method, Text)
endpoint @Api.PutSettings MkLink PutSettings Text -> Text
forall a. a -> a
id
getSettings
:: (Method, Text)
getSettings :: (Method, Text)
getSettings =
(MkLink GetSettings Text -> Text) -> (Method, Text)
forall endpoint.
(HasLink endpoint, IsElem endpoint endpoint, HasVerb endpoint) =>
(MkLink endpoint Text -> Text) -> (Method, Text)
endpoint @Api.GetSettings MkLink GetSettings Text -> Text
forall a. a -> a
id
getCurrentSMASHHealth
:: (Method, Text)
getCurrentSMASHHealth :: (Method, Text)
getCurrentSMASHHealth = Maybe SmashServer -> (Method, Text)
getCurrentSMASHHealth' Maybe SmashServer
forall a. Maybe a
Nothing
getCurrentSMASHHealth'
:: Maybe SmashServer
-> (Method, Text)
getCurrentSMASHHealth' :: Maybe SmashServer -> (Method, Text)
getCurrentSMASHHealth' Maybe SmashServer
smash =
(MkLink GetCurrentSMASHHealth Text -> Text) -> (Method, Text)
forall endpoint.
(HasLink endpoint, IsElem endpoint endpoint, HasVerb endpoint) =>
(MkLink endpoint Text -> Text) -> (Method, Text)
endpoint @Api.GetCurrentSMASHHealth (\MkLink GetCurrentSMASHHealth Text
mk -> MkLink GetCurrentSMASHHealth Text
Maybe (ApiT SmashServer) -> Text
mk (SmashServer -> ApiT SmashServer
forall a. a -> ApiT a
ApiT (SmashServer -> ApiT SmashServer)
-> Maybe SmashServer -> Maybe (ApiT SmashServer)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe SmashServer
smash))
patchSharedWallet
:: forall w.
( HasType (ApiT WalletId) w
)
=> w
-> CredentialType
-> (Method, Text)
patchSharedWallet :: w -> CredentialType -> (Method, Text)
patchSharedWallet w
w CredentialType
cred =
case CredentialType
cred of
CredentialType
Payment ->
(MkLink PatchSharedWalletInPayment Text -> Text) -> (Method, Text)
forall endpoint.
(HasLink endpoint, IsElem endpoint endpoint, HasVerb endpoint) =>
(MkLink endpoint Text -> Text) -> (Method, Text)
endpoint @Api.PatchSharedWalletInPayment (ApiT WalletId
wid ApiT WalletId -> (ApiT WalletId -> Text) -> Text
forall a b. a -> (a -> b) -> b
&)
CredentialType
Delegation ->
(MkLink PatchSharedWalletInDelegation Text -> Text)
-> (Method, Text)
forall endpoint.
(HasLink endpoint, IsElem endpoint endpoint, HasVerb endpoint) =>
(MkLink endpoint Text -> Text) -> (Method, Text)
endpoint @Api.PatchSharedWalletInDelegation (ApiT WalletId
wid ApiT WalletId -> (ApiT WalletId -> Text) -> Text
forall a b. a -> (a -> b) -> b
&)
where
wid :: ApiT WalletId
wid = w
w w
-> ((ApiT WalletId -> Const (ApiT WalletId) (ApiT WalletId))
-> w -> Const (ApiT WalletId) w)
-> ApiT WalletId
forall s a. s -> ((a -> Const a a) -> s -> Const a s) -> a
^. forall s.
HasType (ApiT WalletId) s =>
Lens s s (ApiT WalletId) (ApiT WalletId)
forall a s. HasType a s => Lens s s a a
typed @(ApiT WalletId)
endpoint
:: forall endpoint.
( HasLink endpoint
, IsElem endpoint endpoint
, HasVerb endpoint
)
=> (MkLink endpoint Text -> Text)
-> (Method, Text)
endpoint :: (MkLink endpoint Text -> Text) -> (Method, Text)
endpoint MkLink endpoint Text -> Text
mk =
( Proxy endpoint -> Method
forall k (api :: k). HasVerb api => Proxy api -> Method
method (Proxy endpoint
forall k (t :: k). Proxy t
Proxy @endpoint)
, Text
"v2/" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> MkLink endpoint Text -> Text
mk ((Link -> Text)
-> Proxy endpoint -> Proxy endpoint -> MkLink endpoint Text
forall endpoint api a.
(IsElem endpoint api, HasLink endpoint) =>
(Link -> a) -> Proxy api -> Proxy endpoint -> MkLink endpoint a
safeLink' Link -> Text
forall a. ToHttpApiData a => a -> Text
toUrlPiece (Proxy endpoint
forall k (t :: k). Proxy t
Proxy @endpoint) (Proxy endpoint
forall k (t :: k). Proxy t
Proxy @endpoint))
)
class Discriminate (style :: WalletStyle) where
discriminate :: a -> a -> a -> a
instance Discriminate 'Shelley where
discriminate :: a -> a -> a -> a
discriminate a
a a
_ a
_ = a
a
instance Discriminate 'Byron where
discriminate :: a -> a -> a -> a
discriminate a
_ a
a a
_ = a
a
instance Discriminate 'Shared where
discriminate :: a -> a -> a -> a
discriminate a
_ a
_ a
a = a
a
notSupported :: HasCallStack => String -> a
notSupported :: String -> a
notSupported String
style = String -> a
forall a. HasCallStack => String -> a
error (String -> a) -> String -> a
forall a b. (a -> b) -> a -> b
$ String
"Endpoint not supported for " String -> String -> String
forall a. Semigroup a => a -> a -> a
<> String
style String -> String -> String
forall a. Semigroup a => a -> a -> a
<> String
" style"
type Net = 'Mainnet
class HasVerb api where
method :: Proxy api -> Method
instance (ReflectMethod m) => HasVerb (NoContentVerb m) where
method :: Proxy (NoContentVerb m) -> Method
method Proxy (NoContentVerb m)
_ = Proxy m -> Method
forall k (a :: k). ReflectMethod a => Proxy a -> Method
reflectMethod (Proxy m
forall k (t :: k). Proxy t
Proxy @m)
instance (ReflectMethod m) => HasVerb (Verb m s ct a) where
method :: Proxy (Verb m s ct a) -> Method
method Proxy (Verb m s ct a)
_ = Proxy m -> Method
forall k (a :: k). ReflectMethod a => Proxy a -> Method
reflectMethod (Proxy m
forall k (t :: k). Proxy t
Proxy @m)
instance HasVerb sub => HasVerb ((path :: Symbol) :> sub) where
method :: Proxy (path :> sub) -> Method
method Proxy (path :> sub)
_ = Proxy sub -> Method
forall k (api :: k). HasVerb api => Proxy api -> Method
method (Proxy sub
forall k (t :: k). Proxy t
Proxy @sub)
instance HasVerb sub => HasVerb (Capture param t :> sub) where
method :: Proxy (Capture param t :> sub) -> Method
method Proxy (Capture param t :> sub)
_ = Proxy sub -> Method
forall k (api :: k). HasVerb api => Proxy api -> Method
method (Proxy sub
forall k (t :: k). Proxy t
Proxy @sub)
instance HasVerb sub => HasVerb (ReqBody a b :> sub) where
method :: Proxy (ReqBody a b :> sub) -> Method
method Proxy (ReqBody a b :> sub)
_ = Proxy sub -> Method
forall k (api :: k). HasVerb api => Proxy api -> Method
method (Proxy sub
forall k (t :: k). Proxy t
Proxy @sub)
instance HasVerb sub => HasVerb (QueryParam a b :> sub) where
method :: Proxy (QueryParam a b :> sub) -> Method
method Proxy (QueryParam a b :> sub)
_ = Proxy sub -> Method
forall k (api :: k). HasVerb api => Proxy api -> Method
method (Proxy sub
forall k (t :: k). Proxy t
Proxy @sub)
instance HasVerb sub => HasVerb (QueryFlag sym :> sub) where
method :: Proxy (QueryFlag sym :> sub) -> Method
method Proxy (QueryFlag sym :> sub)
_ = Proxy sub -> Method
forall k (api :: k). HasVerb api => Proxy api -> Method
method (Proxy sub
forall k (t :: k). Proxy t
Proxy @sub)
instance HasVerb sub => HasVerb (Header' opts name ty :> sub) where
method :: Proxy (Header' opts name ty :> sub) -> Method
method Proxy (Header' opts name ty :> sub)
_ = Proxy sub -> Method
forall k (api :: k). HasVerb api => Proxy api -> Method
method (Proxy sub
forall k (t :: k). Proxy t
Proxy @sub)