Skip to content

Commit

Permalink
Factor out embedFile functions
Browse files Browse the repository at this point in the history
  • Loading branch information
paolino committed Jan 31, 2025
1 parent 13a411f commit 20188bc
Show file tree
Hide file tree
Showing 5 changed files with 42 additions and 44 deletions.
1 change: 1 addition & 0 deletions lib/ui/cardano-wallet-ui.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -114,6 +114,7 @@ library
Cardano.Wallet.UI.Shelley.Html.Pages.Wallets.NewWallet
Cardano.Wallet.UI.Shelley.Server
Cardano.Wallet.UI.Signal
Cardano.Wallet.UI.Static
Cardano.Wallet.UI.Type

other-modules: Paths_cardano_wallet_ui
Expand Down
22 changes: 5 additions & 17 deletions lib/ui/src/Cardano/Wallet/UI/Common/Handlers/Wallet.hs
Original file line number Diff line number Diff line change
@@ -1,5 +1,4 @@
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE TypeApplications #-}

module Cardano.Wallet.UI.Common.Handlers.Wallet
Expand All @@ -21,35 +20,24 @@ import Cardano.Wallet.Api.Types
import Control.Monad
( replicateM
)
import Data.ByteString
( ByteString
)
import Data.FileEmbed
( embedFile
, makeRelativeToProject
)
import Data.Text
( Text
)
import System.Random.Stateful
( randomRIO
)

import qualified Data.ByteString.Char8 as B8
import qualified Data.Text.Encoding as T
import Cardano.Wallet.UI.Static
( englishWords
)

pickMnemonic :: Int -> Maybe Bool -> IO (Maybe [Text])
pickMnemonic _n (Just True) = pure Nothing
pickMnemonic n _ = do
let wordsList :: ByteString
wordsList =
$(makeRelativeToProject "data/english.txt" >>= embedFile)
let dict = fmap T.decodeUtf8 . B8.words $ wordsList

let loop = do
xs <- replicateM n $ do
i <- randomRIO (0, length dict - 1)
pure $ dict !! i
i <- randomRIO (0, length englishWords - 1)
pure $ englishWords !! i
case mkSomeMnemonic @(AllowedMnemonics 'Shelley) xs of
Left _ -> loop
Right _ -> pure xs
Expand Down
17 changes: 4 additions & 13 deletions lib/ui/src/Cardano/Wallet/UI/Deposit/Server.hs
Original file line number Diff line number Diff line change
Expand Up @@ -3,7 +3,6 @@
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE TypeApplications #-}

module Cardano.Wallet.UI.Deposit.Server
Expand Down Expand Up @@ -129,13 +128,12 @@ import Cardano.Wallet.UI.Deposit.Server.Wallet
, serveWalletPage
, serveWalletStatus
)
import Cardano.Wallet.UI.Static
( favicon
)
import Control.Tracer
( Tracer (..)
)
import Data.FileEmbed
( embedFile
, makeRelativeToProject
)
import Data.Functor
( ($>)
)
Expand All @@ -152,7 +150,6 @@ import Servant.Types.SourceT
)

import qualified Cardano.Read.Ledger.Block.Block as Read
import qualified Data.ByteString.Lazy as BL

serveUI
:: forall n
Expand Down Expand Up @@ -181,7 +178,7 @@ serveUI wtc tr ul env dbDir config nid nl bs =
:<|> serveSSESettings ul
:<|> serveToggleSSE ul
:<|> serveSSE ul
:<|> serveFavicon
:<|> pure favicon
:<|> serveMnemonic
:<|> serveWalletPage ul
:<|> servePostMnemonicWallet wtc tr env dbDir ul
Expand Down Expand Up @@ -239,12 +236,6 @@ serveNavigation ul mp = withSessionLayer ul $ \l -> do
wp <- walletPresence l
pure $ renderSmoothHtml $ headerElementH mp wp

serveFavicon :: Handler BL.ByteString
serveFavicon =
pure
$ BL.fromStrict
$(makeRelativeToProject "data/images/icon.png" >>= embedFile)

serveNetworkInformation
:: forall n
. HasSNetworkId n
Expand Down
18 changes: 4 additions & 14 deletions lib/ui/src/Cardano/Wallet/UI/Shelley/Server.hs
Original file line number Diff line number Diff line change
Expand Up @@ -4,7 +4,6 @@
{-# LANGUAGE NoMonomorphismRestriction #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE TypeApplications #-}

module Cardano.Wallet.UI.Shelley.Server where
Expand Down Expand Up @@ -129,16 +128,15 @@ import Cardano.Wallet.UI.Shelley.Html.Pages.Wallet
import Cardano.Wallet.UI.Shelley.Html.Pages.Wallets
( walletListH
)
import Cardano.Wallet.UI.Static
( favicon
)
import Control.Lens
( view
)
import Control.Monad.Trans
( MonadIO (..)
)
import Data.FileEmbed
( embedFile
, makeRelativeToProject
)
import Data.Functor
( ($>)
)
Expand All @@ -159,8 +157,6 @@ import Servant
, (:<|>) (..)
)

import qualified Data.ByteString.Lazy as BL

pageHandler
:: UILayer (Maybe WalletId)
-> PageConfig
Expand Down Expand Up @@ -218,7 +214,7 @@ serveUI ul config _ alByron _alIcarus alShelley _alShared _spl _ntp bs =
:<|> wsl (\l -> toggleSSE l $> RawHtml "")
:<|> (\w -> wsl (\l -> selectWallet l w $> RawHtml ""))
:<|> withSessionLayerRead ul (sse . sseConfig)
:<|> serveFavicon
:<|> pure favicon
where
ph = pageHandler ul config
ok _ = renderHtml . rogerH @Text $ "ok"
Expand All @@ -229,9 +225,3 @@ serveUI ul config _ alByron _alIcarus alShelley _alShared _spl _ntp bs =
NodeSource{} -> Node
_ = networkInfoH
wsl = withSessionLayer ul

serveFavicon :: Handler BL.ByteString
serveFavicon =
pure
$ BL.fromStrict
$(makeRelativeToProject "data/images/icon.png" >>= embedFile)
28 changes: 28 additions & 0 deletions lib/ui/src/Cardano/Wallet/UI/Static.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,28 @@
{-# LANGUAGE TemplateHaskell #-}

module Cardano.Wallet.UI.Static
( favicon
, englishWords
)
where

import Prelude

import Data.FileEmbed
import Data.Text
( Text
)

import qualified Data.ByteString.Char8 as B8
import qualified Data.ByteString.Lazy as BL
import qualified Data.Text.Encoding as T

favicon :: BL.ByteString
favicon =
BL.fromStrict
$(makeRelativeToProject "data/images/icon.png" >>= embedFile)

englishWords :: [Text]
englishWords =
fmap T.decodeUtf8 . B8.words
$ $(makeRelativeToProject "data/english.txt" >>= embedFile)

0 comments on commit 20188bc

Please sign in to comment.