Skip to content

Commit

Permalink
Remove network page from deposit web UI (#4986)
Browse files Browse the repository at this point in the history
### Changes

- remove network page from deposit web UI

### Issues

fix #4963
  • Loading branch information
abailly authored Feb 19, 2025
2 parents 62d79d2 + 496a8b2 commit 45371a4
Show file tree
Hide file tree
Showing 4 changed files with 11 additions and 87 deletions.
18 changes: 2 additions & 16 deletions lib/exe/lib/Cardano/Wallet/Application.hs
Original file line number Diff line number Diff line change
Expand Up @@ -450,9 +450,6 @@ serveWallet
bootEnv
databaseDir'
socket
sNetwork
netLayer
blockchainSource
ContT $ \k ->
withAsync uiService $ \_ -> k ()
pure $ Just (databaseDir', resource)
Expand Down Expand Up @@ -649,25 +646,17 @@ serveWallet
socket
application
startDepositUiServer
:: forall n
. ( HasSNetworkId n
)
=> UILayer WalletResource
:: UILayer WalletResource
-> WalletBootEnv IO
-> FilePath
-> Socket
-> SNetworkId n
-> NetworkLayer IO (CardanoBlock StandardCrypto)
-> BlockchainSource
-> IO ()
startDepositUiServer
ui
bootEnv
databaseDir'
socket
_proxy
nl
bs = do
= do
let serverSettings = Warp.defaultSettings
api = Proxy @DepositUi.UI
application =
Expand All @@ -679,9 +668,6 @@ serveWallet
bootEnv
databaseDir'
(PageConfig "" "Deposit Cardano Wallet")
_proxy
nl
bs
start
serverSettings
apiServerTracer
Expand Down
11 changes: 1 addition & 10 deletions lib/ui/src/Cardano/Wallet/UI/Deposit/API.hs
Original file line number Diff line number Diff line change
Expand Up @@ -85,7 +85,6 @@ instance FromForm PostWalletViaXPub

data Page
= About
| Network
| Settings
| Wallet
| Addresses
Expand All @@ -96,7 +95,6 @@ makePrisms ''Page

instance ToHttpApiData Page where
toUrlPiece About = "about"
toUrlPiece Network = "network"
toUrlPiece Settings = "settings"
toUrlPiece Wallet = "wallet"
toUrlPiece Addresses = "addresses"
Expand All @@ -105,7 +103,6 @@ instance ToHttpApiData Page where

instance FromHttpApiData Page where
parseUrlPiece "about" = Right About
parseUrlPiece "network" = Right Network
parseUrlPiece "settings" = Right Settings
parseUrlPiece "wallet" = Right Wallet
parseUrlPiece "addresses" = Right Addresses
Expand All @@ -116,7 +113,6 @@ instance FromHttpApiData Page where
-- | Pages endpoints
type Pages =
"about" :> SessionedHtml Get
:<|> "network" :> SessionedHtml Get
:<|> "settings" :> SessionedHtml Get
:<|> "wallet" :> SessionedHtml Get
:<|> "addresses" :> SessionedHtml Get
Expand All @@ -125,8 +121,7 @@ type Pages =

-- | Data endpoints
type Data =
"network" :> "info" :> SessionedHtml Get
:<|> "settings" :> SessionedHtml Get
"settings" :> SessionedHtml Get
:<|> "settings" :> "sse" :> "toggle" :> SessionedHtml Post
:<|> "sse" :> (CookieRequest :> SSE)
:<|> "favicon.ico" :> Get '[Image] BL.ByteString
Expand Down Expand Up @@ -260,13 +255,11 @@ type UI =

homePageLink :: Link
aboutPageLink :: Link
networkPageLink :: Link
settingsPageLink :: Link
walletPageLink :: Link
addressesPageLink :: Link
depositPageLink :: Link
paymentsPageLink :: Link
networkInfoLink :: Link
settingsGetLink :: Link
settingsSseToggleLink :: Link
sseLink :: Link
Expand Down Expand Up @@ -306,13 +299,11 @@ paymentsResetLink :: Link
walletStatusLink :: Link
homePageLink
:<|> aboutPageLink
:<|> networkPageLink
:<|> settingsPageLink
:<|> walletPageLink
:<|> addressesPageLink
:<|> depositPageLink
:<|> paymentsPageLink
:<|> networkInfoLink
:<|> settingsGetLink
:<|> settingsSseToggleLink
:<|> sseLink
Expand Down
10 changes: 1 addition & 9 deletions lib/ui/src/Cardano/Wallet/UI/Deposit/Html/Pages/Page.hs
Original file line number Diff line number Diff line change
Expand Up @@ -23,9 +23,6 @@ import Cardano.Wallet.UI.Common.Html.Modal
import Cardano.Wallet.UI.Common.Html.Pages.Lib
( sseH
)
import Cardano.Wallet.UI.Common.Html.Pages.Network
( networkH
)
import Cardano.Wallet.UI.Common.Html.Pages.Settings
( settingsPageH
)
Expand All @@ -44,7 +41,6 @@ import Cardano.Wallet.UI.Deposit.API
, _About
, _Addresses
, _Deposits
, _Network
, _Payments
, _Settings
, _Wallet
Expand All @@ -54,8 +50,6 @@ import Cardano.Wallet.UI.Deposit.API
, depositsLink
, faviconLink
, navigationLink
, networkInfoLink
, networkPageLink
, paymentsLink
, paymentsPageLink
, settingsGetLink
Expand Down Expand Up @@ -112,7 +106,6 @@ page c p = RawHtml
imageOverlay
case p of
About -> aboutH
Network -> networkH networkInfoLink
Settings -> settingsPageH settingsGetLink
Wallet -> walletH
Addresses -> addressesH
Expand All @@ -136,8 +129,7 @@ headerElementH p wp =
<> [ (is' _Payments, paymentsPageLink, "Payments")
| isPresent wp
]
<> [ (is' _Network, networkPageLink, "Network")
, (is' _Settings, settingsPageLink, "Settings")
<> [ (is' _Settings, settingsPageLink, "Settings")
, (is' _About, aboutPageLink, "About")
]
where
Expand Down
59 changes: 7 additions & 52 deletions lib/ui/src/Cardano/Wallet/UI/Deposit/Server.hs
Original file line number Diff line number Diff line change
Expand Up @@ -3,37 +3,19 @@
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeApplications #-}

module Cardano.Wallet.UI.Deposit.Server
( serveUI
) where

import Prelude

import Cardano.Wallet.Api.Http.Server.Handlers.NetworkInformation
( getNetworkInformation
)
import Cardano.Wallet.Api.Types
( ApiWalletMode (..)
)
import Cardano.Wallet.Deposit.IO
( WalletBootEnv (networkEnv)
)
import Cardano.Wallet.Deposit.REST
( WalletResource
)
import Cardano.Wallet.Network
( NetworkLayer
)
import Cardano.Wallet.Primitive.NetworkId
( HasSNetworkId (..)
, SNetworkId
, networkIdVal
)
import Cardano.Wallet.Shelley.BlockchainSource
( BlockchainSource (..)
)
import Cardano.Wallet.UI.Common.Handlers.Session
( withSessionLayer
, withSessionLayerRead
Expand All @@ -51,9 +33,6 @@ import Cardano.Wallet.UI.Common.Handlers.State
import Cardano.Wallet.UI.Common.Html.Html
( RawHtml (..)
)
import Cardano.Wallet.UI.Common.Html.Pages.Network
( networkInfoH
)
import Cardano.Wallet.UI.Common.Html.Pages.Settings
( settingsStateH
)
Expand All @@ -67,7 +46,6 @@ import Cardano.Wallet.UI.Common.Layer
import Cardano.Wallet.UI.Cookies
( CookieResponse
, RequestCookies
, sessioning
)
import Cardano.Wallet.UI.Deposit.API
( UI
Expand All @@ -78,7 +56,6 @@ import Cardano.Wallet.UI.Deposit.Handlers.Lib
)
import Cardano.Wallet.UI.Deposit.Html.Common
( modalElementH
, showTimeSecs
)
import Cardano.Wallet.UI.Deposit.Html.Pages.Page
( Page (..)
Expand Down Expand Up @@ -149,32 +126,28 @@ import Servant.Types.SourceT
( SourceT
)

import qualified Cardano.Read.Ledger.Block.Block as Read

serveUI
:: forall n
. HasSNetworkId n
=> Tracer IO ()
:: Tracer IO ()
-- ^ Tracer for wallet tip changes
-> Tracer IO String
-- ^ Tracer for logging
-> UILayer WalletResource
-- ^ UI layer
-> WalletBootEnv IO
-- ^ Wallet boot environment
-> FilePath
-- ^ Database directory
-> PageConfig
-> SNetworkId n
-> NetworkLayer IO Read.ConsensusBlock
-> BlockchainSource
-- ^ Page configuration
-> Server UI
serveUI wtc tr ul env dbDir config nid nl bs =
serveUI wtc tr ul env dbDir config =
serveTabPage ul config Wallet
:<|> serveTabPage ul config About
:<|> serveTabPage ul config Network
:<|> serveTabPage ul config Settings
:<|> serveTabPage ul config Wallet
:<|> serveTabPage ul config Addresses
:<|> serveTabPage ul config Deposits
:<|> serveTabPage ul config Payments
:<|> serveNetworkInformation nid nl bs
:<|> serveSSESettings ul
:<|> serveToggleSSE ul
:<|> serveSSE ul
Expand Down Expand Up @@ -236,24 +209,6 @@ serveNavigation ul mp = withSessionLayer ul $ \l -> do
wp <- walletPresence l
pure $ renderSmoothHtml $ headerElementH mp wp

serveNetworkInformation
:: forall n
. HasSNetworkId n
=> SNetworkId n
-> NetworkLayer IO Read.ConsensusBlock
-> BlockchainSource
-> Maybe RequestCookies
-> Handler (CookieResponse RawHtml)
serveNetworkInformation _ nl bs =
sessioning
$ renderSmoothHtml . networkInfoH showTimeSecs
<$> getNetworkInformation nid nl mode
where
nid = networkIdVal (sNetworkId @n)
mode = case bs of
NodeSource{} -> Node
_ = networkInfoH

serveSSESettings
:: UILayer WalletResource
-> Maybe RequestCookies
Expand Down

0 comments on commit 45371a4

Please sign in to comment.