Skip to content

Commit

Permalink
Add customer transactions history page
Browse files Browse the repository at this point in the history
  • Loading branch information
paolino committed Sep 28, 2024
1 parent 87caa54 commit 12a998f
Show file tree
Hide file tree
Showing 9 changed files with 415 additions and 42 deletions.
3 changes: 3 additions & 0 deletions lib/ui/cardano-wallet-ui.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -61,10 +61,13 @@ library
Cardano.Wallet.UI.Deposit.API
Cardano.Wallet.UI.Deposit.Handlers.Addresses
Cardano.Wallet.UI.Deposit.Handlers.Lib
Cardano.Wallet.UI.Deposit.Handlers.Transactions
Cardano.Wallet.UI.Deposit.Handlers.Wallet
Cardano.Wallet.UI.Deposit.Html.Lib
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.Transactions
Cardano.Wallet.UI.Deposit.Html.Pages.Wallet
Cardano.Wallet.UI.Deposit.Server
Cardano.Wallet.UI.Lib.Address
Expand Down
Binary file added lib/ui/data/images/fake-data.png
Loading
Sorry, something went wrong. Reload?
Sorry, we cannot display this file.
Sorry, this file is invalid so it cannot be displayed.
24 changes: 23 additions & 1 deletion lib/ui/src/Cardano/Wallet/UI/Deposit/API.hs
Original file line number Diff line number Diff line change
Expand Up @@ -71,6 +71,7 @@ data Page
| Settings
| Wallet
| Addresses
| Transactions

makePrisms ''Page

Expand All @@ -80,13 +81,15 @@ instance ToHttpApiData Page where
toUrlPiece Settings = "settings"
toUrlPiece Wallet = "wallet"
toUrlPiece Addresses = "addresses"
toUrlPiece Transactions = "transactions"

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 "transactions" = Right Transactions
parseUrlPiece _ = Left "Invalid page"

-- | Pages endpoints
Expand All @@ -96,6 +99,7 @@ type Pages =
:<|> "settings" :> SessionedHtml Get
:<|> "wallet" :> SessionedHtml Get
:<|> "addresses" :> SessionedHtml Get
:<|> "transactions" :> SessionedHtml Get

-- | Data endpoints
type Data =
Expand All @@ -104,6 +108,9 @@ type Data =
:<|> "settings" :> "sse" :> "toggle" :> SessionedHtml Post
:<|> "sse" :> (CookieRequest :> SSE)
:<|> "favicon.ico" :> Get '[Image] BL.ByteString
:<|> "images"
:> "fake-data.png"
:> Get '[Image] BL.ByteString
:<|> "wallet"
:> "mnemonic"
:> QueryParam "clean" Bool
Expand All @@ -125,6 +132,12 @@ type Data =
:> SessionedHtml Post
:<|> "addresses" :> SessionedHtml Get
:<|> "navigation" :> QueryParam "page" Page :> SessionedHtml Get
:<|> "transactions" :> SessionedHtml Get
:<|> "customer"
:> "transactions"
:> "history"
:> ReqBody '[FormUrlEncoded] Customer
:> SessionedHtml Post

instance FromForm Customer where
fromForm form = fromIntegral @Int <$> parseUnique "customer" form
Expand All @@ -144,11 +157,13 @@ aboutPageLink :: Link
networkPageLink :: Link
settingsPageLink :: Link
addressesPageLink :: Link
transactionsPageLink :: Link
networkInfoLink :: Link
settingsGetLink :: Link
settingsSseToggleLink :: Link
sseLink :: Link
faviconLink :: Link
fakeDataBackgroundLink :: Link
walletMnemonicLink :: Maybe Bool -> Link
walletPageLink :: Link
walletLink :: Link
Expand All @@ -159,17 +174,21 @@ walletDeleteModalLink :: Link
customerAddressLink :: Link
addressesLink :: Link
navigationLink :: Maybe Page -> Link
transactionsLink :: Link
customerHistoryLink :: Link
homePageLink
:<|> aboutPageLink
:<|> networkPageLink
:<|> settingsPageLink
:<|> walletPageLink
:<|> addressesPageLink
:<|> transactionsPageLink
:<|> networkInfoLink
:<|> settingsGetLink
:<|> settingsSseToggleLink
:<|> sseLink
:<|> faviconLink
:<|> fakeDataBackgroundLink
:<|> walletMnemonicLink
:<|> walletLink
:<|> walletPostMnemonicLink
Expand All @@ -178,5 +197,8 @@ homePageLink
:<|> walletDeleteModalLink
:<|> customerAddressLink
:<|> addressesLink
:<|> navigationLink =
:<|> navigationLink
:<|> transactionsLink
:<|> customerHistoryLink
=
allLinks (Proxy @UI)
104 changes: 104 additions & 0 deletions lib/ui/src/Cardano/Wallet/UI/Deposit/Handlers/Transactions.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,104 @@
{-# LANGUAGE TupleSections #-}
module Cardano.Wallet.UI.Deposit.Handlers.Transactions
where

import Prelude

import Cardano.Wallet.Deposit.Pure
( Customer
, TxSummary (..)
, ValueTransfer (ValueTransfer)
)
import Cardano.Wallet.Deposit.REST
( WalletResource
)
import Cardano.Wallet.Read
( SlotNo (..)
, txIdFromHash
)
import Cardano.Wallet.Read.Hash
( hashFromStringAsHex
)
import Cardano.Wallet.UI.Common.Layer
( SessionLayer (..)
)
import Cardano.Wallet.UI.Deposit.Handlers.Lib
( catchRunWalletResourceHtml
)
import Control.Monad
( replicateM
)
import Data.Foldable
( toList
)
import Data.Function
( on
)
import Data.List
( sortBy
)
import Data.Maybe
( fromJust
)
import Servant
( Handler
)
import System.Random.Stateful
( UniformRange (..)
, mkStdGen
, runStateGen_
)

import qualified Cardano.Wallet.Deposit.REST as REST
import qualified Cardano.Wallet.Read as Read
import qualified Data.ByteString.Lazy.Char8 as BL

getCustomerHistory
:: SessionLayer WalletResource
-> (Bool -> [TxSummary] -> html)
-> (BL.ByteString -> html)
-> Customer
-> Handler html
getCustomerHistory layer render alert customer = do
catchRunWalletResourceHtml layer alert (uncurry render) $ do
fakeData customer . toList <$> REST.getCustomerHistory customer

-- fake data generation until DB is implemented

fakeData :: Customer -> [TxSummary] -> (Bool,[TxSummary])
fakeData c [] = (True, ) $
sortBy
(on compare $ \(TxSummaryC _ cp _) -> cp )
$ txSummaryG (fromIntegral c)
fakeData _c xs = (False, xs)

unsafeMkTxId :: String -> Read.TxId
unsafeMkTxId = txIdFromHash . fromJust . hashFromStringAsHex

hexOfInt :: Int -> Char
hexOfInt n = "0123456789abcdef" !! (n `mod` 16)

txSummaryG :: Int -> [TxSummary]
txSummaryG c = runStateGen_ pureGen $ \g -> do
ns <- uniformRM (1, 10) g
replicateM ns $ do
txId <- txIdR g
cp <- chainPointR g
spent <- Read.ValueC <$> uniformRM (0, 1000) g <*> pure mempty
received <- Read.ValueC <$> uniformRM (0, 1000) g <*> pure mempty
pure $ TxSummaryC txId cp $ ValueTransfer spent received
where
pureGen = mkStdGen c
txIdR g = do
ls <- replicateM 64 $ hexOfInt <$> uniformRM (0, 15) g
pure $ unsafeMkTxId ls
headerHash g = replicateM 64 $ hexOfInt <$> uniformRM (0, 15) g
chainPointR g = do
slot <- uniformRM (0, 100) g
case slot of
0 -> pure Read.GenesisPoint
_ -> do
r <- hashFromStringAsHex <$> headerHash g
case r of
Just h -> pure $ Read.BlockPoint (SlotNo slot) h
Nothing -> error "chainPointR: invalid hash"
66 changes: 66 additions & 0 deletions lib/ui/src/Cardano/Wallet/UI/Deposit/Html/Lib.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,66 @@
{-# LANGUAGE TypeApplications #-}

module Cardano.Wallet.UI.Deposit.Html.Lib
( imageOverlay
, overlayFakeDataH
, selectCustomerH
)
where

import Cardano.Wallet.UI.Common.Html.Htmx
import Cardano.Wallet.UI.Common.Html.Lib (linkText)
import Cardano.Wallet.UI.Common.Html.Pages.Lib (simpleField, AssocRow)
import Cardano.Wallet.UI.Deposit.API (fakeDataBackgroundLink)
import Data.Text.Class (ToText (..))
import Lucid
( HtmlT
, ToHtml (toHtml)
, class_
, div_
, img_
, input_
, max_
, min_
, name_
, size_
, src_
, step_
, style_
, type_
, value_
)
import Prelude
import Data.Text (Text)
import Servant (Link)
import Cardano.Wallet.UI.Lib.ListOf (ListOf)

imageOverlay :: Monad m => HtmlT m ()
imageOverlay =
style_ []
$ toHtml @String
".overlay-image { position: absolute; top: 0; left: 0; z-index: 10;\
\ width: 100%; opacity: 20%; }"

overlayFakeDataH :: Monad m => HtmlT m () -> HtmlT m ()
overlayFakeDataH x = div_ [style_ "position: relative;"] $ do
x
img_ [class_ "overlay-image", src_ $ linkText fakeDataBackgroundLink]

selectCustomerH :: Monad m => Text -> Link -> Int -> ListOf (AssocRow m)
selectCustomerH identifier link trackedUsers =
simpleField "Customer Number"
$ div_ [class_ "d-flex justify-content-end"]
$ input_
[ type_ "number"
, hxTarget_ identifier
, class_ "form-control"
, hxTrigger_ "load, change"
, hxPost_ $ linkText link
, min_ "0"
, max_ $ toText $ trackedUsers - 1
, step_ "1"
, name_ "customer"
, value_ "0"
, size_ "5"
, style_ "width: 7em"
]
43 changes: 6 additions & 37 deletions lib/ui/src/Cardano/Wallet/UI/Deposit/Html/Pages/Addresses.hs
Original file line number Diff line number Diff line change
Expand Up @@ -13,14 +13,8 @@ import Cardano.Wallet.Deposit.IO
import Cardano.Wallet.Deposit.Read
( Address
)
import Cardano.Wallet.UI.Common.Html.Htmx
( hxPost_
, hxTarget_
, hxTrigger_
)
import Cardano.Wallet.UI.Common.Html.Lib
( linkText
, truncatableText
( truncatableText
)
import Cardano.Wallet.UI.Common.Html.Pages.Lib
( record
Expand All @@ -41,29 +35,18 @@ import Cardano.Wallet.UI.Lib.Address
import Cardano.Wallet.UI.Type
( WHtml
)
import Data.Text.Class
( ToText (..)
)
import Lucid
( Html
, HtmlT
, ToHtml (..)
, class_
, div_
, id_
, input_
, min_
, name_
, style_
, type_
, value_
)
import Lucid.Html5
( max_
, size_
, step_
)

import Cardano.Wallet.UI.Deposit.Html.Lib
( selectCustomerH
)
import qualified Data.ByteString.Lazy.Char8 as BL

addressesH :: WHtml ()
Expand All @@ -80,22 +63,8 @@ addressElementH = onWalletPresentH $ \case
(WalletPublicIdentity _xpub customers) -> do
div_ [class_ "row mt-5"] $ do
div_ [class_ "col"] $ record (Just 11) $ do
simpleField "Customer Number"
$ div_ [class_ "d-flex justify-content-end"]
$ 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"
, size_ "5"
, style_ "width: 7em"
]
selectCustomerH "customer-address" customerAddressLink
$ fromIntegral customers
simpleField "Address"
$ div_
[ id_ "customer-address"
Expand Down
Loading

0 comments on commit 12a998f

Please sign in to comment.