Compare commits
No commits in common. "856ade051e5e62c609a707874c7897231dd96c10" and "cb63b786e824bdcbecbd87be12a06a5ba878b2d9" have entirely different histories.
856ade051e
...
cb63b786e8
5 changed files with 154 additions and 463 deletions
|
@ -3,10 +3,9 @@
|
|||
|
||||
module Zenith.CLI where
|
||||
|
||||
import Control.Exception (throw, try)
|
||||
import Control.Exception (throw)
|
||||
import Control.Monad (void)
|
||||
import Control.Monad.IO.Class (liftIO)
|
||||
import Data.Maybe
|
||||
import qualified Data.Text as T
|
||||
import qualified Graphics.Vty as V
|
||||
import Lens.Micro ((&), (.~), (^.), set)
|
||||
|
@ -44,9 +43,7 @@ import Brick.Widgets.Core
|
|||
, padBottom
|
||||
, padRight
|
||||
, str
|
||||
, strWrap
|
||||
, txt
|
||||
, txtWrap
|
||||
, vBox
|
||||
, vLimit
|
||||
, withAttr
|
||||
|
@ -56,12 +53,10 @@ import qualified Brick.Widgets.Dialog as D
|
|||
import qualified Brick.Widgets.List as L
|
||||
import qualified Data.Vector as Vec
|
||||
import Database.Persist
|
||||
import ZcashHaskell.Keys (generateWalletSeedPhrase, getWalletSeed)
|
||||
import ZcashHaskell.Orchard (encodeUnifiedAddress, genOrchardSpendingKey)
|
||||
import ZcashHaskell.Keys (generateWalletSeedPhrase)
|
||||
import ZcashHaskell.Types
|
||||
import Zenith.Core
|
||||
import Zenith.DB
|
||||
import Zenith.Utils (showAddress)
|
||||
|
||||
data Name
|
||||
= WList
|
||||
|
@ -81,21 +76,13 @@ makeLenses ''DialogInput
|
|||
data DialogType
|
||||
= WName
|
||||
| AName
|
||||
| AdName
|
||||
| WSelect
|
||||
| ASelect
|
||||
| Blank
|
||||
|
||||
data DisplayType
|
||||
= AddrDisplay
|
||||
| MsgDisplay
|
||||
| BlankDisplay
|
||||
|
||||
data State = State
|
||||
{ _network :: !ZcashNet
|
||||
{ _network :: !String
|
||||
, _wallets :: !(L.List Name (Entity ZcashWallet))
|
||||
, _accounts :: !(L.List Name (Entity ZcashAccount))
|
||||
, _addresses :: !(L.List Name (Entity WalletAddress))
|
||||
, _addresses :: !(L.List Name String)
|
||||
, _transactions :: !(L.List Name String)
|
||||
, _msg :: !String
|
||||
, _helpBox :: !Bool
|
||||
|
@ -105,13 +92,12 @@ data State = State
|
|||
, _focusRing :: !(F.FocusRing Name)
|
||||
, _startBlock :: !Int
|
||||
, _dbPath :: !T.Text
|
||||
, _displayBox :: !DisplayType
|
||||
}
|
||||
|
||||
makeLenses ''State
|
||||
|
||||
drawUI :: State -> [Widget Name]
|
||||
drawUI s = [splashDialog s, helpDialog s, displayDialog s, inputDialog s, ui s]
|
||||
drawUI s = [splashDialog s, helpDialog s, inputDialog s, ui s]
|
||||
where
|
||||
ui :: State -> Widget Name
|
||||
ui st =
|
||||
|
@ -120,24 +106,25 @@ drawUI s = [splashDialog s, helpDialog s, displayDialog s, inputDialog s, ui s]
|
|||
B.borderWithLabel
|
||||
(str
|
||||
("Zenith - " <>
|
||||
show (st ^. network) <>
|
||||
st ^. network <>
|
||||
" - " <>
|
||||
T.unpack
|
||||
(maybe
|
||||
"(None)"
|
||||
(\(_, w) -> zcashWalletName $ entityVal w)
|
||||
(L.listSelectedElement (st ^. wallets)))))
|
||||
(C.hCenter
|
||||
(str
|
||||
("Account: " ++
|
||||
T.unpack
|
||||
(maybe
|
||||
"(None)"
|
||||
(\(_, a) -> zcashAccountName $ entityVal a)
|
||||
(L.listSelectedElement (st ^. accounts))))) <=>
|
||||
listAddressBox "Addresses" (st ^. addresses) <+>
|
||||
B.vBorder <+> C.center (listBox "Transactions" (st ^. transactions)))
|
||||
listBox :: Show e => String -> L.List Name e -> Widget Name
|
||||
(L.listSelectedElement (st ^. wallets))))) $
|
||||
(C.hCenter
|
||||
(str
|
||||
("Account: " ++
|
||||
T.unpack
|
||||
(maybe
|
||||
"(None)"
|
||||
(\(_, a) -> zcashAccountName $ entityVal a)
|
||||
(L.listSelectedElement (st ^. accounts))))) <=>
|
||||
listBox "Addresses" (st ^. addresses) <+>
|
||||
B.vBorder <+> C.center (listBox "Transactions" (st ^. transactions))) <=>
|
||||
msgBox (st ^. msg)
|
||||
listBox :: String -> L.List Name String -> Widget Name
|
||||
listBox titleLabel l =
|
||||
C.vCenter $
|
||||
vBox
|
||||
|
@ -147,31 +134,10 @@ drawUI s = [splashDialog s, helpDialog s, displayDialog s, inputDialog s, ui s]
|
|||
, str " "
|
||||
, C.hCenter $ str "Select "
|
||||
]
|
||||
selectListBox ::
|
||||
Show e
|
||||
=> String
|
||||
-> L.List Name e
|
||||
-> (Bool -> e -> Widget Name)
|
||||
-> Widget Name
|
||||
selectListBox titleLabel l drawF =
|
||||
msgBox :: String -> Widget Name
|
||||
msgBox m =
|
||||
vBox
|
||||
[ C.hCenter
|
||||
(B.borderWithLabel (str titleLabel) $
|
||||
hLimit 25 $ vLimit 15 $ L.renderList drawF True l)
|
||||
, str " "
|
||||
, C.hCenter $ str "Select "
|
||||
]
|
||||
listAddressBox ::
|
||||
String -> L.List Name (Entity WalletAddress) -> Widget Name
|
||||
listAddressBox titleLabel a =
|
||||
C.vCenter $
|
||||
vBox
|
||||
[ C.hCenter
|
||||
(B.borderWithLabel (str titleLabel) $
|
||||
hLimit 40 $ vLimit 15 $ L.renderList listDrawAddress True a)
|
||||
, str " "
|
||||
, C.hCenter $ str "Use arrows to select"
|
||||
]
|
||||
[B.hBorderWithLabel (str "Messages"), hLimit 70 $ padRight Max $ str m]
|
||||
helpDialog :: State -> Widget Name
|
||||
helpDialog st =
|
||||
if st ^. helpBox
|
||||
|
@ -181,17 +147,11 @@ drawUI s = [splashDialog s, helpDialog s, displayDialog s, inputDialog s, ui s]
|
|||
vBox ([str "Actions", B.hBorder] <> actionList))
|
||||
else emptyWidget
|
||||
where
|
||||
keyList = map (C.hCenter . str) ["?", "Esc", "w", "a", "v", "q"]
|
||||
keyList = map (C.hCenter . str) ["?", "Esc", "c", "q"]
|
||||
actionList =
|
||||
map
|
||||
(hLimit 40 . str)
|
||||
[ "Open help"
|
||||
, "Close dialog"
|
||||
, "Switch wallets"
|
||||
, "Switch accounts"
|
||||
, "View address"
|
||||
, "Quit"
|
||||
]
|
||||
["Open help", "Close dialog", "Create Wallet", "Quit"]
|
||||
inputDialog :: State -> Widget Name
|
||||
inputDialog st =
|
||||
case st ^. dialogBox of
|
||||
|
@ -203,18 +163,6 @@ drawUI s = [splashDialog s, helpDialog s, displayDialog s, inputDialog s, ui s]
|
|||
D.renderDialog
|
||||
(D.dialog (Just (str "Create Account")) Nothing 50)
|
||||
(renderForm $ st ^. inputForm)
|
||||
AdName ->
|
||||
D.renderDialog
|
||||
(D.dialog (Just (str "Create Address")) Nothing 50)
|
||||
(renderForm $ st ^. inputForm)
|
||||
WSelect ->
|
||||
D.renderDialog
|
||||
(D.dialog (Just (str "Select Wallet")) Nothing 50)
|
||||
(selectListBox "Wallets" (st ^. wallets) listDrawWallet)
|
||||
ASelect ->
|
||||
D.renderDialog
|
||||
(D.dialog (Just (str "Select Account")) Nothing 50)
|
||||
(selectListBox "Accounts" (st ^. accounts) listDrawAccount)
|
||||
Blank -> emptyWidget
|
||||
splashDialog :: State -> Widget Name
|
||||
splashDialog st =
|
||||
|
@ -229,28 +177,6 @@ drawUI s = [splashDialog s, helpDialog s, displayDialog s, inputDialog s, ui s]
|
|||
C.hCenter (withAttr titleAttr (str "Zcash Wallet v0.4.3.0")) <=>
|
||||
C.hCenter (withAttr blinkAttr $ str "Press any key..."))
|
||||
else emptyWidget
|
||||
displayDialog :: State -> Widget Name
|
||||
displayDialog st =
|
||||
case st ^. displayBox of
|
||||
AddrDisplay ->
|
||||
case L.listSelectedElement $ st ^. addresses of
|
||||
Just (_, a) ->
|
||||
withBorderStyle unicodeBold $
|
||||
D.renderDialog
|
||||
(D.dialog
|
||||
(Just $ txt ("Address: " <> walletAddressName (entityVal a)))
|
||||
Nothing
|
||||
60)
|
||||
(padAll 1 $
|
||||
txtWrap $
|
||||
encodeUnifiedAddress $ walletAddressUAddress $ entityVal a)
|
||||
Nothing -> emptyWidget
|
||||
MsgDisplay ->
|
||||
withBorderStyle unicodeBold $
|
||||
D.renderDialog
|
||||
(D.dialog (Just $ txt "Message") Nothing 50)
|
||||
(padAll 1 $ strWrap $ st ^. msg)
|
||||
BlankDisplay -> emptyWidget
|
||||
|
||||
mkInputForm :: DialogInput -> Form DialogInput e Name
|
||||
mkInputForm =
|
||||
|
@ -268,33 +194,6 @@ listDrawElement sel a =
|
|||
else str s
|
||||
in C.hCenter $ selStr $ show a
|
||||
|
||||
listDrawWallet :: Bool -> Entity ZcashWallet -> Widget Name
|
||||
listDrawWallet sel w =
|
||||
let selStr s =
|
||||
if sel
|
||||
then withAttr customAttr (txt $ "<" <> s <> ">")
|
||||
else txt s
|
||||
in C.hCenter $ selStr $ zcashWalletName (entityVal w)
|
||||
|
||||
listDrawAccount :: Bool -> Entity ZcashAccount -> Widget Name
|
||||
listDrawAccount sel w =
|
||||
let selStr s =
|
||||
if sel
|
||||
then withAttr customAttr (txt $ "<" <> s <> ">")
|
||||
else txt s
|
||||
in C.hCenter $ selStr $ zcashAccountName (entityVal w)
|
||||
|
||||
listDrawAddress :: Bool -> Entity WalletAddress -> Widget Name
|
||||
listDrawAddress sel w =
|
||||
let selStr s =
|
||||
if sel
|
||||
then withAttr customAttr (txt $ "<" <> s <> ">")
|
||||
else txt s
|
||||
in C.hCenter $
|
||||
selStr $
|
||||
walletAddressName (entityVal w) <>
|
||||
": " <> showAddress (walletAddressUAddress (entityVal w))
|
||||
|
||||
customAttr :: A.AttrName
|
||||
customAttr = L.listSelectedAttr <> A.attrName "custom"
|
||||
|
||||
|
@ -317,104 +216,52 @@ appEvent (BT.VtyEvent e) = do
|
|||
BT.modify $ set helpBox False
|
||||
_ev -> return ()
|
||||
else do
|
||||
case s ^. displayBox of
|
||||
AddrDisplay -> BT.modify $ set displayBox BlankDisplay
|
||||
MsgDisplay -> BT.modify $ set displayBox BlankDisplay
|
||||
BlankDisplay -> do
|
||||
case s ^. dialogBox of
|
||||
WName -> do
|
||||
case e of
|
||||
V.EvKey V.KEsc [] -> BT.modify $ set dialogBox Blank
|
||||
V.EvKey V.KEnter [] -> do
|
||||
fs <- BT.zoom inputForm $ BT.gets formState
|
||||
nw <- liftIO $ addNewWallet (fs ^. dialogInput) s
|
||||
ns <- liftIO $ refreshWallet nw
|
||||
BT.put ns
|
||||
aL <- use accounts
|
||||
BT.modify $ set displayBox MsgDisplay
|
||||
BT.modify $
|
||||
set dialogBox $
|
||||
if not (null $ L.listElements aL)
|
||||
then Blank
|
||||
else AName
|
||||
ev ->
|
||||
BT.zoom inputForm $ handleFormEvent (BT.VtyEvent ev)
|
||||
AName -> do
|
||||
case e of
|
||||
V.EvKey V.KEsc [] -> BT.modify $ set dialogBox Blank
|
||||
V.EvKey V.KEnter [] -> do
|
||||
fs <- BT.zoom inputForm $ BT.gets formState
|
||||
na <- liftIO $ addNewAccount (fs ^. dialogInput) s
|
||||
ns <- liftIO $ refreshAccount na
|
||||
BT.put ns
|
||||
addrL <- use addresses
|
||||
BT.modify $ set displayBox MsgDisplay
|
||||
BT.modify $
|
||||
set dialogBox $
|
||||
if not (null $ L.listElements addrL)
|
||||
then Blank
|
||||
else AdName
|
||||
ev ->
|
||||
BT.zoom inputForm $ handleFormEvent (BT.VtyEvent ev)
|
||||
AdName -> do
|
||||
case e of
|
||||
V.EvKey V.KEsc [] -> BT.modify $ set dialogBox Blank
|
||||
V.EvKey V.KEnter [] -> do
|
||||
fs <- BT.zoom inputForm $ BT.gets formState
|
||||
nAddr <- liftIO $ addNewAddress (fs ^. dialogInput) s
|
||||
BT.put nAddr
|
||||
BT.modify $ set displayBox MsgDisplay
|
||||
BT.modify $ set dialogBox Blank
|
||||
ev ->
|
||||
BT.zoom inputForm $ handleFormEvent (BT.VtyEvent ev)
|
||||
WSelect -> do
|
||||
case e of
|
||||
V.EvKey V.KEsc [] -> BT.modify $ set dialogBox Blank
|
||||
V.EvKey V.KEnter [] -> do
|
||||
ns <- liftIO $ refreshWallet s
|
||||
BT.put ns
|
||||
BT.modify $ set dialogBox Blank
|
||||
V.EvKey (V.KChar 'c') [] -> do
|
||||
BT.modify $
|
||||
set inputForm $
|
||||
updateFormState (DialogInput "New Wallet") $
|
||||
s ^. inputForm
|
||||
BT.modify $ set dialogBox WName
|
||||
ev -> BT.zoom wallets $ L.handleListEvent ev
|
||||
ASelect -> do
|
||||
case e of
|
||||
V.EvKey V.KEsc [] -> BT.modify $ set dialogBox Blank
|
||||
V.EvKey V.KEnter [] -> do
|
||||
ns <- liftIO $ refreshAccount s
|
||||
BT.put ns
|
||||
BT.modify $ set dialogBox Blank
|
||||
V.EvKey (V.KChar 'c') [] -> do
|
||||
BT.modify $
|
||||
set inputForm $
|
||||
updateFormState (DialogInput "New Account") $
|
||||
s ^. inputForm
|
||||
BT.modify $ set dialogBox AName
|
||||
ev -> BT.zoom accounts $ L.handleListEvent ev
|
||||
Blank -> do
|
||||
case e of
|
||||
V.EvKey (V.KChar '\t') [] -> focusRing %= F.focusNext
|
||||
V.EvKey (V.KChar 'q') [] -> M.halt
|
||||
V.EvKey (V.KChar '?') [] -> BT.modify $ set helpBox True
|
||||
V.EvKey (V.KChar 'n') [] ->
|
||||
BT.modify $ set dialogBox AdName
|
||||
V.EvKey (V.KChar 'v') [] ->
|
||||
BT.modify $ set displayBox AddrDisplay
|
||||
V.EvKey (V.KChar 'w') [] ->
|
||||
BT.modify $ set dialogBox WSelect
|
||||
V.EvKey (V.KChar 'a') [] ->
|
||||
BT.modify $ set dialogBox ASelect
|
||||
ev ->
|
||||
case r of
|
||||
Just AList ->
|
||||
BT.zoom addresses $ L.handleListEvent ev
|
||||
Just TList ->
|
||||
BT.zoom transactions $ L.handleListEvent ev
|
||||
_anyName -> return ()
|
||||
case s ^. dialogBox of
|
||||
WName -> do
|
||||
case e of
|
||||
V.EvKey V.KEsc [] -> BT.modify $ set dialogBox Blank
|
||||
V.EvKey V.KEnter [] -> do
|
||||
fs <- BT.zoom inputForm $ BT.gets formState
|
||||
nw <- liftIO $ addNewWallet (fs ^. dialogInput) s
|
||||
BT.put nw
|
||||
aL <- use accounts
|
||||
BT.modify $
|
||||
set dialogBox $
|
||||
if not (null $ L.listElements aL)
|
||||
then Blank
|
||||
else AName
|
||||
ev -> BT.zoom inputForm $ handleFormEvent (BT.VtyEvent ev)
|
||||
AName -> do
|
||||
case e of
|
||||
V.EvKey V.KEsc [] -> BT.modify $ set dialogBox Blank
|
||||
V.EvKey V.KEnter [] -> do
|
||||
fs <- BT.zoom inputForm $ BT.gets formState
|
||||
na <- liftIO $ addNewAccount (fs ^. dialogInput) s
|
||||
BT.put na
|
||||
BT.modify $ set dialogBox Blank
|
||||
ev -> BT.zoom inputForm $ handleFormEvent (BT.VtyEvent ev)
|
||||
Blank -> do
|
||||
case e of
|
||||
V.EvKey (V.KChar '\t') [] -> focusRing %= F.focusNext
|
||||
V.EvKey (V.KChar 'q') [] -> M.halt
|
||||
V.EvKey (V.KChar '?') [] -> BT.modify $ set helpBox True
|
||||
V.EvKey (V.KChar 'w') [] -> do
|
||||
BT.modify $
|
||||
set inputForm $
|
||||
updateFormState (DialogInput "New Wallet") $
|
||||
s ^. inputForm
|
||||
BT.modify $ set dialogBox WName
|
||||
V.EvKey (V.KChar 'a') [] -> do
|
||||
BT.modify $
|
||||
set inputForm $
|
||||
updateFormState (DialogInput "New Account") $
|
||||
s ^. inputForm
|
||||
BT.modify $ set dialogBox AName
|
||||
ev ->
|
||||
case r of
|
||||
Just AList -> BT.zoom addresses $ L.handleListEvent ev
|
||||
Just TList -> BT.zoom transactions $ L.handleListEvent ev
|
||||
_anyName -> return ()
|
||||
where
|
||||
printMsg :: String -> BT.EventM Name State ()
|
||||
printMsg s = BT.modify $ updateMsg s
|
||||
|
@ -459,17 +306,13 @@ runZenithCLI host port dbFilePath = do
|
|||
if not (null walList)
|
||||
then getAccounts dbFilePath $ entityKey $ head walList
|
||||
else return []
|
||||
addrList <-
|
||||
if not (null accList)
|
||||
then getAddresses dbFilePath $ entityKey $ head accList
|
||||
else return []
|
||||
void $
|
||||
M.defaultMain theApp $
|
||||
State
|
||||
(zgb_net chainInfo)
|
||||
((show . zgb_net) chainInfo)
|
||||
(L.list WList (Vec.fromList walList) 1)
|
||||
(L.list AcList (Vec.fromList accList) 0)
|
||||
(L.list AList (Vec.fromList addrList) 1)
|
||||
(L.list AList (Vec.fromList ["utest...hn8zg", "utest...qfex8"]) 1)
|
||||
(L.list TList (Vec.fromList ["tx1", "tx2", "tx3"]) 1)
|
||||
("Start up Ok! Connected to Zebra " ++
|
||||
(T.unpack . zgi_build) zebra ++ " on port " ++ show port ++ ".")
|
||||
|
@ -482,39 +325,16 @@ runZenithCLI host port dbFilePath = do
|
|||
(F.focusRing [AList, TList])
|
||||
(zgb_blocks chainInfo)
|
||||
dbFilePath
|
||||
MsgDisplay
|
||||
Nothing -> do
|
||||
print $
|
||||
"No Zebra node available on port " <>
|
||||
show port <> ". Check your configuration"
|
||||
|
||||
refreshWallet :: State -> IO State
|
||||
refreshWallet s = do
|
||||
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 w1
|
||||
Just (_k, w) -> return w
|
||||
aL <- getAccounts (s ^. dbPath) $ entityKey selWallet
|
||||
addrL <-
|
||||
if not (null aL)
|
||||
then getAddresses (s ^. dbPath) $ entityKey $ head aL
|
||||
else return []
|
||||
let aL' = L.listReplace (Vec.fromList aL) (Just 0) (s ^. accounts)
|
||||
let addrL' = L.listReplace (Vec.fromList addrL) (Just 0) (s ^. addresses)
|
||||
return $
|
||||
(s & accounts .~ aL') & addresses .~ addrL' & msg .~ "Switched to wallet: " ++
|
||||
T.unpack (zcashWalletName $ entityVal selWallet)
|
||||
|
||||
addNewWallet :: T.Text -> State -> IO State
|
||||
addNewWallet n s = do
|
||||
sP <- generateWalletSeedPhrase
|
||||
let bH = s ^. startBlock
|
||||
let netName = s ^. network
|
||||
let netName = read $ s ^. network
|
||||
r <- saveWallet (s ^. dbPath) $ ZcashWallet n netName sP bH
|
||||
case r of
|
||||
Nothing -> do
|
||||
|
@ -538,70 +358,21 @@ addNewAccount n s = do
|
|||
Just (_j, w1) -> return w1
|
||||
Just (_k, w) -> return w
|
||||
aL' <- getMaxAccount (s ^. dbPath) (entityKey selWallet)
|
||||
zA <-
|
||||
try $ createZcashAccount n (aL' + 1) selWallet :: IO
|
||||
(Either IOError ZcashAccount)
|
||||
case zA of
|
||||
Left e -> return $ s & msg .~ ("Error: " ++ show e)
|
||||
Right zA' -> do
|
||||
r <- saveAccount (s ^. dbPath) zA'
|
||||
case r of
|
||||
Nothing ->
|
||||
return $ s & msg .~ ("Account already exists: " ++ T.unpack n)
|
||||
Just x -> do
|
||||
aL <- getAccounts (s ^. dbPath) (entityKey selWallet)
|
||||
let nL =
|
||||
L.listMoveToElement x $
|
||||
L.listReplace (Vec.fromList aL) (Just 0) (s ^. accounts)
|
||||
return $
|
||||
(s & accounts .~ nL) & msg .~ "Created new account: " ++ T.unpack n
|
||||
|
||||
refreshAccount :: State -> IO State
|
||||
refreshAccount s = do
|
||||
selAccount <-
|
||||
do case L.listSelectedElement $ s ^. accounts of
|
||||
Nothing -> do
|
||||
let fAcc =
|
||||
L.listSelectedElement $ L.listMoveToBeginning $ s ^. accounts
|
||||
case fAcc of
|
||||
Nothing -> throw $ userError "Failed to select account"
|
||||
Just (_j, w1) -> return w1
|
||||
Just (_k, w) -> return w
|
||||
aL <- getAddresses (s ^. dbPath) $ entityKey selAccount
|
||||
let aL' = L.listReplace (Vec.fromList aL) (Just 0) (s ^. addresses)
|
||||
return $
|
||||
s & addresses .~ aL' & msg .~ "Switched to account: " ++
|
||||
T.unpack (zcashAccountName $ entityVal selAccount)
|
||||
|
||||
addNewAddress :: T.Text -> State -> IO State
|
||||
addNewAddress n s = do
|
||||
selAccount <-
|
||||
do case L.listSelectedElement $ s ^. accounts of
|
||||
Nothing -> do
|
||||
let fAcc =
|
||||
L.listSelectedElement $ L.listMoveToBeginning $ s ^. accounts
|
||||
case fAcc of
|
||||
Nothing -> throw $ userError "Failed to select account"
|
||||
Just (_j, a1) -> return a1
|
||||
Just (_k, a) -> return a
|
||||
maxAddr <- getMaxAddress (s ^. dbPath) (entityKey selAccount)
|
||||
uA <-
|
||||
try $ createWalletAddress n (maxAddr + 1) (s ^. network) selAccount :: IO
|
||||
(Either IOError WalletAddress)
|
||||
case uA of
|
||||
Left e -> return $ s & msg .~ ("Error: " ++ show e)
|
||||
Right uA' -> do
|
||||
nAddr <- saveAddress (s ^. dbPath) uA'
|
||||
case nAddr of
|
||||
Nothing ->
|
||||
return $ s & msg .~ ("Address already exists: " ++ T.unpack n)
|
||||
Just x -> do
|
||||
addrL <- getAddresses (s ^. dbPath) (entityKey selAccount)
|
||||
let nL =
|
||||
L.listMoveToElement x $
|
||||
L.listReplace (Vec.fromList addrL) (Just 0) (s ^. addresses)
|
||||
return $
|
||||
(s & addresses .~ nL) & msg .~ "Created new address: " ++
|
||||
T.unpack n ++
|
||||
"(" ++
|
||||
T.unpack (showAddress $ walletAddressUAddress $ entityVal x) ++ ")"
|
||||
r <-
|
||||
saveAccount (s ^. dbPath) $
|
||||
ZcashAccount
|
||||
(aL' + 1)
|
||||
(entityKey selWallet)
|
||||
n
|
||||
"fakeOrchKey"
|
||||
"fakeSapKey"
|
||||
"fakeTKey"
|
||||
case r of
|
||||
Nothing -> return $ s & msg .~ ("Account already exists: " ++ T.unpack n)
|
||||
Just x -> do
|
||||
aL <- getAccounts (s ^. dbPath) (entityKey selWallet)
|
||||
let nL =
|
||||
L.listMoveToElement x $
|
||||
L.listReplace (Vec.fromList aL) (Just 0) (s ^. accounts)
|
||||
return $
|
||||
(s & accounts .~ nL) & msg .~ "Created new account: " ++ T.unpack n
|
||||
|
|
|
@ -3,18 +3,64 @@
|
|||
-- Core wallet functionality for Zenith
|
||||
module Zenith.Core where
|
||||
|
||||
import Control.Exception (throwIO)
|
||||
import Data.Aeson
|
||||
import qualified Data.ByteString as BS
|
||||
import qualified Data.Text as T
|
||||
import Database.Persist
|
||||
import Database.Persist.Sqlite
|
||||
import Network.HTTP.Client
|
||||
import ZcashHaskell.Keys
|
||||
import ZcashHaskell.Orchard
|
||||
import ZcashHaskell.Types
|
||||
import ZcashHaskell.Utils
|
||||
import Zenith.DB
|
||||
|
||||
-- * Database functions
|
||||
-- | Initializes the database
|
||||
initDb ::
|
||||
T.Text -- ^ The database path to check
|
||||
-> IO ()
|
||||
initDb dbName = do
|
||||
runSqlite dbName $ do runMigration migrateAll
|
||||
|
||||
-- | Save a new wallet to the database
|
||||
saveWallet ::
|
||||
T.Text -- ^ The database path to use
|
||||
-> ZcashWallet -- ^ The wallet to add to the database
|
||||
-> IO (Maybe (Entity ZcashWallet))
|
||||
saveWallet dbFp w = runSqlite dbFp $ insertUniqueEntity w
|
||||
|
||||
-- | Returns a list of accounts associated with the given wallet
|
||||
getAccounts ::
|
||||
T.Text -- ^ The database path
|
||||
-> ZcashWalletId -- ^ The wallet ID to check
|
||||
-> IO [Entity ZcashAccount]
|
||||
getAccounts dbFp w = runSqlite dbFp $ selectList [ZcashAccountWalletId ==. w] []
|
||||
|
||||
-- | Returns the largest account index for the given wallet
|
||||
getMaxAccount ::
|
||||
T.Text -- ^ The database path
|
||||
-> ZcashWalletId -- ^ The wallet ID to check
|
||||
-> IO Int
|
||||
getMaxAccount dbFp w = do
|
||||
a <-
|
||||
runSqlite dbFp $
|
||||
selectFirst [ZcashAccountWalletId ==. w] [Desc ZcashAccountIndex]
|
||||
case a of
|
||||
Nothing -> return $ -1
|
||||
Just x -> return $ zcashAccountIndex $ entityVal x
|
||||
|
||||
-- | Save a new account to the database
|
||||
saveAccount ::
|
||||
T.Text -- ^ The database path
|
||||
-> ZcashAccount -- ^ The account to add to the database
|
||||
-> IO (Maybe (Entity ZcashAccount))
|
||||
saveAccount dbFp a = runSqlite dbFp $ insertUniqueEntity a
|
||||
|
||||
-- | Returns a list of addresses associated with the given account
|
||||
getAddresses ::
|
||||
T.Text -- ^ The database path
|
||||
-> ZcashAccountId -- ^ The account ID to check
|
||||
-> IO [Entity WalletAddress]
|
||||
getAddresses dbFp a = runSqlite dbFp $ selectList [WalletAddressAccId ==. a] []
|
||||
|
||||
-- * Zebra Node interaction
|
||||
-- | Checks the status of the `zebrad` node
|
||||
checkZebra ::
|
||||
|
@ -33,7 +79,7 @@ checkBlockChain ::
|
|||
-> IO (Maybe ZebraGetBlockChainInfo)
|
||||
checkBlockChain nodeHost nodePort = do
|
||||
let f = makeZebraCall nodeHost nodePort
|
||||
result . responseBody <$> f "getblockchaininfo" []
|
||||
result <$> (responseBody <$> f "getblockchaininfo" [])
|
||||
|
||||
-- | Generic RPC call function
|
||||
connectZebra ::
|
||||
|
@ -42,52 +88,3 @@ connectZebra nodeHost nodePort m params = do
|
|||
res <- makeZebraCall nodeHost nodePort m params
|
||||
let body = responseBody res
|
||||
return $ result body
|
||||
|
||||
-- * Spending Keys
|
||||
-- | Create an Orchard Spending Key for the given wallet and account index
|
||||
createOrchardSpendingKey :: ZcashWallet -> Int -> IO BS.ByteString
|
||||
createOrchardSpendingKey zw i = do
|
||||
let s = getWalletSeed $ zcashWalletSeedPhrase zw
|
||||
case s of
|
||||
Nothing -> throwIO $ userError "Unable to generate seed"
|
||||
Just s' -> do
|
||||
let coinType =
|
||||
case zcashWalletNetwork zw of
|
||||
MainNet -> MainNetCoin
|
||||
TestNet -> TestNetCoin
|
||||
RegTestNet -> RegTestNetCoin
|
||||
let r = genOrchardSpendingKey s' coinType i
|
||||
case r of
|
||||
Nothing -> throwIO $ userError "Unable to generate Orchard spending key"
|
||||
Just sk -> return sk
|
||||
|
||||
-- * Accounts
|
||||
-- | Create an account for the given wallet and account index
|
||||
createZcashAccount ::
|
||||
T.Text -- ^ The account's name
|
||||
-> Int -- ^ The account's index
|
||||
-> Entity ZcashWallet -- ^ The Zcash wallet that this account will be attached to
|
||||
-> IO ZcashAccount
|
||||
createZcashAccount n i zw = do
|
||||
orSk <- createOrchardSpendingKey (entityVal zw) i
|
||||
return $ ZcashAccount i (entityKey zw) n orSk "fakeSapKey" "fakeTkey"
|
||||
|
||||
-- * Addresses
|
||||
-- | Create a unified address for the given account and index
|
||||
createWalletAddress ::
|
||||
T.Text -- ^ The address nickname
|
||||
-> Int -- ^ The address' index
|
||||
-> ZcashNet -- ^ The network for this address
|
||||
-> Entity ZcashAccount -- ^ The Zcash account that the address will be attached to
|
||||
-> IO WalletAddress
|
||||
createWalletAddress n i zNet za = do
|
||||
return $
|
||||
WalletAddress
|
||||
i
|
||||
(entityKey za)
|
||||
n
|
||||
(UnifiedAddress
|
||||
zNet
|
||||
"fakeBString"
|
||||
"fakeBString"
|
||||
(Just $ TransparentAddress P2PKH zNet "fakeBString"))
|
||||
|
|
|
@ -23,12 +23,10 @@ import qualified Data.Text as T
|
|||
import Database.Persist
|
||||
import Database.Persist.Sqlite
|
||||
import Database.Persist.TH
|
||||
import ZcashHaskell.Types (Phrase, UnifiedAddress(..), ZcashNet)
|
||||
import ZcashHaskell.Types (Phrase, ZcashNet)
|
||||
|
||||
derivePersistField "ZcashNet"
|
||||
|
||||
derivePersistField "UnifiedAddress"
|
||||
|
||||
share
|
||||
[mkPersist sqlSettings, mkMigrate "migrateAll"]
|
||||
[persistLowerCase|
|
||||
|
@ -47,87 +45,19 @@ share
|
|||
sapSpendKey BS.ByteString
|
||||
tPrivateKey BS.ByteString
|
||||
UniqueAccount index walletId
|
||||
UniqueAccName walletId name
|
||||
deriving Show Eq
|
||||
WalletAddress
|
||||
index Int
|
||||
accId ZcashAccountId
|
||||
name T.Text
|
||||
uAddress UnifiedAddress
|
||||
UniqueAddress index accId
|
||||
UniqueAddName accId name
|
||||
index Int
|
||||
orchRec BS.ByteString Maybe
|
||||
sapRec BS.ByteString Maybe
|
||||
tRec BS.ByteString Maybe
|
||||
encoded T.Text
|
||||
deriving Show Eq
|
||||
|]
|
||||
|
||||
-- * Database functions
|
||||
-- | Initializes the database
|
||||
initDb ::
|
||||
T.Text -- ^ The database path to check
|
||||
-> IO ()
|
||||
initDb dbName = do
|
||||
runSqlite dbName $ do runMigration migrateAll
|
||||
|
||||
-- | Get existing wallets from database
|
||||
getWallets :: T.Text -> ZcashNet -> IO [Entity ZcashWallet]
|
||||
getWallets dbFp n = runSqlite dbFp $ selectList [ZcashWalletNetwork ==. n] []
|
||||
|
||||
-- | Save a new wallet to the database
|
||||
saveWallet ::
|
||||
T.Text -- ^ The database path to use
|
||||
-> ZcashWallet -- ^ The wallet to add to the database
|
||||
-> IO (Maybe (Entity ZcashWallet))
|
||||
saveWallet dbFp w = runSqlite dbFp $ insertUniqueEntity w
|
||||
|
||||
-- | Returns a list of accounts associated with the given wallet
|
||||
getAccounts ::
|
||||
T.Text -- ^ The database path
|
||||
-> ZcashWalletId -- ^ The wallet ID to check
|
||||
-> IO [Entity ZcashAccount]
|
||||
getAccounts dbFp w = runSqlite dbFp $ selectList [ZcashAccountWalletId ==. w] []
|
||||
|
||||
-- | Returns the largest account index for the given wallet
|
||||
getMaxAccount ::
|
||||
T.Text -- ^ The database path
|
||||
-> ZcashWalletId -- ^ The wallet ID to check
|
||||
-> IO Int
|
||||
getMaxAccount dbFp w = do
|
||||
a <-
|
||||
runSqlite dbFp $
|
||||
selectFirst [ZcashAccountWalletId ==. w] [Desc ZcashAccountIndex]
|
||||
case a of
|
||||
Nothing -> return $ -1
|
||||
Just x -> return $ zcashAccountIndex $ entityVal x
|
||||
|
||||
-- | Save a new account to the database
|
||||
saveAccount ::
|
||||
T.Text -- ^ The database path
|
||||
-> ZcashAccount -- ^ The account to add to the database
|
||||
-> IO (Maybe (Entity ZcashAccount))
|
||||
saveAccount dbFp a = runSqlite dbFp $ insertUniqueEntity a
|
||||
|
||||
-- | Returns a list of addresses associated with the given account
|
||||
getAddresses ::
|
||||
T.Text -- ^ The database path
|
||||
-> ZcashAccountId -- ^ The account ID to check
|
||||
-> IO [Entity WalletAddress]
|
||||
getAddresses dbFp a = runSqlite dbFp $ selectList [WalletAddressAccId ==. a] []
|
||||
|
||||
-- | Returns the largest address index for the given account
|
||||
getMaxAddress ::
|
||||
T.Text -- ^ The database path
|
||||
-> ZcashAccountId -- ^ The wallet ID to check
|
||||
-> IO Int
|
||||
getMaxAddress dbFp w = do
|
||||
a <-
|
||||
runSqlite dbFp $
|
||||
selectFirst [WalletAddressAccId ==. w] [Desc WalletAddressIndex]
|
||||
case a of
|
||||
Nothing -> return $ -1
|
||||
Just x -> return $ walletAddressIndex $ entityVal x
|
||||
|
||||
-- | Save a new address to the database
|
||||
saveAddress ::
|
||||
T.Text -- ^ the database path
|
||||
-> WalletAddress -- ^ The wallet to add to the database
|
||||
-> IO (Maybe (Entity WalletAddress))
|
||||
saveAddress dbFp w = runSqlite dbFp $ insertUniqueEntity w
|
||||
getWallets dbFp n =
|
||||
runSqlite dbFp $ do
|
||||
s <- selectList [ZcashWalletNetwork ==. n] []
|
||||
liftIO $ return s
|
||||
|
|
|
@ -13,9 +13,8 @@ import qualified Data.Text.IO as TIO
|
|||
import System.Process (createProcess_, shell)
|
||||
import Text.Read (readMaybe)
|
||||
import Text.Regex.Posix
|
||||
import ZcashHaskell.Orchard (encodeUnifiedAddress, isValidUnifiedAddress)
|
||||
import ZcashHaskell.Orchard (isValidUnifiedAddress)
|
||||
import ZcashHaskell.Sapling (isValidShieldedAddress)
|
||||
import ZcashHaskell.Types (UnifiedAddress(..))
|
||||
import Zenith.Types
|
||||
( AddressGroup(..)
|
||||
, AddressSource(..)
|
||||
|
@ -31,12 +30,6 @@ displayZec s
|
|||
| s < 100000000 = show (fromIntegral s / 100000) ++ " mZEC "
|
||||
| otherwise = show (fromIntegral s / 100000000) ++ " ZEC "
|
||||
|
||||
-- | Helper function to display abbreviated Unified Address
|
||||
showAddress :: UnifiedAddress -> T.Text
|
||||
showAddress u = T.take 20 t <> "..."
|
||||
where
|
||||
t = encodeUnifiedAddress u
|
||||
|
||||
-- | Helper function to extract addresses from AddressGroups
|
||||
getAddresses :: AddressGroup -> [ZcashAddress]
|
||||
getAddresses ag = agtransparent ag <> agsapling ag <> agunified ag
|
||||
|
|
|
@ -1 +1 @@
|
|||
Subproject commit e371fcdb724686bfb51157911c5d4c0fda433c53
|
||||
Subproject commit a52d2231f1a4f85a6504bfb9228a1475a0773088
|
Loading…
Reference in a new issue