-
Notifications
You must be signed in to change notification settings - Fork 214
Commit
This commit does not belong to any branch on this repository, and may belong to a fork outside of the repository.
Add partial payments page to deposit wallet UI
Just transaction definition component and base 58 transaction copy component
- Loading branch information
Showing
9 changed files
with
497 additions
and
2 deletions.
There are no files selected for viewing
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
Original file line number | Diff line number | Diff line change |
---|---|---|
@@ -0,0 +1,47 @@ | ||
{-# LANGUAGE GADTs #-} | ||
{-# LANGUAGE NamedFieldPuns #-} | ||
{-# LANGUAGE ScopedTypeVariables #-} | ||
{-# OPTIONS_GHC -Wno-orphans #-} | ||
{-# LANGUAGE FlexibleInstances #-} | ||
{-# LANGUAGE NumericUnderscores #-} | ||
|
||
module Cardano.Wallet.UI.Deposit.API.Payments | ||
( NewReceiver (..) | ||
, WithReceivers (..) | ||
) | ||
where | ||
|
||
import Prelude | ||
|
||
import Cardano.Wallet.UI.Deposit.Types.Payments | ||
( Receiver (..) | ||
) | ||
import Web.FormUrlEncoded | ||
( FromForm (..) | ||
, parseAll | ||
, parseUnique | ||
) | ||
|
||
data WithReceivers a | ||
= WithReceivers | ||
{ receivers :: [Receiver] | ||
, what :: a | ||
} | ||
|
||
newtype NewReceiver = NewReceiver (WithReceivers Receiver) | ||
|
||
instance FromForm NewReceiver where | ||
fromForm form = do | ||
WithReceivers receivers () <- fromForm form | ||
address <- parseUnique "new-receiver-address" form | ||
amountDouble :: Double <- parseUnique "new-receiver-amount" form | ||
let amount = round $ amountDouble * 1_000_000 | ||
pure | ||
$ NewReceiver | ||
$ WithReceivers{receivers, what = Receiver{address, amount}} | ||
|
||
instance FromForm (WithReceivers ()) where | ||
fromForm form = do | ||
receivers <- parseAll "receiver-defined" form | ||
pure | ||
$ WithReceivers{receivers, what = ()} |
65 changes: 65 additions & 0 deletions
65
lib/ui/src/Cardano/Wallet/UI/Deposit/Handlers/Payments/Transaction.hs
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
Original file line number | Diff line number | Diff line change |
---|---|---|
@@ -0,0 +1,65 @@ | ||
{-# LANGUAGE NamedFieldPuns #-} | ||
|
||
module Cardano.Wallet.UI.Deposit.Handlers.Payments.Transaction | ||
where | ||
|
||
import Prelude | ||
|
||
import Cardano.Read.Ledger.Tx.CBOR | ||
( serializeTx | ||
) | ||
import Cardano.Wallet.Deposit.REST | ||
( WalletResource | ||
, createPayment | ||
) | ||
import Cardano.Wallet.Read | ||
( Coin (..) | ||
, Value (..) | ||
) | ||
import Cardano.Wallet.UI.Common.Layer | ||
( SessionLayer | ||
) | ||
import Cardano.Wallet.UI.Deposit.Handlers.Lib | ||
( catchRunWalletResourceHtml | ||
) | ||
import Cardano.Wallet.UI.Deposit.Types.Payments | ||
( Receiver (..) | ||
) | ||
import Data.Text | ||
( Text | ||
) | ||
import Servant | ||
( Handler | ||
) | ||
|
||
import qualified Data.ByteString.Base58 as Base58 | ||
import qualified Data.ByteString.Lazy as BL | ||
import qualified Data.ByteString.Lazy.Char8 as BL8 | ||
import qualified Data.Text.Encoding as T | ||
|
||
createPaymentHandler | ||
:: SessionLayer WalletResource | ||
-> (BL.ByteString -> html) | ||
-- ^ Function to render the exception as HTML | ||
-> ([Receiver] -> Maybe Text -> html) | ||
-- ^ Function to render the transaction cbor | ||
-> [Receiver] | ||
-- ^ Current receivers | ||
-> Handler html | ||
createPaymentHandler layer alert render receivers = do | ||
catchRunWalletResourceHtml layer alert id $ do | ||
case receivers of | ||
[] -> pure $ render receivers Nothing | ||
_ -> do | ||
r <- createPayment $ do | ||
Receiver{address, amount} <- receivers | ||
pure (address, ValueC (CoinC $ fromIntegral amount) mempty) | ||
pure $ case r of | ||
Left e -> alert $ "Error: " <> BL8.pack (show e) | ||
Right tx -> | ||
render receivers | ||
$ Just | ||
$ T.decodeUtf8 | ||
$ Base58.encodeBase58 Base58.bitcoinAlphabet | ||
$ BL.toStrict | ||
$ serializeTx tx |
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
Oops, something went wrong.