docs: prepare for release

This commit is contained in:
Rene Vergara 2025-02-28 12:59:41 -06:00
parent 2a3bdf0f65
commit 15cf671523
Signed by: pitmutt
SSH key fingerprint: SHA256:vNa8FIqbBZjV9hOCkXyOzd7gqWCMCfkcfiPH2zaGfQ0
6 changed files with 247 additions and 196 deletions

2
.gitmodules vendored
View file

@ -1,4 +1,4 @@
[submodule "zcash-haskell"]
path = zcash-haskell
url = https://code.vergara.tech/Vergara_Tech/zcash-haskell
branch = rav001
branch = master

View file

@ -5,7 +5,7 @@ All notable changes to this project will be documented in this file.
The format is based on [Keep a Changelog](https://keepachangelog.com/en/1.0.0/),
and this project adheres to [Semantic Versioning](https://semver.org/spec/v2.0.0.html).
## [Unreleased]
## [0.9.0.0-beta]
### Added

View file

@ -105,13 +105,14 @@ import ZcashHaskell.Orchard
, parseAddress
)
import ZcashHaskell.Transparent (encodeTransparentReceiver)
import ZcashHaskell.Types
import ZcashHaskell.Types
import ZcashHaskell.Utils (makeZebraCall)
import Zenith.Core
import Zenith.DB
import Zenith.Scanner (checkIntegrity, processTx, rescanZebra, updateConfs)
import Zenith.Types
( Config(..)
( AccountType(..)
, Config(..)
, HexStringDB(..)
, OrchardSpendingKeyDB(..)
, PhraseDB(..)
@ -126,9 +127,8 @@ import Zenith.Types
, ZcashPool(..)
, ZenithStatus(..)
, ZenithUuid(..)
, getFvk
, getFvk
, getIvk
, AccountType(..)
)
import Zenith.Utils
( createZip321
@ -136,15 +136,15 @@ import Zenith.Utils
, displayZec
, getChainTip
, getZcashPrice
, isNotEmptyAfterTrim
, isRecipientValid
, isRecipientValidGUI
, jsonNumber
, parseZcashPayment
, showAddress
, validBarValue
, isNotEmptyAfterTrim
, scientificToInt
, showAddress
, toPhrase
, validBarValue
)
data Name
@ -231,7 +231,7 @@ data IViewingKey = IViewingKey
makeLenses ''IViewingKey
data ISeedPhrase = ISeedPhrase
data ISeedPhrase = ISeedPhrase
{ _iSpName :: !T.Text
, _iSpString :: !T.Text
, _iSpBHeight :: !Scientific
@ -273,7 +273,6 @@ data DisplayType
| SendDisplay
| AdrBookEntryDisplay
| BlankDisplay
| MsgDisplayWKey
data Tick
= TickVal !Float
@ -321,7 +320,7 @@ data State = State
, _pmtURIForm :: !(Form PaymentInput () Name)
, _payUsingURIForm :: !(Form URIText () Name)
, _importVKForm :: !(Form IViewingKey () Name)
, _importSeedPhraseForm :: !(Form ISeedPhrase() Name)
, _importSeedPhraseForm :: !(Form ISeedPhrase () Name)
}
makeLenses ''State
@ -363,8 +362,8 @@ drawUI s = [splashDialog s, helpDialog s, displayDialog s, inputDialog s, ui s]
(maybe
"(None)"
(\(_, w) -> zcashWalletName $ entityVal w)
(L.listSelectedElement (st ^. wallets))) ++
(isReadOnlyWallet $ L.listSelectedElement (st ^. wallets))))
(L.listSelectedElement (st ^. wallets))) ++
(isReadOnlyWallet $ L.listSelectedElement (st ^. wallets))))
(C.hCenter
(str
("Account: " ++
@ -376,27 +375,27 @@ drawUI s = [splashDialog s, helpDialog s, displayDialog s, inputDialog s, ui s]
C.hCenter
(str
("Balance: " ++
if st ^. network == MainNet
then do
if (walletHasBalance $ L.listSelectedElement (st ^. accounts))
then displayZec (st ^. balance)
else "N/A"
else do
if (walletHasBalance $ L.listSelectedElement (st ^. accounts))
then displayTaz (st ^. balance)
else "N/A" )) <=>
if st ^. network == MainNet
then do
if (walletHasBalance $ L.listSelectedElement (st ^. accounts))
then displayZec (st ^. balance)
else "N/A"
else do
if (walletHasBalance $ L.listSelectedElement (st ^. accounts))
then displayTaz (st ^. balance)
else "N/A")) <=>
C.hCenter
(str
("Unconf: " ++
if st ^. network == MainNet
then do
if (walletHasBalance $ L.listSelectedElement (st ^. accounts))
then displayZec (st ^. unconfBalance)
else "N/A"
else do
if (walletHasBalance $ L.listSelectedElement (st ^. accounts))
then displayTaz (st ^. unconfBalance)
else "N/A" )) <=>
then do
if (walletHasBalance $ L.listSelectedElement (st ^. accounts))
then displayZec (st ^. unconfBalance)
else "N/A"
else do
if (walletHasBalance $ L.listSelectedElement (st ^. accounts))
then displayTaz (st ^. unconfBalance)
else "N/A")) <=>
listAddressBox " Addresses " (st ^. addresses) <+>
B.vBorder <+>
(C.hCenter
@ -536,11 +535,10 @@ drawUI s = [splashDialog s, helpDialog s, displayDialog s, inputDialog s, ui s]
vBox
[ C.hCenter
(capCommand "N" "ew" <+>
capCommand "S" "how phrase" <+>
capCommand3 "" "I" "mport VK" )
, C.hCenter
(capCommand3 "Import Seed " "P" "hrase")
, C.hCenter (str " ")
capCommand "S" "how phrase" <+>
capCommand3 "" "I" "mport VK")
, C.hCenter (capCommand3 "Import Seed " "P" "hrase")
, C.hCenter (str " ")
, C.hCenter
(capCommand "↑↓ " "move" <+>
capCommand "" "select" <+> xCommand)
@ -776,7 +774,7 @@ drawUI s = [splashDialog s, helpDialog s, displayDialog s, inputDialog s, ui s]
(D.dialog (Just $ txt " Import Seed Phrase ") Nothing 60)
(withAttr abMBarAttr $
vBox
[ padAll 1 $ vBox [renderForm (st ^. importSeedPhraseForm) ]
[ padAll 1 $ vBox [renderForm (st ^. importSeedPhraseForm)]
, C.hCenter
(hBox
[capCommand "" " Save", capCommand3 "" "<Esc>" " Cancel"])
@ -796,7 +794,7 @@ drawUI s = [splashDialog s, helpDialog s, displayDialog s, inputDialog s, ui s]
(str
" _____ _ _ _ \n|__ /___ _ __ (_) |_| |__\n / // _ \\ '_ \\| | __| '_ \\\n / /| __/ | | | | |_| | | |\n/____\\___|_| |_|_|\\__|_| |_|") <=>
C.hCenter
(withAttr titleAttr (str "Zcash Wallet v0.8.0.0-beta")) <=>
(withAttr titleAttr (str "Zcash Wallet v0.9.0.0-beta")) <=>
C.hCenter (withAttr blinkAttr $ str "Press any key..."))
else emptyWidget
capCommand3 :: String -> String -> String -> Widget Name
@ -865,7 +863,7 @@ drawUI s = [splashDialog s, helpDialog s, displayDialog s, inputDialog s, ui s]
withBorderStyle unicodeBold $
D.renderDialog
(D.dialog (Just $ txt " Message ") Nothing 50)
(padAll 1 $ (C.hCenter (strWrap (st ^. msg) )) )
(padAll 1 $ (C.hCenter (strWrap (st ^. msg))))
TxIdDisplay ->
withBorderStyle unicodeBold $
D.renderDialog
@ -1030,7 +1028,8 @@ mkImportVKeyForm :: IViewingKey -> Form IViewingKey e Name
mkImportVKeyForm =
newForm
[ label "Account Name: " @@= editTextField iVkName IViewingKeyName (Just 1)
, label "Viewing Key: " @@= editTextField iVkString IViewingKeyString (Just 1)
, label "Viewing Key: " @@=
editTextField iVkString IViewingKeyString (Just 1)
, label "Birthday Height: " @@=
editShowableFieldWithValidate
iVkBHeight
@ -1046,7 +1045,8 @@ mkImportSeedPhraseForm :: ISeedPhrase -> Form ISeedPhrase e Name
mkImportSeedPhraseForm =
newForm
[ label "Account Name: " @@= editTextField iSpName ISeedPhraseName (Just 1)
, label "Seed Phrase: " @@= editTextField iSpString ISeedPhraseString (Just 1)
, label "Seed Phrase: " @@=
editTextField iSpString ISeedPhraseString (Just 1)
, label "Birthday Height: " @@=
editShowableFieldWithValidate
iSpBHeight
@ -1505,17 +1505,20 @@ appEvent (BT.VtyEvent e) = do
BT.put ns
BT.modify $ set dialogBox Blank
V.EvKey (V.KChar 'n') [] -> do
let cw = currentWallet $ L.listSelectedElement $ s ^. wallets
if (zcashWalletLocal . entityVal <$> cw ) == Just True
then do
BT.modify $
set inputForm $
updateFormState (DialogInput " New Account ") $
s ^. inputForm
BT.modify $ set dialogBox AName
else do
BT.modify $ set msg "Operation not allowed for this account!"
BT.modify $ set displayBox MsgDisplay
let cw =
currentWallet $
L.listSelectedElement $ s ^. wallets
if (zcashWalletLocal . entityVal <$> cw) == Just True
then do
BT.modify $
set inputForm $
updateFormState (DialogInput " New Account ") $
s ^. inputForm
BT.modify $ set dialogBox AName
else do
BT.modify $
set msg "Operation not allowed for this account!"
BT.modify $ set displayBox MsgDisplay
ev -> BT.zoom accounts $ L.handleListEvent ev
SendTx -> do
case e of
@ -1946,14 +1949,16 @@ appEvent (BT.VtyEvent e) = do
userError "Failed to select account"
Just (_j, w1) -> return w1
Just (_k, w) -> return w
case (zcashAccountFvk $ entityVal selAccount) of
Just fvk -> do
BT.modify $ set vkName "Full"
BT.modify $ set vkData (encodeVK $ FullVk $ getFvk fvk)
BT.modify $ set dialogBox ViewingKeyShow
_ -> do
BT.modify $ set msg " Full viewing key not available "
BT.modify $ set displayBox MsgDisplay
case (zcashAccountFvk $ entityVal selAccount) of
Just fvk -> do
BT.modify $ set vkName "Full"
BT.modify $
set vkData (encodeVK $ FullVk $ getFvk fvk)
BT.modify $ set dialogBox ViewingKeyShow
_ -> do
BT.modify $
set msg " Full viewing key not available "
BT.modify $ set displayBox MsgDisplay
--
-- Incoming viewing key display
--
@ -1970,15 +1975,16 @@ appEvent (BT.VtyEvent e) = do
userError "Failed to select account"
Just (_j, w1) -> return w1
Just (_k, w) -> return w
case (zcashAccountIvk $ entityVal selAccount) of
Just ivk -> do
BT.modify $ set vkName "Incomming"
BT.modify $ set vkData (encodeVK $ IncomingVk $ getIvk ivk)
BT.modify $ set dialogBox ViewingKeyShow
_ -> do
BT.modify $ set msg " Incoming viewing key not available "
BT.modify $ set displayBox MsgDisplay
case (zcashAccountIvk $ entityVal selAccount) of
Just ivk -> do
BT.modify $ set vkName "Incomming"
BT.modify $
set vkData (encodeVK $ IncomingVk $ getIvk ivk)
BT.modify $ set dialogBox ViewingKeyShow
_ -> do
BT.modify $
set msg " Incoming viewing key not available "
BT.modify $ set displayBox MsgDisplay
V.EvKey (V.KChar 'e') [] ->
BT.modify $ set dialogBox Blank
_ev -> return ()
@ -2113,41 +2119,57 @@ appEvent (BT.VtyEvent e) = do
ImportVKeyForm -> do
case e of
V.EvKey V.KEnter [] -> do
fs <- BT.zoom importVKForm $ BT.gets formState
if isNotEmptyAfterTrim (fs ^. iVkName)
then do
let vk = parseVK (fs ^. iVkString)
case vk of
Nothing -> do
BT.modify $ set msg "Error: Invalid Viewing Key!!"
BT.modify $ set displayBox MsgDisplay
Just k -> do
if (fs ^. iVkBHeight) >= 1687104
then do
pool <- liftIO $ runNoLoggingT $ initPool $ s ^. dbPath
acc <- liftIO $ importViewingKey pool (fs ^. iVkName) (s ^. network) k (scientificToInt (fs ^. iVkBHeight))
case acc of
Right v -> do
BT.modify $ set dialogBox Blank
BT.modify $ set msg "Viewing Key Imported!!"
BT.modify $ set displayBox MsgDisplay
fs <- BT.zoom importVKForm $ BT.gets formState
if isNotEmptyAfterTrim (fs ^. iVkName)
then do
let vk = parseVK (fs ^. iVkString)
case vk of
Nothing -> do
BT.modify $
set msg "Error: Invalid Viewing Key!!"
BT.modify $ set displayBox MsgDisplay
Just k -> do
if (fs ^. iVkBHeight) >= 1687104
then do
pool <-
liftIO $
runNoLoggingT $ initPool $ s ^. dbPath
acc <-
liftIO $
importViewingKey
pool
(fs ^. iVkName)
(s ^. network)
k
(scientificToInt (fs ^. iVkBHeight))
case acc of
Right v -> do
BT.modify $ set dialogBox Blank
BT.modify $
set msg "Viewing Key Imported!!"
BT.modify $ set displayBox MsgDisplay
--
-- Update Wallet status
--
updatedState <- BT.get
ns <- liftIO $ refreshWalletAfterImport updatedState
BT.put ns
Left e -> do
BT.modify $ set dialogBox Blank
BT.modify $ set msg (T.unpack e)
BT.modify $ set displayBox MsgDisplay
else do
BT.modify $ set msg "Error: Invalid Birthday Height!!"
BT.modify $ set displayBox MsgDisplay
else do
BT.modify $ set msg "Error: Viewing Key Name is missing!!"
BT.modify $ set displayBox MsgDisplay
updatedState <- BT.get
ns <-
liftIO $
refreshWalletAfterImport updatedState
BT.put ns
Left e -> do
BT.modify $ set dialogBox Blank
BT.modify $ set msg (T.unpack e)
BT.modify $ set displayBox MsgDisplay
else do
BT.modify $
set
msg
"Error: Invalid Birthday Height!!"
BT.modify $ set displayBox MsgDisplay
else do
BT.modify $
set msg "Error: Viewing Key Name is missing!!"
BT.modify $ set displayBox MsgDisplay
V.EvKey V.KEsc [] -> BT.modify $ set dialogBox Blank
ev -> do
BT.zoom importVKForm $ do
@ -2158,35 +2180,60 @@ appEvent (BT.VtyEvent e) = do
ImportSeedPhraseForm -> do
case e of
V.EvKey V.KEnter [] -> do
fs <- BT.zoom importSeedPhraseForm $ BT.gets formState
if isNotEmptyAfterTrim (fs ^. iSpName)
then
if isNotEmptyAfterTrim (fs ^. iSpString)
then
if (fs ^. iSpBHeight) >= 1687104
then do
pool <- liftIO $ runNoLoggingT $ initPool $ s ^. dbPath
acc <- liftIO $ importSeedPhrase pool (fs ^. iSpName) (s ^. network) (toPhrase ( E.encodeUtf8 (fs ^. iSpString))) (scientificToInt (fs ^. iSpBHeight))
case acc of
Right v -> do
BT.modify $ set dialogBox Blank
BT.modify $ set msg "Seed Phrase Imported!!"
BT.modify $ set displayBox MsgDisplay
fs <- BT.zoom importSeedPhraseForm $ BT.gets formState
if isNotEmptyAfterTrim (fs ^. iSpName)
then if isNotEmptyAfterTrim (fs ^. iSpString)
then if (fs ^. iSpBHeight) >= 1687104
then do
pool <-
liftIO $
runNoLoggingT $
initPool $ s ^. dbPath
acc <-
liftIO $
importSeedPhrase
pool
(fs ^. iSpName)
(s ^. network)
(toPhrase
(E.encodeUtf8
(fs ^. iSpString)))
(scientificToInt
(fs ^. iSpBHeight))
case acc of
Right v -> do
BT.modify $ set dialogBox Blank
BT.modify $
set
msg
"Seed Phrase Imported!!"
BT.modify $
set displayBox MsgDisplay
--
-- Update Wallet status
--
updatedState <- BT.get
ns <- liftIO $ refreshWalletAfterImport updatedState
BT.put ns
else do
BT.modify $ set msg "Error: Invalid Birthday Height!!"
BT.modify $ set displayBox MsgDisplay
else do
BT.modify $ set msg "Error: Viewing Key Name is missing!!"
BT.modify $ set displayBox MsgDisplay
else do
BT.modify $ set msg "Error: Seed Phrase Name is missing!!"
BT.modify $ set displayBox MsgDisplay
updatedState <- BT.get
ns <-
liftIO $
refreshWalletAfterImport
updatedState
BT.put ns
else do
BT.modify $
set
msg
"Error: Invalid Birthday Height!!"
BT.modify $ set displayBox MsgDisplay
else do
BT.modify $
set
msg
"Error: Viewing Key Name is missing!!"
BT.modify $ set displayBox MsgDisplay
else do
BT.modify $
set msg "Error: Seed Phrase Name is missing!!"
BT.modify $ set displayBox MsgDisplay
V.EvKey V.KEsc [] -> BT.modify $ set dialogBox Blank
ev -> do
BT.zoom importSeedPhraseForm $ do
@ -2213,16 +2260,21 @@ appEvent (BT.VtyEvent e) = do
V.EvKey (V.KChar 'a') [] ->
BT.modify $ set dialogBox ASelect
V.EvKey (V.KChar 's') [] -> do
let cw = currentWallet $ L.listSelectedElement $ s ^. wallets
if (zcashWalletLocal . entityVal <$> cw ) == Just True
then do
BT.modify $
set txForm $
mkSendForm (s ^. balance) (SendInput "" 0.0 "" Full)
BT.modify $ set dialogBox SendTx
else do
BT.modify $ set msg "Operation not allowed for this account!"
BT.modify $ set displayBox MsgDisplay
let cw =
currentWallet $
L.listSelectedElement $ s ^. wallets
if (zcashWalletLocal . entityVal <$> cw) == Just True
then do
BT.modify $
set txForm $
mkSendForm
(s ^. balance)
(SendInput "" 0.0 "" Full)
BT.modify $ set dialogBox SendTx
else do
BT.modify $
set msg "Operation not allowed for this account!"
BT.modify $ set displayBox MsgDisplay
V.EvKey (V.KChar 'u') [] ->
BT.modify $ set dialogBox ProcessURIMenu
V.EvKey (V.KChar 'b') [] ->
@ -2559,10 +2611,11 @@ refreshWalletAfterImport s = do
addrL' &
transactions .~
txL' &
timer .~ 89 &
timer .~
89 &
msg .~
"Import process completed. Switching to : " ++
T.unpack (zcashWalletName $ entityVal selWallet)
T.unpack (zcashWalletName $ entityVal selWallet)
addNewWallet :: T.Text -> State -> IO State
addNewWallet n s = do
@ -2819,25 +2872,25 @@ deshieldTransaction pool chan zHost zPort znet accId bl pnote = do
Right txId -> BC.writeBChan chan $ TickTx txId
currentWallet :: Maybe (Int, Entity ZcashWallet) -> Maybe (Entity ZcashWallet)
currentWallet cw =
case cw of
currentWallet cw =
case cw of
Nothing -> Nothing
Just ( _, w ) -> Just w
Just (_, w) -> Just w
isReadOnlyWallet :: Maybe (Int, Entity ZcashWallet) -> String
isReadOnlyWallet cw =
case cw of
isReadOnlyWallet :: Maybe (Int, Entity ZcashWallet) -> String
isReadOnlyWallet cw =
case cw of
Nothing -> " "
Just ( _, w ) -> do
if (zcashWalletLocal . entityVal <$> Just w ) == Just True
Just (_, w) -> do
if (zcashWalletLocal . entityVal <$> Just w) == Just True
then " "
else " (Read Only) "
walletHasBalance :: Maybe (Int, Entity ZcashAccount) -> Bool
walletHasBalance ca =
case ca of
Nothing -> False
Just (_, a) -> do
case zcashAccountType $ entityVal a of
IncomingViewKey -> False
_ -> True
walletHasBalance ca =
case ca of
Nothing -> False
Just (_, a) -> do
case zcashAccountType $ entityVal a of
IncomingViewKey -> False
_ -> True

View file

@ -60,16 +60,16 @@ import ZcashHaskell.Transparent
)
import ZcashHaskell.Types
( BlockResponse(..)
, Phrase(..)
, Scope(..)
, ToBytes(..)
, UnifiedAddress(..)
, ValidAddress(..)
, ValidVk(..)
, ValidVk(..)
, ZcashNet(..)
, ZebraGetBlockChainInfo(..)
, ZebraGetInfo(..)
, ValidVk (..)
, Phrase (..)
)
import ZcashHaskell.Utils (getBlockTime, makeZebraCall)
import Zenith.Core
@ -82,6 +82,7 @@ import Zenith.Utils
, displayAmount
, getChainTip
, getZcashPrice
, isNotEmptyAfterTrim
, isRecipientValidGUI
, isValidString
, isZecAddressValid
@ -89,9 +90,8 @@ import Zenith.Utils
, padWithZero
, parseZcashPayment
, showAddress
, validBarValue
, isNotEmptyAfterTrim
, toPhrase
, validBarValue
)
data VkTypeDef
@ -199,7 +199,7 @@ data AppEvent
| ShowNSeedPhrase
| CloseNSpShow
| SaveSeedPhrase
| ReportSeedSaved
| ReportSeedSaved
deriving (Eq, Show)
data AppModel = AppModel
@ -2110,8 +2110,7 @@ handleEvent wenv node model evt =
--
-- Show Import Viewing Key Form
--
SetTimerCount ->
[ Model $ model & timer .~ 85 ]
SetTimerCount -> [Model $ model & timer .~ 85]
ShowNViewingKey -> [Model $ model & nVkShow .~ True & menuPopup .~ False]
CloseNVkShow -> [Model $ model & nVkShow .~ False]
SaveViewKey ->
@ -2133,8 +2132,8 @@ handleEvent wenv node model evt =
Right i -> return $ ReportVKeySaved
]
--
ReportVKeySaved ->
[ Task $ do
ReportVKeySaved ->
[ Task $ do
generateQRCodes $ model ^. configuration
pool <- runNoLoggingT $ initPool $ c_dbPath $ model ^. configuration
wL <- getWallets pool (model ^. network)
@ -2142,7 +2141,7 @@ handleEvent wenv node model evt =
, Event $ CloseNVkShow
, Event $ ShowMessage "Viewing Key imported!"
, Event $ StartSync
]
]
--
-- Show Import Seed Phrase Form
--
@ -2150,43 +2149,42 @@ handleEvent wenv node model evt =
[ Task $ do
pool <- runNoLoggingT $ initPool $ c_dbPath $ model ^. configuration
if isNotEmptyAfterTrim (model ^. nSpName)
then
if isNotEmptyAfterTrim (model ^. nSpName)
then
if (model ^. nSpBirthday) >= 1687104
then do
let sp = Phrase ( E.encodeUtf8 (model ^. nSpString) )
x <-
importSeedPhrase
pool
(model ^. nSpName)
(model ^. network)
sp
(model ^. nSpBirthday)
case x of
Left e -> return $ ShowError e
Right i -> return $ ReportSeedSaved
else return $ ShowError "Invalid Birthday Block!"
else return $ ShowError "Seed Phrase not provided"
then if isNotEmptyAfterTrim (model ^. nSpName)
then if (model ^. nSpBirthday) >= 1687104
then do
let sp = Phrase (E.encodeUtf8 (model ^. nSpString))
x <-
importSeedPhrase
pool
(model ^. nSpName)
(model ^. network)
sp
(model ^. nSpBirthday)
case x of
Left e -> return $ ShowError e
Right i -> return $ ReportSeedSaved
else return $ ShowError "Invalid Birthday Block!"
else return $ ShowError "Seed Phrase not provided"
else return $ ShowError "Seed Phrase name invalid!"
]
--
ReportSeedSaved ->
[ Task $ do
ReportSeedSaved ->
[ Task $ do
generateQRCodes $ model ^. configuration
pool <- runNoLoggingT $ initPool $ c_dbPath $ model ^. configuration
wL <- getWallets pool (model ^. network)
return $ LoadWallets wL
, Event $ CloseNSpShow
, Event $ ShowMessage "Seed Phrase imported!!"
, Event $ SetTimerCount
]
ShowNSeedPhrase -> [Model $ model & nSpShow .~ True &
nSpName .~ "" &
nSpString .~ "" &
nSpBirthday .~ 0 &
menuPopup .~ False]
, Event $ SetTimerCount
]
ShowNSeedPhrase ->
[ Model $
model & nSpShow .~ True & nSpName .~ "" & nSpString .~ "" & nSpBirthday .~
0 &
menuPopup .~
False
]
CloseNSpShow -> [Model $ model & nSpShow .~ False]
--
-- Show Balance in FIAT
@ -2956,7 +2954,7 @@ runZenithGUI config = do
Left _e -> print "Zebra not available"
where
params hd =
[ appWindowTitle "Zenith - Zcash Full Node Wallet - 0.8.0.0-beta"
[ appWindowTitle "Zenith - Zcash Full Node Wallet - 0.9.0.0-beta"
, appWindowState $ MainWindowNormal (1000, 700)
, appTheme zenithTheme
, appFontDef

View file

@ -610,7 +610,7 @@ zenithServer state = getinfo :<|> handleRPC
getinfo =
return $
object
[ "version" .= ("0.8.0.0-beta" :: String)
[ "version" .= ("0.9.0.0-beta" :: String)
, "network" .= ("testnet" :: String)
]
handleRPC :: Bool -> RpcCall -> Handler ZenithResponse
@ -686,7 +686,7 @@ zenithServer state = getinfo :<|> handleRPC
return $
InfoResponse
(callId req)
(ZenithInfo "0.8.0.0-beta" (w_network state) (w_build state))
(ZenithInfo "0.9.0.0-beta" (w_network state) (w_build state))
_anyOtherParams ->
return $ ErrorResponse (callId req) (-32602) "Invalid params"
ListReceived ->

@ -1 +1 @@
Subproject commit ffc71152ad4873ef0fdc48b51f2e11c3c338a405
Subproject commit 0d042d639d471af14ebe94707f64b5ff5c2cb5eb