Importing Viewing Keys and Seed Phrases (#119)
This PR adds the functionality to import a Unified Viewing Key (full or incoming) and to use it to scan the blockchain for transactions. It also adds the functionality to import a seed phrase as a new wallet. Co-authored-by: Rene V. Vergara <rvergara59@protonmail.com> Reviewed-on: #119 Co-authored-by: Rene Vergara <rene@vergara.network> Co-committed-by: Rene Vergara <rene@vergara.network>
This commit is contained in:
parent
30757d7f28
commit
9ab91a6dc8
17 changed files with 2019 additions and 574 deletions
1
.gitmodules
vendored
1
.gitmodules
vendored
|
@ -1,3 +1,4 @@
|
|||
[submodule "zcash-haskell"]
|
||||
path = zcash-haskell
|
||||
url = https://code.vergara.tech/Vergara_Tech/zcash-haskell
|
||||
branch = master
|
||||
|
|
20
CHANGELOG.md
20
CHANGELOG.md
|
@ -5,6 +5,26 @@ 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).
|
||||
|
||||
## [0.9.0.0-beta]
|
||||
|
||||
### Added
|
||||
|
||||
- RPC
|
||||
- `importvk`
|
||||
- TUI
|
||||
- Import viewing keys
|
||||
- Import seed phrase
|
||||
- GUI
|
||||
- Import viewing keys
|
||||
- Import seed phrase
|
||||
|
||||
### Changed
|
||||
|
||||
- Database schema for wallets and accounts
|
||||
- RPC:
|
||||
- New field in wallet schema
|
||||
- New field in account schema
|
||||
|
||||
## [0.8.0.0-beta]
|
||||
|
||||
### Added
|
||||
|
|
|
@ -5,7 +5,7 @@ module Server where
|
|||
import Control.Concurrent (forkIO, threadDelay)
|
||||
import Control.Exception (throwIO, throwTo, try)
|
||||
import Control.Monad (forever, when)
|
||||
import Control.Monad.Logger (runNoLoggingT)
|
||||
import Control.Monad.Logger (runNoLoggingT, runStderrLoggingT)
|
||||
import Data.Configurator
|
||||
import qualified Data.Text as T
|
||||
import Network.Wai.Handler.Warp (run)
|
||||
|
@ -14,7 +14,7 @@ import System.Exit
|
|||
import System.Posix.Signals
|
||||
import ZcashHaskell.Types (ZebraGetBlockChainInfo(..), ZebraGetInfo(..))
|
||||
import Zenith.Core (checkBlockChain, checkZebra)
|
||||
import Zenith.DB (getWallets, initDb, initPool)
|
||||
import Zenith.DB (getWallets, initDb, initPool, upgradeAccountTable)
|
||||
import Zenith.RPC
|
||||
( State(..)
|
||||
, ZenithRPC(..)
|
||||
|
@ -57,12 +57,13 @@ main = do
|
|||
case bc of
|
||||
Left e1 -> throwIO e1
|
||||
Right chainInfo -> do
|
||||
x <- initDb dbFilePath
|
||||
x <- runNoLoggingT $ initDb dbFilePath
|
||||
case x of
|
||||
Left e2 -> throwIO $ userError e2
|
||||
Right x' -> do
|
||||
when x' $ rescanZebra zebraHost zebraPort dbFilePath
|
||||
pool <- runNoLoggingT $ initPool dbFilePath
|
||||
_ <- runNoLoggingT $ upgradeAccountTable pool
|
||||
walList <- getWallets pool $ zgb_net chainInfo
|
||||
if not (null walList)
|
||||
then do
|
||||
|
@ -76,7 +77,7 @@ main = do
|
|||
zebraPort
|
||||
(zgb_net chainInfo)
|
||||
threadDelay 90000000
|
||||
putStrLn "Zenith RPC Server 0.8.0.0-beta"
|
||||
putStrLn "Zenith RPC Server 0.9.0.0-beta"
|
||||
putStrLn "------------------------------"
|
||||
putStrLn $
|
||||
"Connected to " ++
|
||||
|
|
|
@ -13,3 +13,8 @@ source-repository-package
|
|||
type: git
|
||||
location: https://code.vergara.tech/Vergara_Tech/haskell-foreign-rust.git
|
||||
tag: 335e804454cd30da2c526457be37e477f71e4665
|
||||
|
||||
source-repository-package
|
||||
type: git
|
||||
location: https://code.vergara.tech/Vergara_Tech/persistent-sqlite.git
|
||||
tag: 85093ef51cb2bd245ac9a85925770fdb55afce9e
|
||||
|
|
|
@ -42,6 +42,8 @@ import Brick.Widgets.Core
|
|||
, joinBorders
|
||||
, padAll
|
||||
, padBottom
|
||||
, padLeft
|
||||
, padRight
|
||||
, padTop
|
||||
, setAvailableSize
|
||||
, str
|
||||
|
@ -63,7 +65,7 @@ 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, void, when)
|
||||
import Control.Monad.IO.Class (liftIO)
|
||||
import Control.Monad.Logger
|
||||
( LoggingT
|
||||
|
@ -90,37 +92,33 @@ import Lens.Micro.Mtl
|
|||
import Lens.Micro.TH
|
||||
import System.Hclip
|
||||
import Text.Printf
|
||||
import Text.Wrap
|
||||
( FillScope(..)
|
||||
, FillStrategy(..)
|
||||
, WrapSettings(..)
|
||||
, defaultWrapSettings
|
||||
, wrapTextToLines
|
||||
import Text.Wrap (FillScope(..), FillStrategy(..), WrapSettings(..))
|
||||
import ZcashHaskell.Keys
|
||||
( deriveUfvk
|
||||
, deriveUivk
|
||||
, encodeVK
|
||||
, generateWalletSeedPhrase
|
||||
)
|
||||
import ZcashHaskell.Keys (deriveUfvk, deriveUivk, generateWalletSeedPhrase)
|
||||
import ZcashHaskell.Orchard
|
||||
( getSaplingFromUA
|
||||
, isValidUnifiedAddress
|
||||
, parseAddress
|
||||
)
|
||||
import ZcashHaskell.Transparent
|
||||
( decodeTransparentAddress
|
||||
, encodeTransparentReceiver
|
||||
)
|
||||
import ZcashHaskell.Transparent (encodeTransparentReceiver)
|
||||
import ZcashHaskell.Types
|
||||
import ZcashHaskell.Utils (getBlockTime, makeZebraCall)
|
||||
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(..)
|
||||
, PrivacyPolicy(..)
|
||||
, ProposedNote(..)
|
||||
, SaplingSpendingKeyDB(..)
|
||||
, ShieldDeshieldOp(..)
|
||||
, TransparentSpendingKeyDB(..)
|
||||
, UnifiedAddressDB(..)
|
||||
, ValidAddressAPI(..)
|
||||
|
@ -129,6 +127,8 @@ import Zenith.Types
|
|||
, ZcashPool(..)
|
||||
, ZenithStatus(..)
|
||||
, ZenithUuid(..)
|
||||
, getFvk
|
||||
, getIvk
|
||||
)
|
||||
import Zenith.Utils
|
||||
( createZip321
|
||||
|
@ -136,11 +136,14 @@ import Zenith.Utils
|
|||
, displayZec
|
||||
, getChainTip
|
||||
, getZcashPrice
|
||||
, isNotEmptyAfterTrim
|
||||
, isRecipientValid
|
||||
, isRecipientValidGUI
|
||||
, jsonNumber
|
||||
, parseZcashPayment
|
||||
, scientificToInt
|
||||
, showAddress
|
||||
, toPhrase
|
||||
, validBarValue
|
||||
)
|
||||
|
||||
|
@ -170,6 +173,12 @@ data Name
|
|||
| URITransparentAddress
|
||||
| URISaplingAddress
|
||||
| URIUnifiedAddress
|
||||
| IViewingKeyName
|
||||
| IViewingKeyString
|
||||
| IViewingKeyBirthday
|
||||
| ISeedPhraseName
|
||||
| ISeedPhraseString
|
||||
| ISeedPhraseBirthday
|
||||
deriving (Eq, Show, Ord)
|
||||
|
||||
data DialogInput = DialogInput
|
||||
|
@ -201,7 +210,7 @@ newtype ShDshEntry = ShDshEntry
|
|||
makeLenses ''ShDshEntry
|
||||
|
||||
data PaymentInput = PaymentInput
|
||||
{ _pmtAddressPool :: ZcashPool
|
||||
{ _pmtAddressPool :: !ZcashPool
|
||||
, _pmtAmt :: !Scientific
|
||||
, _pmtMemo :: !T.Text
|
||||
} deriving (Show)
|
||||
|
@ -214,6 +223,22 @@ data URIText = URIText
|
|||
|
||||
makeLenses ''URIText
|
||||
|
||||
data IViewingKey = IViewingKey
|
||||
{ _iVkName :: !T.Text
|
||||
, _iVkString :: !T.Text
|
||||
, _iVkBHeight :: !Scientific
|
||||
} deriving (Show)
|
||||
|
||||
makeLenses ''IViewingKey
|
||||
|
||||
data ISeedPhrase = ISeedPhrase
|
||||
{ _iSpName :: !T.Text
|
||||
, _iSpString :: !T.Text
|
||||
, _iSpBHeight :: !Scientific
|
||||
} deriving (Show)
|
||||
|
||||
makeLenses ''ISeedPhrase
|
||||
|
||||
data DialogType
|
||||
= WName
|
||||
| AName
|
||||
|
@ -235,6 +260,8 @@ data DialogType
|
|||
| PaymentURIShow
|
||||
| PayUsingURIShow
|
||||
| ProcessURIMenu
|
||||
| ImportVKeyForm
|
||||
| ImportSeedPhraseForm
|
||||
|
||||
data DisplayType
|
||||
= AddrDisplay
|
||||
|
@ -292,6 +319,8 @@ data State = State
|
|||
, _vkData :: !T.Text
|
||||
, _pmtURIForm :: !(Form PaymentInput () Name)
|
||||
, _payUsingURIForm :: !(Form URIText () Name)
|
||||
, _importVKForm :: !(Form IViewingKey () Name)
|
||||
, _importSeedPhraseForm :: !(Form ISeedPhrase () Name)
|
||||
}
|
||||
|
||||
makeLenses ''State
|
||||
|
@ -334,7 +363,7 @@ drawUI s = [splashDialog s, helpDialog s, displayDialog s, inputDialog s, ui s]
|
|||
"(None)"
|
||||
(\(_, w) -> zcashWalletName $ entityVal w)
|
||||
(L.listSelectedElement (st ^. wallets))) ++
|
||||
" "))
|
||||
(isReadOnlyWallet $ L.listSelectedElement (st ^. wallets))))
|
||||
(C.hCenter
|
||||
(str
|
||||
("Account: " ++
|
||||
|
@ -347,15 +376,27 @@ drawUI s = [splashDialog s, helpDialog s, displayDialog s, inputDialog s, ui s]
|
|||
(str
|
||||
("Balance: " ++
|
||||
if st ^. network == MainNet
|
||||
then displayZec (st ^. balance)
|
||||
else displayTaz (st ^. balance))) <=>
|
||||
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 displayZec (st ^. unconfBalance)
|
||||
else displayTaz (st ^. unconfBalance))) <=>
|
||||
listAddressBox "Addresses" (st ^. addresses) <+>
|
||||
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
|
||||
(str ("Last block seen: " ++ show (st ^. syncBlock) ++ "\n")) <=>
|
||||
|
@ -404,7 +445,7 @@ drawUI s = [splashDialog s, helpDialog s, displayDialog s, inputDialog s, ui s]
|
|||
vBox
|
||||
[ C.hCenter
|
||||
(B.borderWithLabel (str titleLabel) $
|
||||
hLimit 25 $ vLimit 15 $ L.renderList drawF True l)
|
||||
hLimit 38 $ vLimit 15 $ L.renderList drawF True l)
|
||||
, str " "
|
||||
]
|
||||
listAddressBox ::
|
||||
|
@ -487,13 +528,20 @@ drawUI s = [splashDialog s, helpDialog s, displayDialog s, inputDialog s, ui s]
|
|||
D.renderDialog
|
||||
(D.dialog (Just (str " Select Wallet ")) Nothing 50)
|
||||
(selectListBox " Wallets " (st ^. wallets) listDrawWallet <=>
|
||||
C.hCenter
|
||||
(hBox
|
||||
[ capCommand "↑↓ " "move"
|
||||
, capCommand "↲ " "select"
|
||||
, capCommand "N" "ew"
|
||||
, capCommand "S" "how phrase"
|
||||
, xCommand
|
||||
vLimit
|
||||
4
|
||||
(hLimit 50 $
|
||||
withAttr abMBarAttr $
|
||||
vBox
|
||||
[ C.hCenter
|
||||
(capCommand "N" "ew" <+>
|
||||
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)
|
||||
]))
|
||||
ASelect ->
|
||||
D.renderDialog
|
||||
|
@ -601,8 +649,9 @@ drawUI s = [splashDialog s, helpDialog s, displayDialog s, inputDialog s, ui s]
|
|||
, capCommand "P" "ay using an URI"
|
||||
, capCommand3 "" "E" "xit"
|
||||
]))
|
||||
Blank -> emptyWidget
|
||||
--
|
||||
-- Address Book List
|
||||
--
|
||||
AdrBook ->
|
||||
D.renderDialog
|
||||
(D.dialog (Just $ str " Address Book ") Nothing 60)
|
||||
|
@ -629,21 +678,27 @@ drawUI s = [splashDialog s, helpDialog s, displayDialog s, inputDialog s, ui s]
|
|||
capCommand "S" "end Zcash" <+> capCommand3 "E" "x" "it")
|
||||
]
|
||||
])
|
||||
--
|
||||
-- Address Book new entry form
|
||||
--
|
||||
AdrBookForm ->
|
||||
D.renderDialog
|
||||
(D.dialog (Just $ str " New Address Book Entry ") Nothing 50)
|
||||
(renderForm (st ^. abForm) <=>
|
||||
C.hCenter
|
||||
(hBox [capCommand "↲" " Save", capCommand3 "" "<Esc>" " Cancel"]))
|
||||
--
|
||||
-- Address Book edit/update entry form
|
||||
--
|
||||
AdrBookUpdForm ->
|
||||
D.renderDialog
|
||||
(D.dialog (Just $ str " Edit Address Book Entry ") Nothing 50)
|
||||
(renderForm (st ^. abForm) <=>
|
||||
C.hCenter
|
||||
(hBox [capCommand "↲" " Save", capCommand3 "" "<Esc>" " Cancel"]))
|
||||
--
|
||||
-- Address Book edit/update entry form
|
||||
--
|
||||
AdrBookDelForm ->
|
||||
D.renderDialog
|
||||
(D.dialog (Just $ str " Delete Address Book Entry ") Nothing 50)
|
||||
|
@ -653,7 +708,9 @@ drawUI s = [splashDialog s, helpDialog s, displayDialog s, inputDialog s, ui s]
|
|||
[ capCommand "C" "onfirm delete"
|
||||
, capCommand3 "" "<Esc>" " Cancel"
|
||||
]))
|
||||
--
|
||||
-- Show Balance in FIAT form
|
||||
--
|
||||
ShowFIATBalance ->
|
||||
D.renderDialog
|
||||
(D.dialog
|
||||
|
@ -697,6 +754,35 @@ drawUI s = [splashDialog s, helpDialog s, displayDialog s, inputDialog s, ui s]
|
|||
]
|
||||
])
|
||||
--
|
||||
-- Import Viewing Key form
|
||||
--
|
||||
ImportVKeyForm -> do
|
||||
D.renderDialog
|
||||
(D.dialog (Just $ txt " Import Viewing Key ") Nothing 60)
|
||||
(withAttr abMBarAttr $
|
||||
vBox
|
||||
[ padAll 1 $ vBox [renderForm (st ^. importVKForm)]
|
||||
, C.hCenter
|
||||
(hBox
|
||||
[capCommand "↲" " Save", capCommand3 "" "<Esc>" " Cancel"])
|
||||
])
|
||||
--
|
||||
-- Import Seed Phrase form
|
||||
--
|
||||
ImportSeedPhraseForm -> do
|
||||
D.renderDialog
|
||||
(D.dialog (Just $ txt " Import Seed Phrase ") Nothing 60)
|
||||
(withAttr abMBarAttr $
|
||||
vBox
|
||||
[ padAll 1 $ vBox [renderForm (st ^. importSeedPhraseForm)]
|
||||
, C.hCenter
|
||||
(hBox
|
||||
[capCommand "↲" " Save", capCommand3 "" "<Esc>" " Cancel"])
|
||||
])
|
||||
--
|
||||
--
|
||||
Blank -> emptyWidget
|
||||
--
|
||||
splashDialog :: State -> Widget Name
|
||||
splashDialog st =
|
||||
if st ^. splashBox
|
||||
|
@ -708,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
|
||||
|
@ -777,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 $ strWrap $ st ^. msg)
|
||||
(padAll 1 $ (C.hCenter (strWrap (st ^. msg))))
|
||||
TxIdDisplay ->
|
||||
withBorderStyle unicodeBold $
|
||||
D.renderDialog
|
||||
|
@ -938,6 +1024,40 @@ mkNewABForm =
|
|||
label s w =
|
||||
padBottom (Pad 1) $ vLimit 1 (hLimit 10 $ str s <+> fill ' ') <+> w
|
||||
|
||||
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 "Birthday Height: " @@=
|
||||
editShowableFieldWithValidate
|
||||
iVkBHeight
|
||||
IViewingKeyBirthday
|
||||
isValidBirthdayHeight
|
||||
]
|
||||
where
|
||||
isValidBirthdayHeight :: Scientific -> Bool
|
||||
isValidBirthdayHeight h = h >= 1687104 -- NU5 upgrade block
|
||||
label s w = vLimit 1 (hLimit 18 $ str s <+> fill ' ') <+> w
|
||||
|
||||
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 "Birthday Height: " @@=
|
||||
editShowableFieldWithValidate
|
||||
iSpBHeight
|
||||
ISeedPhraseBirthday
|
||||
isValidBirthdayHeight
|
||||
]
|
||||
where
|
||||
isValidBirthdayHeight :: Scientific -> Bool
|
||||
isValidBirthdayHeight h = h >= 1687104 -- NU5 upgrade block
|
||||
label s w = vLimit 1 (hLimit 18 $ str s <+> fill ' ') <+> w
|
||||
|
||||
listDrawElement :: (Show a) => Bool -> a -> Widget Name
|
||||
listDrawElement sel a =
|
||||
let selStr s =
|
||||
|
@ -1199,6 +1319,8 @@ appEvent (BT.AppEvent t) = do
|
|||
PaymentURICreate -> return ()
|
||||
PaymentURIShow -> return ()
|
||||
PayUsingURIShow -> return ()
|
||||
ImportVKeyForm -> return ()
|
||||
ImportSeedPhraseForm -> return ()
|
||||
Blank -> do
|
||||
if s ^. timer == 90
|
||||
then do
|
||||
|
@ -1354,11 +1476,10 @@ appEvent (BT.VtyEvent e) = do
|
|||
BT.zoom inputForm $ handleFormEvent (BT.VtyEvent ev)
|
||||
WSelect -> do
|
||||
case e of
|
||||
V.EvKey (V.KChar 'x') [] ->
|
||||
BT.modify $ set dialogBox Blank
|
||||
V.EvKey V.KEnter [] -> do
|
||||
ns <- liftIO $ refreshWallet s
|
||||
BT.put ns
|
||||
BT.modify $ set timer 89
|
||||
BT.modify $ set dialogBox Blank
|
||||
V.EvKey (V.KChar 'n') [] -> do
|
||||
BT.modify $
|
||||
|
@ -1368,6 +1489,12 @@ appEvent (BT.VtyEvent e) = do
|
|||
BT.modify $ set dialogBox WName
|
||||
V.EvKey (V.KChar 's') [] ->
|
||||
BT.modify $ set displayBox PhraseDisplay
|
||||
V.EvKey (V.KChar 'i') [] ->
|
||||
BT.modify $ set dialogBox ImportVKeyForm
|
||||
V.EvKey (V.KChar 'p') [] ->
|
||||
BT.modify $ set dialogBox ImportSeedPhraseForm
|
||||
V.EvKey (V.KChar 'x') [] ->
|
||||
BT.modify $ set dialogBox Blank
|
||||
ev -> BT.zoom wallets $ L.handleListEvent ev
|
||||
ASelect -> do
|
||||
case e of
|
||||
|
@ -1378,11 +1505,20 @@ appEvent (BT.VtyEvent e) = do
|
|||
BT.put ns
|
||||
BT.modify $ set dialogBox Blank
|
||||
V.EvKey (V.KChar 'n') [] -> do
|
||||
BT.modify $
|
||||
set inputForm $
|
||||
updateFormState (DialogInput " New Account ") $
|
||||
s ^. inputForm
|
||||
BT.modify $ set dialogBox AName
|
||||
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
|
||||
|
@ -1813,19 +1949,16 @@ appEvent (BT.VtyEvent e) = do
|
|||
userError "Failed to select account"
|
||||
Just (_j, w1) -> return w1
|
||||
Just (_k, w) -> return w
|
||||
let osk =
|
||||
getOrchSK $
|
||||
zcashAccountOrchSpendKey $ entityVal selAccount
|
||||
let ssk =
|
||||
getSapSK $
|
||||
zcashAccountSapSpendKey $ entityVal selAccount
|
||||
let tsk =
|
||||
getTranSK $
|
||||
zcashAccountTPrivateKey $ entityVal selAccount
|
||||
fvk <- liftIO $ deriveUfvk (s ^. network) osk ssk tsk
|
||||
BT.modify $ set vkName "Full"
|
||||
BT.modify $ set vkData fvk
|
||||
BT.modify $ set dialogBox ViewingKeyShow
|
||||
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
|
||||
--
|
||||
|
@ -1842,22 +1975,19 @@ appEvent (BT.VtyEvent e) = do
|
|||
userError "Failed to select account"
|
||||
Just (_j, w1) -> return w1
|
||||
Just (_k, w) -> return w
|
||||
let osk =
|
||||
getOrchSK $
|
||||
zcashAccountOrchSpendKey $ entityVal selAccount
|
||||
let ssk =
|
||||
getSapSK $
|
||||
zcashAccountSapSpendKey $ entityVal selAccount
|
||||
let tsk =
|
||||
getTranSK $
|
||||
zcashAccountTPrivateKey $ entityVal selAccount
|
||||
ivk <- liftIO $ deriveUivk (s ^. network) osk ssk tsk
|
||||
BT.modify $ set vkName "Incomming"
|
||||
BT.modify $ set vkData ivk
|
||||
BT.modify $ set dialogBox ViewingKeyShow
|
||||
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 ()
|
||||
_ev -> return ()
|
||||
--
|
||||
-- Create Payment URI Form Events
|
||||
--
|
||||
|
@ -1959,15 +2089,15 @@ appEvent (BT.VtyEvent e) = do
|
|||
BT.modify $
|
||||
set msg "URI error - Invalid value "
|
||||
BT.modify $ set displayBox MsgDisplay
|
||||
Left e -> do
|
||||
BT.modify $ set msg e
|
||||
Left e1 -> do
|
||||
BT.modify $ set msg e1
|
||||
BT.modify $ set displayBox MsgDisplay
|
||||
V.EvKey V.KEsc [] -> BT.modify $ set dialogBox Blank
|
||||
ev -> do
|
||||
BT.zoom payUsingURIForm $ do
|
||||
handleFormEvent (BT.VtyEvent ev)
|
||||
--
|
||||
-- Open URI process form
|
||||
-- URI process form event handler
|
||||
--
|
||||
ProcessURIMenu -> do
|
||||
case e of
|
||||
|
@ -1982,7 +2112,132 @@ appEvent (BT.VtyEvent e) = do
|
|||
BT.modify $ set dialogBox PayUsingURIShow
|
||||
V.EvKey (V.KChar 'e') [] ->
|
||||
BT.modify $ set dialogBox Blank
|
||||
ev -> return ()
|
||||
_ev -> return ()
|
||||
--
|
||||
-- Import Viewing Key event handler
|
||||
--
|
||||
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
|
||||
--
|
||||
-- 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
|
||||
V.EvKey V.KEsc [] -> BT.modify $ set dialogBox Blank
|
||||
ev -> do
|
||||
BT.zoom importVKForm $ do
|
||||
handleFormEvent (BT.VtyEvent ev)
|
||||
--
|
||||
-- Import Seed Prhase event handler
|
||||
--
|
||||
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
|
||||
--
|
||||
-- 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
|
||||
V.EvKey V.KEsc [] -> BT.modify $ set dialogBox Blank
|
||||
ev -> do
|
||||
BT.zoom importSeedPhraseForm $ do
|
||||
handleFormEvent (BT.VtyEvent ev)
|
||||
--
|
||||
-- Process any other event
|
||||
--
|
||||
|
@ -2005,10 +2260,21 @@ appEvent (BT.VtyEvent e) = do
|
|||
V.EvKey (V.KChar 'a') [] ->
|
||||
BT.modify $ set dialogBox ASelect
|
||||
V.EvKey (V.KChar 's') [] -> do
|
||||
BT.modify $
|
||||
set txForm $
|
||||
mkSendForm (s ^. balance) (SendInput "" 0.0 "" Full)
|
||||
BT.modify $ set dialogBox SendTx
|
||||
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') [] ->
|
||||
|
@ -2143,7 +2409,7 @@ runZenithTUI config = do
|
|||
let host = c_zebraHost config
|
||||
let port = c_zebraPort config
|
||||
let dbFilePath = c_dbPath config
|
||||
let currencyCode = c_currencyCode config
|
||||
let currCode = c_currencyCode config
|
||||
pool <- runNoLoggingT $ initPool dbFilePath
|
||||
w <- try $ checkZebra host port :: IO (Either IOError ZebraGetInfo)
|
||||
case w of
|
||||
|
@ -2154,8 +2420,9 @@ runZenithTUI config = do
|
|||
case bc of
|
||||
Left e1 -> throwIO e1
|
||||
Right chainInfo -> do
|
||||
x <- initDb dbFilePath
|
||||
x <- runNoLoggingT $ initDb dbFilePath
|
||||
_ <- upgradeQrTable pool
|
||||
_ <- runNoLoggingT $ upgradeAccountTable pool
|
||||
case x of
|
||||
Left e2 -> throwIO $ userError e2
|
||||
Right x' -> do
|
||||
|
@ -2241,12 +2508,14 @@ runZenithTUI config = do
|
|||
(mkDeshieldForm 0 (ShDshEntry 0.0))
|
||||
tBal
|
||||
sBal
|
||||
currencyCode
|
||||
currCode
|
||||
0
|
||||
""
|
||||
""
|
||||
(mkPaymentURIForm $ PaymentInput OrchardPool 0.0 "")
|
||||
(mkPayUsingURIForm $ URIText "")
|
||||
(mkImportVKeyForm $ IViewingKey "" "" 0)
|
||||
(mkImportSeedPhraseForm $ ISeedPhrase "" "" 0)
|
||||
Left _e -> do
|
||||
print $
|
||||
"No Zebra node available on port " <>
|
||||
|
@ -2299,13 +2568,63 @@ refreshWallet s = do
|
|||
"Switched to wallet: " ++
|
||||
T.unpack (zcashWalletName $ entityVal selWallet)
|
||||
|
||||
refreshWalletAfterImport :: State -> IO State
|
||||
refreshWalletAfterImport s = do
|
||||
pool <- runNoLoggingT $ initPool $ s ^. dbPath
|
||||
walList <- getWallets pool $ s ^. network
|
||||
(ix, selWallet) <-
|
||||
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 (j, w1)
|
||||
Just (k, w) -> return (k, w)
|
||||
aL <- runNoLoggingT $ getAccounts pool $ entityKey selWallet
|
||||
let bl = zcashWalletLastSync $ entityVal $ walList !! ix
|
||||
addrL <-
|
||||
if not (null aL)
|
||||
then runNoLoggingT $ getAddresses pool $ entityKey $ head aL
|
||||
else return []
|
||||
bal <-
|
||||
if not (null aL)
|
||||
then getBalance pool $ entityKey $ head aL
|
||||
else return 0
|
||||
uBal <-
|
||||
if not (null aL)
|
||||
then getUnconfirmedBalance pool $ entityKey $ head aL
|
||||
else return 0
|
||||
txL <-
|
||||
if not (null addrL)
|
||||
then getUserTx pool $ entityKey $ head addrL
|
||||
else return []
|
||||
let wL = L.listReplace (Vec.fromList walList) (Just ix) (s ^. wallets)
|
||||
let aL' = L.listReplace (Vec.fromList aL) (Just 0) (s ^. accounts)
|
||||
let addrL' = L.listReplace (Vec.fromList addrL) (Just 0) (s ^. addresses)
|
||||
let txL' = L.listReplace (Vec.fromList txL) (Just 0) (s ^. transactions)
|
||||
return $
|
||||
s & wallets .~ wL & accounts .~ aL' & syncBlock .~ bl & balance .~ bal &
|
||||
unconfBalance .~
|
||||
uBal &
|
||||
addresses .~
|
||||
addrL' &
|
||||
transactions .~
|
||||
txL' &
|
||||
timer .~
|
||||
89 &
|
||||
msg .~
|
||||
"Import process completed. Switching to : " ++
|
||||
T.unpack (zcashWalletName $ entityVal selWallet)
|
||||
|
||||
addNewWallet :: T.Text -> State -> IO State
|
||||
addNewWallet n s = do
|
||||
sP <- generateWalletSeedPhrase
|
||||
pool <- runNoLoggingT $ initPool $ s ^. dbPath
|
||||
let bH = s ^. startBlock
|
||||
let netName = s ^. network
|
||||
r <- saveWallet pool $ ZcashWallet n (ZcashNetDB netName) (PhraseDB sP) bH 0
|
||||
r <-
|
||||
saveWallet pool $ ZcashWallet n (ZcashNetDB netName) (PhraseDB sP) bH 0 True
|
||||
case r of
|
||||
Nothing -> return $ s & msg .~ ("Wallet already exists: " ++ T.unpack n)
|
||||
Just _ -> do
|
||||
|
@ -2329,7 +2648,7 @@ addNewAccount n s = do
|
|||
Just (_k, w) -> return w
|
||||
aL' <- getMaxAccount pool (entityKey selWallet)
|
||||
zA <-
|
||||
try $ createZcashAccount n (aL' + 1) selWallet :: IO
|
||||
try $ createZcashAccount n (aL' + 1) (s ^. network) selWallet :: IO
|
||||
(Either IOError ZcashAccount)
|
||||
case zA of
|
||||
Left e -> return $ s & msg .~ "Error: " ++ show e
|
||||
|
@ -2551,3 +2870,27 @@ deshieldTransaction pool chan zHost zPort znet accId bl pnote = do
|
|||
case resp of
|
||||
Left e1 -> BC.writeBChan chan $ TickMsg $ "Zebra error: " ++ show e1
|
||||
Right txId -> BC.writeBChan chan $ TickTx txId
|
||||
|
||||
currentWallet :: Maybe (Int, Entity ZcashWallet) -> Maybe (Entity ZcashWallet)
|
||||
currentWallet cw =
|
||||
case cw of
|
||||
Nothing -> Nothing
|
||||
Just (_, w) -> Just w
|
||||
|
||||
isReadOnlyWallet :: Maybe (Int, Entity ZcashWallet) -> String
|
||||
isReadOnlyWallet cw =
|
||||
case cw of
|
||||
Nothing -> " "
|
||||
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
|
||||
|
|
File diff suppressed because it is too large
Load diff
298
src/Zenith/DB.hs
298
src/Zenith/DB.hs
|
@ -20,13 +20,14 @@ module Zenith.DB where
|
|||
|
||||
import Codec.Borsh
|
||||
import Control.Exception (SomeException(..), throw, throwIO, try)
|
||||
import Control.Monad (unless, when)
|
||||
import Control.Monad (forM_, unless, when)
|
||||
import Control.Monad.IO.Class (MonadIO, liftIO)
|
||||
import Control.Monad.Logger
|
||||
( LoggingT
|
||||
, NoLoggingT
|
||||
, logDebugN
|
||||
, logErrorN
|
||||
, logInfoN
|
||||
, runNoLoggingT
|
||||
, runStderrLoggingT
|
||||
)
|
||||
|
@ -52,6 +53,7 @@ import Haskoin.Transaction.Common
|
|||
)
|
||||
import System.Directory (doesFileExist, getHomeDirectory, removeFile)
|
||||
import System.FilePath ((</>))
|
||||
import ZcashHaskell.Keys (deriveUfvk, deriveUivk)
|
||||
import ZcashHaskell.Orchard
|
||||
( compareAddress
|
||||
, getSaplingFromUA
|
||||
|
@ -65,6 +67,7 @@ import ZcashHaskell.Types
|
|||
, OrchardBundle(..)
|
||||
, OrchardReceiver(..)
|
||||
, OrchardWitness(..)
|
||||
, Phrase(..)
|
||||
, SaplingAddress(..)
|
||||
, SaplingBundle(..)
|
||||
, SaplingReceiver(..)
|
||||
|
@ -80,11 +83,13 @@ import ZcashHaskell.Types
|
|||
, TxError(..)
|
||||
, UnifiedAddress(..)
|
||||
, ValidAddress(..)
|
||||
, ValidVk(..)
|
||||
, ZcashNet(..)
|
||||
)
|
||||
import Zenith.Tree (OrchardNode(..), SaplingNode(..), Tree(..), truncateTree)
|
||||
import Zenith.Types
|
||||
( AccountBalance(..)
|
||||
, AccountType(..)
|
||||
, HexStringDB(..)
|
||||
, OrchardSpendingKeyDB(..)
|
||||
, PhraseDB(..)
|
||||
|
@ -92,8 +97,10 @@ import Zenith.Types
|
|||
, RseedDB(..)
|
||||
, SaplingSpendingKeyDB(..)
|
||||
, ScopeDB(..)
|
||||
, TransparentSpendingKeyDB
|
||||
, TransparentSpendingKeyDB(..)
|
||||
, UnifiedAddressDB(..)
|
||||
, UnifiedFvkDB(..)
|
||||
, UnifiedIvkDB(..)
|
||||
, ZcashAccountAPI(..)
|
||||
, ZcashAddressAPI(..)
|
||||
, ZcashNetDB(..)
|
||||
|
@ -104,6 +111,16 @@ import Zenith.Types
|
|||
, ZenithUuid(..)
|
||||
)
|
||||
|
||||
share
|
||||
[mkPersist sqlSettings, mkMigrate "schemaMigration"]
|
||||
[persistLowerCase|
|
||||
ZenithSchema
|
||||
version Int
|
||||
action T.Text
|
||||
UniqueAction version action
|
||||
deriving Show Eq
|
||||
|]
|
||||
|
||||
share
|
||||
[mkPersist sqlSettings, mkMigrate "migrateAll"]
|
||||
[persistLowerCase|
|
||||
|
@ -113,15 +130,19 @@ share
|
|||
seedPhrase PhraseDB
|
||||
birthdayHeight Int
|
||||
lastSync Int default=0
|
||||
local Bool default=TRUE
|
||||
UniqueWallet name network
|
||||
deriving Show Eq
|
||||
ZcashAccount
|
||||
index Int
|
||||
walletId ZcashWalletId
|
||||
name T.Text
|
||||
orchSpendKey OrchardSpendingKeyDB
|
||||
sapSpendKey SaplingSpendingKeyDB
|
||||
tPrivateKey TransparentSpendingKeyDB
|
||||
orchSpendKey OrchardSpendingKeyDB Maybe default=NULL
|
||||
sapSpendKey SaplingSpendingKeyDB Maybe default=NULL
|
||||
tPrivateKey TransparentSpendingKeyDB Maybe default=NULL
|
||||
fvk UnifiedFvkDB Maybe default=NULL
|
||||
ivk UnifiedIvkDB Maybe default=NULL
|
||||
type AccountType default='Local'
|
||||
UniqueAccount index walletId
|
||||
UniqueAccName walletId name
|
||||
deriving Show Eq
|
||||
|
@ -325,6 +346,7 @@ toZcashWalletAPI w =
|
|||
(getNet $ zcashWalletNetwork $ entityVal w)
|
||||
(zcashWalletBirthdayHeight $ entityVal w)
|
||||
(zcashWalletLastSync $ entityVal w)
|
||||
(zcashWalletLocal $ entityVal w)
|
||||
|
||||
-- | @ZcashAccount@
|
||||
toZcashAccountAPI :: Entity ZcashAccount -> ZcashAccountAPI
|
||||
|
@ -333,6 +355,7 @@ toZcashAccountAPI a =
|
|||
(fromIntegral $ fromSqlKey $ entityKey a)
|
||||
(fromIntegral $ fromSqlKey $ zcashAccountWalletId $ entityVal a)
|
||||
(zcashAccountName $ entityVal a)
|
||||
(zcashAccountType $ entityVal a)
|
||||
|
||||
-- | @WalletAddress@
|
||||
toZcashAddressAPI :: Entity WalletAddress -> ZcashAddressAPI
|
||||
|
@ -425,61 +448,159 @@ orchToZcashNoteAPI pool n = do
|
|||
-- | Initializes the database
|
||||
initDb ::
|
||||
T.Text -- ^ The database path to check
|
||||
-> IO (Either String Bool)
|
||||
-> NoLoggingT IO (Either String Bool)
|
||||
initDb dbName = do
|
||||
j <-
|
||||
try $ PS.runSqlite dbName $ runMigrationQuiet migrateAll :: IO
|
||||
(Either SomeException [T.Text])
|
||||
case j of
|
||||
Left _e1 -> do
|
||||
pool <- runNoLoggingT $ initPool dbName
|
||||
wallets <-
|
||||
runNoLoggingT $
|
||||
PS.retryOnBusy $
|
||||
flip PS.runSqlPool pool $ do select . from $ table @ZcashWallet
|
||||
accounts <-
|
||||
runNoLoggingT $
|
||||
PS.retryOnBusy $
|
||||
flip PS.runSqlPool pool $ do select . from $ table @ZcashAccount
|
||||
abook <-
|
||||
runNoLoggingT $
|
||||
PS.retryOnBusy $
|
||||
flip PS.runSqlPool pool $ do select . from $ table @AddressBook
|
||||
hDir <- getHomeDirectory
|
||||
let backupDb = hDir </> "Zenith/.backup.db"
|
||||
checkDbFile <- doesFileExist backupDb
|
||||
when checkDbFile $ removeFile backupDb
|
||||
_ <- PS.runSqlite (T.pack backupDb) $ runMigrationQuiet migrateAll
|
||||
backupPool <- runNoLoggingT $ initPool $ T.pack backupDb
|
||||
_ <-
|
||||
runNoLoggingT $
|
||||
PS.retryOnBusy $
|
||||
flip PS.runSqlPool backupPool $ insertMany_ $ entityVal <$> wallets
|
||||
_ <-
|
||||
runNoLoggingT $
|
||||
PS.retryOnBusy $
|
||||
flip PS.runSqlPool backupPool $ insertMany_ $ entityVal <$> accounts
|
||||
_ <-
|
||||
runNoLoggingT $
|
||||
PS.retryOnBusy $
|
||||
flip PS.runSqlPool backupPool $ insertMany_ $ entityVal <$> abook
|
||||
clearWalletTransactions pool
|
||||
clearWalletData pool
|
||||
m <-
|
||||
try $ PS.runSqlite dbName $ runMigrationUnsafeQuiet migrateAll :: IO
|
||||
(Either SomeException [T.Text])
|
||||
case m of
|
||||
Left e2 -> return $ Left $ "Failed to migrate data tables" ++ show e2
|
||||
Right _ -> do
|
||||
return $ Right True
|
||||
x <-
|
||||
liftIO
|
||||
(try $ PS.runSqlite dbName $ runMigrationUnsafeQuiet schemaMigration :: IO
|
||||
(Either SomeException [T.Text]))
|
||||
case x of
|
||||
Left _ -> do
|
||||
logErrorN "Failed to initiate schema table"
|
||||
return $ Left "Failed to initiate schema table"
|
||||
Right _ -> do
|
||||
return $ Right False
|
||||
pool <- liftIO $ runNoLoggingT $ initPool dbName
|
||||
j <-
|
||||
liftIO
|
||||
(try $ PS.runSqlite dbName $ runMigrationQuiet migrateAll :: IO
|
||||
(Either SomeException [T.Text]))
|
||||
case j of
|
||||
Left e1 -> do
|
||||
logDebugN "Automatic migration failed, starting manual"
|
||||
versions <- liftIO $ getVersions pool
|
||||
migrateTables pool versions
|
||||
PS.runSqlite dbName $ printMigration migrateAll
|
||||
m <-
|
||||
liftIO
|
||||
(try $ PS.runSqlite dbName $ runMigration migrateAll :: IO
|
||||
(Either SomeException ()))
|
||||
case m of
|
||||
Left e2 -> do
|
||||
logErrorN $ "Failed to migrate data tables " <> T.pack (show e2)
|
||||
return $ Left $ "Failed to migrate data tables" ++ show e2
|
||||
Right _ -> do
|
||||
logInfoN "Migration of tables successful"
|
||||
return $ Right False
|
||||
Right _ -> do
|
||||
_ <-
|
||||
runNoLoggingT $
|
||||
PS.retryOnBusy $
|
||||
flip PS.runSqlPool pool $ do
|
||||
upsert (ZenithSchema 1 "Viewing Keys") []
|
||||
wallets <-
|
||||
runNoLoggingT $
|
||||
PS.retryOnBusy $
|
||||
flip PS.runSqlPool pool $ do select . from $ table @ZcashWallet
|
||||
accounts <-
|
||||
runNoLoggingT $
|
||||
PS.retryOnBusy $
|
||||
flip PS.runSqlPool pool $ do select . from $ table @ZcashAccount
|
||||
addresses <-
|
||||
runNoLoggingT $
|
||||
PS.retryOnBusy $
|
||||
flip PS.runSqlPool pool $ do select . from $ table @WalletAddress
|
||||
abook <-
|
||||
runNoLoggingT $
|
||||
PS.retryOnBusy $
|
||||
flip PS.runSqlPool pool $ do select . from $ table @AddressBook
|
||||
hDir <- liftIO getHomeDirectory
|
||||
let backupDb = hDir </> "Zenith/.backup.db"
|
||||
checkDbFile <- liftIO $ doesFileExist backupDb
|
||||
when checkDbFile $ liftIO $ removeFile backupDb
|
||||
_ <- PS.runSqlite (T.pack backupDb) $ runMigrationQuiet migrateAll
|
||||
backupPool <- liftIO $ runNoLoggingT $ initPool $ T.pack backupDb
|
||||
_ <-
|
||||
runNoLoggingT $
|
||||
PS.retryOnBusy $
|
||||
flip PS.runSqlPool backupPool $ insertMany_ $ entityVal <$> wallets
|
||||
_ <-
|
||||
runNoLoggingT $
|
||||
PS.retryOnBusy $
|
||||
flip PS.runSqlPool backupPool $ insertMany_ $ entityVal <$> accounts
|
||||
_ <-
|
||||
runNoLoggingT $
|
||||
PS.retryOnBusy $
|
||||
flip PS.runSqlPool backupPool $ insertMany_ $ entityVal <$> abook
|
||||
_ <-
|
||||
runNoLoggingT $
|
||||
PS.retryOnBusy $
|
||||
flip PS.runSqlPool backupPool $
|
||||
insertMany_ $ entityVal <$> addresses
|
||||
return $ Right False
|
||||
|
||||
migrateTables :: ConnectionPool -> [Int] -> NoLoggingT IO ()
|
||||
migrateTables pool versions = do
|
||||
unless (1 `elem` versions) $ do
|
||||
logDebugN "Making version 1 changes"
|
||||
_ <-
|
||||
runNoLoggingT $
|
||||
PS.retryOnBusy $
|
||||
flip PS.runSqlPool pool $ do
|
||||
rawExecute
|
||||
"ALTER TABLE \"zcash_wallet\" ADD COLUMN \"local\" BOOLEAN NOT NULL DEFAULT TRUE;"
|
||||
[]
|
||||
rawExecute
|
||||
"ALTER TABLE \"zcash_account\" RENAME COLUMN \"orch_spend_key\" TO \"orch_spend_key_old\";"
|
||||
[]
|
||||
rawExecute
|
||||
"ALTER TABLE \"zcash_account\" RENAME COLUMN \"sap_spend_key\" TO \"sap_spend_key_old\";"
|
||||
[]
|
||||
rawExecute
|
||||
"ALTER TABLE \"zcash_account\" RENAME COLUMN \"t_private_key\" TO \"t_private_key_old\";"
|
||||
[]
|
||||
rawExecute
|
||||
"ALTER TABLE \"zcash_account\" ADD COLUMN \"orch_spend_key\" VARCHAR NULL DEFAULT NULL;"
|
||||
[]
|
||||
rawExecute
|
||||
"ALTER TABLE \"zcash_account\" ADD COLUMN \"sap_spend_key\" VARCHAR NULL DEFAULT NULL;"
|
||||
[]
|
||||
rawExecute
|
||||
"ALTER TABLE \"zcash_account\" ADD COLUMN \"t_private_key\" VARCHAR NULL DEFAULT NULL;"
|
||||
[]
|
||||
rawExecute
|
||||
"UPDATE \"zcash_account\" SET \"orch_spend_key\" = \"orch_spend_key_old\", \"sap_spend_key\" = \"sap_spend_key_old\", \"t_private_key\" = \"t_private_key_old\" WHERE 1=1;"
|
||||
[]
|
||||
rawExecute
|
||||
"ALTER TABLE \"zcash_account\" DROP COLUMN \"orch_spend_key_old\";"
|
||||
[]
|
||||
rawExecute
|
||||
"ALTER TABLE \"zcash_account\" DROP COLUMN \"sap_spend_key_old\";"
|
||||
[]
|
||||
rawExecute
|
||||
"ALTER TABLE \"zcash_account\" DROP COLUMN \"t_private_key_old\";"
|
||||
[]
|
||||
rawExecute
|
||||
"ALTER TABLE \"zcash_account\" ADD COLUMN \"fvk\" VARCHAR NULL DEFAULT NULL;"
|
||||
[]
|
||||
rawExecute
|
||||
"ALTER TABLE \"zcash_account\" ADD COLUMN \"ivk\" VARCHAR NULL DEFAULT NULL;"
|
||||
[]
|
||||
rawExecute
|
||||
"ALTER TABLE \"zcash_account\" ADD COLUMN \"type\" VARCHAR NOT NULL DEFAULT 'Local';"
|
||||
[]
|
||||
_ <-
|
||||
runNoLoggingT $
|
||||
PS.retryOnBusy $
|
||||
flip PS.runSqlPool pool $ do upsert (ZenithSchema 1 "Viewing Keys") []
|
||||
logDebugN "Version 1 changes complete"
|
||||
|
||||
initPool :: T.Text -> NoLoggingT IO ConnectionPool
|
||||
initPool dbPath = do
|
||||
let dbInfo = PS.mkSqliteConnectionInfo dbPath
|
||||
PS.createSqlitePoolFromInfo dbInfo 5
|
||||
|
||||
getVersions :: ConnectionPool -> IO [Int]
|
||||
getVersions pool = do
|
||||
versions <-
|
||||
runNoLoggingT $
|
||||
PS.retryOnBusy $
|
||||
flip PS.runSqlPool pool $ do
|
||||
select $ do
|
||||
v <- from $ table @ZenithSchema
|
||||
orderBy [asc $ v ^. ZenithSchemaVersion]
|
||||
pure (v ^. ZenithSchemaVersion)
|
||||
return $ map (\(Value x) -> x) versions
|
||||
|
||||
-- | Upgrade the database
|
||||
upgradeDb ::
|
||||
T.Text -- ^ database path
|
||||
|
@ -508,6 +629,32 @@ walletExists pool n =
|
|||
where_ (wallets ^. ZcashWalletId ==. val (toSqlKey $ fromIntegral n))
|
||||
pure wallets
|
||||
|
||||
getVkWallet :: ConnectionPool -> IO (Maybe (Entity ZcashWallet))
|
||||
getVkWallet pool = do
|
||||
runNoLoggingT $
|
||||
PS.retryOnBusy $
|
||||
flip PS.runSqlPool pool $ do
|
||||
selectOne $ do
|
||||
wal <- from $ table @ZcashWallet
|
||||
where_ (wal ^. ZcashWalletName ==. val "Viewing Keys")
|
||||
where_ (wal ^. ZcashWalletLocal ==. val False)
|
||||
pure wal
|
||||
|
||||
saveVkWallet ::
|
||||
ConnectionPool -> ZcashNet -> Int -> IO (Maybe (Entity ZcashWallet))
|
||||
saveVkWallet pool znet bh = do
|
||||
runNoLoggingT $
|
||||
PS.retryOnBusy $
|
||||
flip PS.runSqlPool pool $
|
||||
insertUniqueEntity $
|
||||
ZcashWallet
|
||||
"Viewing Keys"
|
||||
(ZcashNetDB znet)
|
||||
(PhraseDB $ Phrase "")
|
||||
bh
|
||||
0
|
||||
False
|
||||
|
||||
getNetwork :: ConnectionPool -> WalletAddressId -> IO ZcashNet
|
||||
getNetwork pool a = do
|
||||
n <-
|
||||
|
@ -560,6 +707,23 @@ getAccounts pool w =
|
|||
where_ (accs ^. ZcashAccountWalletId ==. val w)
|
||||
pure accs
|
||||
|
||||
-- | Returns a list of accounts with no viewing keys. For database migration purposes
|
||||
getAccountsNoVKs ::
|
||||
ConnectionPool -- ^ The database path
|
||||
-> NoLoggingT IO [(Value ZcashNetDB, Entity ZcashAccount)]
|
||||
getAccountsNoVKs pool =
|
||||
PS.retryOnBusy $
|
||||
flip PS.runSqlPool pool $ do
|
||||
select $ do
|
||||
(wallet :& acc) <-
|
||||
from $ table @ZcashWallet `innerJoin` table @ZcashAccount `on`
|
||||
(\(wallet :& acc) ->
|
||||
wallet ^. ZcashWalletId ==. acc ^. ZcashAccountWalletId)
|
||||
where_
|
||||
(acc ^. ZcashAccountType ==. val Local &&.
|
||||
isNothing (acc ^. ZcashAccountFvk))
|
||||
pure (wallet ^. ZcashWalletNetwork, acc)
|
||||
|
||||
getAccountById ::
|
||||
ConnectionPool -> ZcashAccountId -> IO (Maybe (Entity ZcashAccount))
|
||||
getAccountById pool za = do
|
||||
|
@ -911,6 +1075,36 @@ upgradeQrTable pool = do
|
|||
[PersistText "TransparentPool", PersistText "Transparent"]
|
||||
return ()
|
||||
|
||||
upgradeAccountTable :: ConnectionPool -> NoLoggingT IO ()
|
||||
upgradeAccountTable pool = do
|
||||
accs <- liftIO $ runNoLoggingT $ getAccountsNoVKs pool
|
||||
logDebugN $ T.pack $ show $ length accs
|
||||
forM_ accs $ \(Value znet, a) -> do
|
||||
FullVk b <-
|
||||
liftIO $
|
||||
deriveUfvk
|
||||
(getNet znet)
|
||||
(getOrchSK <$> zcashAccountOrchSpendKey (entityVal a))
|
||||
(getSapSK <$> zcashAccountSapSpendKey (entityVal a))
|
||||
(getTranSK <$> zcashAccountTPrivateKey (entityVal a))
|
||||
IncomingVk c <-
|
||||
liftIO $
|
||||
deriveUivk
|
||||
(getNet znet)
|
||||
(getOrchSK <$> zcashAccountOrchSpendKey (entityVal a))
|
||||
(getSapSK <$> zcashAccountSapSpendKey (entityVal a))
|
||||
(getTranSK <$> zcashAccountTPrivateKey (entityVal a))
|
||||
runNoLoggingT $
|
||||
PS.retryOnBusy $
|
||||
flip PS.runSqlPool pool $ do
|
||||
update $ \w -> do
|
||||
set
|
||||
w
|
||||
[ ZcashAccountFvk =. just (val $ UnifiedFvkDB b)
|
||||
, ZcashAccountIvk =. just (val $ UnifiedIvkDB c)
|
||||
]
|
||||
where_ $ w ^. ZcashAccountId ==. val (entityKey a)
|
||||
|
||||
-- * Wallet
|
||||
-- | Get the block of the last transaction known to the wallet
|
||||
getMaxWalletBlock ::
|
||||
|
|
|
@ -24,7 +24,7 @@ import Data.Aeson
|
|||
import qualified Data.ByteString as BS
|
||||
import qualified Data.ByteString.Lazy as BL
|
||||
import Data.HexString (toText)
|
||||
import Data.Maybe (fromMaybe, isJust, isNothing)
|
||||
import Data.Maybe (fromJust, fromMaybe, isJust, isNothing)
|
||||
import Data.Scientific (Scientific, fromFloatDigits)
|
||||
import qualified Data.Text as T
|
||||
import qualified Data.Text.Encoding as E
|
||||
|
@ -32,7 +32,7 @@ import qualified Data.Text.Lazy as TL
|
|||
import qualified Data.Text.Lazy.Encoding as TLE
|
||||
import Data.Time.Clock.POSIX (posixSecondsToUTCTime)
|
||||
import qualified Data.UUID as U
|
||||
import Database.Esqueleto.Experimental (ConnectionPool, fromSqlKey)
|
||||
import Database.Esqueleto.Experimental (ConnectionPool, fromSqlKey, val)
|
||||
import Database.Persist
|
||||
import Lens.Micro ((&), (+~), (.~), (?~), (^.), set)
|
||||
import Lens.Micro.TH
|
||||
|
@ -43,7 +43,12 @@ import System.FilePath ((</>))
|
|||
import Text.Printf (printf)
|
||||
import Text.Wrap (FillScope(..), FillStrategy(..), WrapSettings(..), wrapText)
|
||||
import TextShow hiding (toText)
|
||||
import ZcashHaskell.Keys (deriveUfvk, deriveUivk, generateWalletSeedPhrase)
|
||||
import ZcashHaskell.Keys
|
||||
( deriveUfvk
|
||||
, deriveUivk
|
||||
, encodeVK
|
||||
, generateWalletSeedPhrase
|
||||
)
|
||||
import ZcashHaskell.Orchard
|
||||
( getSaplingFromUA
|
||||
, isValidUnifiedAddress
|
||||
|
@ -55,10 +60,13 @@ import ZcashHaskell.Transparent
|
|||
)
|
||||
import ZcashHaskell.Types
|
||||
( BlockResponse(..)
|
||||
, Phrase(..)
|
||||
, Scope(..)
|
||||
, ToBytes(..)
|
||||
, UnifiedAddress(..)
|
||||
, ValidAddress(..)
|
||||
, ValidVk(..)
|
||||
, ValidVk(..)
|
||||
, ZcashNet(..)
|
||||
, ZebraGetBlockChainInfo(..)
|
||||
, ZebraGetInfo(..)
|
||||
|
@ -74,6 +82,7 @@ import Zenith.Utils
|
|||
, displayAmount
|
||||
, getChainTip
|
||||
, getZcashPrice
|
||||
, isNotEmptyAfterTrim
|
||||
, isRecipientValidGUI
|
||||
, isValidString
|
||||
, isZecAddressValid
|
||||
|
@ -81,6 +90,7 @@ import Zenith.Utils
|
|||
, padWithZero
|
||||
, parseZcashPayment
|
||||
, showAddress
|
||||
, toPhrase
|
||||
, validBarValue
|
||||
)
|
||||
|
||||
|
@ -163,7 +173,7 @@ data AppEvent
|
|||
| StartSync
|
||||
| TreeSync
|
||||
| ShowFIATBalance
|
||||
| DisplayFIATBalance Double Double
|
||||
| DisplayFIATBalance !Double !Double
|
||||
| CloseFIATBalance
|
||||
| ViewingKeysClicked
|
||||
| PrepareViewingKey !VkTypeDef !(Maybe (Entity ZcashAccount))
|
||||
|
@ -181,6 +191,15 @@ data AppEvent
|
|||
| ClosePayUsingURI
|
||||
| ProcIfValidURI
|
||||
| PreparePaymentURIForm
|
||||
| SetTimerCount
|
||||
| ShowNViewingKey
|
||||
| CloseNVkShow
|
||||
| SaveViewKey
|
||||
| ReportVKeySaved
|
||||
| ShowNSeedPhrase
|
||||
| CloseNSpShow
|
||||
| SaveSeedPhrase
|
||||
| ReportSeedSaved
|
||||
deriving (Eq, Show)
|
||||
|
||||
data AppModel = AppModel
|
||||
|
@ -254,6 +273,14 @@ data AppModel = AppModel
|
|||
, _uriAddr :: !T.Text
|
||||
, _uriQRImage :: !(Maybe URIQrCode)
|
||||
, _uriQRInProgress :: !Bool
|
||||
, _nVkName :: !T.Text
|
||||
, _nVkString :: !T.Text
|
||||
, _nVkBirthday :: !Int
|
||||
, _nVkShow :: !Bool
|
||||
, _nSpName :: !T.Text
|
||||
, _nSpString :: !T.Text
|
||||
, _nSpBirthday :: !Int
|
||||
, _nSpShow :: !Bool
|
||||
} deriving (Eq, Show)
|
||||
|
||||
makeLenses ''AppModel
|
||||
|
@ -305,8 +332,6 @@ buildUI wenv model = widgetTree
|
|||
, txOverlay `nodeVisible` isJust (model ^. showTx)
|
||||
, sendTxOverlay `nodeVisible` model ^. openSend
|
||||
, txIdOverlay `nodeVisible` isJust (model ^. showId)
|
||||
, msgOverlay `nodeVisible` isJust (model ^. msg)
|
||||
, modalOverlay `nodeVisible` isJust (model ^. modalMsg)
|
||||
, adrbookOverlay `nodeVisible` model ^. showAdrBook
|
||||
, newAdrBkOverlay `nodeVisible` model ^. newAdrBkEntry
|
||||
, showABAddressOverlay (model ^. abdescrip) (model ^. abaddress) `nodeVisible`
|
||||
|
@ -319,17 +344,23 @@ buildUI wenv model = widgetTree
|
|||
, deShieldOverlay `nodeVisible` model ^. deShieldZec
|
||||
, dfBalOverlay `nodeVisible` model ^. displayFIATBalance
|
||||
, showVKOverlay `nodeVisible` model ^. viewingKeyDisplay
|
||||
, nViewingkeyOverlay `nodeVisible` model ^. nVkShow
|
||||
, nSeedPhraseOverlay `nodeVisible` model ^. nSpShow
|
||||
, paymentURIOverlay `nodeVisible` model ^. paymentURIDisplay
|
||||
, showURIInProgress `nodeVisible` model ^. uriQRInProgress
|
||||
, showURIOverlay `nodeVisible` model ^. showURIDisplay
|
||||
, pmtUsingURIOverlay `nodeVisible` model ^. usepmtURIOverlay
|
||||
, msgAdrBookOverlay `nodeVisible` isJust (model ^. msgAB)
|
||||
, msgOverlay `nodeVisible` isJust (model ^. msg)
|
||||
, modalOverlay `nodeVisible` isJust (model ^. modalMsg)
|
||||
]
|
||||
mainWindow =
|
||||
vstack
|
||||
[ windowHeader
|
||||
, spacer
|
||||
, balanceBox
|
||||
, balanceBox `nodeVisible`
|
||||
((zcashAccountType . entityVal <$> currentAccount) /=
|
||||
Just IncomingViewKey)
|
||||
, filler
|
||||
, mainPane
|
||||
, filler
|
||||
|
@ -359,7 +390,10 @@ buildUI wenv model = widgetTree
|
|||
, popup accPopup accListPopup
|
||||
]
|
||||
, filler
|
||||
, remixIcon remixErrorWarningFill `styleBasic` [textColor white]
|
||||
, label "Read-Only" `styleBasic` [textColor white] `nodeVisible`
|
||||
((zcashAccountType . entityVal <$> currentAccount) /= Just Local)
|
||||
, remixIcon remixErrorWarningFill `styleBasic` [textColor white] `nodeVisible`
|
||||
(model ^. network == TestNet)
|
||||
, label "Testnet" `styleBasic` [textColor white] `nodeVisible`
|
||||
(model ^. network == TestNet)
|
||||
] `styleBasic`
|
||||
|
@ -441,6 +475,29 @@ buildUI wenv model = widgetTree
|
|||
[alignLeft, onClick NewWallet]
|
||||
(hstack [label "Wallet", filler]) `styleBasic`
|
||||
[bgColor white, borderB 1 gray, padding 3]
|
||||
, box_
|
||||
[alignLeft, onClick ShowNViewingKey]
|
||||
(hstack [label "Import Viewing Key", filler]) `styleBasic`
|
||||
[bgColor white, borderB 1 gray, padding 3]
|
||||
, box_
|
||||
[alignLeft, onClick ShowNSeedPhrase]
|
||||
(hstack [label "Import Seed Phrase", filler]) `styleBasic`
|
||||
[bgColor white, borderB 1 gray, padding 3]
|
||||
])
|
||||
viewingKeysBox =
|
||||
box_
|
||||
[alignMiddle]
|
||||
(vstack
|
||||
[ box_
|
||||
[alignLeft, onClick (PrepareViewingKey VkFull currentAccount)]
|
||||
(hstack [label "Full VK", filler]) `styleBasic`
|
||||
[bgColor white, borderB 1 gray, padding 3]
|
||||
, box_
|
||||
[ alignLeft
|
||||
, onClick (PrepareViewingKey VkIncoming currentAccount)
|
||||
]
|
||||
(hstack [label "Incoming VK", filler]) `styleBasic`
|
||||
[bgColor white, borderB 1 gray, padding 3]
|
||||
])
|
||||
viewingKeysBox =
|
||||
box_
|
||||
|
@ -506,7 +563,9 @@ buildUI wenv model = widgetTree
|
|||
hstack
|
||||
[ addressBox
|
||||
, vstack
|
||||
[ mainButton "Send" ShowSend `styleBasic` [textFont "Bold"]
|
||||
[ mainButton "Send" ShowSend `nodeEnabled`
|
||||
((zcashAccountType . entityVal <$> currentAccount) == Just Local) `styleBasic`
|
||||
[textFont "Bold"]
|
||||
, txBox `nodeVisible` not (null $ model ^. transactions)
|
||||
]
|
||||
]
|
||||
|
@ -1128,38 +1187,196 @@ buildUI wenv model = widgetTree
|
|||
[]
|
||||
]
|
||||
showVKOverlay =
|
||||
-- alert CloseShowVK $
|
||||
box
|
||||
(vstack
|
||||
[ filler
|
||||
, hstack
|
||||
[ filler
|
||||
, box_
|
||||
[]
|
||||
(vstack
|
||||
[ box_
|
||||
[alignMiddle]
|
||||
(label ((model ^. vkTypeName) <> " Viewing Key") `styleBasic`
|
||||
[textFont "Bold", textColor white, textSize 12, padding 3]) `styleBasic`
|
||||
[bgColor btnColor, radius 2, padding 3]
|
||||
, spacer
|
||||
, hstack
|
||||
[filler, label_ (txtWrapN (model ^. vkData) 64) [multiline], filler]
|
||||
, spacer
|
||||
, hstack
|
||||
[ filler
|
||||
, button "Copy to Clipboard" $
|
||||
CopyViewingKey (model ^. vkTypeName) (model ^. vkData)
|
||||
, spacer
|
||||
, button "Close" $ CloseShowVK
|
||||
, filler
|
||||
]
|
||||
]) `styleBasic`
|
||||
[ filler
|
||||
, hstack
|
||||
[ filler
|
||||
, box_
|
||||
[]
|
||||
(vstack
|
||||
[ box_
|
||||
[alignMiddle]
|
||||
(label ((model ^. vkTypeName) <> " Viewing Key") `styleBasic`
|
||||
[ textFont "Bold"
|
||||
, textColor white
|
||||
, textSize 12
|
||||
, padding 3
|
||||
]) `styleBasic`
|
||||
[bgColor btnColor, radius 2, padding 3]
|
||||
, spacer
|
||||
, hstack
|
||||
[ filler
|
||||
, label_ (txtWrapN (model ^. vkData) 64) [multiline]
|
||||
, filler
|
||||
]
|
||||
, spacer
|
||||
, hstack
|
||||
[ filler
|
||||
, button "Copy to Clipboard" $
|
||||
CopyViewingKey
|
||||
(model ^. vkTypeName)
|
||||
(model ^. vkData)
|
||||
, spacer
|
||||
, button "Close" CloseShowVK
|
||||
, filler
|
||||
]
|
||||
]) `styleBasic`
|
||||
[radius 4, border 2 btnColor, bgColor white, padding 4]
|
||||
, filler
|
||||
]
|
||||
, filler
|
||||
] ) `styleBasic`
|
||||
, filler
|
||||
]
|
||||
, filler
|
||||
]) `styleBasic`
|
||||
[bgColor (white & L.a .~ 0.5)]
|
||||
nViewingkeyOverlay =
|
||||
box
|
||||
(vstack
|
||||
[ filler
|
||||
, hstack
|
||||
[ filler
|
||||
, box_
|
||||
[]
|
||||
(vstack
|
||||
[ box_
|
||||
[alignMiddle]
|
||||
(label "Import Viewing Key" `styleBasic`
|
||||
[ textFont "Bold"
|
||||
, textColor white
|
||||
, textSize 12
|
||||
, padding 3
|
||||
]) `styleBasic`
|
||||
[bgColor btnColor, radius 2, padding 3]
|
||||
, spacer
|
||||
, hstack
|
||||
[ filler
|
||||
, label "Account Name:" `styleBasic`
|
||||
[textFont "Bold", padding 3]
|
||||
, spacer
|
||||
, textField nVkName `styleBasic` [padding 3]
|
||||
, filler
|
||||
]
|
||||
, spacer
|
||||
, hstack
|
||||
[ filler
|
||||
, label "Viewing Key:" `styleBasic`
|
||||
[textFont "Bold", padding 3]
|
||||
, spacer
|
||||
, textField nVkString `styleBasic` [padding 3]
|
||||
, filler
|
||||
]
|
||||
, spacer
|
||||
, hstack
|
||||
[ filler
|
||||
, box_
|
||||
[alignMiddle]
|
||||
((label_
|
||||
(txtWrapN (model ^. nVkString) 80)
|
||||
[multiline]) `styleBasic`
|
||||
[textSize 10]) `styleBasic`
|
||||
[radius 4, border 2 blue, bgColor white, padding 4]
|
||||
, filler
|
||||
]
|
||||
, spacer
|
||||
, hstack
|
||||
[ spacer
|
||||
, label "Wallet's Birthday Height:" `styleBasic`
|
||||
[textFont "Bold", padding 3]
|
||||
, spacer
|
||||
, numericField_
|
||||
nVkBirthday
|
||||
[decimals 0, minValue 1687104] `styleBasic`
|
||||
[width 150]
|
||||
, filler
|
||||
]
|
||||
, spacer
|
||||
, hstack
|
||||
[ filler
|
||||
, button "Save Viewing Key" SaveViewKey
|
||||
, spacer
|
||||
, button "Close" CloseNVkShow
|
||||
, filler
|
||||
]
|
||||
]) `styleBasic`
|
||||
[radius 4, border 2 btnColor, bgColor white, padding 4]
|
||||
, filler
|
||||
]
|
||||
, filler
|
||||
]) `styleBasic`
|
||||
[bgColor (white & L.a .~ 0.5)]
|
||||
nSeedPhraseOverlay =
|
||||
box
|
||||
(vstack
|
||||
[ filler
|
||||
, hstack
|
||||
[ filler
|
||||
, box_
|
||||
[]
|
||||
(vstack
|
||||
[ box_
|
||||
[alignMiddle]
|
||||
(label "Import Seed Phrase" `styleBasic`
|
||||
[ textFont "Bold"
|
||||
, textColor white
|
||||
, textSize 12
|
||||
, padding 3
|
||||
]) `styleBasic`
|
||||
[bgColor btnColor, radius 2, padding 3]
|
||||
, spacer
|
||||
, hstack
|
||||
[ filler
|
||||
, label "Account Name:" `styleBasic`
|
||||
[textFont "Bold", padding 3]
|
||||
, spacer
|
||||
, textField nSpName `styleBasic` [padding 3]
|
||||
, filler
|
||||
]
|
||||
, spacer
|
||||
, hstack
|
||||
[ filler
|
||||
, label "Seed Phrase:" `styleBasic`
|
||||
[textFont "Bold", padding 3]
|
||||
, spacer
|
||||
, textField nSpString `styleBasic` [padding 3]
|
||||
, filler
|
||||
]
|
||||
, spacer
|
||||
, hstack
|
||||
[ filler
|
||||
, box_
|
||||
[alignMiddle]
|
||||
((label_
|
||||
(txtWrapN (model ^. nSpString) 80)
|
||||
[multiline]) `styleBasic`
|
||||
[textSize 10]) `styleBasic`
|
||||
[radius 4, border 2 blue, bgColor white, padding 4]
|
||||
, filler
|
||||
]
|
||||
, spacer
|
||||
, hstack
|
||||
[ spacer
|
||||
, label "Wallet's Birthday Height:" `styleBasic`
|
||||
[textFont "Bold", padding 3]
|
||||
, spacer
|
||||
, numericField_
|
||||
nSpBirthday
|
||||
[decimals 0, minValue 1687104] `styleBasic`
|
||||
[width 150]
|
||||
, filler
|
||||
]
|
||||
, spacer
|
||||
, hstack
|
||||
[ filler
|
||||
, button "Save Seed Phrase" SaveSeedPhrase
|
||||
, spacer
|
||||
, button "Close" CloseNSpShow
|
||||
, filler
|
||||
]
|
||||
]) `styleBasic`
|
||||
[radius 4, border 2 btnColor, bgColor white, padding 4]
|
||||
, filler
|
||||
]
|
||||
, filler
|
||||
]) `styleBasic`
|
||||
[bgColor (white & L.a .~ 0.5)]
|
||||
shieldOverlay =
|
||||
box
|
||||
|
@ -1468,6 +1685,7 @@ buildUI wenv model = widgetTree
|
|||
]) `styleBasic`
|
||||
[bgColor (white & L.a .~ 0.5)]
|
||||
|
||||
-- alert CloseShowVK $
|
||||
generateQRCodes :: Config -> IO ()
|
||||
generateQRCodes config = do
|
||||
let dbFilePath = c_dbPath config
|
||||
|
@ -1570,15 +1788,19 @@ handleEvent wenv node model evt =
|
|||
False
|
||||
]
|
||||
NewAccount wal ->
|
||||
[ Model $
|
||||
model & confirmTitle ?~ "New Account" & confirmAccept .~ "Create" &
|
||||
confirmCancel .~
|
||||
"Cancel" &
|
||||
confirmEvent .~
|
||||
SaveAccount wal &
|
||||
menuPopup .~
|
||||
False
|
||||
]
|
||||
if (zcashWalletLocal . entityVal <$> wal) == Just True
|
||||
then [ Model $
|
||||
model & confirmTitle ?~ "New Account" & confirmAccept .~ "Create" &
|
||||
confirmCancel .~
|
||||
"Cancel" &
|
||||
confirmEvent .~
|
||||
SaveAccount wal &
|
||||
menuPopup .~
|
||||
False
|
||||
]
|
||||
else [ Event $ ShowError "Wallet is read-only."
|
||||
, Model $ model & menuPopup .~ False
|
||||
]
|
||||
NewWallet ->
|
||||
[ Model $
|
||||
model & confirmTitle ?~ "New Wallet" & confirmAccept .~ "Create" &
|
||||
|
@ -1592,12 +1814,6 @@ handleEvent wenv node model evt =
|
|||
ConfirmCancel -> [Model $ model & confirmTitle .~ Nothing & mainInput .~ ""]
|
||||
ViewingKeysClicked ->
|
||||
[Model $ model & viewingKeyPopup .~ not (model ^. viewingKeyPopup)]
|
||||
NewAddress vk ->
|
||||
[ Model $
|
||||
model & confirmTitle ?~ "New Address" & confirmCancel .~ "Cancel" &
|
||||
menuPopup .~
|
||||
False
|
||||
]
|
||||
ShowSeed -> [Model $ model & showSeed .~ True & menuPopup .~ False]
|
||||
ShowSend ->
|
||||
[ Model $
|
||||
|
@ -1627,8 +1843,10 @@ handleEvent wenv node model evt =
|
|||
CancelSend ->
|
||||
[ Model $
|
||||
model & openSend .~ False & sendRecipient .~ "" & sendAmount .~ 0.0 &
|
||||
sendMemo .~ "" &
|
||||
uriString .~ ""
|
||||
sendMemo .~
|
||||
"" &
|
||||
uriString .~
|
||||
""
|
||||
]
|
||||
SaveAddress acc ->
|
||||
if T.length (model ^. mainInput) > 1
|
||||
|
@ -1741,7 +1959,8 @@ handleEvent wenv node model evt =
|
|||
pool <-
|
||||
runNoLoggingT $ initPool $ c_dbPath $ model ^. configuration
|
||||
chgAddr <- getInternalAddresses pool $ entityKey acc
|
||||
if not (null chgAddr)
|
||||
if not (null chgAddr) ||
|
||||
(zcashAccountType (entityVal acc) == IncomingViewKey)
|
||||
then return $ SetPool OrchardPool
|
||||
else return $ NewInternalAddress currentAccount
|
||||
]
|
||||
|
@ -1904,6 +2123,85 @@ handleEvent wenv node model evt =
|
|||
model & vkTypeName .~ "" & vkData .~ "" & viewingKeyDisplay .~ False
|
||||
]
|
||||
--
|
||||
-- Show Import Viewing Key Form
|
||||
--
|
||||
SetTimerCount -> [Model $ model & timer .~ 85]
|
||||
ShowNViewingKey -> [Model $ model & nVkShow .~ True & menuPopup .~ False]
|
||||
CloseNVkShow -> [Model $ model & nVkShow .~ False]
|
||||
SaveViewKey ->
|
||||
[ Task $ do
|
||||
pool <- runNoLoggingT $ initPool $ c_dbPath $ model ^. configuration
|
||||
let inKey = parseVK $ model ^. nVkString
|
||||
case inKey of
|
||||
Nothing -> return $ ShowError "Invalid viewing key"
|
||||
Just k -> do
|
||||
x <-
|
||||
importViewingKey
|
||||
pool
|
||||
(model ^. nVkName)
|
||||
(model ^. network)
|
||||
k
|
||||
(model ^. nVkBirthday)
|
||||
case x of
|
||||
Left e -> return $ ShowError e
|
||||
Right i -> return $ ReportVKeySaved
|
||||
]
|
||||
--
|
||||
ReportVKeySaved ->
|
||||
[ Task $ do
|
||||
generateQRCodes $ model ^. configuration
|
||||
pool <- runNoLoggingT $ initPool $ c_dbPath $ model ^. configuration
|
||||
wL <- getWallets pool (model ^. network)
|
||||
return $ LoadWallets wL
|
||||
, Event $ CloseNVkShow
|
||||
, Event $ ShowMessage "Viewing Key imported!"
|
||||
, Event $ StartSync
|
||||
]
|
||||
--
|
||||
-- Show Import Seed Phrase Form
|
||||
--
|
||||
SaveSeedPhrase ->
|
||||
[ 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"
|
||||
else return $ ShowError "Seed Phrase name invalid!"
|
||||
]
|
||||
--
|
||||
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
|
||||
]
|
||||
CloseNSpShow -> [Model $ model & nSpShow .~ False]
|
||||
--
|
||||
-- Show Balance in FIAT
|
||||
--
|
||||
DisplayFIATBalance zpr abal ->
|
||||
|
@ -1924,8 +2222,9 @@ handleEvent wenv node model evt =
|
|||
--
|
||||
PrepareViewingKey vkType cAcc ->
|
||||
case vkType of
|
||||
VkFull -> [Task $ getFullVk (model ^. network) cAcc]
|
||||
VkIncoming -> [Task $ getIncomingVk (model ^. network) cAcc]
|
||||
VkFull -> [Task $ getFullVkFromAcc cAcc]
|
||||
VkIncoming -> [Task $ getIncomingVkFromAcc cAcc]
|
||||
VkNone -> []
|
||||
--
|
||||
-- Show Viewing Keys
|
||||
--
|
||||
|
@ -1946,6 +2245,7 @@ handleEvent wenv node model evt =
|
|||
menuPopup .~
|
||||
False
|
||||
]
|
||||
VkNone -> []
|
||||
--
|
||||
-- Display PaymentURI Form
|
||||
--
|
||||
|
@ -1963,7 +2263,8 @@ handleEvent wenv node model evt =
|
|||
menuPopup .~
|
||||
False
|
||||
]
|
||||
ClosePaymentURIForm -> [Model $ model & paymentURIDisplay .~ False & uriString .~ ""]
|
||||
ClosePaymentURIForm ->
|
||||
[Model $ model & paymentURIDisplay .~ False & uriString .~ ""]
|
||||
--
|
||||
-- Generate URI
|
||||
--
|
||||
|
@ -1997,7 +2298,9 @@ handleEvent wenv node model evt =
|
|||
-- Display Pay using URI Form
|
||||
--
|
||||
DisplayPayUsingURI ->
|
||||
[Model $ model & usepmtURIOverlay .~ True & menuPopup .~ False & uriString .~ ""]
|
||||
[ Model $
|
||||
model & usepmtURIOverlay .~ True & menuPopup .~ False & uriString .~ ""
|
||||
]
|
||||
ClosePayUsingURI -> [Model $ model & usepmtURIOverlay .~ False]
|
||||
ProcIfValidURI -> do
|
||||
let zp = parseZcashPayment $ T.unpack (model ^. uriString)
|
||||
|
@ -2126,8 +2429,12 @@ handleEvent wenv node model evt =
|
|||
pool <- runNoLoggingT $ initPool $ c_dbPath $ model ^. configuration
|
||||
accIx <- getMaxAccount pool $ entityKey w'
|
||||
newAcc <-
|
||||
try $ createZcashAccount n (accIx + 1) w' :: IO
|
||||
(Either IOError ZcashAccount)
|
||||
try $
|
||||
createZcashAccount
|
||||
n
|
||||
(accIx + 1)
|
||||
(getNet $ zcashWalletNetwork $ entityVal w')
|
||||
w' :: IO (Either IOError ZcashAccount)
|
||||
case newAcc of
|
||||
Left e -> return $ ShowError "Failed to create account"
|
||||
Right newAcc' -> do
|
||||
|
@ -2158,6 +2465,7 @@ handleEvent wenv node model evt =
|
|||
(PhraseDB sP)
|
||||
(zgb_blocks chainInfo)
|
||||
0
|
||||
True
|
||||
case r of
|
||||
Nothing -> return $ ShowError "Wallet already exists"
|
||||
Just _ -> do
|
||||
|
@ -2207,35 +2515,51 @@ handleEvent wenv node model evt =
|
|||
--
|
||||
procIfValidURI :: T.Text -> IO AppEvent
|
||||
procIfValidURI ustr = do
|
||||
return $ ShowSend
|
||||
return ShowSend
|
||||
--
|
||||
-- Get Full Viewing Key
|
||||
--
|
||||
getFullVk :: ZcashNet -> Maybe (Entity ZcashAccount) -> IO AppEvent
|
||||
getFullVk n cAcc = do
|
||||
-- getFullVk :: ZcashNet -> Maybe (Entity ZcashAccount) -> IO AppEvent
|
||||
-- getFullVk n cAcc = do
|
||||
-- case cAcc of
|
||||
-- Nothing ->
|
||||
-- return $ ShowMessage "Viewing Key Error: No account selected!"
|
||||
-- Just acc -> do
|
||||
-- let osk =
|
||||
-- getOrchSK $ fromJust $ zcashAccountOrchSpendKey $ entityVal acc
|
||||
-- let ssk =
|
||||
-- getSapSK $ fromJust $ zcashAccountSapSpendKey $ entityVal acc
|
||||
-- let tsk =
|
||||
-- getTranSK $ fromJust $ zcashAccountTPrivateKey $ entityVal acc
|
||||
-- fvk <- deriveUfvk n (Just osk) (Just ssk) (Just tsk)
|
||||
-- return $ ShowViewingKey VkFull (encodeVK fvk)
|
||||
--
|
||||
-- Get Full Viewing Key from Account Record
|
||||
--
|
||||
getFullVkFromAcc :: Maybe (Entity ZcashAccount) -> IO AppEvent
|
||||
getFullVkFromAcc cAcc = do
|
||||
case cAcc of
|
||||
Nothing ->
|
||||
return $ ShowMessage "Viewing Key Error: No account selected!"
|
||||
Just acc -> do
|
||||
let osk = getOrchSK $ zcashAccountOrchSpendKey $ entityVal acc
|
||||
let ssk = getSapSK $ zcashAccountSapSpendKey $ entityVal acc
|
||||
let tsk = getTranSK $ zcashAccountTPrivateKey $ entityVal acc
|
||||
fvk <- deriveUfvk n osk ssk tsk
|
||||
return $ ShowViewingKey VkFull fvk
|
||||
case zcashAccountFvk $ entityVal acc of
|
||||
Nothing -> return $ ShowMessage "No full viewing key available."
|
||||
Just fvk ->
|
||||
return $ ShowViewingKey VkFull (encodeVK $ FullVk $ getFvk fvk)
|
||||
--
|
||||
-- Get Incoming Viewing Key
|
||||
-- Get Incoming Viewing Key from Account Record
|
||||
--
|
||||
getIncomingVk :: ZcashNet -> Maybe (Entity ZcashAccount) -> IO AppEvent
|
||||
getIncomingVk n cAcc = do
|
||||
getIncomingVkFromAcc :: Maybe (Entity ZcashAccount) -> IO AppEvent
|
||||
getIncomingVkFromAcc cAcc = do
|
||||
case cAcc of
|
||||
Nothing ->
|
||||
return $ ShowMessage "Viewing Key Error: No account selected!"
|
||||
Just acc -> do
|
||||
let osk = getOrchSK $ zcashAccountOrchSpendKey $ entityVal acc
|
||||
let ssk = getSapSK $ zcashAccountSapSpendKey $ entityVal acc
|
||||
let tsk = getTranSK $ zcashAccountTPrivateKey $ entityVal acc
|
||||
ivk <- deriveUivk n osk ssk tsk
|
||||
return $ ShowViewingKey VkIncoming ivk
|
||||
case zcashAccountIvk $ entityVal acc of
|
||||
Nothing -> return $ ShowMessage "No incoming viewing key available."
|
||||
Just ivk ->
|
||||
return $
|
||||
ShowViewingKey VkIncoming (encodeVK $ IncomingVk $ getIvk ivk)
|
||||
--
|
||||
-- Get curret zcash address
|
||||
--
|
||||
|
@ -2511,8 +2835,9 @@ runZenithGUI config = do
|
|||
case bc of
|
||||
Left e1 -> throwIO e1
|
||||
Right chainInfo -> do
|
||||
x <- initDb dbFilePath
|
||||
x <- runNoLoggingT $ initDb dbFilePath
|
||||
_ <- upgradeQrTable pool
|
||||
_ <- runNoLoggingT $ upgradeAccountTable pool
|
||||
case x of
|
||||
Left e2 -> throwIO $ userError e2
|
||||
Right x' -> do
|
||||
|
@ -2632,11 +2957,19 @@ runZenithGUI config = do
|
|||
""
|
||||
Nothing
|
||||
False
|
||||
""
|
||||
""
|
||||
0
|
||||
False
|
||||
""
|
||||
""
|
||||
0
|
||||
False
|
||||
startApp model handleEvent buildUI (params hD)
|
||||
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
|
||||
|
|
|
@ -42,6 +42,7 @@ import ZcashHaskell.Types
|
|||
( BlockResponse(..)
|
||||
, RpcError(..)
|
||||
, Scope(..)
|
||||
, ValidVk(..)
|
||||
, ZcashNet(..)
|
||||
, ZebraGetBlockChainInfo(..)
|
||||
)
|
||||
|
@ -51,6 +52,8 @@ import Zenith.Core
|
|||
, createCustomWalletAddress
|
||||
, createZcashAccount
|
||||
, deshieldNotes
|
||||
, importViewingKey
|
||||
, parseVK
|
||||
, prepareTxV2
|
||||
, shieldTransparentNotes
|
||||
, syncWallet
|
||||
|
@ -96,14 +99,15 @@ import Zenith.DB
|
|||
import Zenith.Scanner (checkIntegrity, processTx, updateConfs)
|
||||
import Zenith.Types
|
||||
( AccountBalance(..)
|
||||
, AccountType(..)
|
||||
, Config(..)
|
||||
, HexStringDB(..)
|
||||
, OrchardSpendingKeyDB(..)
|
||||
, PhraseDB(..)
|
||||
, PrivacyPolicy(..)
|
||||
, ProposedNote(..)
|
||||
, SaplingSpendingKeyDB(..)
|
||||
, TransparentSpendingKeyDB(..)
|
||||
, UnifiedFvkDB(..)
|
||||
, UnifiedIvkDB(..)
|
||||
, ZcashAccountAPI(..)
|
||||
, ZcashAddressAPI(..)
|
||||
, ZcashNetDB(..)
|
||||
|
@ -130,6 +134,7 @@ data ZenithMethod
|
|||
| DeshieldFunds
|
||||
| GetFVK
|
||||
| GetIVK
|
||||
| ImportVK
|
||||
| UnknownMethod
|
||||
deriving (Eq, Prelude.Show)
|
||||
|
||||
|
@ -149,6 +154,7 @@ instance ToJSON ZenithMethod where
|
|||
toJSON DeshieldFunds = Data.Aeson.String "deshieldfunds"
|
||||
toJSON GetFVK = Data.Aeson.String "getfullvk"
|
||||
toJSON GetIVK = Data.Aeson.String "getincomingvk"
|
||||
toJSON ImportVK = Data.Aeson.String "importvk"
|
||||
toJSON UnknownMethod = Data.Aeson.Null
|
||||
|
||||
instance FromJSON ZenithMethod where
|
||||
|
@ -169,6 +175,7 @@ instance FromJSON ZenithMethod where
|
|||
"deshieldfunds" -> pure DeshieldFunds
|
||||
"getfullvk" -> pure GetFVK
|
||||
"getincomingvk" -> pure GetIVK
|
||||
"importvk" -> pure ImportVK
|
||||
_ -> pure UnknownMethod
|
||||
|
||||
data ZenithParams
|
||||
|
@ -187,6 +194,7 @@ data ZenithParams
|
|||
| ShieldNotesParams !Int
|
||||
| DeshieldParams !Int !Scientific
|
||||
| ViewingKeyParams !Int
|
||||
| ImportVkParams !T.Text !T.Text !Int
|
||||
deriving (Eq, Prelude.Show)
|
||||
|
||||
instance ToJSON ZenithParams where
|
||||
|
@ -215,6 +223,9 @@ instance ToJSON ZenithParams where
|
|||
toJSON (DeshieldParams i s) =
|
||||
Data.Aeson.Array $ V.fromList [jsonNumber i, Data.Aeson.Number s]
|
||||
toJSON (ViewingKeyParams i) = Data.Aeson.Array $ V.fromList [jsonNumber i]
|
||||
toJSON (ImportVkParams n k b) =
|
||||
Data.Aeson.Array $
|
||||
V.fromList [Data.Aeson.String n, Data.Aeson.String k, jsonNumber b]
|
||||
|
||||
data ZenithResponse
|
||||
= InfoResponse !T.Text !ZenithInfo
|
||||
|
@ -561,6 +572,18 @@ instance FromJSON RpcCall where
|
|||
pure $ RpcCall v i GetIVK (ViewingKeyParams x)
|
||||
else pure $ RpcCall v i GetIVK BadParams
|
||||
_anyOther -> pure $ RpcCall v i GetIVK BadParams
|
||||
ImportVK -> do
|
||||
p <- obj .: "params"
|
||||
case p of
|
||||
Array a ->
|
||||
if V.length a == 3
|
||||
then do
|
||||
x <- parseJSON $ a V.! 0
|
||||
y <- parseJSON $ a V.! 1
|
||||
z <- parseJSON $ a V.! 2
|
||||
pure $ RpcCall v i ImportVK (ImportVkParams x y z)
|
||||
else pure $ RpcCall v i ImportVK BadParams
|
||||
_anyOther -> pure $ RpcCall v i ImportVK BadParams
|
||||
|
||||
type ZenithRPC
|
||||
= "status" :> Get '[ JSON] Value :<|> BasicAuth "zenith-realm" Bool :> ReqBody
|
||||
|
@ -583,7 +606,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
|
||||
|
@ -659,7 +682,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 ->
|
||||
|
@ -706,9 +729,12 @@ zenithServer state = getinfo :<|> handleRPC
|
|||
acc <- liftIO $ getAccountById pool $ toSqlKey i
|
||||
case acc of
|
||||
Just acc' -> do
|
||||
c <- liftIO $ getPoolBalance pool $ entityKey acc'
|
||||
u <- liftIO $ getUnconfPoolBalance pool $ entityKey acc'
|
||||
return $ BalanceResponse (callId req) c u
|
||||
if zcashAccountType (entityVal acc') /= IncomingViewKey
|
||||
then do
|
||||
c <- liftIO $ getPoolBalance pool $ entityKey acc'
|
||||
u <- liftIO $ getUnconfPoolBalance pool $ entityKey acc'
|
||||
return $ BalanceResponse (callId req) c u
|
||||
else return $ readOnlyError $ callId req
|
||||
Nothing ->
|
||||
return $
|
||||
ErrorResponse (callId req) (-32006) "Account does not exist."
|
||||
|
@ -737,6 +763,7 @@ zenithServer state = getinfo :<|> handleRPC
|
|||
(PhraseDB sP)
|
||||
(w_startBlock state)
|
||||
0
|
||||
True
|
||||
case r of
|
||||
Nothing ->
|
||||
return $
|
||||
|
@ -766,27 +793,35 @@ zenithServer state = getinfo :<|> handleRPC
|
|||
case w of
|
||||
Just w' -> do
|
||||
aIdx <- liftIO $ getMaxAccount pool $ entityKey w'
|
||||
nAcc <-
|
||||
liftIO
|
||||
(try $ createZcashAccount t (aIdx + 1) w' :: IO
|
||||
(Either IOError ZcashAccount))
|
||||
case nAcc of
|
||||
Left e ->
|
||||
return $
|
||||
ErrorResponse (callId req) (-32010) $ T.pack $ show e
|
||||
Right nAcc' -> do
|
||||
r <- liftIO $ saveAccount pool nAcc'
|
||||
case r of
|
||||
Nothing ->
|
||||
if zcashWalletLocal $ entityVal w'
|
||||
then do
|
||||
nAcc <-
|
||||
liftIO
|
||||
(try $
|
||||
createZcashAccount
|
||||
t
|
||||
(aIdx + 1)
|
||||
(getNet $ zcashWalletNetwork $ entityVal w')
|
||||
w' :: IO (Either IOError ZcashAccount))
|
||||
case nAcc of
|
||||
Left e ->
|
||||
return $
|
||||
ErrorResponse
|
||||
(callId req)
|
||||
(-32007)
|
||||
"Entity with that name already exists."
|
||||
Just x ->
|
||||
return $
|
||||
NewItemResponse (callId req) $
|
||||
fromSqlKey $ entityKey x
|
||||
ErrorResponse (callId req) (-32010) $
|
||||
T.pack $ show e
|
||||
Right nAcc' -> do
|
||||
r <- liftIO $ saveAccount pool nAcc'
|
||||
case r of
|
||||
Nothing ->
|
||||
return $
|
||||
ErrorResponse
|
||||
(callId req)
|
||||
(-32007)
|
||||
"Entity with that name already exists."
|
||||
Just x ->
|
||||
return $
|
||||
NewItemResponse (callId req) $
|
||||
fromSqlKey $ entityKey x
|
||||
else return $ notLocalError $ callId req
|
||||
Nothing ->
|
||||
return $
|
||||
ErrorResponse
|
||||
|
@ -896,45 +931,51 @@ zenithServer state = getinfo :<|> handleRPC
|
|||
liftIO $ getAccountById pool $ toSqlKey $ fromIntegral a
|
||||
case acc of
|
||||
Just acc' -> do
|
||||
bl <-
|
||||
liftIO $
|
||||
getLastSyncBlock
|
||||
pool
|
||||
(zcashAccountWalletId $ entityVal acc')
|
||||
_ <-
|
||||
liftIO $
|
||||
forkIO $ do
|
||||
res <-
|
||||
if zcashAccountType (entityVal acc') == Local
|
||||
then do
|
||||
bl <-
|
||||
liftIO $
|
||||
runNoLoggingT $
|
||||
prepareTxV2
|
||||
getLastSyncBlock
|
||||
pool
|
||||
zHost
|
||||
zPort
|
||||
znet
|
||||
(entityKey acc')
|
||||
bl
|
||||
ns
|
||||
p
|
||||
case res of
|
||||
Left e ->
|
||||
finalizeOperation pool opkey' Failed $
|
||||
T.pack $ show e
|
||||
Right rawTx -> do
|
||||
zebraRes <-
|
||||
makeZebraCall
|
||||
(zcashAccountWalletId $ entityVal acc')
|
||||
_ <-
|
||||
liftIO $
|
||||
forkIO $ do
|
||||
res <-
|
||||
liftIO $
|
||||
runNoLoggingT $
|
||||
prepareTxV2
|
||||
pool
|
||||
zHost
|
||||
zPort
|
||||
"sendrawtransaction"
|
||||
[Data.Aeson.String $ H.toText rawTx]
|
||||
case zebraRes of
|
||||
Left e1 ->
|
||||
znet
|
||||
(entityKey acc')
|
||||
bl
|
||||
ns
|
||||
p
|
||||
case res of
|
||||
Left e ->
|
||||
finalizeOperation pool opkey' Failed $
|
||||
T.pack $ show e1
|
||||
Right txId ->
|
||||
finalizeOperation pool opkey' Successful $
|
||||
"Tx ID: " <> H.toText txId
|
||||
return $ SendResponse (callId req) opid
|
||||
T.pack $ show e
|
||||
Right rawTx -> do
|
||||
zebraRes <-
|
||||
makeZebraCall
|
||||
zHost
|
||||
zPort
|
||||
"sendrawtransaction"
|
||||
[Data.Aeson.String $ H.toText rawTx]
|
||||
case zebraRes of
|
||||
Left e1 ->
|
||||
finalizeOperation pool opkey' Failed $
|
||||
T.pack $ show e1
|
||||
Right txId ->
|
||||
finalizeOperation
|
||||
pool
|
||||
opkey'
|
||||
Successful $
|
||||
"Tx ID: " <> H.toText txId
|
||||
return $ SendResponse (callId req) opid
|
||||
else return $ readOnlyError $ callId req
|
||||
Nothing ->
|
||||
return $
|
||||
ErrorResponse
|
||||
|
@ -1078,25 +1119,19 @@ zenithServer state = getinfo :<|> handleRPC
|
|||
case parameters req of
|
||||
ViewingKeyParams aid -> do
|
||||
let dbPath = w_dbPath state
|
||||
let net = w_network state
|
||||
pool <- liftIO $ runNoLoggingT $ initPool dbPath
|
||||
acc <- liftIO $ getAccountById pool $ toSqlKey $ fromIntegral aid
|
||||
case acc of
|
||||
Just acc' -> do
|
||||
fvk <-
|
||||
liftIO $
|
||||
try
|
||||
(deriveUfvk
|
||||
net
|
||||
(getOrchSK $ zcashAccountOrchSpendKey $ entityVal acc')
|
||||
(getSapSK $ zcashAccountSapSpendKey $ entityVal acc')
|
||||
(getTranSK $ zcashAccountTPrivateKey $ entityVal acc')) :: Handler
|
||||
(Either SomeException T.Text)
|
||||
case fvk of
|
||||
Left _ ->
|
||||
case zcashAccountFvk (entityVal acc') of
|
||||
Nothing ->
|
||||
return $
|
||||
ErrorResponse (callId req) (-32010) "Internal Error"
|
||||
Right fvk' -> return $ ViewingKeyResponse (callId req) fvk'
|
||||
Just fvk ->
|
||||
return $
|
||||
ViewingKeyResponse
|
||||
(callId req)
|
||||
(encodeVK (FullVk $ getFvk fvk))
|
||||
Nothing ->
|
||||
return $
|
||||
ErrorResponse (callId req) (-32006) "Account does not exist."
|
||||
|
@ -1106,30 +1141,39 @@ zenithServer state = getinfo :<|> handleRPC
|
|||
case parameters req of
|
||||
ViewingKeyParams aid -> do
|
||||
let dbPath = w_dbPath state
|
||||
let net = w_network state
|
||||
pool <- liftIO $ runNoLoggingT $ initPool dbPath
|
||||
acc <- liftIO $ getAccountById pool $ toSqlKey $ fromIntegral aid
|
||||
case acc of
|
||||
Just acc' -> do
|
||||
ivk <-
|
||||
liftIO $
|
||||
try
|
||||
(deriveUivk
|
||||
net
|
||||
(getOrchSK $ zcashAccountOrchSpendKey $ entityVal acc')
|
||||
(getSapSK $ zcashAccountSapSpendKey $ entityVal acc')
|
||||
(getTranSK $ zcashAccountTPrivateKey $ entityVal acc')) :: Handler
|
||||
(Either SomeException T.Text)
|
||||
case ivk of
|
||||
Left _ ->
|
||||
case zcashAccountIvk (entityVal acc') of
|
||||
Nothing ->
|
||||
return $
|
||||
ErrorResponse (callId req) (-32010) "Internal Error"
|
||||
Right ivk' -> return $ ViewingKeyResponse (callId req) ivk'
|
||||
Just ivk ->
|
||||
return $
|
||||
ViewingKeyResponse
|
||||
(callId req)
|
||||
(encodeVK $ IncomingVk $ getIvk ivk)
|
||||
Nothing ->
|
||||
return $
|
||||
ErrorResponse (callId req) (-32006) "Account does not exist."
|
||||
_anyOtherParams ->
|
||||
return $ ErrorResponse (callId req) (-32602) "Invalid params"
|
||||
ImportVK -> do
|
||||
case parameters req of
|
||||
ImportVkParams n k b -> do
|
||||
let dbPath = w_dbPath state
|
||||
let znet = w_network state
|
||||
pool <- liftIO $ runNoLoggingT $ initPool dbPath
|
||||
case parseVK k of
|
||||
Nothing -> return $ invalidVkError $ callId req
|
||||
Just vk -> do
|
||||
res <- liftIO $ importViewingKey pool n znet vk b
|
||||
case res of
|
||||
Left e -> return $ ErrorResponse (callId req) (-32010) e
|
||||
Right x -> return $ NewItemResponse (callId req) x
|
||||
_anyOtherParams ->
|
||||
return $ ErrorResponse (callId req) (-32602) "Invalid params"
|
||||
|
||||
authenticate :: Config -> BasicAuthCheck Bool
|
||||
authenticate config = BasicAuthCheck check
|
||||
|
@ -1200,3 +1244,19 @@ scanZebra dbPath zHost zPort net = do
|
|||
(fromIntegral $ bl_time blk)
|
||||
(ZcashNetDB net)
|
||||
mapM_ (processTx zHost zPort bi pool) $ bl_txs blk
|
||||
|
||||
-- * Errors
|
||||
invalidVkError :: T.Text -> ZenithResponse
|
||||
invalidVkError i =
|
||||
ErrorResponse i (-32013) "The viewing key provided is not valid."
|
||||
|
||||
readOnlyError :: T.Text -> ZenithResponse
|
||||
readOnlyError i =
|
||||
ErrorResponse i (-32014) "Read-only account, operation is not valid."
|
||||
|
||||
notLocalError :: T.Text -> ZenithResponse
|
||||
notLocalError i =
|
||||
ErrorResponse
|
||||
i
|
||||
(-32015)
|
||||
"The wallet is not local, cannot create new accounts."
|
||||
|
|
|
@ -50,6 +50,7 @@ import Zenith.DB
|
|||
, saveTransaction
|
||||
, startSync
|
||||
, updateWalletSync
|
||||
, upgradeAccountTable
|
||||
, upgradeQrTable
|
||||
)
|
||||
import Zenith.Types
|
||||
|
@ -77,7 +78,7 @@ rescanZebra host port dbFilePath = do
|
|||
pool1 <- runNoLoggingT $ initPool dbFilePath
|
||||
{-pool2 <- runNoLoggingT $ initPool dbFilePath-}
|
||||
{-pool3 <- runNoLoggingT $ initPool dbFilePath-}
|
||||
_ <- initDb dbFilePath
|
||||
_ <- runNoLoggingT $ initDb dbFilePath
|
||||
upgradeQrTable pool1
|
||||
clearWalletTransactions pool1
|
||||
clearWalletData pool1
|
||||
|
@ -216,8 +217,9 @@ clearSync config = do
|
|||
case bc of
|
||||
Left e1 -> throwIO e1
|
||||
Right chainInfo -> do
|
||||
x <- initDb dbPath
|
||||
x <- runNoLoggingT $ initDb dbPath
|
||||
_ <- upgradeQrTable pool
|
||||
_ <- runNoLoggingT $ upgradeAccountTable pool
|
||||
case x of
|
||||
Left e2 -> throwIO $ userError e2
|
||||
Right x' -> do
|
||||
|
|
|
@ -40,6 +40,8 @@ import ZcashHaskell.Types
|
|||
, Scope(..)
|
||||
, TransparentAddress(..)
|
||||
, TransparentSpendingKey
|
||||
, UnifiedFullViewingKey(..)
|
||||
, UnifiedIncomingViewingKey(..)
|
||||
, ValidAddress(..)
|
||||
, ZcashNet(..)
|
||||
)
|
||||
|
@ -103,6 +105,41 @@ newtype RseedDB = RseedDB
|
|||
|
||||
derivePersistField "RseedDB"
|
||||
|
||||
newtype UnifiedFvkDB = UnifiedFvkDB
|
||||
{ getFvk :: UnifiedFullViewingKey
|
||||
} deriving newtype (Eq, Show, Read)
|
||||
|
||||
derivePersistField "UnifiedFvkDB"
|
||||
|
||||
newtype UnifiedIvkDB = UnifiedIvkDB
|
||||
{ getIvk :: UnifiedIncomingViewingKey
|
||||
} deriving newtype (Eq, Show, Read)
|
||||
|
||||
derivePersistField "UnifiedIvkDB"
|
||||
|
||||
data AccountType
|
||||
= Local
|
||||
| FullViewKey
|
||||
| IncomingViewKey
|
||||
deriving (Eq, Show, Read)
|
||||
|
||||
derivePersistField "AccountType"
|
||||
|
||||
instance ToJSON AccountType where
|
||||
toJSON at =
|
||||
case at of
|
||||
Local -> Data.Aeson.String "Local"
|
||||
FullViewKey -> Data.Aeson.String "FullViewKey"
|
||||
IncomingViewKey -> Data.Aeson.String "IncomingViewKey"
|
||||
|
||||
instance FromJSON AccountType where
|
||||
parseJSON =
|
||||
withText "AccountType" $ \case
|
||||
"Local" -> return Local
|
||||
"FullViewKey" -> return FullViewKey
|
||||
"IncomingViewKey" -> return IncomingViewKey
|
||||
_ -> fail "Not a valid Account type"
|
||||
|
||||
-- * RPC
|
||||
-- | Type for Configuration parameters
|
||||
data Config = Config
|
||||
|
@ -154,6 +191,7 @@ data ZcashWalletAPI = ZcashWalletAPI
|
|||
, zw_network :: !ZcashNet
|
||||
, zw_birthday :: !Int
|
||||
, zw_lastSync :: !Int
|
||||
, zw_local :: !Bool
|
||||
} deriving (Eq, Prelude.Show)
|
||||
|
||||
$(deriveJSON defaultOptions {fieldLabelModifier = drop 3} ''ZcashWalletAPI)
|
||||
|
@ -162,6 +200,7 @@ data ZcashAccountAPI = ZcashAccountAPI
|
|||
{ za_index :: !Int
|
||||
, za_wallet :: !Int
|
||||
, za_name :: !T.Text
|
||||
, za_type :: !AccountType
|
||||
} deriving (Eq, Prelude.Show)
|
||||
|
||||
$(deriveJSON defaultOptions {fieldLabelModifier = drop 3} ''ZcashAccountAPI)
|
||||
|
@ -519,9 +558,8 @@ data ZcashPaymentURI = ZcashPaymentURI
|
|||
} deriving (Show, Eq)
|
||||
|
||||
-- | Define a data structure for the URI QR image
|
||||
data URIQrCode = URIQrCode
|
||||
{
|
||||
uriBytes :: BS.ByteString -- Image as ByteString
|
||||
, uriWidth :: Double -- Number of columns in QR Image
|
||||
, uriHeight :: Double -- Number of rows in a QR Image
|
||||
} deriving (Show, Eq)
|
||||
data URIQrCode = URIQrCode
|
||||
{ uriBytes :: BS.ByteString -- Image as ByteString
|
||||
, uriWidth :: Double -- Number of columns in QR Image
|
||||
, uriHeight :: Double -- Number of rows in a QR Image
|
||||
} deriving (Show, Eq)
|
||||
|
|
|
@ -42,6 +42,7 @@ import ZcashHaskell.Transparent
|
|||
import ZcashHaskell.Types
|
||||
( ExchangeAddress(..)
|
||||
, ExchangeAddress(..)
|
||||
, Phrase(..)
|
||||
, SaplingAddress(..)
|
||||
, TransparentAddress(..)
|
||||
, UnifiedAddress(..)
|
||||
|
@ -371,3 +372,15 @@ createZip321 address mAmount mMemo =
|
|||
|
||||
getTransparentFromUA :: UnifiedAddress -> Maybe TransparentAddress
|
||||
getTransparentFromUA ua = TransparentAddress (ua_net ua) <$> t_rec ua
|
||||
|
||||
-- Function to check if Text is non-empty after trimming leading spaces
|
||||
isNotEmptyAfterTrim :: T.Text -> Bool
|
||||
isNotEmptyAfterTrim txt = not (T.null (T.stripStart txt))
|
||||
|
||||
-- Function to convert a Scientific number to Int
|
||||
scientificToInt :: Scientific -> Int
|
||||
scientificToInt sc = fromIntegral $ round $ toRealFloat sc
|
||||
|
||||
-- Convert a ByteString to Phrase
|
||||
toPhrase :: BS.ByteString -> Phrase
|
||||
toPhrase = Phrase
|
||||
|
|
|
@ -38,7 +38,8 @@ import Zenith.RPC
|
|||
, zenithServer
|
||||
)
|
||||
import Zenith.Types
|
||||
( Config(..)
|
||||
( AccountType(..)
|
||||
, Config(..)
|
||||
, PrivacyPolicy(..)
|
||||
, ProposedNote(..)
|
||||
, ValidAddressAPI(..)
|
||||
|
@ -307,7 +308,9 @@ main = do
|
|||
Left e -> assertFailure e
|
||||
Right r ->
|
||||
r `shouldBe`
|
||||
AccountListResponse "zh" [ZcashAccountAPI 1 1 "Personal"]
|
||||
AccountListResponse
|
||||
"zh"
|
||||
[ZcashAccountAPI 1 1 "Personal" Local]
|
||||
describe "Addresses" $ do
|
||||
describe "listaddresses" $ do
|
||||
it "bad credentials" $ do
|
||||
|
@ -832,6 +835,57 @@ main = do
|
|||
Left e -> assertFailure e
|
||||
Right (ViewingKeyResponse i c) -> c `shouldNotBe` ""
|
||||
Right x -> assertFailure $ show x
|
||||
describe "Importing" $ do
|
||||
it "bad credentials" $ do
|
||||
res <-
|
||||
makeZenithCall
|
||||
"127.0.0.1"
|
||||
nodePort
|
||||
"baduser"
|
||||
"idontknow"
|
||||
ImportVK
|
||||
BlankParams
|
||||
res `shouldBe` Left "Invalid credentials"
|
||||
describe "correct credentials" $ do
|
||||
it "no parameters" $ do
|
||||
res <-
|
||||
makeZenithCall
|
||||
"127.0.0.1"
|
||||
nodePort
|
||||
nodeUser
|
||||
nodePwd
|
||||
ImportVK
|
||||
BlankParams
|
||||
case res of
|
||||
Left e -> assertFailure e
|
||||
Right (ErrorResponse i c m) -> c `shouldBe` (-32602)
|
||||
it "correct params" $ do
|
||||
res <-
|
||||
makeZenithCall
|
||||
"127.0.0.1"
|
||||
nodePort
|
||||
nodeUser
|
||||
nodePwd
|
||||
ImportVK
|
||||
(ImportVkParams
|
||||
"OldWallet"
|
||||
"uviewtest1jna46ql5qns5rlg99jgs6mhf0j9tk8zxvqsm472scgvmj0vs0rqv2kvdf626gftx7dgn2tltyf0s200gvjlsdvz5celpue9wxxw78txswqmayxc3pfrt5fs5frvr3ep0jrjg8euahqzc63yx9sy4z8lql4ev6q3asptl9rhsfzzrup2g5slwnlvy3dgft44jw3l08xtzypjmsrwxskgnp5s03xlc2kg5520a25pa6fdjxhzutam4wkwr6mh4zeq3qndpks8dk0y90y7gucgsp0j5k2xnhh90m3krk5glz4794dj93pf59h85dqms6337f85ccvpxhays94kvsj2hyjsltf52tygqs8y0vp2yf39drxl687the6xkp8nxkfffc3kqlkhw53t5plplde0vk9rwv340ys04gg48fs0pxfp35rvt2f2pvxjmgmln6lp5k2yzkm0r87k89p6xqv68a6uyfpsauswh9fsckfqey02pjedz5gs934qa"
|
||||
3249286)
|
||||
case res of
|
||||
Left e -> assertFailure e
|
||||
Right (NewItemResponse i k) -> k `shouldSatisfy` (> 0)
|
||||
it "list wallets" $ do
|
||||
res <-
|
||||
makeZenithCall
|
||||
"127.0.0.1"
|
||||
nodePort
|
||||
nodeUser
|
||||
nodePwd
|
||||
ListWallets
|
||||
BlankParams
|
||||
case res of
|
||||
Left e -> assertFailure e
|
||||
Right (WalletListResponse i k) -> length k `shouldBe` 2
|
||||
|
||||
startAPI :: Config -> IO ()
|
||||
startAPI config = do
|
||||
|
@ -850,7 +904,7 @@ startAPI config = do
|
|||
case bc of
|
||||
Left e1 -> throwIO e1
|
||||
Right chainInfo -> do
|
||||
x <- initDb "test.db"
|
||||
x <- runNoLoggingT $ initDb "test.db"
|
||||
case x of
|
||||
Left e2 -> throwIO $ userError e2
|
||||
Right x' -> do
|
||||
|
|
|
@ -1 +1 @@
|
|||
Subproject commit a28edcb5995667677e96a08c6952a568bfd6c51e
|
||||
Subproject commit 0d042d639d471af14ebe94707f64b5ff5c2cb5eb
|
|
@ -1,7 +1,7 @@
|
|||
{
|
||||
"openrpc": "1.0.0-rc1",
|
||||
"info": {
|
||||
"version": "0.8.0.0-beta",
|
||||
"version": "0.9.0.0-beta",
|
||||
"title": "Zenith RPC",
|
||||
"description": "The RPC methods to interact with the Zenith Zcash wallet",
|
||||
"license": {
|
||||
|
@ -230,7 +230,8 @@
|
|||
{ "$ref": "#/components/errors/ZebraNotAvailable" },
|
||||
{ "$ref": "#/components/errors/DuplicateName" },
|
||||
{ "$ref": "#/components/errors/ZenithBusy" },
|
||||
{ "$ref": "#/components/errors/InvalidWallet" }
|
||||
{ "$ref": "#/components/errors/InvalidWallet" },
|
||||
{ "$ref": "#/components/errors/NotLocal" }
|
||||
]
|
||||
},
|
||||
{
|
||||
|
@ -496,7 +497,8 @@
|
|||
}
|
||||
],
|
||||
"errors": [
|
||||
{ "$ref": "#/components/errors/InvalidAccount" }
|
||||
{ "$ref": "#/components/errors/InvalidAccount" },
|
||||
{ "$ref": "#/components/errors/ReadOnly" }
|
||||
]
|
||||
},
|
||||
{
|
||||
|
@ -648,7 +650,8 @@
|
|||
"errors": [
|
||||
{ "$ref": "#/components/errors/ZebraNotAvailable" },
|
||||
{ "$ref": "#/components/errors/ZenithBusy" },
|
||||
{ "$ref": "#/components/errors/InvalidAccount" }
|
||||
{ "$ref": "#/components/errors/InvalidAccount" },
|
||||
{ "$ref": "#/components/errors/ReadOnly" }
|
||||
]
|
||||
},
|
||||
{
|
||||
|
@ -865,6 +868,28 @@
|
|||
"errors": [
|
||||
{ "$ref": "#/components/errors/InvalidAccount" }
|
||||
]
|
||||
},
|
||||
{
|
||||
"name": "importvk",
|
||||
"summary": "Import the given Unified Viewing Key",
|
||||
"description": "Imports the given Unified Viewing Key, autodetecting if it is Full or Incoming. Caution: If the given birthday height is lower than the lowest birthday height in the wallet, this will trigger a full re-scan of the wallet.",
|
||||
"tags": [
|
||||
],
|
||||
"params": [
|
||||
{ "$ref": "#/components/contentDescriptors/Name"},
|
||||
{ "$ref": "#/components/contentDescriptors/ViewingKey"},
|
||||
{ "$ref": "#/components/contentDescriptors/BirthdayHeight"}
|
||||
],
|
||||
"paramStructure": "by-position",
|
||||
"result": {
|
||||
"name": "Account Identifier",
|
||||
"schema": { "$ref": "#/components/contentDescriptors/AccountId"}
|
||||
},
|
||||
"errors": [
|
||||
{ "$ref": "#/components/errors/ZebraNotAvailable" },
|
||||
{ "$ref": "#/components/errors/DuplicateName" },
|
||||
{ "$ref": "#/components/errors/ZenithBusy" }
|
||||
]
|
||||
}
|
||||
],
|
||||
"components": {
|
||||
|
@ -960,6 +985,24 @@
|
|||
"type": "string",
|
||||
"enum": ["None", "Low", "Medium", "Full"]
|
||||
}
|
||||
},
|
||||
"BirthdayHeight": {
|
||||
"name": "Birthday Height",
|
||||
"summary": "The block height at which a wallet was created.",
|
||||
"description": "The block height where a wallet was created. The wallet will not scan blocks at a lower block height than this, assuming there are no transactions on-chain before this point.",
|
||||
"required": true,
|
||||
"schema": {
|
||||
"type": "integer"
|
||||
}
|
||||
},
|
||||
"ViewingKey": {
|
||||
"name": "Viewing Key",
|
||||
"summary": "A Unified viewing key.",
|
||||
"description": "A Unified viewing key encoded per [ZIP-316](https://zips.z.cash/zip-0316). Zenith supports both full and incoming viewing keys.",
|
||||
"required": true,
|
||||
"schema": {
|
||||
"type": "string"
|
||||
}
|
||||
}
|
||||
},
|
||||
"schemas": {
|
||||
|
@ -978,7 +1021,8 @@
|
|||
"name": { "type": "string", "description": "User-friendly name of the wallet" },
|
||||
"network": { "type": "string", "description": "Network the wallet is for. Testnet or MainNet" },
|
||||
"birthday": { "type": "integer", "description": "Wallet's birthday height" },
|
||||
"lastSync": { "type": "integer", "description": "Last block the wallet is synced to" }
|
||||
"lastSync": { "type": "integer", "description": "Last block the wallet is synced to" },
|
||||
"local": { "type": "boolean", "description": "True for wallets belonging to this Zenith instance, False for wallets created to manage viewing keys"}
|
||||
}
|
||||
},
|
||||
"ZcashAccount": {
|
||||
|
@ -986,7 +1030,8 @@
|
|||
"properties": {
|
||||
"index": { "type": "integer", "description": "Internal index for account"},
|
||||
"wallet": { "type": "integer", "description": "ID of the wallet this account belongs to"},
|
||||
"name": { "type": "string", "description": "User-friendly name of the account"}
|
||||
"name": { "type": "string", "description": "User-friendly name of the account"},
|
||||
"type": { "type": "string", "description": "Local for accounts belonging to the wallet, FullViewKey for full viewing keys, IncomingViewKey for incoming"}
|
||||
}
|
||||
},
|
||||
"ZcashAddress": {
|
||||
|
@ -1103,6 +1148,18 @@
|
|||
"ZenithBusy": {
|
||||
"code": -32012,
|
||||
"message": "The Zenith server is syncing, please try again later."
|
||||
},
|
||||
"InvalidVK": {
|
||||
"code": -32013,
|
||||
"message": "The viewing key provided is not valid."
|
||||
},
|
||||
"ReadOnly": {
|
||||
"code": -32014,
|
||||
"message": "Read-only account, operation is not valid."
|
||||
},
|
||||
"NotLocal": {
|
||||
"code": -32015,
|
||||
"message": "The wallet is not local, cannot create new accounts."
|
||||
}
|
||||
}
|
||||
}
|
||||
|
|
|
@ -1,6 +1,6 @@
|
|||
cabal-version: 3.0
|
||||
name: zenith
|
||||
version: 0.8.0.0-beta
|
||||
version: 0.9.0.0-beta
|
||||
license: MIT
|
||||
license-file: LICENSE
|
||||
author: Rene Vergara
|
||||
|
|
14
zenith.cfg
14
zenith.cfg
|
@ -9,20 +9,24 @@ nodeUser = "user"
|
|||
# nodePwd -
|
||||
nodePwd = "superSecret"
|
||||
# -------------------------------------------------------------
|
||||
# nodePort -
|
||||
nodePort = 8234
|
||||
# -------------------------------------------------------------
|
||||
# nodePwd -
|
||||
# dbFileName - contains the SQLite database name used for
|
||||
# keeping all Zenith's data
|
||||
# keeping all Zenith's data
|
||||
# default = zenith.db
|
||||
#
|
||||
dbFileName = "zenith.db"
|
||||
# -------------------------------------------------------------
|
||||
# zebraHost - Zebra IP
|
||||
# Default - "127.0.0.1"
|
||||
# Default - "127.0.0.1"
|
||||
zebraHost = "127.0.0.1"
|
||||
# -------------------------------------------------------------
|
||||
# zebraPort - Port used for access Zebra API endpoints
|
||||
# must be the same port configured for your
|
||||
# Zebra node
|
||||
zebraPort = 18232
|
||||
# must be the same port configured for your
|
||||
# Zebra node
|
||||
zebraPort = 8232
|
||||
# -------------------------------------------------------------
|
||||
# currencyCode - ISO 4217 currency code
|
||||
#
|
||||
|
|
Loading…
Add table
Reference in a new issue