Compare commits

..

No commits in common. "ff6168b45e4f030993be289088565e92cfca03e5" and "62b6ee3f32b7ce28b8bb3382f2996268858b3543" have entirely different histories.

11 changed files with 151 additions and 656 deletions

4
.gitignore vendored
View file

@ -5,7 +5,3 @@ zenith.db
zenith.log zenith.log
zenith.db-shm zenith.db-shm
zenith.db-wal zenith.db-wal
test.db
test.db-shm
test.db-wal

View file

@ -213,9 +213,7 @@ main = do
currencyCode <- require config "currencyCode" currencyCode <- require config "currencyCode"
dbFP <- getZenithPath dbFP <- getZenithPath
let dbFilePath = T.pack $ dbFP ++ dbFileName let dbFilePath = T.pack $ dbFP ++ dbFileName
let myConfig = let myConfig = Config dbFilePath
Config
dbFilePath
zebraHost zebraHost
zebraPort zebraPort
nodeUser nodeUser

View file

@ -38,15 +38,7 @@ main = do
currencyCode <- require config "currencyCode" currencyCode <- require config "currencyCode"
dbFP <- getZenithPath dbFP <- getZenithPath
let dbFilePath = T.pack $ dbFP ++ dbFileName let dbFilePath = T.pack $ dbFP ++ dbFileName
let myConfig = let myConfig = Config dbFilePath zebraHost zebraPort nodeUser nodePwd nodePort currencyCode
Config
dbFilePath
zebraHost
zebraPort
nodeUser
nodePwd
nodePort
currencyCode
let ctx = authenticate myConfig :. EmptyContext let ctx = authenticate myConfig :. EmptyContext
w <- try $ checkZebra zebraHost zebraPort :: IO (Either IOError ZebraGetInfo) w <- try $ checkZebra zebraHost zebraPort :: IO (Either IOError ZebraGetInfo)
case w of case w of

View file

@ -89,13 +89,7 @@ import Lens.Micro.Mtl
import Lens.Micro.TH import Lens.Micro.TH
import System.Hclip import System.Hclip
import Text.Printf import Text.Printf
import Text.Wrap import Text.Wrap (FillScope(..), FillStrategy(..), WrapSettings(..))
( FillScope(..)
, FillStrategy(..)
, WrapSettings(..)
, defaultWrapSettings
, wrapTextToLines
)
import ZcashHaskell.Keys (generateWalletSeedPhrase) import ZcashHaskell.Keys (generateWalletSeedPhrase)
import ZcashHaskell.Orchard import ZcashHaskell.Orchard
( getSaplingFromUA ( getSaplingFromUA
@ -127,12 +121,12 @@ import Zenith.Utils
( displayTaz ( displayTaz
, displayZec , displayZec
, getChainTip , getChainTip
, getZcashPrice
, isRecipientValid , isRecipientValid
, isRecipientValidGUI , isRecipientValidGUI
, jsonNumber , jsonNumber
, showAddress , showAddress
, validBarValue , validBarValue
, getZcashPrice
) )
data Name data Name
@ -188,13 +182,6 @@ newtype ShDshEntry = ShDshEntry
makeLenses ''ShDshEntry makeLenses ''ShDshEntry
data PaymentInput = PaymentInput
{ _pmtAmt :: !Scientific
, _pmtMemo :: !T.Text
} deriving (Show)
makeLenses ''PaymentInput
data DialogType data DialogType
= WName = WName
| AName | AName
@ -210,9 +197,6 @@ data DialogType
| DeshieldForm | DeshieldForm
| ShieldForm | ShieldForm
| ShowFIATBalance | ShowFIATBalance
| ViewingKeyMenu
| ViewingKeyShow
| PaymentURIShow
data DisplayType data DisplayType
= AddrDisplay = AddrDisplay
@ -266,30 +250,12 @@ data State = State
, _sBalance :: !Integer , _sBalance :: !Integer
, _currencyCode :: !T.Text , _currencyCode :: !T.Text
, _zprice :: !Double , _zprice :: !Double
, _vkName :: !T.Text }
, _vkData :: !T.Text
, _pmtURIForm :: !(Form PaymentInput () Name)
}
makeLenses ''State makeLenses ''State
zBalance :: State -> Double zBalance :: State -> Double
zBalance st = (fromIntegral (st ^. balance)) / 100000000 zBalance st = (fromIntegral (st ^. balance) ) / 100000000
-- Function to split text into fixed-size chunks
splitText :: Int -> T.Text -> [T.Text]
splitText chunkSize text =
let strippedText = T.filter (/= '\n') text -- Remove newlines
in if T.null strippedText
then []
else T.take chunkSize strippedText :
splitText chunkSize (T.drop chunkSize strippedText)
-- Create a widget to display the long text
renderLongText :: Int -> T.Text -> Widget Name
renderLongText lineLength longText =
let linesOfText = splitText lineLength longText
in vBox $ map txt linesOfText
drawUI :: State -> [Widget Name] drawUI :: State -> [Widget Name]
drawUI s = [splashDialog s, helpDialog s, displayDialog s, inputDialog s, ui s] drawUI s = [splashDialog s, helpDialog s, displayDialog s, inputDialog s, ui s]
@ -341,18 +307,13 @@ drawUI s = [splashDialog s, helpDialog s, displayDialog s, inputDialog s, ui s]
, capCommand "A" "ccounts" , capCommand "A" "ccounts"
, capCommand "V" "iew address" , capCommand "V" "iew address"
, capCommand "S" "end Tx" , capCommand "S" "end Tx"
, capCommand2 "Gen " "U" "RI" , capCommand3 "ba" "L" ("ance (" ++ ( T.unpack (st ^. currencyCode) )++ ")" )
, capCommand3
"ba"
"L"
("ance (" ++ (T.unpack (st ^. currencyCode)) ++ ")")
]) ])
, C.hCenter , C.hCenter
(hBox (hBox
[ capCommand2 "Address " "B" "ook" [ capCommand2 "Address " "B" "ook"
, capCommand2 "s" "H" "ield" , capCommand2 "s" "H" "ield"
, capCommand "D" "e-shield" , capCommand "D" "e-shield"
, capCommand2 "Viewing " "K" "eys"
, capCommand "Q" "uit" , capCommand "Q" "uit"
, capCommand "?" " Help" , capCommand "?" " Help"
, str $ show (st ^. timer) , str $ show (st ^. timer)
@ -423,9 +384,7 @@ drawUI s = [splashDialog s, helpDialog s, displayDialog s, inputDialog s, ui s]
else emptyWidget else emptyWidget
where where
keyList = keyList =
map map (C.hCenter . str) ["?", "Esc", "w", "a", "v", "s", "b", "d", "l", "q"]
(C.hCenter . str)
["?", "Esc", "w", "a", "v", "s", "u", "b", "d", "k", "l", "q"]
actionList = actionList =
map map
(hLimit 40 . str) (hLimit 40 . str)
@ -435,10 +394,8 @@ drawUI s = [splashDialog s, helpDialog s, displayDialog s, inputDialog s, ui s]
, "Switch accounts" , "Switch accounts"
, "View address" , "View address"
, "Send Tx" , "Send Tx"
, "Gen URI"
, "Address Book" , "Address Book"
, "Shield/De-Shield" , "Shield/De-Shield"
, "Viewing Keys"
, "Balance in Fiat" , "Balance in Fiat"
, "Quit" , "Quit"
] ]
@ -486,13 +443,6 @@ drawUI s = [splashDialog s, helpDialog s, displayDialog s, inputDialog s, ui s]
(renderForm (st ^. txForm) <=> (renderForm (st ^. txForm) <=>
C.hCenter C.hCenter
(hBox [capCommand "" "Send", capCommand "<esc> " "Cancel"])) (hBox [capCommand "" "Send", capCommand "<esc> " "Cancel"]))
PaymentURIShow ->
D.renderDialog
(D.dialog (Just (str " Create Payment URI ")) Nothing 50)
(renderForm (st ^. pmtURIForm) <=>
C.hCenter
(hBox
[capCommand "P" "rocess", capCommand3 " " "<esc> " "Cancel"]))
DeshieldForm -> DeshieldForm ->
D.renderDialog D.renderDialog
(D.dialog (Just (str " De-Shield ZEC ")) Nothing 50) (D.dialog (Just (str " De-Shield ZEC ")) Nothing 50)
@ -512,7 +462,7 @@ drawUI s = [splashDialog s, helpDialog s, displayDialog s, inputDialog s, ui s]
]) <=> ]) <=>
renderForm (st ^. deshieldForm) <=> renderForm (st ^. deshieldForm) <=>
C.hCenter C.hCenter
(hBox [capCommand "P" "roceed", capCommand3 "" "<esc> " "Cancel"])) (hBox [capCommand "P" "roceed", capCommand "<esc> " "Cancel"]))
ShieldForm -> ShieldForm ->
D.renderDialog D.renderDialog
(D.dialog (Just (str " Shield ZEC ")) Nothing 50) (D.dialog (Just (str " Shield ZEC ")) Nothing 50)
@ -523,26 +473,7 @@ drawUI s = [splashDialog s, helpDialog s, displayDialog s, inputDialog s, ui s]
then displayZec (st ^. tBalance) then displayZec (st ^. tBalance)
else displayTaz (st ^. tBalance) ++ "?") <=> else displayTaz (st ^. tBalance) ++ "?") <=>
C.hCenter C.hCenter
(hBox [capCommand "P" "roceed", capCommand3 "" "<esc> " "Cancel"])) (hBox [capCommand "P" "roceed", capCommand "<esc> " "Cancel"]))
ViewingKeyShow ->
D.renderDialog
(D.dialog
(Just (str (" " ++ (T.unpack (st ^. vkName)) ++ " Viewing Key ")))
Nothing
50)
(padAll 1 (C.hCenter (renderLongText 45 (st ^. vkData))) <=>
C.hCenter
(hBox
[capCommand "C" "opy to Clipoard", capCommand3 "" "E" "xit"]))
ViewingKeyMenu ->
D.renderDialog
(D.dialog (Just (str " Viewing Keys ")) Nothing 50)
(C.hCenter
(hBox
[ capCommand "F" "ull"
, capCommand "I" "ncoming"
, capCommand3 "" "E" "xit"
]))
Blank -> emptyWidget Blank -> emptyWidget
-- Address Book List -- Address Book List
AdrBook -> AdrBook ->
@ -598,36 +529,21 @@ drawUI s = [splashDialog s, helpDialog s, displayDialog s, inputDialog s, ui s]
-- Show Balance in FIAT form -- Show Balance in FIAT form
ShowFIATBalance -> ShowFIATBalance ->
D.renderDialog D.renderDialog
(D.dialog (D.dialog (Just $ str (" Account Balance (" ++ ( T.unpack (st ^. currencyCode)) ++ ") ") ) Nothing 60)
(Just $
str
(" Account Balance (" ++
(T.unpack (st ^. currencyCode)) ++ ") "))
Nothing
60)
(withAttr abDefAttr $ (withAttr abDefAttr $
setAvailableSize (50, 8) $ setAvailableSize (50, 8) $
viewport SFBViewPort BT.Vertical $ viewport SFBViewPort BT.Vertical $
vLimit 8 $ vLimit 8 $
hLimit 50 $ hLimit 50 $
vBox $ vBox $
[ vLimit 4 $ [
vLimit 4 $
hLimit 50 $ hLimit 50 $
vBox $ vBox $
[ C.hCenter (str $ " ") [ C.hCenter (str $ " ")
, C.hCenter , C.hCenter (str $ "1 ZEC = " ++ ( printf "%.2f" ( s ^. zprice ) ) ++ " " ++ (T.unpack ( s ^. currencyCode) ))
(str $
"1 ZEC = " ++
(printf "%.2f" (s ^. zprice)) ++
" " ++ (T.unpack (s ^. currencyCode)))
, C.hCenter (str $ " ") , C.hCenter (str $ " ")
, C.hCenter , C.hCenter ( str $ " Balance: " ++ ( printf "%.8f" $ zBalance s ) ++ " ZEC ==> " ++ ( printf "%.2f" (( s ^. zprice ) * (zBalance s) ) ++ " " ++ (T.unpack ( s ^. currencyCode) )) )
(str $
" Balance: " ++
(printf "%.8f" $ zBalance s) ++
" ZEC ==> " ++
(printf "%.2f" ((s ^. zprice) * (zBalance s)) ++
" " ++ (T.unpack (s ^. currencyCode))))
] ]
, padTop Max $ , padTop Max $
vLimit 4 $ vLimit 4 $
@ -651,7 +567,7 @@ drawUI s = [splashDialog s, helpDialog s, displayDialog s, inputDialog s, ui s]
(str (str
" _____ _ _ _ \n|__ /___ _ __ (_) |_| |__\n / // _ \\ '_ \\| | __| '_ \\\n / /| __/ | | | | |_| | | |\n/____\\___|_| |_|_|\\__|_| |_|") <=> " _____ _ _ _ \n|__ /___ _ __ (_) |_| |__\n / // _ \\ '_ \\| | __| '_ \\\n / /| __/ | | | | |_| | | |\n/____\\___|_| |_|_|\\__|_| |_|") <=>
C.hCenter C.hCenter
(withAttr titleAttr (str "Zcash Wallet v0.7.1.0-beta")) <=> (withAttr titleAttr (str "Zcash Wallet v0.7.0.0-beta")) <=>
C.hCenter (withAttr blinkAttr $ str "Press any key...")) C.hCenter (withAttr blinkAttr $ str "Press any key..."))
else emptyWidget else emptyWidget
capCommand3 :: String -> String -> String -> Widget Name capCommand3 :: String -> String -> String -> Widget Name
@ -830,19 +746,6 @@ mkSendForm bal =
label s w = label s w =
padBottom (Pad 1) $ vLimit 1 (hLimit 15 $ str s <+> fill ' ') <+> w padBottom (Pad 1) $ vLimit 1 (hLimit 15 $ str s <+> fill ' ') <+> w
mkPaymentURIForm :: Integer -> PaymentInput -> Form PaymentInput e Name
mkPaymentURIForm bal =
newForm
[ label "Amount: " @@=
editShowableFieldWithValidate pmtAmt AmtField (isAmountValid bal)
, label "Memo: " @@= editTextField pmtMemo MemoField (Just 1)
]
where
isAmountValid :: Integer -> Scientific -> Bool
isAmountValid b i = fromIntegral b >= (i * scientific 1 8)
label s w =
padBottom (Pad 1) $ vLimit 1 (hLimit 15 $ str s <+> fill ' ') <+> w
mkDeshieldForm :: Integer -> ShDshEntry -> Form ShDshEntry e Name mkDeshieldForm :: Integer -> ShDshEntry -> Form ShDshEntry e Name
mkDeshieldForm tbal = mkDeshieldForm tbal =
newForm newForm
@ -854,19 +757,7 @@ mkDeshieldForm tbal =
isAmountValid b i = fromIntegral b >= (i * scientific 1 8) isAmountValid b i = fromIntegral b >= (i * scientific 1 8)
label s w = label s w =
padBottom (Pad 1) $ vLimit 1 (hLimit 15 $ str s <+> fill ' ') <+> w padBottom (Pad 1) $ vLimit 1 (hLimit 15 $ str s <+> fill ' ') <+> w
{--
mkShieldForm :: Integer -> ShDshEntry -> Form ShDshEntry e Name
mkShieldForm bal =
newForm
[ label "Amount to Shield: " @@=
editShowableFieldWithValidate shAmt AmtField (isAmountValid bal)
]
where
isAmountValid :: Integer -> Scientific -> Bool
isAmountValid b i = (fromIntegral b / 100000000.0) >= i
label s w =
padBottom (Pad 1) $ vLimit 1 (hLimit 15 $ str s <+> fill ' ') <+> w
--}
mkNewABForm :: AdrBookEntry -> Form AdrBookEntry e Name mkNewABForm :: AdrBookEntry -> Form AdrBookEntry e Name
mkNewABForm = mkNewABForm =
newForm newForm
@ -1144,10 +1035,7 @@ appEvent (BT.AppEvent t) = do
AdrBookDelForm -> return () AdrBookDelForm -> return ()
DeshieldForm -> return () DeshieldForm -> return ()
ShieldForm -> return () ShieldForm -> return ()
ViewingKeyShow -> return () ShowFIATBalance -> return()
ViewingKeyMenu -> return ()
ShowFIATBalance -> return ()
PaymentURIShow -> return ()
Blank -> do Blank -> do
if s ^. timer == 90 if s ^. timer == 90
then do then do
@ -1738,58 +1626,12 @@ appEvent (BT.VtyEvent e) = do
BT.modify $ set zprice p BT.modify $ set zprice p
BT.modify $ set dialogBox ShowFIATBalance BT.modify $ set dialogBox ShowFIATBalance
Nothing -> do Nothing -> do
BT.modify $ BT.modify $ set msg ("CoinGecko is not responding!!!")
set msg ("CoinGecko is not responding!!!")
BT.modify $ set displayBox MsgDisplay BT.modify $ set displayBox MsgDisplay
-- Process any other event -- Process any other event
ev -> BT.zoom abAddresses $ L.handleListEvent ev ev -> BT.zoom abAddresses $ L.handleListEvent ev
-- --
-- Viewing Key Display Support
--
ViewingKeyShow -> do
case e of
V.EvKey (V.KChar 'c') [] -> do
liftIO $ setClipboard $ T.unpack $ s ^. vkData
BT.modify $
set msg $
(T.unpack (s ^. vkName)) ++
" viewing key copied to Clipboard!!"
BT.modify $ set displayBox MsgDisplay
V.EvKey (V.KChar 'e') [] -> do
BT.modify $ set vkName ""
BT.modify $ set vkData ""
BT.modify $ set dialogBox ViewingKeyMenu
ev -> return ()
--
ViewingKeyMenu -> do
case e of
V.EvKey (V.KChar 'f') [] -> do
BT.modify $ set vkName "Full"
BT.modify $
set
vkData
"VKFull->ztestsapling1tgjr4zppwk4ne8xy6gdq4z2gwq7dmf5jq8z2ctpn8nlmtse0a74fa5z0m8z383gmpgqz6q6duu4"
BT.modify $ set dialogBox ViewingKeyShow
V.EvKey (V.KChar 'i') [] -> do
BT.modify $ set vkName "Incomming"
BT.modify $
set
vkData
"VKIncoming->ztestsapling1tgjr4zppwk4ne8xy6gdq4z2gwq7dmf5jq8z2ctpn8nlmtse0a74fa5z0m8z383gmpgqz6q6duu4"
BT.modify $ set dialogBox ViewingKeyShow
V.EvKey (V.KChar 'e') [] ->
BT.modify $ set dialogBox Blank
ev -> return ()
--
-- Payment URI Form Events
--
PaymentURIShow -> do
case e of
V.EvKey V.KEsc [] -> BT.modify $ set dialogBox Blank
ev -> return ()
--
-- Process any other event -- Process any other event
--
Blank -> do Blank -> do
case e of case e of
V.EvKey (V.KChar '\t') [] -> focusRing %= F.focusNext V.EvKey (V.KChar '\t') [] -> focusRing %= F.focusNext
@ -1813,13 +1655,9 @@ appEvent (BT.VtyEvent e) = do
set txForm $ set txForm $
mkSendForm (s ^. balance) (SendInput "" 0.0 "" Full) mkSendForm (s ^. balance) (SendInput "" 0.0 "" Full)
BT.modify $ set dialogBox SendTx BT.modify $ set dialogBox SendTx
V.EvKey (V.KChar 'u') [] -> do
BT.modify $
set pmtURIForm $
mkPaymentURIForm (s ^. balance) (PaymentInput 0.0 "")
BT.modify $ set dialogBox PaymentURIShow
V.EvKey (V.KChar 'b') [] -> V.EvKey (V.KChar 'b') [] ->
BT.modify $ set dialogBox AdrBook BT.modify $ set dialogBox AdrBook
-- >>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>
V.EvKey (V.KChar 'l') [] -> do V.EvKey (V.KChar 'l') [] -> do
if s ^. network == MainNet if s ^. network == MainNet
then do then do
@ -1829,18 +1667,12 @@ appEvent (BT.VtyEvent e) = do
BT.modify $ set zprice p BT.modify $ set zprice p
BT.modify $ set dialogBox ShowFIATBalance BT.modify $ set dialogBox ShowFIATBalance
Nothing -> do Nothing -> do
BT.modify $ BT.modify $ set msg ("Currency not supported (" ++ T.unpack (s ^. currencyCode ) ++ ")!!!")
set
msg
("Currency not supported (" ++
T.unpack (s ^. currencyCode) ++ ")!!!")
BT.modify $ set displayBox MsgDisplay BT.modify $ set displayBox MsgDisplay
else do else do
BT.modify $ BT.modify $ set msg "Balance conversion not available for TestNet"
set
msg
"Balance conversion not available for TestNet"
BT.modify $ set displayBox MsgDisplay BT.modify $ set displayBox MsgDisplay
-- <<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<
V.EvKey (V.KChar 'd') [] -> do V.EvKey (V.KChar 'd') [] -> do
pool <- liftIO $ runNoLoggingT $ initPool $ s ^. dbPath pool <- liftIO $ runNoLoggingT $ initPool $ s ^. dbPath
selAcc <- selAcc <-
@ -1892,8 +1724,7 @@ appEvent (BT.VtyEvent e) = do
msg msg
"Not enough transparent funds in this account" "Not enough transparent funds in this account"
BT.modify $ set displayBox MsgDisplay BT.modify $ set displayBox MsgDisplay
V.EvKey (V.KChar 'k') [] -> do
BT.modify $ set dialogBox ViewingKeyMenu
ev -> ev ->
case r of case r of
Just AList -> Just AList ->
@ -2048,9 +1879,6 @@ runZenithTUI config = do
sBal sBal
currencyCode currencyCode
0 0
""
""
(mkPaymentURIForm 0 $ PaymentInput 0.0 "")
Left _e -> do Left _e -> do
print $ print $
"No Zebra node available on port " <> "No Zebra node available on port " <>

View file

@ -69,21 +69,21 @@ import Zenith.Types hiding (ZcashAddress(..))
import Zenith.Utils import Zenith.Utils
( displayAmount ( displayAmount
, getChainTip , getChainTip
, getZcashPrice
, isRecipientValidGUI , isRecipientValidGUI
, isValidString , isValidString
, isZecAddressValid , isZecAddressValid
, jsonNumber , jsonNumber
, padWithZero , padWithZero
, parseZcashPayment
, showAddress , showAddress
, validBarValue , validBarValue
, getZcashPrice
) )
data VkTypeDef data VkTypeDef
= VkNone = VkNone
| VkFull | VkFull
| VkIncoming | VkIncoming
| VkOutgoing
deriving (Eq, Show) deriving (Eq, Show)
data AppEvent data AppEvent
@ -163,11 +163,6 @@ data AppEvent
| ShowViewingKey !VkTypeDef !T.Text | ShowViewingKey !VkTypeDef !T.Text
| CopyViewingKey !T.Text !T.Text | CopyViewingKey !T.Text !T.Text
| CloseShowVK | CloseShowVK
| DisplayPaymentURI
| ClosePaymentURI
| DisplayPayUsingURI
| ClosePayUsingURI
| ProcIfValidURI
deriving (Eq, Show) deriving (Eq, Show)
data AppModel = AppModel data AppModel = AppModel
@ -234,9 +229,6 @@ data AppModel = AppModel
, _viewingKeyDisplay :: !Bool , _viewingKeyDisplay :: !Bool
, _vkTypeName :: !T.Text , _vkTypeName :: !T.Text
, _vkData :: !T.Text , _vkData :: !T.Text
, _paymentURIDisplay :: !Bool
, _usepmtURIOverlay :: !Bool
, _uriString :: !T.Text
} deriving (Eq, Show) } deriving (Eq, Show)
makeLenses ''AppModel makeLenses ''AppModel
@ -288,8 +280,6 @@ buildUI wenv model = widgetTree
model ^. model ^.
updateABAddress updateABAddress
, showVKOverlay `nodeVisible` model ^. viewingKeyDisplay , showVKOverlay `nodeVisible` model ^. viewingKeyDisplay
, paymentURIOverlay `nodeVisible` model ^. paymentURIDisplay
, pmtUsingURIOverlay `nodeVisible` model ^. usepmtURIOverlay
, shieldOverlay `nodeVisible` model ^. shieldZec , shieldOverlay `nodeVisible` model ^. shieldZec
, deShieldOverlay `nodeVisible` model ^. deShieldZec , deShieldOverlay `nodeVisible` model ^. deShieldZec
, msgAdrBookOverlay `nodeVisible` isJust (model ^. msgAB) , msgAdrBookOverlay `nodeVisible` isJust (model ^. msgAB)
@ -374,21 +364,10 @@ buildUI wenv model = widgetTree
, widgetIf (model ^. viewingKeyPopup) $ , widgetIf (model ^. viewingKeyPopup) $
remixIcon remixMenuFoldFill remixIcon remixMenuFoldFill
]) ])
, widgetIf (model ^. viewingKeyPopup) $ , widgetIf (model ^. viewingKeyPopup) $ animSlideIn viewingKeysBox
animSlideIn viewingKeysBox
]) `styleBasic` ]) `styleBasic`
[bgColor white, borderB 1 gray, padding 3] [bgColor white, borderB 1 gray, padding 3]
, box_ , box_ [alignLeft, onClick ShowFIATBalance] ( label ("Balance in " <> T.toUpper (c_currencyCode (model ^. configuration) ) ) ) `styleBasic`
[alignLeft, onClick ShowFIATBalance]
(label
("Balance in " <>
T.toUpper (c_currencyCode (model ^. configuration)))) `styleBasic`
[bgColor white, borderB 1 gray, padding 3]
, box_ [alignLeft, onClick DisplayPaymentURI] (label "Create URI") `styleBasic`
[bgColor white, borderB 1 gray, padding 3]
, box_
[alignLeft, onClick DisplayPayUsingURI]
(label "Pay using URI") `styleBasic`
[bgColor white, borderB 1 gray, padding 3] [bgColor white, borderB 1 gray, padding 3]
]) `styleBasic` ]) `styleBasic`
[bgColor btnColor, padding 3] [bgColor btnColor, padding 3]
@ -414,23 +393,17 @@ buildUI wenv model = widgetTree
[alignMiddle] [alignMiddle]
(vstack (vstack
[ box_ [ box_
[ alignLeft [alignLeft, onClick (ShowViewingKey VkFull "VKFull->ztestsapling1tgjr4zppwk4ne8xy6gdq4z2gwq7dmf5jq8z2ctpn8nlmtse0a74fa5z0m8z383gmpgqz6q6duu4")]
, onClick
(ShowViewingKey
VkFull
"VKFull->ztestsapling1tgjr4zppwk4ne8xy6gdq4z2gwq7dmf5jq8z2ctpn8nlmtse0a74fa5z0m8z383gmpgqz6q6duu4")
]
(hstack [label "Full VK", filler]) `styleBasic` (hstack [label "Full VK", filler]) `styleBasic`
[bgColor white, borderB 1 gray, padding 3] [bgColor white, borderB 1 gray, padding 3]
, box_ , box_
[ alignLeft [alignLeft, onClick $ (ShowViewingKey VkIncoming "VKIncoming->ztestsapling1tgjr4zppwk4ne8xy6gdq4z2gwq7dmf5jq8z2ctpn8nlmtse0a74fa5z0m8z383gmpgqz6q6duu4")]
, onClick $
(ShowViewingKey
VkIncoming
"VKIncoming->ztestsapling1tgjr4zppwk4ne8xy6gdq4z2gwq7dmf5jq8z2ctpn8nlmtse0a74fa5z0m8z383gmpgqz6q6duu4")
]
(hstack [label "Incoming VK", filler]) `styleBasic` (hstack [label "Incoming VK", filler]) `styleBasic`
[bgColor white, borderB 1 gray, padding 3] [bgColor white, borderB 1 gray, padding 3]
, box_
[alignLeft, onClick $ (ShowViewingKey VkOutgoing "VKOutgoing->ztestsapling1tgjr4zppwk4ne8xy6gdq4z2gwq7dmf5jq8z2ctpn8nlmtse0a74fa5z0m8z383gmpgqz6q6duu4")]
(hstack [label "Outgoing VK", filler]) `styleBasic`
[bgColor white, borderB 1 gray, padding 3]
]) ])
walletButton = walletButton =
hstack hstack
@ -1083,24 +1056,13 @@ buildUI wenv model = widgetTree
vstack vstack
[ box_ [ box_
[] []
(label (label ("Account Balance in " <> (T.toUpper (c_currencyCode (model ^. configuration))) ) `styleBasic`
("Account Balance in " <>
(T.toUpper (c_currencyCode (model ^. configuration)))) `styleBasic`
[textFont "Bold", textSize 12, textColor white]) `styleBasic` [textFont "Bold", textSize 12, textColor white]) `styleBasic`
[bgColor btnColor, radius 2, padding 3] [bgColor btnColor, radius 2, padding 3]
, filler , filler
, (label , (label ("1 ZEC = " <> ( T.pack (printf "%.2f" ( model ^. zPrice ))) <> " " <> (T.toUpper (c_currencyCode (model ^. configuration))) ) ) `styleBasic` []
("1 ZEC = " <>
(T.pack (printf "%.2f" (model ^. zPrice))) <>
" " <> (T.toUpper (c_currencyCode (model ^. configuration))))) `styleBasic`
[]
, filler , filler
, (label , (label ( ( T.pack (printf "%.8f" (model ^. aBal) ) <> " ZEC = " <> ( T.pack (printf "%.2f" (( model ^. zPrice )*( model ^. aBal ) ) ) ) <> " " <> (T.toUpper (c_currencyCode (model ^. configuration))) ) ) ) `styleBasic` []
((T.pack (printf "%.8f" (model ^. aBal)) <>
" ZEC = " <>
(T.pack (printf "%.2f" ((model ^. zPrice) * (model ^. aBal)))) <>
" " <> (T.toUpper (c_currencyCode (model ^. configuration)))))) `styleBasic`
[]
] ]
showVKOverlay = showVKOverlay =
alert CloseShowVK $ alert CloseShowVK $
@ -1111,13 +1073,11 @@ buildUI wenv model = widgetTree
[textFont "Bold", textColor white, textSize 12, padding 3]) `styleBasic` [textFont "Bold", textColor white, textSize 12, padding 3]) `styleBasic`
[bgColor btnColor, radius 2, padding 3] [bgColor btnColor, radius 2, padding 3]
, spacer , spacer
, hstack , hstack [filler, label_ (txtWrapN (model ^. vkData) 64) [multiline], filler]
[filler, label_ (txtWrapN (model ^. vkData) 64) [multiline], filler]
, spacer , spacer
, hstack , hstack
[ filler [ filler
, button "Copy to Clipboard" $ , button "Copy to Clipboard" $ CopyViewingKey (model ^. vkTypeName) (model ^. vkData)
CopyViewingKey (model ^. vkTypeName) (model ^. vkData)
, filler , filler
] ]
] ]
@ -1236,106 +1196,8 @@ buildUI wenv model = widgetTree
, filler , filler
]) `styleBasic` ]) `styleBasic`
[bgColor (white & L.a .~ 0.5)] [bgColor (white & L.a .~ 0.5)]
paymentURIOverlay =
box notImplemented = NotImplemented
(vstack
[ filler
, hstack
[ filler
, box_
[]
(vstack
[ box_
[alignMiddle]
(label "Create URI" `styleBasic`
[textColor white, textFont "Bold", textSize 12]) `styleBasic`
[bgColor btnColor]
, separatorLine `styleBasic` [fgColor btnColor]
, spacer
, hstack
[ label "Amount:" `styleBasic`
[width 50, textFont "Bold"]
, spacer
, numericField_
sendAmount
[ decimals 8
, minValue 0.0
, maxValue
(fromIntegral (model ^. balance) / 100000000.0)
, validInput amountValid
, onChange CheckAmount
] `styleBasic`
[ width 150
, styleIf
(not $ model ^. amountValid)
(textColor red)
]
]
, hstack
[ label "Memo:" `styleBasic`
[width 50, textFont "Bold"]
, spacer
, textArea sendMemo `styleBasic`
[width 150, height 40]
]
, spacer
, box_
[alignMiddle]
(hstack
[ spacer
, mainButton "Create URI" NotImplemented `nodeEnabled`
True
, spacer
, button "Cancel" ClosePaymentURI
, spacer
])
]) `styleBasic`
[radius 4, border 2 btnColor, bgColor white, padding 4]
, filler
]
, filler
]) `styleBasic`
[bgColor (white & L.a .~ 0.5)]
pmtUsingURIOverlay =
box
(vstack
[ filler
, hstack
[ filler
, box_
[]
(vstack
[ box_
[alignMiddle]
(label "Pay using URI" `styleBasic`
[textColor white, textFont "Bold", textSize 12]) `styleBasic`
[bgColor btnColor]
, separatorLine `styleBasic` [fgColor btnColor]
, spacer
, hstack
[ label "URI :" `styleBasic`
[width 30, textFont "Bold"]
, spacer
, textArea uriString `styleBasic`
[width 170, height 30]
]
, spacer
, box_
[alignMiddle]
(hstack
[ spacer
, button "Cancel" ClosePayUsingURI
, spacer
, mainButton "Process" ProcIfValidURI
, spacer
])
]) `styleBasic`
[radius 4, border 2 btnColor, bgColor white, padding 4]
, filler
]
, filler
]) `styleBasic`
[bgColor (white & L.a .~ 0.5)]
generateQRCodes :: Config -> IO () generateQRCodes :: Config -> IO ()
generateQRCodes config = do generateQRCodes config = do
@ -1458,13 +1320,11 @@ handleEvent wenv node model evt =
False False
] ]
ConfirmCancel -> [Model $ model & confirmTitle .~ Nothing & mainInput .~ ""] ConfirmCancel -> [Model $ model & confirmTitle .~ Nothing & mainInput .~ ""]
ViewingKeysClicked -> ViewingKeysClicked -> [Model $ model & viewingKeyPopup .~ not (model ^. viewingKeyPopup)]
[Model $ model & viewingKeyPopup .~ not (model ^. viewingKeyPopup)]
NewAddress vk -> NewAddress vk ->
[ Model $ [ Model $
model & confirmTitle ?~ "New Address" & confirmCancel .~ "Cancel" & model & confirmTitle ?~ "New Address" &
menuPopup .~ confirmCancel .~ "Cancel" & menuPopup .~ False
False
] ]
ShowSeed -> [Model $ model & showSeed .~ True & menuPopup .~ False] ShowSeed -> [Model $ model & showSeed .~ True & menuPopup .~ False]
ShowSend -> ShowSend ->
@ -1729,7 +1589,7 @@ handleEvent wenv node model evt =
CopyViewingKey t v -> CopyViewingKey t v ->
[ setClipboardData ClipboardEmpty [ setClipboardData ClipboardEmpty
, setClipboardData $ ClipboardText v , setClipboardData $ ClipboardText v
, Event $ ShowMessage (t <> " viewing key copied!!") , Event $ ShowMessage ( t <> " viewing key copied!!")
] ]
DeleteABEntry a -> DeleteABEntry a ->
[ Task $ deleteAdrBook (model ^. configuration) a [ Task $ deleteAdrBook (model ^. configuration) a
@ -1746,22 +1606,17 @@ handleEvent wenv node model evt =
model & msgAB ?~ "Function not implemented..." & menuPopup .~ False model & msgAB ?~ "Function not implemented..." & menuPopup .~ False
] ]
CloseMsgAB -> [Model $ model & msgAB .~ Nothing & inError .~ False] CloseMsgAB -> [Model $ model & msgAB .~ Nothing & inError .~ False]
CloseShowVK -> CloseShowVK -> [Model $ model & vkTypeName .~ "" & vkData .~ "" & viewingKeyDisplay .~ False]
[ Model $
model & vkTypeName .~ "" & vkData .~ "" & viewingKeyDisplay .~ False
]
-- --
-- Show Balance in FIAT -- Show Balance in FIAT
-- --
DisplayFIATBalance zpr abal -> DisplayFIATBalance zpr abal ->
[ Model $ [ Model $ model & zPrice .~ zpr & aBal .~ abal & displayFIATBalance .~ True & menuPopup .~ False
model & zPrice .~ zpr & aBal .~ abal & displayFIATBalance .~ True &
menuPopup .~
False
] ]
ShowFIATBalance -> ShowFIATBalance ->
if model ^. network == MainNet if model ^. network == MainNet
then [Task $ sfBalance (model ^. configuration)] then [ Task $ sfBalance (model ^. configuration)
]
else [ Model $ model & zPrice .~ 0.0 & aBal .~ 0.0 else [ Model $ model & zPrice .~ 0.0 & aBal .~ 0.0
, Event $ ShowError "Balance conversion not available for TestNet" , Event $ ShowError "Balance conversion not available for TestNet"
] ]
@ -1771,68 +1626,9 @@ handleEvent wenv node model evt =
-- --
ShowViewingKey vkType vkText -> ShowViewingKey vkType vkText ->
case vkType of case vkType of
VkFull -> VkFull -> [ Model $ model & vkTypeName .~ "Full" & vkData .~ vkText & viewingKeyDisplay .~ True & menuPopup .~ False]
[ Model $ VkIncoming -> [ Model $ model & vkTypeName .~ "Incoming" & vkData .~ vkText & viewingKeyDisplay .~ True & menuPopup .~ False]
model & vkTypeName .~ "Full" & vkData .~ vkText & viewingKeyDisplay .~ VkOutgoing -> [ Model $ model & vkTypeName .~ "Outgoing" & vkData .~ vkText & viewingKeyDisplay .~ True & menuPopup .~ False]
True &
menuPopup .~
False
]
VkIncoming ->
[ Model $
model & vkTypeName .~ "Incoming" & vkData .~ vkText &
viewingKeyDisplay .~
True &
menuPopup .~
False
]
--
-- Display PaymentURI Form
--
DisplayPaymentURI ->
[ Model $
model & paymentURIDisplay .~ True & uriString .~ "" & menuPopup .~ False
]
ClosePaymentURI -> [Model $ model & paymentURIDisplay .~ False]
--
-- Display Pay using URI Form
--
DisplayPayUsingURI ->
[Model $ model & usepmtURIOverlay .~ True & menuPopup .~ False]
ClosePayUsingURI -> [Model $ model & usepmtURIOverlay .~ False]
ProcIfValidURI -> do
let zp = parseZcashPayment $ T.unpack (model ^. uriString)
case zp of
Right p -> do
case uriAmount p of
Just a ->
[ Model $
model & usepmtURIOverlay .~ False & openSend .~ True &
privacyChoice .~
Full &
recipientValid .~
False &
sendRecipient .~
T.pack (uriAddress p) &
sendAmount .~
realToFrac a &
sendMemo .~
(uriMemo p)
, Event $ ClosePaymentURI
]
Nothing ->
[ Model $
model & usepmtURIOverlay .~ False & openSend .~ False &
uriString .~
""
, Event $ ShowError "Invalid URI"
]
Left e ->
[ Model $
model & usepmtURIOverlay .~ False & openSend .~ False & uriString .~
""
, Event $ ShowError "Invalid URI"
]
-- --
-- --
ShowShield -> ShowShield ->
@ -1847,8 +1643,7 @@ handleEvent wenv node model evt =
[ Task $ updAddrBookDescrip (model ^. configuration) d a [ Task $ updAddrBookDescrip (model ^. configuration) d a
, Model $ , Model $
model & abdescrip .~ "" & abaddress .~ "" & updateABAddress .~ False & model & abdescrip .~ "" & abaddress .~ "" & updateABAddress .~ False &
showABAddress .~ showABAddress .~ False
False
, Task $ do , Task $ do
dbPool <- runNoLoggingT $ initPool $ c_dbPath $ model ^. configuration dbPool <- runNoLoggingT $ initPool $ c_dbPath $ model ^. configuration
abList <- getAdrBook dbPool $ model ^. network abList <- getAdrBook dbPool $ model ^. network
@ -2001,16 +1796,9 @@ handleEvent wenv node model evt =
zpr <- liftIO $ getZcashPrice $ c_currencyCode config zpr <- liftIO $ getZcashPrice $ c_currencyCode config
case zpr of case zpr of
Just zp -> do Just zp -> do
let zbal = (dbal (model ^. balance)) / 100000000 let zbal = ( dbal (model ^. balance) ) / 100000000
return $ DisplayFIATBalance zp zbal return $ DisplayFIATBalance zp zbal
Nothing -> Nothing -> return $ ShowMessage ( "Currency not supported [" <> c_currencyCode config <> "]")
return $
ShowMessage
("Currency not supported [" <> c_currencyCode config <> "]")
--
procIfValidURI :: T.Text -> IO AppEvent
procIfValidURI ustr = do
return $ ShowSend
scanZebra :: scanZebra ::
T.Text T.Text
@ -2375,9 +2163,6 @@ runZenithGUI config = do
False False
"" ""
"" ""
False
False
""
startApp model handleEvent buildUI (params hD) startApp model handleEvent buildUI (params hD)
Left _e -> print "Zebra not available" Left _e -> print "Zebra not available"
where where

View file

@ -10,7 +10,6 @@ import Control.Monad.Logger
( NoLoggingT ( NoLoggingT
, logErrorN , logErrorN
, logInfoN , logInfoN
, runFileLoggingT
, runNoLoggingT , runNoLoggingT
, runStderrLoggingT , runStderrLoggingT
) )
@ -59,7 +58,6 @@ import Zenith.Types
, ZcashNetDB(..) , ZcashNetDB(..)
, ZenithStatus(..) , ZenithStatus(..)
) )
import Zenith.Types (Config(..), HexStringDB(..), ZcashNetDB(..))
import Zenith.Utils (jsonNumber) import Zenith.Utils (jsonNumber)
-- | Function to scan the Zcash blockchain through the Zebra node and populate the Zenith database -- | Function to scan the Zcash blockchain through the Zebra node and populate the Zenith database

View file

@ -508,12 +508,3 @@ encodeHexText' t =
if T.length t > 0 if T.length t > 0
then C.unpack . B64.encode $ E.encodeUtf8 t then C.unpack . B64.encode $ E.encodeUtf8 t
else C.unpack . B64.encode $ E.encodeUtf8 "Sent from Zenith" else C.unpack . B64.encode $ E.encodeUtf8 "Sent from Zenith"
-- | Define a data structure for the parsed components
data ZcashPaymentURI = ZcashPaymentURI
{ uriAddress :: String
, uriAmount :: Maybe Double
, uriMemo :: T.Text
, uriLabel :: Maybe String
, uriMessage :: Maybe String
} deriving (Show, Eq)

View file

@ -2,31 +2,25 @@
module Zenith.Utils where module Zenith.Utils where
import Control.Exception (SomeException, try)
import Control.Monad (when)
import Data.Aeson import Data.Aeson
import Data.Aeson.Types (parseMaybe)
import qualified Data.Aeson.Key as K import qualified Data.Aeson.Key as K
import qualified Data.Aeson.KeyMap as KM import qualified Data.Aeson.KeyMap as KM
import Data.Aeson.Types (parseMaybe)
import qualified Data.ByteString.Base64 as B64
import qualified Data.ByteString.Char8 as BC
import qualified Data.ByteString.Lazy as B
import qualified Data.ByteString.Lazy.Char8 as BL
import Data.Char (isAlphaNum, isSpace) import Data.Char (isAlphaNum, isSpace)
import Data.Functor (void) import Data.Functor (void)
import Data.Maybe import Data.Maybe
import Data.Ord (clamp) import Data.Ord (clamp)
import Data.Scientific (Scientific(..), scientific) import Data.Scientific (Scientific(..), scientific)
import Data.Scientific (Scientific, toRealFloat)
import qualified Data.Text as T import qualified Data.Text as T
import qualified Data.Text.Encoding as E import qualified Data.Text.Encoding as E
import qualified Data.Text.Encoding as TE import Control.Exception (try, SomeException)
import Network.HTTP.Simple import Control.Monad (when)
import qualified Data.ByteString.Lazy as B
import qualified Data.ByteString.Lazy.Char8 as BL
import System.Directory import System.Directory
import System.Process (createProcess_, shell) import System.Process (createProcess_, shell)
import Text.Printf (printf)
import Text.Read (readMaybe)
import Text.Regex.Posix import Text.Regex.Posix
import Text.Printf (printf)
import ZcashHaskell.Orchard import ZcashHaskell.Orchard
( encodeUnifiedAddress ( encodeUnifiedAddress
, isValidUnifiedAddress , isValidUnifiedAddress
@ -39,12 +33,10 @@ import ZcashHaskell.Transparent
) )
import ZcashHaskell.Types import ZcashHaskell.Types
( ExchangeAddress(..) ( ExchangeAddress(..)
, ExchangeAddress(..)
, SaplingAddress(..) , SaplingAddress(..)
, TransparentAddress(..) , TransparentAddress(..)
, UnifiedAddress(..) , UnifiedAddress(..)
, ValidAddress(..) , ValidAddress(..)
, ValidAddress(..)
, ZcashNet(..) , ZcashNet(..)
) )
import ZcashHaskell.Utils (makeZebraCall) import ZcashHaskell.Utils (makeZebraCall)
@ -53,9 +45,11 @@ import Zenith.Types
, PrivacyPolicy(..) , PrivacyPolicy(..)
, UnifiedAddressDB(..) , UnifiedAddressDB(..)
, ZcashAddress(..) , ZcashAddress(..)
, ZcashPaymentURI(..)
, ZcashPool(..) , ZcashPool(..)
) )
import Network.HTTP.Simple
import Data.Scientific (Scientific, toRealFloat)
-- | Helper function to convert numbers into JSON -- | Helper function to convert numbers into JSON
jsonNumber :: Int -> Value jsonNumber :: Int -> Value
@ -269,68 +263,17 @@ getChainTip zHost zPort = do
-- Function to fetch Zcash price from CoinGecko -- Function to fetch Zcash price from CoinGecko
getZcashPrice :: T.Text -> IO (Maybe Double) getZcashPrice :: T.Text -> IO (Maybe Double)
getZcashPrice currency = do getZcashPrice currency = do
let url = let url = "https://api.coingecko.com/api/v3/simple/price?ids=zcash&vs_currencies=" <> T.unpack currency
"https://api.coingecko.com/api/v3/simple/price?ids=zcash&vs_currencies=" <>
T.unpack currency
response <- httpJSONEither (parseRequest_ url) response <- httpJSONEither (parseRequest_ url)
case getResponseBody response of case getResponseBody response of
Right (Object obj) Right (Object obj) -> do
-- Extract "zcash" object -- Extract "zcash" object
-> do
case KM.lookup "zcash" obj of case KM.lookup "zcash" obj of
Just (Object zcashObj) Just (Object zcashObj) ->
-- Extract the currency price -- Extract the currency price
->
case KM.lookup (K.fromText (T.toLower currency)) zcashObj of case KM.lookup (K.fromText (T.toLower currency)) zcashObj of
Just (Number price) -> return (Just (toRealFloat price)) Just (Number price) -> return (Just (toRealFloat price))
_ -> return Nothing _ -> return Nothing
_ -> return Nothing _ -> return Nothing
_ -> return Nothing _ -> return Nothing
-- Parse memo result to convert it to a ByteString
processEither :: Either String BC.ByteString -> BC.ByteString
processEither (Right bs) = bs
processEither (Left e) = BC.pack e -- Returns the error message
-- Parse the query string into key-value pairs
parseQuery :: String -> [(String, String)]
parseQuery query = map (breakOn '=') (splitOn '&' query)
where
splitOn :: Char -> String -> [String]
splitOn _ [] = [""]
splitOn delim (c:cs)
| c == delim = "" : rest
| otherwise = (c : head rest) : tail rest
where
rest = splitOn delim cs
breakOn :: Char -> String -> (String, String)
breakOn delim str = (key, drop 1 value)
where
(key, value) = span (/= delim) str
-- Parse a ZIP-321 encoded string into a ZcashPayment structure
parseZcashPayment :: String -> Either String ZcashPaymentURI
parseZcashPayment input
| not (T.isPrefixOf "zcash:" (T.pack input)) = Left "Invalid scheme: must start with 'zcash:'"
| otherwise =
let (addrPart, queryPart) = break (== '?') (drop 6 input)
queryParams = parseQuery (drop 1 queryPart)
in Right ZcashPaymentURI
{ uriAddress = addrPart
, uriAmount = lookup "amount" queryParams >>= readMaybe
, uriMemo = case lookup "memo" queryParams of
Just m -> T.pack ( BC.unpack (processEither $ decodeBase64Unpadded (BC.pack m) ) )
_ -> ""
, uriLabel = lookup "label" queryParams
, uriMessage = lookup "message" queryParams
}
-- Function to pad a base64 string if it's not a multiple of 4
padBase64 :: BC.ByteString -> BC.ByteString
padBase64 bs = bs <> BC.replicate paddingLength '='
where
paddingLength = (4 - BC.length bs `mod` 4) `mod` 4
-- Function to decode a base64 un-padded string
decodeBase64Unpadded :: BC.ByteString -> Either String BC.ByteString
decodeBase64Unpadded = B64.decode . padBase64

View file

@ -58,16 +58,7 @@ main = do
zebraPort <- require config "zebraPort" zebraPort <- require config "zebraPort"
zebraHost <- require config "zebraHost" zebraHost <- require config "zebraHost"
nodePort <- require config "nodePort" nodePort <- require config "nodePort"
currencyCode <- require config "currencyCode" let myConfig = Config dbFilePath zebraHost zebraPort nodeUser nodePwd nodePort
let myConfig =
Config
dbFilePath
zebraHost
zebraPort
nodeUser
nodePwd
nodePort
currencyCode
hspec $ do hspec $ do
describe "RPC methods" $ do describe "RPC methods" $ do
beforeAll_ (startAPI myConfig) $ do beforeAll_ (startAPI myConfig) $ do

View file

@ -645,7 +645,8 @@ main = do
case ix of case ix of
Nothing -> assertFailure "couldn't find index at block" Nothing -> assertFailure "couldn't find index at block"
Just i -> do Just i -> do
updatedTree <- runNoLoggingT $ truncateTree oTree i updatedTree <-
runNoLoggingT $ truncateTree oTree i
let finalAnchor = let finalAnchor =
getOrchardTreeAnchor $ getOrchardTreeAnchor $
OrchardCommitmentTree $ ztiOrchard zebraTreesIn OrchardCommitmentTree $ ztiOrchard zebraTreesIn
@ -1110,31 +1111,3 @@ main = do
case price of case price of
Just p -> p `shouldNotBe` 0.0 Just p -> p `shouldNotBe` 0.0
Nothing -> assertFailure "Failed to get ZEC price" Nothing -> assertFailure "Failed to get ZEC price"
describe "Parse an URI payment string (all fields filled) " $ do
it ("Parsing URI -> " ++ "zcash:ztestsapling10yy2ex5....") $ do
let zcashURI2 =
"zcash:ztestsapling10yy2ex5dcqkclhc7z7yrnjq2z6feyjad56ptwlfgmy77dmaqqrl9gyhprdx59qgmsnyfska2kez?amount=100&memo=SGVsbG8sIFdvcmxkIQ==&message=Test"
case parseZcashPayment zcashURI2 of
Right p -> do
print p
(uriAmount p) `shouldBe` Just 100.0
Left e -> assertFailure $ "Error: " ++ e
describe
"Parse an URI payment string (just address and amount fields provided) " $ do
it ("Parsing URI -> " ++ "zcash:ztestsapling10yy2ex5....") $ do
let zcashURI3 =
"zcash:ztestsapling10yy2ex5dcqkclhc7z7yrnjq2z6feyjad56ptwlfgmy77dmaqqrl9gyhprdx59qgmsnyfska2kez?amount=100"
case parseZcashPayment zcashURI3 of
Right p -> do
print p
(uriAmount p) `shouldBe` Just 100.0
Left e -> assertFailure $ "Error: " ++ e
describe "Parse an URI payment string (invalid URI provided) " $ do
it ("Parsing URI -> " ++ "zcash:ztestsapling10yy2ex5....") $ do
let zcashURI3 =
"z:ztestsapling10yy2ex5dcqkclhc7z7yrnjq2z6feyjad56ptwlfgmy77dmaqqrl9gyhprdx59qgmsnyfska2kez?amount=100"
case parseZcashPayment zcashURI3 of
Right p -> do
print p
(uriAmount p) `shouldBe` Just 100.0
Left e -> assertFailure $ "Error: " ++ e

@ -1 +1 @@
Subproject commit cfa862ec9495e810e7296fa6fe724b46dbe0ee52 Subproject commit 7d3ae36d2b48b8ed91a70e40a77fb7efe57765a0