Compare commits

..

No commits in common. "f3098646710a2deb088add00dbe4bf3977490080" and "f1daf576ccc28203a48b9fc92acdcd15a7e1dad8" have entirely different histories.

4 changed files with 60 additions and 526 deletions

View file

@ -2,7 +2,6 @@
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE LambdaCase #-}
module Zenith.CLI where
@ -63,14 +62,14 @@ import qualified Brick.Widgets.List as L
import qualified Brick.Widgets.ProgressBar as P
import Control.Concurrent (forkIO, threadDelay)
import Control.Exception (throw, throwIO, try)
import Control.Monad (forM_, forever, unless, void, when)
import Control.Monad (forever, unless, void, when)
import Control.Monad.IO.Class (liftIO)
import Control.Monad.Logger
( LoggingT
, NoLoggingT
, logDebugN
, runFileLoggingT
, runNoLoggingT
, runStderrLoggingT
)
import Data.Aeson
import Data.HexString (HexString(..), toText)
@ -95,10 +94,7 @@ import ZcashHaskell.Orchard
, isValidUnifiedAddress
, parseAddress
)
import ZcashHaskell.Transparent
( decodeTransparentAddress
, encodeTransparentReceiver
)
import ZcashHaskell.Transparent (encodeTransparentReceiver)
import ZcashHaskell.Types
import ZcashHaskell.Utils (getBlockTime, makeZebraCall)
import Zenith.Core
@ -173,8 +169,11 @@ data AdrBookEntry = AdrBookEntry
makeLenses ''AdrBookEntry
newtype ShDshEntry = ShDshEntry
{ _shAmt :: Float
data ShDshEntry = ShDshEntry
{ _totalTransparent :: !Float
, _totalShielded :: !Float
, _shieldOp :: !ShieldDeshieldOp
, _shAmt :: !Float
} deriving (Show)
makeLenses ''ShDshEntry
@ -191,8 +190,7 @@ data DialogType
| AdrBookForm
| AdrBookUpdForm
| AdrBookDelForm
| DeshieldForm
| ShieldForm
| ShieldDeshieldForm
data DisplayType
= AddrDisplay
@ -241,9 +239,7 @@ data State = State
, _abCurAdrs :: !T.Text -- used for address book CRUD operations
, _sentTx :: !(Maybe HexString)
, _unconfBalance :: !Integer
, _deshieldForm :: !(Form ShDshEntry () Name)
, _tBalance :: !Integer
, _sBalance :: !Integer
, _shdshForm :: !(Form ShDshEntry () Name)
}
makeLenses ''State
@ -260,11 +256,11 @@ drawUI s = [splashDialog s, helpDialog s, displayDialog s, inputDialog s, ui s]
(" Zenith - " <>
show (st ^. network) <>
" - " <>
T.unpack
(maybe
"(None)"
(\(_, w) -> zcashWalletName $ entityVal w)
(L.listSelectedElement (st ^. wallets))) ++
(T.unpack
(maybe
"(None)"
(\(_, w) -> zcashWalletName $ entityVal w)
(L.listSelectedElement (st ^. wallets)))) ++
" "))
(C.hCenter
(str
@ -302,8 +298,7 @@ drawUI s = [splashDialog s, helpDialog s, displayDialog s, inputDialog s, ui s]
, C.hCenter
(hBox
[ capCommand2 "Address " "B" "ook"
, capCommand2 "s" "H" "ield"
, capCommand "D" "e-shield"
, capCommand2 "Shield/" "D" "eshield"
, capCommand "Q" "uit"
, capCommand "?" " Help"
, str $ show (st ^. timer)
@ -432,35 +427,10 @@ drawUI s = [splashDialog s, helpDialog s, displayDialog s, inputDialog s, ui s]
(renderForm (st ^. txForm) <=>
C.hCenter
(hBox [capCommand "" "Send", capCommand "<esc> " "Cancel"]))
DeshieldForm ->
ShieldDeshieldForm ->
D.renderDialog
(D.dialog (Just (str " De-Shield ZEC ")) Nothing 50)
(C.hCenter
(padAll 1 $
vBox
[ str $
"Transparent Bal.: " ++
if st ^. network == MainNet
then displayZec (st ^. tBalance)
else displayTaz (st ^. tBalance)
, str $
"Shielded Bal.: " ++
if st ^. network == MainNet
then displayZec (st ^. sBalance)
else displayTaz (st ^. sBalance)
]) <=>
renderForm (st ^. deshieldForm) <=>
C.hCenter
(hBox [capCommand "P" "roceed", capCommand "<esc> " "Cancel"]))
ShieldForm ->
D.renderDialog
(D.dialog (Just (str " Shield ZEC ")) Nothing 50)
(C.hCenter
(str $
"Shield " ++
if st ^. network == MainNet
then displayZec (st ^. tBalance)
else displayTaz (st ^. tBalance) ++ "?") <=>
(D.dialog (Just (str " Shield / De-Shield ")) Nothing 50)
(renderForm (st ^. shdshForm) <=>
C.hCenter
(hBox [capCommand "P" "roceed", capCommand "<esc> " "Cancel"]))
Blank -> emptyWidget
@ -706,11 +676,27 @@ mkSendForm bal =
label s w =
padBottom (Pad 1) $ vLimit 1 (hLimit 15 $ str s <+> fill ' ') <+> w
mkDeshieldForm :: Integer -> ShDshEntry -> Form ShDshEntry e Name
mkDeshieldForm tbal =
mkshieldDeshieldForm :: Integer -> ShDshEntry -> Form ShDshEntry e Name
mkshieldDeshieldForm bal =
newForm
[ label "Amount: " @@=
editShowableFieldWithValidate shAmt AmtField (isAmountValid tbal)
[ label "Total Transp. : " @@=
editShowableFieldWithValidate
totalTransparent
TotalTranspField
(isAmountValid bal)
, label "Total Shielded : " @@=
editShowableFieldWithValidate
totalShielded
TotalShieldedField
(isAmountValid bal)
, label "Select :" @@=
radioField
shieldOp
[ (Shield, ShieldField, "Shield")
, (Deshield, DeshieldField, "De-Shield")
]
, label "Amount: " @@=
editShowableFieldWithValidate shAmt AmtField (isAmountValid bal)
]
where
isAmountValid :: Integer -> Float -> Bool
@ -826,7 +812,7 @@ scanZebra ::
-> Int
-> BC.BChan Tick
-> ZcashNet
-> LoggingT IO ()
-> NoLoggingT IO ()
scanZebra dbP zHost zPort b eChan znet = do
bStatus <- liftIO $ checkBlockChain zHost zPort
pool <- liftIO $ runNoLoggingT $ initPool dbP
@ -858,7 +844,7 @@ scanZebra dbP zHost zPort b eChan znet = do
_ <- liftIO $ startSync pool
mapM_ (liftIO . processBlock pool step) bList
confUp <-
liftIO $ try $ updateConfs zHost zPort pool :: LoggingT
liftIO $ try $ updateConfs zHost zPort pool :: NoLoggingT
IO
(Either IOError ())
case confUp of
@ -963,11 +949,11 @@ appEvent (BT.AppEvent t) = do
"pwd"
8080)
selWallet
BT.modify $ set displayBox BlankDisplay
BT.modify $ set barValue 0.0
updatedState <- BT.get
ns <- liftIO $ refreshWallet updatedState
BT.put ns
BT.modify $ set displayBox BlankDisplay
BT.modify $ set barValue 0.0
else BT.modify $ set barValue $ validBarValue (v + s ^. barValue)
BlankDisplay -> do
case s ^. dialogBox of
@ -981,8 +967,7 @@ appEvent (BT.AppEvent t) = do
AdrBookForm -> return ()
AdrBookUpdForm -> return ()
AdrBookDelForm -> return ()
DeshieldForm -> return ()
ShieldForm -> return ()
ShieldDeshieldForm -> return ()
Blank -> do
if s ^. timer == 90
then do
@ -992,7 +977,7 @@ appEvent (BT.AppEvent t) = do
_ <-
liftIO $
forkIO $
runStderrLoggingT $
runNoLoggingT $
scanZebra
(s ^. dbPath)
(s ^. zebraHost)
@ -1234,98 +1219,11 @@ appEvent (BT.VtyEvent e) = do
(fs ^. policyField)
(fs ^. sendTo))
RecField
DeshieldForm -> do
ShieldDeshieldForm -> do
case e of
V.EvKey V.KEsc [] -> BT.modify $ set dialogBox Blank
V.EvKey (V.KChar 'p') [] -> do
if allFieldsValid (s ^. deshieldForm)
then do
pool <-
liftIO $ runNoLoggingT $ initPool $ s ^. dbPath
selWal <-
do case L.listSelectedElement $ s ^. wallets of
Nothing -> do
let fWall =
L.listSelectedElement $
L.listMoveToBeginning $ s ^. wallets
case fWall of
Nothing ->
throw $
userError "Failed to select wallet"
Just (_j, w1) -> return w1
Just (_k, w) -> return w
selAcc <-
do case L.listSelectedElement $ s ^. accounts of
Nothing -> do
let fAcc =
L.listSelectedElement $
L.listMoveToBeginning $
s ^. accounts
case fAcc of
Nothing ->
throw $
userError "Failed to select wallet"
Just (_j, w1) -> return w1
Just (_k, w) -> return w
selAddr <-
do case L.listSelectedElement $ s ^. addresses of
Nothing -> do
let fAddr =
L.listSelectedElement $
L.listMoveToBeginning $
s ^. addresses
case fAddr of
Nothing ->
throw $
userError "Failed to select address"
Just (_j, w1) -> return w1
Just (_k, w) -> return w
fs1 <- BT.zoom deshieldForm $ BT.gets formState
let tAddrMaybe =
Transparent <$>
((decodeTransparentAddress .
E.encodeUtf8 .
encodeTransparentReceiver (s ^. network)) =<<
(t_rec =<<
(isValidUnifiedAddress .
E.encodeUtf8 .
getUA . walletAddressUAddress)
(entityVal selAddr)))
bl <-
liftIO $ getLastSyncBlock pool $ entityKey selWal
case tAddrMaybe of
Nothing -> do
BT.modify $
set
msg
"Failed to obtain transparent address"
BT.modify $ set displayBox MsgDisplay
BT.modify $ set dialogBox Blank
Just tAddr -> do
_ <-
liftIO $
forkIO $
deshieldTransaction
pool
(s ^. eventDispatch)
(s ^. zebraHost)
(s ^. zebraPort)
(s ^. network)
(entityKey selAcc)
bl
(ProposedNote
(ValidAddressAPI tAddr)
(fs1 ^. shAmt)
Nothing)
BT.modify $ set displayBox SendDisplay
BT.modify $ set dialogBox Blank
else do
BT.modify $ set msg "Invalid inputs"
BT.modify $ set displayBox MsgDisplay
BT.modify $ set dialogBox Blank
ev ->
BT.zoom deshieldForm $ do
handleFormEvent (BT.VtyEvent ev)
BT.zoom shdshForm $ do handleFormEvent (BT.VtyEvent ev)
AdrBook -> do
case e of
V.EvKey (V.KChar 'x') [] ->
@ -1509,53 +1407,6 @@ appEvent (BT.VtyEvent e) = do
BT.put s'
BT.modify $ set dialogBox AdrBook
ev -> BT.modify $ set dialogBox AdrBookDelForm
ShieldForm -> do
case e of
V.EvKey V.KEsc [] -> BT.modify $ set dialogBox Blank
V.EvKey (V.KChar 'p') [] -> do
pool <- liftIO $ runNoLoggingT $ initPool $ s ^. dbPath
selWal <-
do case L.listSelectedElement $ s ^. wallets of
Nothing -> do
let fWall =
L.listSelectedElement $
L.listMoveToBeginning $ s ^. wallets
case fWall of
Nothing ->
throw $
userError "Failed to select wallet"
Just (_j, w1) -> return w1
Just (_k, w) -> return w
selAcc <-
do case L.listSelectedElement $ s ^. accounts of
Nothing -> do
let fAcc =
L.listSelectedElement $
L.listMoveToBeginning $ s ^. accounts
case fAcc of
Nothing ->
throw $
userError "Failed to select account"
Just (_j, w1) -> return w1
Just (_k, w) -> return w
bl <- liftIO $ getLastSyncBlock pool $ entityKey selWal
_ <-
liftIO $
forkIO $
shieldTransaction
pool
(s ^. eventDispatch)
(s ^. zebraHost)
(s ^. zebraPort)
(s ^. network)
(entityKey selAcc)
bl
BT.modify $ set msg "Preparing transaction..."
BT.modify $ set displayBox SendDisplay
BT.modify $ set dialogBox Blank
ev ->
BT.zoom deshieldForm $ do
handleFormEvent (BT.VtyEvent ev)
-- Process any other event
Blank -> do
case e of
@ -1593,46 +1444,11 @@ appEvent (BT.VtyEvent e) = do
case fAcc of
Nothing ->
throw $
userError "Failed to select account"
userError "Failed to select wallet"
Just (_j, w1) -> return w1
Just (_k, w) -> return w
tBal <-
liftIO $
getTransparentBalance pool $ entityKey selAcc
sBal <-
liftIO $ getShieldedBalance pool $ entityKey selAcc
BT.modify $ set tBalance tBal
BT.modify $ set sBalance sBal
BT.modify $
set deshieldForm $
mkDeshieldForm sBal (ShDshEntry 0.0)
BT.modify $ set dialogBox DeshieldForm
V.EvKey (V.KChar 'h') [] -> do
pool <- liftIO $ runNoLoggingT $ initPool $ s ^. dbPath
selAcc <-
do case L.listSelectedElement $ s ^. accounts of
Nothing -> do
let fAcc =
L.listSelectedElement $
L.listMoveToBeginning $ s ^. accounts
case fAcc of
Nothing ->
throw $
userError "Failed to select account"
Just (_j, w1) -> return w1
Just (_k, w) -> return w
tBal <-
liftIO $
getTransparentBalance pool $ entityKey selAcc
BT.modify $ set tBalance tBal
if tBal > 20000
then BT.modify $ set dialogBox ShieldForm
else do
BT.modify $
set
msg
"Not enough transparent funds in this account"
BT.modify $ set displayBox MsgDisplay
c <- liftIO $ getPoolBalance pool $ entityKey selAcc
BT.modify $ set dialogBox ShieldDeshieldForm
ev ->
case r of
Just AList ->
@ -1731,14 +1547,6 @@ runZenithTUI config = do
if not (null accList)
then getUnconfirmedBalance pool $ entityKey $ head accList
else return 0
tBal <-
if not (null accList)
then getTransparentBalance pool $ entityKey $ head accList
else return 0
sBal <-
if not (null accList)
then getShieldedBalance pool $ entityKey $ head accList
else return 0
eventChan <- BC.newBChan 10
_ <-
forkIO $
@ -1752,7 +1560,7 @@ runZenithTUI config = do
State
(zgb_net chainInfo)
(L.list WList (Vec.fromList walList) 1)
(L.list AcList (Vec.fromList accList) 1)
(L.list AcList (Vec.fromList accList) 0)
(L.list AList (Vec.fromList addrList) 1)
(L.list TList (Vec.fromList txList) 1)
("Start up Ok! Connected to Zebra " ++
@ -1781,9 +1589,7 @@ runZenithTUI config = do
""
Nothing
uBal
(mkDeshieldForm 0 (ShDshEntry 0.0))
tBal
sBal
(mkshieldDeshieldForm 0 (ShDshEntry 0 0 Shield 0.0))
Left _e -> do
print $
"No Zebra node available on port " <>
@ -1803,7 +1609,7 @@ refreshWallet s = do
Just (j, w1) -> return (j, w1)
Just (k, w) -> return (k, w)
aL <- runNoLoggingT $ getAccounts pool $ entityKey selWallet
let bl = zcashWalletLastSync $ entityVal $ walList !! ix
let bl = zcashWalletLastSync $ entityVal selWallet
addrL <-
if not (null aL)
then runNoLoggingT $ getAddresses pool $ entityKey $ head aL
@ -2034,56 +1840,3 @@ sendTransaction pool chan zHost zPort znet accId bl amt ua memo policy = do
case resp of
Left e1 -> BC.writeBChan chan $ TickMsg $ "Zebra error: " ++ show e1
Right txId -> BC.writeBChan chan $ TickTx txId
shieldTransaction ::
ConnectionPool
-> BC.BChan Tick
-> T.Text
-> Int
-> ZcashNet
-> ZcashAccountId
-> Int
-> IO ()
shieldTransaction pool chan zHost zPort znet accId bl = do
BC.writeBChan chan $ TickMsg "Preparing shielding transaction..."
res <- runNoLoggingT $ shieldTransparentNotes pool zHost zPort znet accId bl
forM_ res $ \case
Left e -> BC.writeBChan chan $ TickMsg $ show e
Right rawTx -> do
BC.writeBChan chan $ TickMsg "Transaction ready, sending to Zebra..."
resp <-
makeZebraCall
zHost
zPort
"sendrawtransaction"
[Data.Aeson.String $ toText rawTx]
case resp of
Left e1 -> BC.writeBChan chan $ TickMsg $ "Zebra error: " ++ show e1
Right txId -> BC.writeBChan chan $ TickTx txId
deshieldTransaction ::
ConnectionPool
-> BC.BChan Tick
-> T.Text
-> Int
-> ZcashNet
-> ZcashAccountId
-> Int
-> ProposedNote
-> IO ()
deshieldTransaction pool chan zHost zPort znet accId bl pnote = do
BC.writeBChan chan $ TickMsg "Deshielding funds..."
res <- runNoLoggingT $ deshieldNotes pool zHost zPort znet accId bl pnote
case res of
Left e -> BC.writeBChan chan $ TickMsg $ show e
Right rawTx -> do
BC.writeBChan chan $ TickMsg "Transaction ready, sending to Zebra..."
resp <-
makeZebraCall
zHost
zPort
"sendrawtransaction"
[Data.Aeson.String $ toText rawTx]
case resp of
Left e1 -> BC.writeBChan chan $ TickMsg $ "Zebra error: " ++ show e1
Right txId -> BC.writeBChan chan $ TickTx txId

View file

@ -2030,51 +2030,6 @@ getUnconfPoolBalance pool za = do
let oBal = sum oAmts
return $ AccountBalance tBal sBal oBal
rewindWalletTransactions :: ConnectionPool -> Int -> IO ()
rewindWalletTransactions pool b = do
runNoLoggingT $
PS.retryOnBusy $
flip PS.runSqlPool pool $ do
delete $ do
_ <- from $ table @UserTx
return ()
oldTxs <-
select $ do
txs <- from $ table @WalletTransaction
where_ $ txs ^. WalletTransactionBlock >. val b
pure txs
let oldKeys = map entityKey oldTxs
delete $ do
x <- from $ table @WalletOrchSpend
where_ $ x ^. WalletOrchSpendTx `in_` valList oldKeys
return ()
delete $ do
x <- from $ table @WalletOrchNote
where_ $ x ^. WalletOrchNoteTx `in_` valList oldKeys
return ()
delete $ do
x <- from $ table @WalletSapNote
where_ $ x ^. WalletSapNoteTx `in_` valList oldKeys
return ()
delete $ do
x <- from $ table @WalletSapSpend
where_ $ x ^. WalletSapSpendTx `in_` valList oldKeys
return ()
delete $ do
x <- from $ table @WalletTrNote
where_ $ x ^. WalletTrNoteTx `in_` valList oldKeys
return ()
delete $ do
x <- from $ table @WalletTrSpend
where_ $ x ^. WalletTrSpendTx `in_` valList oldKeys
return ()
delete $ do
txs <- from $ table @WalletTransaction
where_ $ txs ^. WalletTransactionBlock >. val b
return ()
update $ \w -> do
set w [ZcashWalletLastSync =. val b]
clearWalletTransactions :: ConnectionPool -> IO ()
clearWalletTransactions pool = do
runNoLoggingT $
@ -2623,40 +2578,10 @@ completeSync pool st = do
-- | Rewind the data store to a given block height
rewindWalletData :: ConnectionPool -> Int -> IO ()
rewindWalletData pool b = do
rewindWalletTransactions pool b
runNoLoggingT $
PS.retryOnBusy $
flip PS.runSqlPool pool $ do
oldBlocks <-
select $ do
blk <- from $ table @ZcashBlock
where_ $ blk ^. ZcashBlockHeight >. val b
pure blk
let oldBlkKeys = map entityKey oldBlocks
oldTxs <-
select $ do
txs <- from $ table @ZcashTransaction
where_ $ txs ^. ZcashTransactionBlockId `in_` valList oldBlkKeys
pure txs
let oldTxKeys = map entityKey oldTxs
delete $ do
x <- from $ table @TransparentNote
where_ $ x ^. TransparentNoteTx `in_` valList oldTxKeys
delete $ do
x <- from $ table @TransparentSpend
where_ $ x ^. TransparentSpendTx `in_` valList oldTxKeys
delete $ do
x <- from $ table @ShieldOutput
where_ $ x ^. ShieldOutputTx `in_` valList oldTxKeys
delete $ do
x <- from $ table @ShieldSpend
where_ $ x ^. ShieldSpendTx `in_` valList oldTxKeys
delete $ do
x <- from $ table @OrchAction
where_ $ x ^. OrchActionTx `in_` valList oldTxKeys
delete $ do
x <- from $ table @ZcashTransaction
where_ $ x ^. ZcashTransactionId `in_` valList oldTxKeys
delete $ do
blk <- from $ table @ZcashBlock
where_ $ blk ^. ZcashBlockHeight >. val b
flip PS.runSqlPool pool $
delete $ do
blk <- from $ table @ZcashBlock
where_ $ blk ^. ZcashBlockHeight >=. val b
clearWalletTransactions pool

View file

@ -126,10 +126,6 @@ data AppEvent
| DeleteABEntry !T.Text
| UpdateABDescrip !T.Text !T.Text
| ResetRecipientValid
| ShowShield
| CloseShield
| ShowDeShield
| CloseDeShield
deriving (Eq, Show)
data AppModel = AppModel
@ -183,12 +179,6 @@ data AppModel = AppModel
, _showABAddress :: !Bool
, _updateABAddress :: !Bool
, _privacyChoice :: !PrivacyPolicy
, _shieldZec :: !Bool
, _deShieldZec :: !Bool
, _tBalance :: !Integer
, _tBalanceValid :: !Bool
, _sBalance :: !Integer
, _sBalanceValid :: !Bool
} deriving (Eq, Show)
makeLenses ''AppModel
@ -238,8 +228,6 @@ buildUI wenv model = widgetTree
, updateABAddressOverlay (model ^. abdescrip) (model ^. abaddress) `nodeVisible`
model ^.
updateABAddress
, shieldOverlay `nodeVisible` model ^. shieldZec
, deShieldOverlay `nodeVisible` model ^. deShieldZec
, msgAdrBookOverlay `nodeVisible` isJust (model ^. msgAB)
]
mainWindow =
@ -305,10 +293,6 @@ buildUI wenv model = widgetTree
[bgColor white, borderB 1 gray, padding 3]
, box_ [alignLeft, onClick ShowAdrBook] (label "Address Book") `styleBasic`
[bgColor white, borderB 1 gray, padding 3]
, box_ [alignLeft, onClick ShowShield] (label "Shield ZEC") `styleBasic`
[bgColor white, borderB 1 gray, padding 3]
, box_ [alignLeft, onClick ShowDeShield] (label "De-Shield ZEC") `styleBasic`
[bgColor white, borderB 1 gray, padding 3]
]) `styleBasic`
[bgColor btnColor, padding 3]
newBox =
@ -974,125 +958,7 @@ buildUI wenv model = widgetTree
, label_ (txtWrapN (fromMaybe "" (model ^. msgAB)) 64) [multiline]
, filler
]
shieldOverlay =
box
(vstack
[ filler
, hstack
[ filler
, box_
[]
(vstack
[ box_
[alignMiddle]
(label "Shield Zcash" `styleBasic`
[textFont "Bold", textSize 12])
, separatorLine `styleBasic` [fgColor btnColor]
, spacer
, hstack
[ filler
, label ("Amount : " ) `styleBasic`
[width 50, textFont "Bold"]
, spacer
, label (displayAmount (model ^. network) 100 ) `styleBasic`
[width 50, textFont "Bold"]
, filler
-- , spacer
-- , numericField_
-- sendAmount
-- [ decimals 8
-- , minValue 0.0
-- , maxValue
-- (fromIntegral (model ^. tBalance) / 100000000.0)
-- , validInput tBalanceValid
-- , onChange CheckAmount
-- ] `styleBasic`
-- [ width 150
-- , styleIf
-- (not $ model ^. tBalanceValid)
-- (textColor red)
-- ]
]
, spacer
, box_
[alignMiddle]
(hstack
[ filler
, mainButton "Proceed" NotImplemented `nodeEnabled` True
-- (model ^. amountValid && model ^. recipientValid)
, spacer
, mainButton "Cancel" CloseShield `nodeEnabled` True
, filler
])
]) `styleBasic`
[radius 4, border 2 btnColor, bgColor white, padding 4]
, filler
]
, filler
]) `styleBasic`
[bgColor (white & L.a .~ 0.5)]
deShieldOverlay =
box
(vstack
[ filler
, hstack
[ filler
, box_
[]
(vstack
[ box_
[alignMiddle]
(label "De-Shield Zcash" `styleBasic`
[textFont "Bold", textSize 12])
, separatorLine `styleBasic` [fgColor btnColor]
, spacer
, hstack
[ (label "Total Transparent : " `styleBasic` [ textFont "Bold" ])
, (label "0.00" )
]
, spacer
, hstack
[ (label "Total Shielded : " `styleBasic` [ textFont "Bold" ])
, (label "0.00" )
]
, spacer
, hstack
[ label "Amount:" `styleBasic`
[width 50, textFont "Bold"]
, spacer
, numericField_
sendAmount
[ decimals 8
, minValue 0.0
, maxValue
(fromIntegral (model ^. sBalance) / 100000000.0)
, validInput sBalanceValid
, onChange CheckAmount
] `styleBasic`
[ width 150
, styleIf
(not $ model ^. sBalanceValid)
(textColor red)
]
]
, spacer
, box_
[alignMiddle]
(hstack
[ filler
, mainButton "Proceed" NotImplemented `nodeEnabled` True
-- (model ^. amountValid && model ^. recipientValid)
, spacer
, mainButton "Cancel" CloseDeShield `nodeEnabled` True
, filler
])
]) `styleBasic`
[radius 4, border 2 btnColor, bgColor white, padding 4]
, filler
]
, filler
]) `styleBasic`
[bgColor (white & L.a .~ 0.5)]
notImplemented = NotImplemented
generateQRCodes :: Config -> IO ()
@ -1482,10 +1348,6 @@ handleEvent wenv node model evt =
model & msgAB ?~ "Function not implemented..." & menuPopup .~ False
]
CloseMsgAB -> [Model $ model & msgAB .~ Nothing & inError .~ False]
ShowShield -> [ Model $ model & shieldZec .~ True & menuPopup .~ False ]
CloseShield -> [Model $ model & shieldZec .~ False]
ShowDeShield -> [ Model $ model & deShieldZec .~ True & menuPopup .~ False ]
CloseDeShield -> [Model $ model & deShieldZec .~ False]
LoadAbList a -> [Model $ model & abaddressList .~ a]
UpdateABDescrip d a ->
[ Task $ updAddrBookDescrip (model ^. configuration) d a
@ -1862,12 +1724,6 @@ runZenithGUI config = do
False
False
Full
False
False
0
False
0
False
startApp model handleEvent buildUI (params hD)
Left _e -> print "Zebra not available"
where

@ -1 +1 @@
Subproject commit 396f15140a00fd9a00f06c89910f76a22354e8d8
Subproject commit 003293cc3f978c146824d0695c5c458cf2cc9bb5