Skip to content
This repository was archived by the owner on Aug 18, 2020. It is now read-only.

Commit 1d02503

Browse files
committed
move CHW endpoints to a new the new path: /unimplemented..
1 parent 4021ad9 commit 1d02503

File tree

11 files changed

+265
-169
lines changed

11 files changed

+265
-169
lines changed

wallet-new/cardano-sl-wallet-new.cabal

+3
Original file line numberDiff line numberDiff line change
@@ -66,6 +66,9 @@ library
6666
Cardano.Wallet.API.V1.Transactions
6767
Cardano.Wallet.API.V1.Types
6868
Cardano.Wallet.API.V1.Wallets
69+
Cardano.Wallet.API.WIP
70+
Cardano.Wallet.API.WIP.Handlers
71+
Cardano.Wallet.API.WIP.LegacyHandlers
6972
Cardano.Wallet.Kernel
7073
Cardano.Wallet.Kernel.Accounts
7174
Cardano.Wallet.Kernel.Actions

wallet-new/src/Cardano/Wallet/API.hs

+4-1
Original file line numberDiff line numberDiff line change
@@ -10,6 +10,7 @@ module Cardano.Wallet.API
1010
, walletAPI
1111
, WalletDocAPI
1212
, walletDocAPI
13+
, WIPAPI
1314
) where
1415

1516
import Cardano.Wallet.API.Types (WalletLoggingConfig)
@@ -20,6 +21,7 @@ import Servant.Swagger.UI (SwaggerSchemaUI)
2021
import qualified Cardano.Wallet.API.Internal as Internal
2122
import qualified Cardano.Wallet.API.V0 as V0
2223
import qualified Cardano.Wallet.API.V1 as V1
24+
import qualified Cardano.Wallet.API.WIP as WIP
2325

2426
-- | The complete API, qualified by its versions. For backward compatibility's sake, we still expose
2527
-- the old API under @/api/@. Specification is split under separate modules.
@@ -54,8 +56,9 @@ type InternalAPI = "api" :> "internal" :> Internal.API
5456
internalAPI :: Proxy InternalAPI
5557
internalAPI = Proxy
5658

59+
type WIPAPI = "api" :> "unimplemented" :> WIP.API
5760

58-
type WalletAPI = LoggingApi WalletLoggingConfig (V0API' :<|> V0API :<|> V1API :<|> InternalAPI)
61+
type WalletAPI = LoggingApi WalletLoggingConfig (V0API' :<|> V0API :<|> V1API :<|> InternalAPI :<|> WIPAPI)
5962
walletAPI :: Proxy WalletAPI
6063
walletAPI = Proxy
6164

wallet-new/src/Cardano/Wallet/API/V1/Handlers/Wallets.hs

-21
Original file line numberDiff line numberDiff line change
@@ -23,9 +23,6 @@ handlers pwl = newWallet pwl
2323
:<|> getWallet pwl
2424
:<|> updateWallet pwl
2525
:<|> getUtxoStatistics pwl
26-
:<|> checkExternalWallet pwl
27-
:<|> newExternalWallet pwl
28-
:<|> deleteExternalWallet pwl
2926

3027
-- | Creates a new or restores an existing @wallet@ given a 'NewWallet' payload.
3128
-- Returns to the client the representation of the created or restored
@@ -107,21 +104,3 @@ getUtxoStatistics pwl wid = do
107104
Left e -> throwM e
108105
Right w ->
109106
return $ single $ V1.computeUtxoStatistics V1.log10 (map snd w)
110-
111-
checkExternalWallet :: PassiveWalletLayer IO
112-
-> PublicKeyAsBase58
113-
-> Handler (WalletResponse WalletAndTxHistory)
114-
checkExternalWallet _encodedRootPK =
115-
error "[CHW-54], Cardano Hardware Wallet feature, , check external wallet, unimplemented yet."
116-
117-
newExternalWallet :: PassiveWalletLayer IO
118-
-> NewExternalWallet
119-
-> Handler (WalletResponse Wallet)
120-
newExternalWallet _newExtWallet =
121-
error "[CHW-80], Cardano Hardware Wallet feature, new external wallet, unimplemented yet."
122-
123-
deleteExternalWallet :: PassiveWalletLayer IO
124-
-> PublicKeyAsBase58
125-
-> Handler NoContent
126-
deleteExternalWallet _encodedRootPK =
127-
error "[CHW-106], Cardano Hardware Wallet feature, , delete external wallet, unimplemented yet."

wallet-new/src/Cardano/Wallet/API/V1/LegacyHandlers/Wallets.hs

+1-131
Original file line numberDiff line numberDiff line change
@@ -6,7 +6,6 @@ module Cardano.Wallet.API.V1.LegacyHandlers.Wallets (
66
, newWallet
77
) where
88

9-
import Formatting (build, sformat)
109
import Universum
1110
import UnliftIO (MonadUnliftIO)
1211

@@ -22,11 +21,9 @@ import Cardano.Wallet.API.V1.Types as V1
2221
import qualified Cardano.Wallet.API.V1.Wallets as Wallets
2322
import qualified Cardano.Wallet.Kernel.DB.Util.IxSet as IxSet
2423
import Pos.Chain.Update ()
25-
import Pos.Client.KeyStorage (addPublicKey)
2624
import qualified Pos.Core as Core
2725

28-
import Pos.Util (HasLens (..), maybeThrow)
29-
import Pos.Util.Servant (encodeCType)
26+
import Pos.Util (HasLens (..))
3027
import qualified Pos.Wallet.WalletMode as V0
3128
import Pos.Wallet.Web.Methods.Logic (MonadWalletLogic,
3229
MonadWalletLogicRead)
@@ -44,9 +41,6 @@ handlers = newWallet
4441
:<|> getWallet
4542
:<|> updateWallet
4643
:<|> getUtxoStatistics
47-
:<|> checkExternalWallet
48-
:<|> newExternalWallet
49-
:<|> deleteExternalWallet
5044

5145
-- | Pure function which returns whether or not the underlying node is
5246
-- \"synced enough\" to allow wallet creation/restoration. The notion of
@@ -195,127 +189,3 @@ getUtxoStatistics
195189
-> m (WalletResponse UtxoStatistics)
196190
getUtxoStatistics _ = do
197191
return $ single (V1.computeUtxoStatistics V1.log10 [])
198-
199-
-- | Check if external wallet is presented in node's wallet db.
200-
checkExternalWallet
201-
:: -- ( V0.MonadWalletLogic ctx m
202-
-- , V0.MonadWalletHistory ctx m
203-
-- , MonadUnliftIO m
204-
-- , HasLens SyncQueue ctx SyncQueue
205-
-- )
206-
-- =>
207-
PublicKeyAsBase58
208-
-> m (WalletResponse WalletAndTxHistory)
209-
checkExternalWallet _encodedRootPK =
210-
error "[CHW-54], Cardano Hardware Wallet, check external wallet, legacy handler, unimplemented yet."
211-
212-
-- | Creates a new or restores an existing external @wallet@ given a 'NewExternalWallet' payload.
213-
-- Returns to the client the representation of the created or restored wallet in the 'Wallet' type.
214-
newExternalWallet
215-
:: ( MonadThrow m
216-
, MonadUnliftIO m
217-
-- , HasLens SyncQueue ctx SyncQueue
218-
, V0.MonadBlockchainInfo m
219-
, V0.MonadWalletLogic ctx m
220-
)
221-
=> NewExternalWallet
222-
-> m (WalletResponse Wallet)
223-
newExternalWallet (NewExternalWallet rootPK assuranceLevel name operation) = do
224-
let newExternalWalletHandler CreateWallet = createNewExternalWallet
225-
newExternalWalletHandler RestoreWallet = restoreExternalWallet
226-
walletMeta <- V0.CWalletMeta <$> pure name
227-
<*> migrate assuranceLevel
228-
<*> pure 0
229-
single <$> do
230-
v0wallet <- newExternalWalletHandler operation walletMeta rootPK
231-
ws <- V0.askWalletSnapshot
232-
migrateWallet ws v0wallet True
233-
234-
-- | Creates new external wallet.
235-
createNewExternalWallet
236-
:: ( MonadThrow m
237-
, V0.MonadWalletLogic ctx m
238-
)
239-
=> V0.CWalletMeta
240-
-> PublicKeyAsBase58
241-
-> m V0.CWallet
242-
createNewExternalWallet walletMeta encodedRootPK = do
243-
rootPK <- case mkPublicKeyFromBase58 encodedRootPK of
244-
Left problem -> throwM (InvalidPublicKey $ sformat build problem)
245-
Right rootPK -> return rootPK
246-
247-
-- This extended public key will be used during synchronization
248-
-- with the blockchain.
249-
addPublicKey rootPK
250-
251-
let walletId = encodeCType . Core.makePubKeyAddressBoot $ rootPK
252-
isReady = True -- We don't need to sync new wallet with the blockchain.
253-
254-
-- Create new external wallet.
255-
-- This is safe: if the client will try to create an external wallet from the same
256-
-- root public key - error will be thrown.
257-
void $ V0.createWalletSafe walletId walletMeta isReady
258-
259-
addInitAccountInExternalWallet walletId
260-
261-
V0.getWallet walletId
262-
263-
-- | Restore external wallet using it's root public key and metadata.
264-
restoreExternalWallet
265-
:: -- ( MonadThrow m
266-
-- , MonadUnliftIO m
267-
-- , HasLens SyncQueue ctx SyncQueue
268-
-- , V0.MonadWalletLogic ctx m
269-
-- )
270-
-- =>
271-
V0.CWalletMeta
272-
-> PublicKeyAsBase58
273-
-> m V0.CWallet
274-
restoreExternalWallet _walletMeta _encodedRootPK =
275-
error "[CHW-54], restore external wallet, unimplemented yet."
276-
277-
addInitAccountInExternalWallet
278-
:: ( MonadThrow m
279-
, V0.MonadWalletLogic ctx m
280-
)
281-
=> V0.CId V0.Wal
282-
-> m ()
283-
addInitAccountInExternalWallet walletId = do
284-
let accountName = "Initial account"
285-
accountMeta = V0.CAccountMeta accountName
286-
accountInit = V0.CAccountInit accountMeta walletId
287-
includeUnready = True
288-
void $ V0.newExternalAccountIncludeUnready includeUnready accountInit
289-
290-
-- | On the disk, once imported or created, there's so far not much difference
291-
-- between a wallet and an external wallet, except one: node stores a public key
292-
-- for external wallet, there's no secret key.
293-
deleteExternalWallet
294-
:: (V0.MonadWalletLogic ctx m)
295-
=> PublicKeyAsBase58
296-
-> m NoContent
297-
deleteExternalWallet encodedRootPK =
298-
case V1.mkPublicKeyFromBase58 encodedRootPK of
299-
Left problem -> throwM (InvalidPublicKey $ sformat build problem)
300-
Right rootPK -> V0.deleteExternalWallet rootPK
301-
302-
migrateWallet
303-
:: ( V0.MonadWalletLogicRead ctx m
304-
, V0.MonadBlockchainInfo m
305-
)
306-
=> V0.WalletSnapshot
307-
-> V0.CWallet
308-
-> Bool
309-
-> m Wallet
310-
migrateWallet snapshot wallet walletIsReady = do
311-
let walletId = V0.cwId wallet
312-
walletInfo <- if walletIsReady
313-
then maybeThrow WalletNotFound $ V0.getWalletInfo walletId snapshot
314-
else
315-
-- Wallet is not ready yet (because of restoring),
316-
-- the only information we can provide is the default one.
317-
pure $ V0.getUnreadyWalletInfo snapshot
318-
walletIsExternal <- V0.isWalletExternal walletId
319-
let walletType = if walletIsExternal then WalletExternal else WalletRegular
320-
currentDepth <- V0.networkChainDifficulty
321-
migrate (wallet, walletInfo, walletType, currentDepth)

wallet-new/src/Cardano/Wallet/API/V1/Wallets.hs

-12
Original file line numberDiff line numberDiff line change
@@ -40,16 +40,4 @@ type API = Tags '["Wallets"] :>
4040
:<|> "wallets" :> CaptureWalletId :> "statistics" :> "utxos"
4141
:> Summary "Returns Utxo statistics for the Wallet identified by the given walletId."
4242
:> Get '[ValidJSON] (WalletResponse UtxoStatistics)
43-
:<|> "external-wallets"
44-
:> Capture "rootPK" PublicKeyAsBase58
45-
:> Summary "Check if this external wallet is presented in the node."
46-
:> PostCreated '[ValidJSON] (WalletResponse WalletAndTxHistory)
47-
:<|> "external-wallets"
48-
:> Summary "Creates a new or restores an existing external wallet (mobile client or hardware wallet)."
49-
:> ReqBody '[ValidJSON] (New ExternalWallet)
50-
:> PostCreated '[ValidJSON] (WalletResponse Wallet)
51-
:<|> "external-wallets"
52-
:> Capture "rootPK" PublicKeyAsBase58
53-
:> Summary "Deletes the given external wallet and all its accounts."
54-
:> DeleteNoContent '[ValidJSON] NoContent
5543
)
+26
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,26 @@
1+
-- | This module contains the top level API definition for the Cardano hardware wallet.
2+
-- The Cardano hardware wallet is work in progress.
3+
--
4+
module Cardano.Wallet.API.WIP where
5+
6+
import Servant
7+
8+
import Cardano.Wallet.API.Response
9+
import Cardano.Wallet.API.Types
10+
import Cardano.Wallet.API.V1.Types
11+
12+
type API = Tags '["WIP"] :>
13+
(
14+
"external-wallets"
15+
:> Capture "rootPK" PublicKeyAsBase58
16+
:> Summary "Check if this external wallet is presented in the node."
17+
:> PostCreated '[ValidJSON] (WalletResponse WalletAndTxHistory)
18+
:<|> "external-wallets"
19+
:> Summary "Creates a new or restores an existing external wallet (mobile client or hardware wallet)."
20+
:> ReqBody '[ValidJSON] (New ExternalWallet)
21+
:> PostCreated '[ValidJSON] (WalletResponse Wallet)
22+
:<|> "external-wallets"
23+
:> Capture "rootPK" PublicKeyAsBase58
24+
:> Summary "Deletes the given external wallet and all its accounts."
25+
:> DeleteNoContent '[ValidJSON] NoContent
26+
)
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,35 @@
1+
module Cardano.Wallet.API.WIP.Handlers (handlers)
2+
where
3+
4+
import Universum
5+
6+
import Servant
7+
8+
import Cardano.Wallet.API.Response
9+
import Cardano.Wallet.API.V1.Types as V1
10+
import qualified Cardano.Wallet.API.WIP as WIP (API)
11+
import Cardano.Wallet.WalletLayer (PassiveWalletLayer)
12+
13+
-- | WIP @Servant@ handlers the are not part of the offical api yet.
14+
handlers :: PassiveWalletLayer IO -> ServerT WIP.API Handler
15+
handlers pwl = checkExternalWallet pwl
16+
:<|> newExternalWallet pwl
17+
:<|> deleteExternalWallet pwl
18+
19+
checkExternalWallet :: PassiveWalletLayer IO
20+
-> PublicKeyAsBase58
21+
-> Handler (WalletResponse WalletAndTxHistory)
22+
checkExternalWallet _encodedRootPK =
23+
error "[CHW-54], Cardano Hardware Wallet feature, , check external wallet, unimplemented yet."
24+
25+
newExternalWallet :: PassiveWalletLayer IO
26+
-> NewExternalWallet
27+
-> Handler (WalletResponse Wallet)
28+
newExternalWallet _newExtWallet =
29+
error "[CHW-80], Cardano Hardware Wallet feature, new external wallet, unimplemented yet."
30+
31+
deleteExternalWallet :: PassiveWalletLayer IO
32+
-> PublicKeyAsBase58
33+
-> Handler NoContent
34+
deleteExternalWallet _encodedRootPK =
35+
error "[CHW-106], Cardano Hardware Wallet feature, , delete external wallet, unimplemented yet."

0 commit comments

Comments
 (0)