diff --git a/lib/ui/cardano-wallet-ui.cabal b/lib/ui/cardano-wallet-ui.cabal index 7d178265b41..f9541d9b60b 100644 --- a/lib/ui/cardano-wallet-ui.cabal +++ b/lib/ui/cardano-wallet-ui.cabal @@ -59,9 +59,11 @@ library Cardano.Wallet.UI.Common.Layer Cardano.Wallet.UI.Cookies Cardano.Wallet.UI.Deposit.API + Cardano.Wallet.UI.Deposit.Handlers.Addresses Cardano.Wallet.UI.Deposit.Handlers.Lib Cardano.Wallet.UI.Deposit.Handlers.Wallet Cardano.Wallet.UI.Deposit.Html.Pages.About + Cardano.Wallet.UI.Deposit.Html.Pages.Addresses Cardano.Wallet.UI.Deposit.Html.Pages.Page Cardano.Wallet.UI.Deposit.Html.Pages.Wallet Cardano.Wallet.UI.Deposit.Server 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 ba00acd24df..fe67cacfa43 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 @@ -41,8 +41,8 @@ bodyH -- ^ Body content -> HtmlT m () bodyH sseLink header body = do - header - div_ [hxSse_ $ sseConnectFromLink sseLink] $ + div_ [hxSse_ $ sseConnectFromLink sseLink] $ do + header div_ [class_ "container-fluid"] $ do div_ [class_ "main"] body initClipboardScript diff --git a/lib/ui/src/Cardano/Wallet/UI/Common/Html/Pages/Template/Navigation.hs b/lib/ui/src/Cardano/Wallet/UI/Common/Html/Pages/Template/Navigation.hs index 572fbe05d63..dcf7a59c241 100644 --- a/lib/ui/src/Cardano/Wallet/UI/Common/Html/Pages/Template/Navigation.hs +++ b/lib/ui/src/Cardano/Wallet/UI/Common/Html/Pages/Template/Navigation.hs @@ -10,6 +10,7 @@ import Cardano.Wallet.UI.Common.Html.Lib ) import Cardano.Wallet.UI.Deposit.API ( faviconLink + , homePageLink ) import Control.Monad ( forM_ @@ -54,7 +55,7 @@ navElem navElem prefix c p = a_ ([href_ $ prefix <> linkText p, class_ class']) where class' = baseClass <> " " <> if c then "active" else "" - baseClass = "nav-link ms-auto fs-3" + baseClass = "nav-link ms-auto fs-4 fs-5-md" -- | Navigation bar definition. @@ -70,7 +71,7 @@ navigationH prefix pages = do nav_ [class_ "navbar navbar-expand-lg bg-body-tertiary mb-2"] $ div_ [class_ "container-fluid"] $ do - a_ [class_ "navbar-brand", href_ "/"] + a_ [class_ "navbar-brand", href_ $ linkText homePageLink] $ img_ [src_ $ linkText faviconLink , alt_ "Cardano Deposit Wallet" , class_ "img-fluid" diff --git a/lib/ui/src/Cardano/Wallet/UI/Deposit/API.hs b/lib/ui/src/Cardano/Wallet/UI/Deposit/API.hs index 123c2197c8a..3c04c186f46 100644 --- a/lib/ui/src/Cardano/Wallet/UI/Deposit/API.hs +++ b/lib/ui/src/Cardano/Wallet/UI/Deposit/API.hs @@ -2,16 +2,16 @@ {-# LANGUAGE DataKinds #-} {-# LANGUAGE DuplicateRecordFields #-} {-# LANGUAGE FlexibleContexts #-} +{-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE MultiParamTypeClasses #-} -{-# LANGUAGE NoMonomorphismRestriction #-} {-# LANGUAGE PolyKinds #-} {-# LANGUAGE RankNTypes #-} {-# LANGUAGE ScopedTypeVariables #-} +{-# LANGUAGE TemplateHaskell #-} {-# LANGUAGE TypeApplications #-} {-# LANGUAGE TypeFamilies #-} {-# LANGUAGE TypeOperators #-} {-# OPTIONS_GHC -Wno-orphans #-} -{-# LANGUAGE FlexibleInstances #-} module Cardano.Wallet.UI.Deposit.API where @@ -36,15 +36,20 @@ import Cardano.Wallet.UI.Common.Handlers.SSE import Cardano.Wallet.UI.Cookies ( CookieRequest ) +import Control.Lens + ( makePrisms + ) import Servant ( Delete , FormUrlEncoded + , FromHttpApiData (..) , Get , Link , Post , Proxy (..) , QueryParam , ReqBody + , ToHttpApiData (..) , allLinks , (:<|>) (..) , (:>) @@ -60,12 +65,37 @@ instance FromForm PostWalletViaMenmonic instance FromForm PostWalletViaXPub +data Page + = About + | Network + | Settings + | Wallet + | Addresses + +makePrisms ''Page + +instance ToHttpApiData Page where + toUrlPiece About = "about" + toUrlPiece Network = "network" + toUrlPiece Settings = "settings" + toUrlPiece Wallet = "wallet" + toUrlPiece Addresses = "addresses" + +instance FromHttpApiData Page where + parseUrlPiece "about" = Right About + parseUrlPiece "network" = Right Network + parseUrlPiece "settings" = Right Settings + parseUrlPiece "wallet" = Right Wallet + parseUrlPiece "addresses" = Right Addresses + parseUrlPiece _ = Left "Invalid page" + -- | Pages endpoints type Pages = "about" :> SessionedHtml Get :<|> "network" :> SessionedHtml Get :<|> "settings" :> SessionedHtml Get :<|> "wallet" :> SessionedHtml Get + :<|> "addresses" :> SessionedHtml Get -- | Data endpoints type Data = @@ -89,8 +119,12 @@ type Data = :> SessionedHtml Post :<|> "wallet" :> SessionedHtml Delete :<|> "wallet" :> "delete" :> "modal" :> SessionedHtml Get - :<|> "customer" :> "address" :> ReqBody '[FormUrlEncoded] Customer + :<|> "customer" + :> "address" + :> ReqBody '[FormUrlEncoded] Customer :> SessionedHtml Post + :<|> "addresses" :> SessionedHtml Get + :<|> "navigation" :> QueryParam "page" Page :> SessionedHtml Get instance FromForm Customer where fromForm form = fromIntegral @Int <$> parseUnique "customer" form @@ -109,6 +143,7 @@ homePageLink :: Link aboutPageLink :: Link networkPageLink :: Link settingsPageLink :: Link +addressesPageLink :: Link networkInfoLink :: Link settingsGetLink :: Link settingsSseToggleLink :: Link @@ -122,11 +157,14 @@ walletPostXPubLink :: Link walletDeleteLink :: Link walletDeleteModalLink :: Link customerAddressLink :: Link +addressesLink :: Link +navigationLink :: Maybe Page -> Link homePageLink :<|> aboutPageLink :<|> networkPageLink :<|> settingsPageLink :<|> walletPageLink + :<|> addressesPageLink :<|> networkInfoLink :<|> settingsGetLink :<|> settingsSseToggleLink @@ -139,5 +177,6 @@ homePageLink :<|> walletDeleteLink :<|> walletDeleteModalLink :<|> customerAddressLink - = + :<|> addressesLink + :<|> navigationLink = allLinks (Proxy @UI) diff --git a/lib/ui/src/Cardano/Wallet/UI/Deposit/Handlers/Addresses.hs b/lib/ui/src/Cardano/Wallet/UI/Deposit/Handlers/Addresses.hs new file mode 100644 index 00000000000..7e9cef109c3 --- /dev/null +++ b/lib/ui/src/Cardano/Wallet/UI/Deposit/Handlers/Addresses.hs @@ -0,0 +1,52 @@ +{-# LANGUAGE LambdaCase #-} + +module Cardano.Wallet.UI.Deposit.Handlers.Addresses +where + +import Prelude + +import Cardano.Wallet.Deposit.Pure + ( Customer + ) +import Cardano.Wallet.Deposit.Read + ( Address + ) +import Cardano.Wallet.Deposit.REST + ( WalletResource + , customerAddress + ) +import Cardano.Wallet.UI.Common.Layer + ( SessionLayer (..) + ) +import Cardano.Wallet.UI.Deposit.Handlers.Lib + ( catchRunWalletResourceHtml + , walletPresence + ) +import Cardano.Wallet.UI.Deposit.Html.Pages.Wallet + ( WalletPresent + ) +import Servant + ( Handler + ) + +import qualified Data.ByteString.Lazy.Char8 as BL + +getAddresses + :: SessionLayer WalletResource + -> (WalletPresent -> html) -- success report + -> Handler html +getAddresses layer render = render <$> walletPresence layer + +getCustomerAddress + :: SessionLayer WalletResource + -> (Address -> html) + -> (BL.ByteString -> html) + -> Customer + -> Handler html +getCustomerAddress layer render alert customer = do + catchRunWalletResourceHtml layer alert render' + $ customerAddress customer + where + render' = \case + Just a -> render a + Nothing -> alert "Address not discovered" 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 fc00332940b..f0638fcd87e 100644 --- a/lib/ui/src/Cardano/Wallet/UI/Deposit/Handlers/Wallet.hs +++ b/lib/ui/src/Cardano/Wallet/UI/Deposit/Handlers/Wallet.hs @@ -1,4 +1,3 @@ -{-# LANGUAGE LambdaCase #-} {-# LANGUAGE NamedFieldPuns #-} module Cardano.Wallet.UI.Deposit.Handlers.Wallet @@ -12,13 +11,9 @@ import Cardano.Address.Derivation import Cardano.Wallet.Deposit.Pure ( Customer ) -import Cardano.Wallet.Deposit.Read - ( Address - ) import Cardano.Wallet.Deposit.REST ( WalletResource , WalletResourceM - , customerAddress ) import Cardano.Wallet.Deposit.REST.Wallet.Create ( PostWalletViaMenmonic (..) @@ -122,17 +117,3 @@ deleteWalletHandler -> Handler html deleteWalletHandler layer deleteWallet alert render = catchRunWalletResourceHtml layer alert render deleteWallet - -getCustomerAddress - :: SessionLayer WalletResource - -> (Address -> html) - -> (BL.ByteString -> html) - -> Customer - -> Handler html -getCustomerAddress layer render alert customer = do - catchRunWalletResourceHtml layer alert render' - $ customerAddress customer - where - render' = \case - Just a -> render a - Nothing -> alert "Address not discovered" diff --git a/lib/ui/src/Cardano/Wallet/UI/Deposit/Html/Pages/Addresses.hs b/lib/ui/src/Cardano/Wallet/UI/Deposit/Html/Pages/Addresses.hs new file mode 100644 index 00000000000..fd5d654f4ac --- /dev/null +++ b/lib/ui/src/Cardano/Wallet/UI/Deposit/Html/Pages/Addresses.hs @@ -0,0 +1,114 @@ +{-# LANGUAGE FlexibleContexts #-} +{-# LANGUAGE LambdaCase #-} +{-# LANGUAGE ScopedTypeVariables #-} + +module Cardano.Wallet.UI.Deposit.Html.Pages.Addresses +where + +import Prelude + +import Cardano.Wallet.Deposit.IO + ( WalletPublicIdentity (..) + ) +import Cardano.Wallet.Deposit.Read + ( Address + ) +import Cardano.Wallet.UI.Common.Html.Copy + ( copyButton + , copyableHidden + ) +import Cardano.Wallet.UI.Common.Html.Htmx + ( hxPost_ + , hxTarget_ + , hxTrigger_ + ) +import Cardano.Wallet.UI.Common.Html.Lib + ( linkText + ) +import Cardano.Wallet.UI.Common.Html.Pages.Lib + ( record + , simpleField + , sseH + ) +import Cardano.Wallet.UI.Deposit.API + ( addressesLink + , customerAddressLink + ) +import Cardano.Wallet.UI.Deposit.Html.Pages.Wallet + ( WalletPresent (..) + ) +import Cardano.Wallet.UI.Lib.Address + ( encodeMainnetAddress + ) +import Cardano.Wallet.UI.Type + ( WHtml + ) +import Data.Text.Class + ( ToText (..) + ) +import Lucid + ( Html + , HtmlT + , ToHtml (..) + , class_ + , div_ + , id_ + , input_ + , min_ + , name_ + , type_ + , value_ + ) +import Lucid.Html5 + ( max_ + , step_ + ) + +import qualified Data.ByteString.Lazy.Char8 as BL +import qualified Data.Text as T + +addressesH :: WHtml () +addressesH = do + sseH addressesLink "addresses" ["wallet"] + +customerAddressH :: Monad m => Address -> HtmlT m () +customerAddressH addr = div_ [class_ "d-flex justify-content-end"] $ do + div_ (copyableHidden "address") $ toHtml encodedAddr + div_ [class_ "d-block d-md-none"] $ toHtml addrShortened + div_ [class_ "d-none d-md-block"] $ toHtml encodedAddr + div_ [class_ "ms-1"] $ copyButton "address" + where + encodedAddr = encodeMainnetAddress addr + addrShortened = + T.take 10 (T.drop 5 encodedAddr) + <> " .. " + <> T.takeEnd 10 encodedAddr + +addressElementH :: (BL.ByteString -> Html ()) -> WalletPresent -> Html () +addressElementH alert = \case + WalletPresent (WalletPublicIdentity _xpub customers) -> do + div_ [class_ "row mt-5"] $ do + div_ [class_ "col"] $ record $ do + simpleField "Customer Number" + $ input_ + [ type_ "number" + , hxTarget_ "#customer-address" + , class_ "form-control" + , hxTrigger_ "load, change" + , hxPost_ $ linkText customerAddressLink + , min_ "0" + , max_ $ toText $ customers - 1 + , step_ "1" + , name_ "customer" + , value_ "0" + , class_ "w-3" + ] + simpleField "Address" $ div_ [id_ "customer-address"] mempty + WalletAbsent -> alert "Wallet is absent" + WalletFailedToInitialize err -> + alert + $ "Failed to initialize wallet" + <> BL.pack (show err) + WalletVanished e -> alert $ "Wallet vanished " <> BL.pack (show e) + WalletInitializing -> alert "Wallet is initializing" + WalletClosing -> alert "Wallet is closing" 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 d28264c0b0f..ceecfc7ca52 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 @@ -1,12 +1,11 @@ {-# LANGUAGE AllowAmbiguousTypes #-} {-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE RankNTypes #-} -{-# LANGUAGE RecordWildCards #-} -{-# LANGUAGE TemplateHaskell #-} module Cardano.Wallet.UI.Deposit.Html.Pages.Page ( Page (..) , page + , headerElementH ) where @@ -18,6 +17,9 @@ import Cardano.Wallet.UI.Common.Html.Html import Cardano.Wallet.UI.Common.Html.Modal ( modalsH ) +import Cardano.Wallet.UI.Common.Html.Pages.Lib + ( sseH + ) import Cardano.Wallet.UI.Common.Html.Pages.Network ( networkH ) @@ -35,8 +37,16 @@ import Cardano.Wallet.UI.Common.Html.Pages.Template.Navigation ( navigationH ) import Cardano.Wallet.UI.Deposit.API - ( aboutPageLink + ( Page (..) + , _About + , _Addresses + , _Network + , _Settings + , _Wallet + , aboutPageLink + , addressesPageLink , faviconLink + , navigationLink , networkInfoLink , networkPageLink , settingsGetLink @@ -47,47 +57,41 @@ import Cardano.Wallet.UI.Deposit.API import Cardano.Wallet.UI.Deposit.Html.Pages.About ( aboutH ) +import Cardano.Wallet.UI.Deposit.Html.Pages.Addresses + ( addressesH + ) import Cardano.Wallet.UI.Deposit.Html.Pages.Wallet - ( walletH + ( WalletPresent + , isPresent + , walletH ) import Cardano.Wallet.UI.Type ( WalletType (..) , runWHtml ) +import Control.Lens + ( _Just + ) import Control.Lens.Extras ( is ) -import Control.Lens.TH - ( makePrisms - ) -import Data.Text - ( Text - ) import Lucid ( HtmlT , renderBS ) -data Page - = About - | Network - | Settings - | Wallet - -makePrisms ''Page - page :: PageConfig -- ^ Page configuration -> Page -- ^ Current page -> RawHtml -page c@PageConfig{..} p = RawHtml +page c p = RawHtml $ renderBS $ runWHtml Deposit $ pageFromBodyH faviconLink c $ do - bodyH sseLink (headerH prefix p) + bodyH sseLink (headerH p) $ do modalsH case p of @@ -95,13 +99,22 @@ page c@PageConfig{..} p = RawHtml Network -> networkH networkInfoLink Settings -> settingsPageH settingsGetLink Wallet -> walletH + Addresses -> addressesH + +headerH :: Monad m => Page -> HtmlT m () +headerH p = sseH (navigationLink $ Just p) "header" ["wallet"] -headerH :: Text -> Page -> Monad m => HtmlT m () -headerH prefix p = +headerElementH :: Maybe Page -> WalletPresent -> Monad m => HtmlT m () +headerElementH p wp = navigationH - prefix - [ (is _Wallet p, walletPageLink, "Wallet") - , (is _Network p, networkPageLink, "Network") - , (is _Settings p, settingsPageLink, "Settings") - , (is _About p, aboutPageLink, "About") - ] + mempty + $ [(is' _Wallet, walletPageLink, "Wallet")] + <> [ (is' _Addresses, addressesPageLink, "Addresses") + | isPresent wp + ] + <> [ (is' _Network, networkPageLink, "Network") + , (is' _Settings, settingsPageLink, "Settings") + , (is' _About, aboutPageLink, "About") + ] + where + is' l = is (_Just . l) p 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 c5b980334e7..e040dbd06c9 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 @@ -14,9 +14,6 @@ import Cardano.Address.Derivation import Cardano.Wallet.Deposit.IO ( WalletPublicIdentity (..) ) -import Cardano.Wallet.Deposit.Read - ( Address - ) import Cardano.Wallet.Deposit.REST ( ErrDatabase ) @@ -29,10 +26,7 @@ import Cardano.Wallet.UI.Common.Html.Copy ) import Cardano.Wallet.UI.Common.Html.Htmx ( hxDelete_ - , hxPost_ , hxSwap_ - , hxTarget_ - , hxTrigger_ ) import Cardano.Wallet.UI.Common.Html.Lib ( dataBsDismiss_ @@ -54,17 +48,13 @@ import Cardano.Wallet.UI.Common.Html.Pages.Wallet , newWalletFromXPubH ) import Cardano.Wallet.UI.Deposit.API - ( customerAddressLink - , walletDeleteLink + ( walletDeleteLink , walletDeleteModalLink , walletLink , walletMnemonicLink , walletPostMnemonicLink , walletPostXPubLink ) -import Cardano.Wallet.UI.Lib.Address - ( encodeMainnetAddress - ) import Cardano.Wallet.UI.Type ( WHtml , WalletType (..) @@ -93,25 +83,14 @@ import Lucid , button_ , class_ , div_ - , h5_ , hr_ , id_ - , input_ - , min_ - , name_ , p_ , section_ - , type_ - , value_ - ) -import Lucid.Html5 - ( max_ - , step_ ) import qualified Data.ByteString.Char8 as B8 import qualified Data.ByteString.Lazy.Char8 as BL -import qualified Data.Text as T data WalletPresent = WalletPresent WalletPublicIdentity @@ -121,6 +100,10 @@ data WalletPresent | WalletInitializing | WalletClosing +isPresent :: WalletPresent -> Bool +isPresent = \case + WalletPresent _ -> True + _ -> False instance Show WalletPresent where show (WalletPresent x) = "WalletPresent: " <> show x show WalletAbsent = "WalletAbsent" @@ -135,24 +118,15 @@ walletH = sseH walletLink "wallet" ["wallet"] base64 :: ByteString -> ByteString base64 = convertToBase Base64 -customerAddressH :: Monad m => Address -> HtmlT m () -customerAddressH addr = div_ [class_ "d-flex justify-content-end"] $ do - div_ (copyableHidden "address") $ toHtml encodedAddr - div_ [class_ ""] $ toHtml addrShortened - div_ [class_ "ms-1"] $ 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_ "d-flex justify-content-end"] $ do div_ (copyableHidden "public_key") $ toHtml xpubByteString - div_ [class_ ""] $ toHtml $ headAndTail 4 $ B8.dropEnd 1 xpubByteString - div_ [class_ "ms-1"] - $ copyButton "public_key" + div_ [class_ "d-block d-lg-none"] + $ toHtml + $ headAndTail 5 + $ B8.dropEnd 1 xpubByteString + div_ [class_ "d-none d-lg-block"] $ toHtml xpubByteString + div_ [class_ "ms-1"] $ copyButton "public_key" where xpubByteString = base64 $ xpubToBytes xpub @@ -190,30 +164,11 @@ 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"] "Addresses" - div_ [class_ "col"] $ record $ do - simpleField "Customer Number" - $ input_ - [ type_ "number" - , hxTarget_ "#customer-address" - , class_ "form-control" - , 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"] "Details" div_ [class_ "col"] $ record $ do simpleField "Public Key" $ pubKeyH xpub simpleField "Tracked Addresses" $ toHtml $ toText customers div_ [class_ "row mt-5"] $ do - 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 2435dc5a11e..4b9a82af27c 100644 --- a/lib/ui/src/Cardano/Wallet/UI/Deposit/Server.hs +++ b/lib/ui/src/Cardano/Wallet/UI/Deposit/Server.hs @@ -84,20 +84,30 @@ import Cardano.Wallet.UI.Deposit.API ( UI , settingsSseToggleLink ) +import Cardano.Wallet.UI.Deposit.Handlers.Addresses + ( getAddresses + , getCustomerAddress + ) +import Cardano.Wallet.UI.Deposit.Handlers.Lib + ( walletPresence + ) import Cardano.Wallet.UI.Deposit.Handlers.Wallet ( deleteWalletHandler - , getCustomerAddress , getWallet , postMnemonicWallet , postXPubWallet ) +import Cardano.Wallet.UI.Deposit.Html.Pages.Addresses + ( addressElementH + , customerAddressH + ) import Cardano.Wallet.UI.Deposit.Html.Pages.Page ( Page (..) + , headerElementH , page ) import Cardano.Wallet.UI.Deposit.Html.Pages.Wallet - ( customerAddressH - , deleteWalletModalH + ( deleteWalletModalH , walletElementH ) import Control.Monad.Trans @@ -154,6 +164,7 @@ serveUI tr ul env dbDir config _ nl bs = :<|> ph Network :<|> ph Settings :<|> ph Wallet + :<|> ph Addresses :<|> sessioning (renderSmoothHtml . networkInfoH showTime <$> getNetworkInformation nid nl mode) :<|> wsl (\l -> getState l (renderSmoothHtml . settingsStateH settingsSseToggleLink)) :<|> wsl (\l -> toggleSSE l $> RawHtml "") @@ -166,7 +177,13 @@ serveUI tr ul env dbDir config _ nl bs = :<|> wsl (\l -> deleteWalletHandler l (deleteWallet dbDir) alert ok) :<|> wsl (\_l -> pure $ renderSmoothHtml deleteWalletModalH) :<|> (\c -> wsl (\l -> getCustomerAddress l (renderSmoothHtml . customerAddressH) alert c)) + :<|> wsl (\l -> getAddresses l (renderSmoothHtml . addressElementH alertH)) + :<|> serveNavigation -- (\l -> getAddresses l (renderSmoothHtml . headerElementH _ _ _)) where + serveNavigation mp = wsl $ \l -> do + wp <- walletPresence l + + pure $ renderSmoothHtml $ headerElementH mp wp ph p = wsl $ \_ -> pure $ page config p ok _ = renderHtml . rogerH @Text $ "ok" alert = renderHtml . alertH