Skip to content

Commit

Permalink
Add smooth UI data swapping
Browse files Browse the repository at this point in the history
  • Loading branch information
paolino committed Sep 23, 2024
1 parent 0743527 commit e37ea43
Show file tree
Hide file tree
Showing 3 changed files with 25 additions and 7 deletions.
8 changes: 8 additions & 0 deletions lib/ui/src/Cardano/Wallet/UI/Common/Html/Pages/Lib.hs
Original file line number Diff line number Diff line change
Expand Up @@ -23,6 +23,7 @@ module Cardano.Wallet.UI.Common.Html.Pages.Lib
, showAdaOfLoveLace
, showThousandDots
, copyButton
, fadeInId
)
where

Expand Down Expand Up @@ -65,6 +66,7 @@ import Lucid
, role_
, scope_
, script_
, style_
, table_
, td_
, tr_
Expand Down Expand Up @@ -139,6 +141,11 @@ fieldHtml as = field as . toHtml
fieldShow :: (Show a, Monad m) => [Attribute] -> Text -> a -> ListOf (AssocRow m)
fieldShow attrs key val = field attrs (toHtml key) (toHtml $ show val)

fadeInId :: Monad m => HtmlT m ()
fadeInId = style_ [] $ toHtml @Text
".smooth.htmx-added { transition: opacity: 0.1s ease-in; opacity: 0} \
\.smooth { opacity: 1; transition: opacity 0.1s ease-out; }"

-- | A tag that can self populate with data that is fetched as GET from a link
-- whenever some specific events are received from an SSE endpoint.
-- It also self populate on load.
Expand All @@ -163,6 +170,7 @@ sseH link target events = do
[ id_ target
, hxGet_ $ linkText link
, hxTrigger_ "load"
, class_ "smooth"
]
""
where
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -16,6 +16,9 @@ import Cardano.Wallet.UI.Common.Html.Htmx
import Cardano.Wallet.UI.Common.Html.Lib
( linkText
)
import Cardano.Wallet.UI.Common.Html.Pages.Lib
( fadeInId
)
import Data.Text
( Text
)
Expand Down Expand Up @@ -109,7 +112,9 @@ pageFromBodyH faviconLink PageConfig{..} body =
favicon faviconLink
useHtmxVersion (1, 9, 12)
useHtmxExtension "json-enc"
body_ body
body_ $ do
fadeInId
body

data PageConfig = PageConfig
{ prefix :: Text
Expand Down
17 changes: 11 additions & 6 deletions lib/ui/src/Cardano/Wallet/UI/Deposit/Server.hs
Original file line number Diff line number Diff line change
Expand Up @@ -117,6 +117,10 @@ import Data.Time
, defaultTimeLocale
, formatTime
)
import Lucid
( class_
, div_
)
import Paths_cardano_wallet_ui
( getDataFileName
)
Expand Down Expand Up @@ -150,18 +154,18 @@ serveUI tr ul env dbDir config _ nl bs =
:<|> ph Network
:<|> ph Settings
:<|> ph Wallet
:<|> sessioning (renderHtml . networkInfoH showTime <$> getNetworkInformation nid nl mode)
:<|> wsl (\l -> getState l (renderHtml . settingsStateH settingsSseToggleLink))
:<|> sessioning (renderSmoothHtml . networkInfoH showTime <$> getNetworkInformation nid nl mode)
:<|> wsl (\l -> getState l (renderSmoothHtml . settingsStateH settingsSseToggleLink))
:<|> wsl (\l -> toggleSSE l $> RawHtml "")
:<|> withSessionLayerRead ul (sse . sseConfig)
:<|> serveFavicon
:<|> (\c -> sessioning $ renderHtml . mnemonicH <$> liftIO (pickMnemonic 15 c))
:<|> wsl (\l -> getWallet l (renderHtml . walletElementH alertH))
:<|> (\c -> sessioning $ renderSmoothHtml . mnemonicH <$> liftIO (pickMnemonic 15 c))
:<|> wsl (\l -> getWallet l (renderSmoothHtml . walletElementH alertH))
:<|> (\v -> wsl (\l -> postMnemonicWallet l initWallet alert ok v))
:<|> (\v -> wsl (\l -> postXPubWallet l initWallet 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))
:<|> wsl (\_l -> pure $ renderSmoothHtml deleteWalletModalH)
:<|> (\c -> wsl (\l -> getCustomerAddress l (renderSmoothHtml . customerAddressH) alert c))
where
ph p = wsl $ \_ -> pure $ page config p
ok _ = renderHtml . rogerH @Text $ "ok"
Expand All @@ -172,6 +176,7 @@ serveUI tr ul env dbDir config _ nl bs =
_ = networkInfoH
wsl f = withSessionLayer ul $ \l -> f l
initWallet = initXPubWallet tr env dbDir
renderSmoothHtml response = renderHtml $ div_ [class_ "smooth"] response

serveFavicon :: Handler BL.ByteString
serveFavicon = do
Expand Down

0 comments on commit e37ea43

Please sign in to comment.