From f670b97e870429f38702110ad6aca652912535d5 Mon Sep 17 00:00:00 2001 From: paolino Date: Wed, 18 Sep 2024 16:36:03 +0000 Subject: [PATCH 1/6] Add customerAddress function to REST interface --- .../Cardano/Wallet/Deposit/HTTP/Endpoints.hs | 13 +++++++------ .../Wallet/Deposit/HTTP/Implementation.hs | 2 +- .../src/Cardano/Wallet/Deposit/IO.hs | 13 ++++--------- .../src/Cardano/Wallet/Deposit/Pure.hs | 17 +++++++---------- .../src/Cardano/Wallet/Deposit/REST.hs | 14 +++++++------- .../Scenario/Wallet/Deposit/Exchanges.lhs.md | 14 +++++++------- .../Test/Scenario/Wallet/Deposit/Run.hs | 6 +++--- 7 files changed, 36 insertions(+), 43 deletions(-) diff --git a/lib/customer-deposit-wallet/http/Cardano/Wallet/Deposit/HTTP/Endpoints.hs b/lib/customer-deposit-wallet/http/Cardano/Wallet/Deposit/HTTP/Endpoints.hs index 35010ec0e1f..1940e0a6f45 100644 --- a/lib/customer-deposit-wallet/http/Cardano/Wallet/Deposit/HTTP/Endpoints.hs +++ b/lib/customer-deposit-wallet/http/Cardano/Wallet/Deposit/HTTP/Endpoints.hs @@ -6,11 +6,9 @@ -- -- Each HTTP endpoint corresponds to a single function from the -- "Cardano.Wallet.Deposit.IO" module. --- module Cardano.Wallet.Deposit.HTTP.Endpoints ( listCustomers - , createAddress - + , customerAddress , getNetworkTip ) where @@ -61,12 +59,15 @@ listCustomers listCustomers w = liftIO $ ApiT <$> Wallet.listCustomers w -createAddress +customerAddress :: Wallet.WalletInstance -> ApiT Customer -> Handler (ApiT Address) -createAddress w a = - liftIO $ ApiT <$> Wallet.createAddress (unApiT a) w +customerAddress w a = do + mAddr <- liftIO $ Wallet.customerAddress (unApiT a) w + case mAddr of + Nothing -> fail "customerAddress: customer not found" + Just addr -> pure $ ApiT addr getNetworkTip :: Wallet.WalletInstance diff --git a/lib/customer-deposit-wallet/http/Cardano/Wallet/Deposit/HTTP/Implementation.hs b/lib/customer-deposit-wallet/http/Cardano/Wallet/Deposit/HTTP/Implementation.hs index a944af7e8bd..7f88ee1e553 100644 --- a/lib/customer-deposit-wallet/http/Cardano/Wallet/Deposit/HTTP/Implementation.hs +++ b/lib/customer-deposit-wallet/http/Cardano/Wallet/Deposit/HTTP/Implementation.hs @@ -35,4 +35,4 @@ api = Proxy implementation :: Wallet.WalletInstance -> Server CustomerAPI implementation w = HTTP.listCustomers w - :<|> HTTP.createAddress w + :<|> HTTP.customerAddress w diff --git a/lib/customer-deposit-wallet/src/Cardano/Wallet/Deposit/IO.hs b/lib/customer-deposit-wallet/src/Cardano/Wallet/Deposit/IO.hs index 9c115ca08d0..431557664f8 100644 --- a/lib/customer-deposit-wallet/src/Cardano/Wallet/Deposit/IO.hs +++ b/lib/customer-deposit-wallet/src/Cardano/Wallet/Deposit/IO.hs @@ -17,7 +17,7 @@ module Cardano.Wallet.Deposit.IO -- ** Mapping between customers and addresses , listCustomers - , createAddress + , customerAddress -- ** Reading from the blockchain , getWalletTip @@ -188,20 +188,15 @@ listCustomers :: WalletInstance -> IO [(Customer, Address)] listCustomers w = Wallet.listCustomers <$> readWalletState w -createAddress :: Customer -> WalletInstance -> IO Address -createAddress c w = - onWalletState w - $ Delta.updateWithResult - $ \s0 -> - let (r,s1) = Wallet.createAddress c s0 - in (Delta.Replace s1, r) +customerAddress :: Customer -> WalletInstance -> IO (Maybe Address) +customerAddress c w = Wallet.customerAddress c <$> readWalletState w walletPublicIdentity :: WalletInstance -> IO WalletPublicIdentity walletPublicIdentity w = do state <- readWalletState w pure $ WalletPublicIdentity { pubXpub = Wallet.walletXPub state - , pubNextUser = Wallet.nextCustomer state + , pubNextUser = Wallet.trackedCustomers state } {----------------------------------------------------------------------------- Operations diff --git a/lib/customer-deposit-wallet/src/Cardano/Wallet/Deposit/Pure.hs b/lib/customer-deposit-wallet/src/Cardano/Wallet/Deposit/Pure.hs index 13b792a14cb..d3be5448fa4 100644 --- a/lib/customer-deposit-wallet/src/Cardano/Wallet/Deposit/Pure.hs +++ b/lib/customer-deposit-wallet/src/Cardano/Wallet/Deposit/Pure.hs @@ -9,12 +9,14 @@ module Cardano.Wallet.Deposit.Pure -- ** Mapping between customers and addresses , Customer , listCustomers - , createAddress , deriveAddress , knownCustomer , knownCustomerAddress , isCustomerAddress , fromRawCustomer + , customerAddress + , trackedCustomers + , walletXPub -- ** Reading from the blockchain , fromXPubAndGenesis @@ -39,8 +41,6 @@ module Cardano.Wallet.Deposit.Pure , addTxSubmission , listTxsInSubmission - , nextCustomer - , walletXPub ) where import Prelude @@ -119,11 +119,8 @@ listCustomers :: WalletState -> [(Customer, Address)] listCustomers = Address.listCustomers . addresses -createAddress :: Customer -> WalletState -> (Address, WalletState) -createAddress customer w0 = - (address, w0{addresses = s1}) - where - (address, s1) = Address.createAddress customer (addresses w0) +customerAddress :: Customer -> WalletState -> Maybe Address +customerAddress c = lookup c . listCustomers -- depend on the private key only, not on the entire wallet state deriveAddress :: WalletState -> (Customer -> Address) @@ -146,8 +143,8 @@ isCustomerAddress address = fromRawCustomer :: Word31 -> Customer fromRawCustomer = id -nextCustomer :: WalletState -> Customer -nextCustomer = fromIntegral . length . Address.addresses . addresses +trackedCustomers :: WalletState -> Customer +trackedCustomers = fromIntegral . length . Address.addresses . addresses walletXPub :: WalletState -> XPub walletXPub = Address.getXPub . addresses diff --git a/lib/customer-deposit-wallet/src/Cardano/Wallet/Deposit/REST.hs b/lib/customer-deposit-wallet/src/Cardano/Wallet/Deposit/REST.hs index dbd69eac0ab..24b10688334 100644 --- a/lib/customer-deposit-wallet/src/Cardano/Wallet/Deposit/REST.hs +++ b/lib/customer-deposit-wallet/src/Cardano/Wallet/Deposit/REST.hs @@ -31,7 +31,6 @@ module Cardano.Wallet.Deposit.REST -- ** Mapping between customers and addresses , listCustomers - , createAddress -- ** Reading from the blockchain , getWalletTip @@ -47,6 +46,7 @@ module Cardano.Wallet.Deposit.REST , walletPublicIdentity , deleteWallet , deleteTheDepositWalletOnDisk + , customerAddress ) where import Prelude @@ -360,14 +360,14 @@ walletPublicIdentity = onWalletInstance WalletIO.walletPublicIdentity {----------------------------------------------------------------------------- Operations ------------------------------------------------------------------------------} -listCustomers - :: WalletResourceM [(Customer, Address)] +-- | List all tracked customers addresses. +listCustomers :: WalletResourceM [(Customer, Address)] listCustomers = onWalletInstance WalletIO.listCustomers -createAddress - :: Customer - -> WalletResourceM Address -createAddress = onWalletInstance . WalletIO.createAddress +-- | Retrieve the address for a customer if it's tracked by the wallet. + +customerAddress :: Customer -> WalletResourceM (Maybe Address) +customerAddress = onWalletInstance . WalletIO.customerAddress {----------------------------------------------------------------------------- Operations diff --git a/lib/customer-deposit-wallet/test/scenario/Test/Scenario/Wallet/Deposit/Exchanges.lhs.md b/lib/customer-deposit-wallet/test/scenario/Test/Scenario/Wallet/Deposit/Exchanges.lhs.md index f698a36cec8..307e61c55e6 100644 --- a/lib/customer-deposit-wallet/test/scenario/Test/Scenario/Wallet/Deposit/Exchanges.lhs.md +++ b/lib/customer-deposit-wallet/test/scenario/Test/Scenario/Wallet/Deposit/Exchanges.lhs.md @@ -90,7 +90,7 @@ scenarioStart env = ## 1. Assign an address to a customer ID A `Customer` is represented by a numeric customer ID. -Given such a customer ID, the function `createAddress` will create an address and add the association between the customer and this address to the wallet state. +Given such a customer ID, the function `customerAddress` will create an address and add the association between the customer and this address to the wallet state. (The mapping from customer ID to address is deterministic and based on the [BIP-32][] address derivation scheme.) @@ -104,14 +104,14 @@ scenarioCreateAddressList :: WalletInstance -> IO () scenarioCreateAddressList w = do let customer = 31 - address <- Wallet.createAddress customer w + Just address <- Wallet.customerAddress customer w customers <- Wallet.listCustomers w assert $ (customer, address) `elem` customers ``` ## 2. Track deposits at this address -As soon as an association between customer and address has been added to the wallet state using `createAddress`, the wallet will track deposits sent to this address. +As soon as an association between customer and address has been added to the wallet state using `customerAddress`, the wallet will track deposits sent to this address. The function `getCustomerHistory` returns a `TxSummary` for each transaction that is related to this customer. For every `TxSummary`, the `received` field records the total deposit made by the customer at this address in this transaction. @@ -123,7 +123,7 @@ The following scenario illustrates how `getCustomerHistory` records deposits: scenarioTrackDepositOne :: ScenarioEnv -> WalletInstance -> IO () scenarioTrackDepositOne env w = do - address <- Wallet.createAddress customer w + Just address <- Wallet.customerAddress customer w -- no deposits txsummaries0<- Wallet.getCustomerHistory customer w @@ -158,8 +158,8 @@ The wallet is synchronized to a particular point on the blockchain — use `getW scenarioTrackDepositAll :: ScenarioEnv -> WalletInstance -> IO () scenarioTrackDepositAll env w = do - address1 <- Wallet.createAddress customer1 w - address2 <- Wallet.createAddress customer2 w + Just address1 <- Wallet.customerAddress customer1 w + Just address2 <- Wallet.customerAddress customer2 w from <- Wallet.getWalletTip w depositFundsAt env address1 coin @@ -193,7 +193,7 @@ scenarioCreatePayment :: XPrv -> ScenarioEnv -> Address -> WalletInstance -> IO () scenarioCreatePayment xprv env destination w = do -- deposit some funds at customer address - address1 <- Wallet.createAddress customer w + Just address1 <- Wallet.customerAddress customer w depositFundsAt env address1 (coin <> coin) value1 <- Wallet.availableBalance w assert $ value1 == (coin <> coin) diff --git a/lib/customer-deposit-wallet/test/scenario/Test/Scenario/Wallet/Deposit/Run.hs b/lib/customer-deposit-wallet/test/scenario/Test/Scenario/Wallet/Deposit/Run.hs index fba4957a75e..d0b61699b0b 100644 --- a/lib/customer-deposit-wallet/test/scenario/Test/Scenario/Wallet/Deposit/Run.hs +++ b/lib/customer-deposit-wallet/test/scenario/Test/Scenario/Wallet/Deposit/Run.hs @@ -56,13 +56,13 @@ scenarios = do it "Assign an address to a customer ID" $ \env -> do withWalletEnvMock env $ \walletEnv -> - Wallet.withWalletInit walletEnv xpub 1 + Wallet.withWalletInit walletEnv xpub 32 Exchanges.scenarioCreateAddressList describe "Temporary tests" $ do it "Wallet receives funds that are sent to customer address" $ \env -> do withWalletEnvMock env $ \walletEnv -> - Wallet.withWalletInit walletEnv xpub 1 $ + Wallet.withWalletInit walletEnv xpub 8 $ testBalance env xpub :: XPub @@ -73,7 +73,7 @@ xpub = testBalance :: ScenarioEnv -> Wallet.WalletInstance -> IO () testBalance env w = do - address <- Wallet.createAddress customer w + Just address <- Wallet.customerAddress customer w payFromFaucet env [(address, coin)] value <- Wallet.availableBalance w assert $ coin == value From 907979069e9263b269938080847e56ae58ffac20 Mon Sep 17 00:00:00 2001 From: paolino Date: Wed, 18 Sep 2024 16:37:23 +0000 Subject: [PATCH 2/6] Add getCustomerAddress handler to deposit wallet --- .../Wallet/UI/Deposit/Handlers/Wallet.hs | 18 ++++++++++++++++++ 1 file changed, 18 insertions(+) diff --git a/lib/ui/src/Cardano/Wallet/UI/Deposit/Handlers/Wallet.hs b/lib/ui/src/Cardano/Wallet/UI/Deposit/Handlers/Wallet.hs index b0583acaabf..eef236e82cd 100644 --- a/lib/ui/src/Cardano/Wallet/UI/Deposit/Handlers/Wallet.hs +++ b/lib/ui/src/Cardano/Wallet/UI/Deposit/Handlers/Wallet.hs @@ -11,10 +11,14 @@ import Cardano.Address.Derivation import Cardano.Wallet.Deposit.Pure ( Customer ) +import Cardano.Wallet.Deposit.Read + ( Address + ) import Cardano.Wallet.Deposit.REST ( ErrWalletResource , WalletResource , WalletResourceM + , customerAddress , runWalletResourceM ) import Cardano.Wallet.UI.Common.Layer @@ -156,3 +160,17 @@ deleteWalletHandler layer deleteWallet alert render = do pure $ case r of Left e -> alert $ BL.pack $ show e Right _ -> render () + +getCustomerAddress + :: SessionLayer WalletResource + -> (Address -> html) + -> (BL.ByteString -> html) + -> Customer + -> Handler html +getCustomerAddress layer render alert customer = do + r <- liftIO $ catchRunWalletResourceM layer $ do + customerAddress customer + case r of + Left e -> pure $ alert $ BL.pack $ show e + Right (Just a) -> pure $ render a + Right Nothing -> pure $ alert "Address not discovered" From 7d0b570d23ada0ad21fecbe9bb8c6475182ad643 Mon Sep 17 00:00:00 2001 From: paolino Date: Wed, 18 Sep 2024 16:38:23 +0000 Subject: [PATCH 3/6] Add customerAddress data endpoint to deposit wallet UI --- lib/ui/src/Cardano/Wallet/UI/Deposit/API.hs | 14 +++++++- .../Wallet/UI/Deposit/Html/Pages/Wallet.hs | 32 +++++++++++++++++-- .../src/Cardano/Wallet/UI/Deposit/Server.hs | 5 ++- 3 files changed, 47 insertions(+), 4 deletions(-) diff --git a/lib/ui/src/Cardano/Wallet/UI/Deposit/API.hs b/lib/ui/src/Cardano/Wallet/UI/Deposit/API.hs index 7d47139691e..8ad9f1f5781 100644 --- a/lib/ui/src/Cardano/Wallet/UI/Deposit/API.hs +++ b/lib/ui/src/Cardano/Wallet/UI/Deposit/API.hs @@ -12,11 +12,15 @@ {-# LANGUAGE TypeFamilies #-} {-# LANGUAGE TypeOperators #-} {-# OPTIONS_GHC -Wno-orphans #-} +{-# LANGUAGE FlexibleInstances #-} module Cardano.Wallet.UI.Deposit.API where import Prelude +import Cardano.Wallet.Deposit.Pure + ( Customer + ) import Cardano.Wallet.UI.Common.API ( Image , SessionedHtml @@ -49,7 +53,8 @@ import Servant , (:>) ) import Web.FormUrlEncoded - ( FromForm + ( FromForm (..) + , parseUnique ) import qualified Data.ByteString.Lazy as BL @@ -99,6 +104,11 @@ type Data = :> SessionedHtml Post :<|> "wallet" :> SessionedHtml Delete :<|> "wallet" :> "delete" :> "modal" :> SessionedHtml Get + :<|> "customer" :> "address" :> ReqBody '[FormUrlEncoded] Customer + :> SessionedHtml Post + +instance FromForm Customer where + fromForm form = fromIntegral @Int <$> parseUnique "customer" form type Home = SessionedHtml Get @@ -126,6 +136,7 @@ walletPostMnemonicLink :: Link walletPostXPubLink :: Link walletDeleteLink :: Link walletDeleteModalLink :: Link +customerAddressLink :: Link homePageLink :<|> aboutPageLink :<|> networkPageLink @@ -142,5 +153,6 @@ homePageLink :<|> walletPostXPubLink :<|> walletDeleteLink :<|> walletDeleteModalLink + :<|> customerAddressLink = allLinks (Proxy @UI) diff --git a/lib/ui/src/Cardano/Wallet/UI/Deposit/Html/Pages/Wallet.hs b/lib/ui/src/Cardano/Wallet/UI/Deposit/Html/Pages/Wallet.hs index 5daa2a3dfd3..c980c56788e 100644 --- a/lib/ui/src/Cardano/Wallet/UI/Deposit/Html/Pages/Wallet.hs +++ b/lib/ui/src/Cardano/Wallet/UI/Deposit/Html/Pages/Wallet.hs @@ -11,9 +11,15 @@ import Cardano.Address.Derivation ( XPub , xpubToBytes ) +import Cardano.Ledger.Address + ( unCompactAddr + ) import Cardano.Wallet.Deposit.IO ( WalletPublicIdentity (..) ) +import Cardano.Wallet.Deposit.Read + ( Address + ) import Cardano.Wallet.Deposit.REST ( ErrDatabase ) @@ -22,7 +28,10 @@ import Cardano.Wallet.UI.Common.API ) import Cardano.Wallet.UI.Common.Html.Htmx ( hxDelete_ + , hxPost_ , hxSwap_ + , hxTarget_ + , hxTrigger_ ) import Cardano.Wallet.UI.Common.Html.Lib ( dataBsDismiss_ @@ -45,7 +54,8 @@ import Cardano.Wallet.UI.Common.Html.Pages.Wallet , newWalletFromXPubH ) import Cardano.Wallet.UI.Deposit.API - ( walletDeleteLink + ( customerAddressLink + , walletDeleteLink , walletDeleteModalLink , walletLink , walletMnemonicLink @@ -80,15 +90,25 @@ import Lucid , button_ , class_ , div_ + , h5_ , hidden_ , hr_ , id_ + , input_ + , min_ + , name_ , p_ , section_ + , type_ + ) +import Lucid.Html5 + ( max_ + , step_ ) import qualified Data.ByteString.Char8 as B8 import qualified Data.ByteString.Lazy.Char8 as BL +import qualified Data.ByteString.Short as B data WalletPresent = WalletPresent WalletPublicIdentity @@ -112,10 +132,18 @@ walletH = sseH walletLink "wallet" ["wallet"] base64 :: ByteString -> ByteString base64 = convertToBase Base64 +customerAddressH :: Monad m => Address -> HtmlT m () +customerAddressH addr = div_ [class_ "row"] $ do + div_ [id_ "address", hidden_ "false"] $ toHtml addr' + div_ [class_ "col-6"] $ toHtml $ headAndTail 4 $ B8.dropEnd 1 addr' + div_ [class_ "col-6"] + $ copyButton "address" + where addr' = base64 $ B.fromShort $ unCompactAddr addr + pubKeyH :: Monad m => XPub -> HtmlT m () pubKeyH xpub = div_ [class_ "row"] $ do div_ [id_ "public_key", hidden_ "false"] $ toHtml xpubByteString - div_ [class_ "col-6"] $ toHtml $ headAndTail 4 $ B8.dropEnd 2 xpubByteString + div_ [class_ "col-6"] $ toHtml $ headAndTail 4 $ B8.dropEnd 1 xpubByteString div_ [class_ "col-6"] $ copyButton "public_key" where diff --git a/lib/ui/src/Cardano/Wallet/UI/Deposit/Server.hs b/lib/ui/src/Cardano/Wallet/UI/Deposit/Server.hs index 0e93f0380ee..678fb49f4ad 100644 --- a/lib/ui/src/Cardano/Wallet/UI/Deposit/Server.hs +++ b/lib/ui/src/Cardano/Wallet/UI/Deposit/Server.hs @@ -95,6 +95,7 @@ import Cardano.Wallet.UI.Deposit.Handlers.Page ) import Cardano.Wallet.UI.Deposit.Handlers.Wallet ( deleteWalletHandler + , getCustomerAddress , getWallet , postMnemonicWallet , postXPubWallet @@ -103,7 +104,8 @@ import Cardano.Wallet.UI.Deposit.Html.Pages.Page ( Page (..) ) import Cardano.Wallet.UI.Deposit.Html.Pages.Wallet - ( deleteWalletModalH + ( customerAddressH + , deleteWalletModalH , walletElementH ) import Control.Monad.Trans @@ -168,6 +170,7 @@ serveUI tr ul env dbDir config _ nl bs = :<|> (\v -> wsl (\l -> postXPubWallet l (initWallet l) alert ok v)) :<|> wsl (\l -> deleteWalletHandler l (deleteWallet dbDir) alert ok) :<|> wsl (\_l -> pure $ renderHtml deleteWalletModalH) + :<|> (\c -> wsl (\l -> getCustomerAddress l (renderHtml . customerAddressH) alert c)) where ph = pageHandler tr ul env dbDir config ok _ = renderHtml . rogerH @Text $ "ok" From 4957e934d0a65ffec77d34d6b9b15d171b6d8966 Mon Sep 17 00:00:00 2001 From: paolino Date: Wed, 18 Sep 2024 16:40:39 +0000 Subject: [PATCH 4/6] Add query customer address form --- lib/ui/cardano-wallet-ui.cabal | 11 +++- .../Wallet/UI/Deposit/Html/Pages/Wallet.hs | 57 +++++++++++++------ lib/ui/src/Cardano/Wallet/UI/Lib/Address.hs | 30 ++++++++++ 3 files changed, 78 insertions(+), 20 deletions(-) create mode 100644 lib/ui/src/Cardano/Wallet/UI/Lib/Address.hs diff --git a/lib/ui/cardano-wallet-ui.cabal b/lib/ui/cardano-wallet-ui.cabal index 9a1da5a86ba..832b10a0d4b 100644 --- a/lib/ui/cardano-wallet-ui.cabal +++ b/lib/ui/cardano-wallet-ui.cabal @@ -20,8 +20,10 @@ common language OverloadedStrings common opts-lib - ghc-options: -Wall -Wcompat -Wredundant-constraints -Wunused-packages - -Wunused-imports -Wincomplete-uni-patterns -Wincomplete-record-updates + ghc-options: + -Wall -Wcompat -Wredundant-constraints -Wunused-packages + -Wunused-imports -Wincomplete-uni-patterns + -Wincomplete-record-updates if flag(release) ghc-options: -O2 -Werror @@ -36,8 +38,8 @@ library exposed-modules: Cardano.Wallet.UI.Common.API Cardano.Wallet.UI.Common.Handlers.Lib - Cardano.Wallet.UI.Common.Handlers.Settings Cardano.Wallet.UI.Common.Handlers.Session + Cardano.Wallet.UI.Common.Handlers.Settings Cardano.Wallet.UI.Common.Handlers.SSE Cardano.Wallet.UI.Common.Handlers.State Cardano.Wallet.UI.Common.Handlers.Wallet @@ -63,6 +65,7 @@ library Cardano.Wallet.UI.Deposit.Html.Pages.Page Cardano.Wallet.UI.Deposit.Html.Pages.Wallet Cardano.Wallet.UI.Deposit.Server + Cardano.Wallet.UI.Lib.Address Cardano.Wallet.UI.Lib.ListOf Cardano.Wallet.UI.Shelley.API Cardano.Wallet.UI.Shelley.Handlers.Addresses @@ -84,6 +87,8 @@ library , aeson , aeson-pretty , base + , bech32 + , bech32-th , bytestring , cardano-addresses , cardano-slotting diff --git a/lib/ui/src/Cardano/Wallet/UI/Deposit/Html/Pages/Wallet.hs b/lib/ui/src/Cardano/Wallet/UI/Deposit/Html/Pages/Wallet.hs index c980c56788e..abe253e0daa 100644 --- a/lib/ui/src/Cardano/Wallet/UI/Deposit/Html/Pages/Wallet.hs +++ b/lib/ui/src/Cardano/Wallet/UI/Deposit/Html/Pages/Wallet.hs @@ -11,9 +11,6 @@ import Cardano.Address.Derivation ( XPub , xpubToBytes ) -import Cardano.Ledger.Address - ( unCompactAddr - ) import Cardano.Wallet.Deposit.IO ( WalletPublicIdentity (..) ) @@ -62,6 +59,9 @@ import Cardano.Wallet.UI.Deposit.API , walletPostMnemonicLink , walletPostXPubLink ) +import Cardano.Wallet.UI.Lib.Address + ( encodeMainnetAddress + ) import Cardano.Wallet.UI.Type ( WHtml , WalletType (..) @@ -108,7 +108,7 @@ import Lucid.Html5 import qualified Data.ByteString.Char8 as B8 import qualified Data.ByteString.Lazy.Char8 as BL -import qualified Data.ByteString.Short as B +import qualified Data.Text as T data WalletPresent = WalletPresent WalletPublicIdentity @@ -134,23 +134,27 @@ base64 = convertToBase Base64 customerAddressH :: Monad m => Address -> HtmlT m () customerAddressH addr = div_ [class_ "row"] $ do - div_ [id_ "address", hidden_ "false"] $ toHtml addr' - div_ [class_ "col-6"] $ toHtml $ headAndTail 4 $ B8.dropEnd 1 addr' - div_ [class_ "col-6"] - $ copyButton "address" - where addr' = base64 $ B.fromShort $ unCompactAddr addr + div_ [id_ "address", hidden_ "true"] $ toHtml encodedAddr + div_ [class_ "col-8"] $ toHtml addrShortened + div_ [class_ "col-4"] $ copyButton "address" + where + encodedAddr = encodeMainnetAddress addr + addrShortened = + T.take 10 (T.drop 5 encodedAddr) + <> " .. " + <> T.takeEnd 10 encodedAddr pubKeyH :: Monad m => XPub -> HtmlT m () pubKeyH xpub = div_ [class_ "row"] $ do - div_ [id_ "public_key", hidden_ "false"] $ toHtml xpubByteString - div_ [class_ "col-6"] $ toHtml $ headAndTail 4 $ B8.dropEnd 1 xpubByteString - div_ [class_ "col-6"] + div_ [id_ "public_key", hidden_ "true"] $ toHtml xpubByteString + div_ [class_ "col-8"] $ toHtml $ headAndTail 4 $ B8.dropEnd 1 xpubByteString + div_ [class_ "col-4"] $ copyButton "public_key" where xpubByteString = base64 $ xpubToBytes xpub headAndTail :: Int -> ByteString -> ByteString -headAndTail n t = B8.take n t <> ".." <> B8.takeEnd n t +headAndTail n t = B8.take n t <> " .. " <> B8.takeEnd n t deleteWalletButtonH :: Html () deleteWalletButtonH = @@ -183,10 +187,29 @@ deleteWalletModalH = walletElementH :: (BL.ByteString -> Html ()) -> WalletPresent -> Html () walletElementH alert = \case WalletPresent (WalletPublicIdentity xpub customers) -> do - record $ do - simpleField "Public Key" $ pubKeyH xpub - simpleField "Customer Discovery" $ toHtml $ toText customers - div_ [class_ "row"] $ do + div_ [class_ "row mt-5 "] $ do + h5_ [class_ "text-center"] "Wallet Details" + div_ [class_ "col"] $ record $ do + simpleField "Public Key" $ pubKeyH xpub + simpleField "Customer Discovery" $ toHtml $ toText customers + div_ [class_ "row mt-5"] $ do + h5_ [class_ "text-center"] "Query Address" + div_ [class_ "col"] $ record $ do + simpleField "Customer number" + $ input_ + [ type_ "number" + , hxTarget_ "#customer-address" + , class_ "form-control" + , hxTrigger_ "change" + , hxPost_ $ linkText customerAddressLink + , min_ "0" + , max_ $ toText $ customers - 1 + , step_ "1" + , name_ "customer" + ] + simpleField "Address" $ div_ [id_ "customer-address"] mempty + div_ [class_ "row mt-5"] $ do + h5_ [class_ "text-center"] "Actions" div_ [class_ "col"] $ do deleteWalletButtonH div_ [id_ "delete-result"] mempty diff --git a/lib/ui/src/Cardano/Wallet/UI/Lib/Address.hs b/lib/ui/src/Cardano/Wallet/UI/Lib/Address.hs new file mode 100644 index 00000000000..120a7e33b76 --- /dev/null +++ b/lib/ui/src/Cardano/Wallet/UI/Lib/Address.hs @@ -0,0 +1,30 @@ +{-# LANGUAGE QuasiQuotes #-} + +module Cardano.Wallet.UI.Lib.Address +where + +import Prelude + +import Cardano.Wallet.Deposit.Read + ( Address + ) +import Cardano.Wallet.Read.Address + ( toShortByteString + ) +import Codec.Binary.Bech32 + ( dataPartFromBytes + ) +import Data.Text + ( Text + ) + +import qualified Codec.Binary.Bech32 as Bech32 +import qualified Codec.Binary.Bech32.TH as Bech32 +import qualified Data.ByteString.Short as B8 + +encodeMainnetAddress :: Address -> Text +encodeMainnetAddress addr = bech32 + where + bytes = B8.fromShort $ toShortByteString addr + bech32 = Bech32.encodeLenient hrp (dataPartFromBytes bytes) + hrp = [Bech32.humanReadablePart|addr|] From 12381a512941fc17eca27deb91d0e4359fc5848d Mon Sep 17 00:00:00 2001 From: paolino Date: Wed, 18 Sep 2024 20:10:30 +0000 Subject: [PATCH 5/6] Some random embellishments --- .../UI/Common/Html/Pages/Template/Body.hs | 2 +- .../UI/Common/Html/Pages/Template/Footer.hs | 2 +- .../Wallet/UI/Deposit/Html/Pages/Page.hs | 4 ++-- .../Wallet/UI/Deposit/Html/Pages/Wallet.hs | 18 ++++++++++-------- lib/ui/src/Cardano/Wallet/UI/Deposit/Server.hs | 2 +- 5 files changed, 15 insertions(+), 13 deletions(-) diff --git a/lib/ui/src/Cardano/Wallet/UI/Common/Html/Pages/Template/Body.hs b/lib/ui/src/Cardano/Wallet/UI/Common/Html/Pages/Template/Body.hs index 19a39bdb2e1..66bf49a83a1 100644 --- a/lib/ui/src/Cardano/Wallet/UI/Common/Html/Pages/Template/Body.hs +++ b/lib/ui/src/Cardano/Wallet/UI/Common/Html/Pages/Template/Body.hs @@ -46,5 +46,5 @@ bodyH sseLink header body = do div_ [class_ "container-fluid"] $ do div_ [class_ "main"] body div_ - [class_ "footer"] + [class_ "footer mt-5"] footerH diff --git a/lib/ui/src/Cardano/Wallet/UI/Common/Html/Pages/Template/Footer.hs b/lib/ui/src/Cardano/Wallet/UI/Common/Html/Pages/Template/Footer.hs index cf705167fc2..e4cc6e6491c 100644 --- a/lib/ui/src/Cardano/Wallet/UI/Common/Html/Pages/Template/Footer.hs +++ b/lib/ui/src/Cardano/Wallet/UI/Common/Html/Pages/Template/Footer.hs @@ -30,7 +30,7 @@ footerH = term "footer_" [ class_ - "text-center text-muted bg-secondary" + "text-center text-muted bg-secondary fs-6" ] $ do div_ [class_ "row d-md-flex align-items-center"] diff --git a/lib/ui/src/Cardano/Wallet/UI/Deposit/Html/Pages/Page.hs b/lib/ui/src/Cardano/Wallet/UI/Deposit/Html/Pages/Page.hs index 58441d0c33c..d28264c0b0f 100644 --- a/lib/ui/src/Cardano/Wallet/UI/Deposit/Html/Pages/Page.hs +++ b/lib/ui/src/Cardano/Wallet/UI/Deposit/Html/Pages/Page.hs @@ -100,8 +100,8 @@ headerH :: Text -> Page -> Monad m => HtmlT m () headerH prefix p = navigationH prefix - [ (is _About p, aboutPageLink, "About") + [ (is _Wallet p, walletPageLink, "Wallet") , (is _Network p, networkPageLink, "Network") , (is _Settings p, settingsPageLink, "Settings") - , (is _Wallet p, walletPageLink, "Wallet") + , (is _About p, aboutPageLink, "About") ] diff --git a/lib/ui/src/Cardano/Wallet/UI/Deposit/Html/Pages/Wallet.hs b/lib/ui/src/Cardano/Wallet/UI/Deposit/Html/Pages/Wallet.hs index abe253e0daa..7a3ad8d6770 100644 --- a/lib/ui/src/Cardano/Wallet/UI/Deposit/Html/Pages/Wallet.hs +++ b/lib/ui/src/Cardano/Wallet/UI/Deposit/Html/Pages/Wallet.hs @@ -100,6 +100,7 @@ import Lucid , p_ , section_ , type_ + , value_ ) import Lucid.Html5 ( max_ @@ -187,29 +188,30 @@ deleteWalletModalH = walletElementH :: (BL.ByteString -> Html ()) -> WalletPresent -> Html () walletElementH alert = \case WalletPresent (WalletPublicIdentity xpub customers) -> do - div_ [class_ "row mt-5 "] $ do - h5_ [class_ "text-center"] "Wallet Details" - div_ [class_ "col"] $ record $ do - simpleField "Public Key" $ pubKeyH xpub - simpleField "Customer Discovery" $ toHtml $ toText customers div_ [class_ "row mt-5"] $ do h5_ [class_ "text-center"] "Query Address" div_ [class_ "col"] $ record $ do - simpleField "Customer number" + simpleField "Customer Number" $ input_ [ type_ "number" , hxTarget_ "#customer-address" , class_ "form-control" - , hxTrigger_ "change" + , hxTrigger_ "load, change" , hxPost_ $ linkText customerAddressLink , min_ "0" , max_ $ toText $ customers - 1 , step_ "1" , name_ "customer" + , value_ "0" ] simpleField "Address" $ div_ [id_ "customer-address"] mempty + div_ [class_ "row mt-5 "] $ do + h5_ [class_ "text-center"] "Wallet Details" + div_ [class_ "col"] $ record $ do + simpleField "Public Key" $ pubKeyH xpub + simpleField "Customer Discovery" $ toHtml $ toText customers div_ [class_ "row mt-5"] $ do - h5_ [class_ "text-center"] "Actions" + h5_ [class_ "text-center"] "Administration" div_ [class_ "col"] $ do deleteWalletButtonH div_ [id_ "delete-result"] mempty diff --git a/lib/ui/src/Cardano/Wallet/UI/Deposit/Server.hs b/lib/ui/src/Cardano/Wallet/UI/Deposit/Server.hs index 678fb49f4ad..d91ccf3ca72 100644 --- a/lib/ui/src/Cardano/Wallet/UI/Deposit/Server.hs +++ b/lib/ui/src/Cardano/Wallet/UI/Deposit/Server.hs @@ -154,7 +154,7 @@ serveUI -> BlockchainSource -> Server UI serveUI tr ul env dbDir config _ nl bs = - ph About + ph Wallet :<|> ph About :<|> ph Network :<|> ph Settings From d265de6dcbadb8707caf393d18202c27d9de4a34 Mon Sep 17 00:00:00 2001 From: paolino Date: Fri, 20 Sep 2024 15:17:00 +0000 Subject: [PATCH 6/6] Exclude mithril test from CI as ATM mithril nix build is broken --- .buildkite/pipeline.yml | 5 ++++- 1 file changed, 4 insertions(+), 1 deletion(-) diff --git a/.buildkite/pipeline.yml b/.buildkite/pipeline.yml index 0193c5511c7..da0cc45849f 100644 --- a/.buildkite/pipeline.yml +++ b/.buildkite/pipeline.yml @@ -143,6 +143,7 @@ steps: - label: Private Network Full Sync timeout_in_minutes: 30 + if: 0 == 1 # Disabled until new mihtril snapshots depends_on: [] command: | rm -rf run/private/nix/logs @@ -161,6 +162,7 @@ steps: - label: Mainnet Boot Sync timeout_in_minutes: 2 + if: 0 == 1 # Disabled until mithril builds again depends_on: [] command: | cd run/mainnet/nix @@ -218,6 +220,7 @@ steps: depends_on: - linux-sanchonet-full-sync-block timeout_in_minutes: 120 + if: 0 == 1 # Disabled until mithril builds again command: | rm -rf run/sanchonet/nix/logs mkdir -p run/sanchonet/nix/logs @@ -242,6 +245,7 @@ steps: depends_on: - linux-preprod-full-sync-block timeout_in_minutes: 240 + if: 0 == 1 # Disabled until mithril builds again command: | cd run/preprod/nix rm -rf logs @@ -685,7 +689,6 @@ steps: - label: Mainnet Boot Sync via Mithril timeout_in_minutes: 120 - if: 0 == 1 # Disabled until new mihtril snapshots command: | cd run/mainnet/docker export WALLET_TAG=$(buildkite-agent meta-data get "release-cabal-version")