Compare commits

..

No commits in common. "eb925c21f7b868cb19af3d9abd0b6242f77ee506" and "dbbce675f5eee3ffedfbc077b9a07e9df614a107" have entirely different histories.

3 changed files with 106 additions and 242 deletions

View file

@ -77,7 +77,6 @@ import Zenith.Types
, TransparentSpendingKeyDB , TransparentSpendingKeyDB
, UnifiedAddressDB(..) , UnifiedAddressDB(..)
, ZcashNetDB(..) , ZcashNetDB(..)
, ZcashPool(..)
) )
share share
@ -247,15 +246,6 @@ share
position Int position Int
UniqueSSPos tx position UniqueSSPos tx position
deriving Show Eq deriving Show Eq
QrCode
address WalletAddressId OnDeleteCascade OnUpdateCascade
version ZcashPool
bytes BS.ByteString
height Int
width Int
name T.Text
UniqueQr address version
deriving Show Eq
|] |]
-- * Database functions -- * Database functions
@ -426,16 +416,6 @@ getWalletAddresses pool w = do
addrs <- mapM (getAddresses pool . entityKey) accs addrs <- mapM (getAddresses pool . entityKey) accs
return $ concat addrs return $ concat addrs
getExternalAddresses :: ConnectionPool -> IO [Entity WalletAddress]
getExternalAddresses pool = do
runNoLoggingT $
PS.retryOnBusy $
flip PS.runSqlPool pool $ do
select $ do
addrs <- from $ table @WalletAddress
where_ $ addrs ^. WalletAddressScope ==. val (ScopeDB External)
return addrs
-- | Returns the largest address index for the given account -- | Returns the largest address index for the given account
getMaxAddress :: getMaxAddress ::
ConnectionPool -- ^ The database path ConnectionPool -- ^ The database path
@ -568,41 +548,6 @@ getZcashTransactions pool b =
orderBy [asc $ txs ^. ZcashTransactionBlock] orderBy [asc $ txs ^. ZcashTransactionBlock]
return txs return txs
-- ** QR codes
-- | Functions to manage the QR codes stored in the database
saveQrCode ::
ConnectionPool -- ^ the connection pool
-> QrCode
-> NoLoggingT IO (Maybe (Entity QrCode))
saveQrCode pool qr =
PS.retryOnBusy $ flip PS.runSqlPool pool $ insertUniqueEntity qr
getQrCodes ::
ConnectionPool -- ^ the connection pool
-> WalletAddressId
-> IO [Entity QrCode]
getQrCodes pool wId =
runNoLoggingT $
PS.retryOnBusy $
flip PS.runSqlPool pool $ do
select $ do
qrs <- from $ table @QrCode
where_ $ qrs ^. QrCodeAddress ==. val wId
return qrs
getQrCode :: ConnectionPool -> ZcashPool -> WalletAddressId -> IO (Maybe QrCode)
getQrCode pool zp wId = do
r <-
runNoLoggingT $
PS.retryOnBusy $
flip PS.runSqlPool pool $ do
selectOne $ do
qrs <- from $ table @QrCode
where_ $ qrs ^. QrCodeAddress ==. val wId
where_ $ qrs ^. QrCodeVersion ==. val zp
return qrs
return $ entityVal <$> r
-- * Wallet -- * Wallet
-- | Get the block of the last transaction known to the wallet -- | Get the block of the last transaction known to the wallet
getMaxWalletBlock :: getMaxWalletBlock ::

View file

@ -15,7 +15,6 @@ import Data.Maybe (fromMaybe, isJust)
import qualified Data.Text as T import qualified Data.Text as T
import qualified Data.Text.Encoding as E import qualified Data.Text.Encoding as E
import Data.Time.Clock.POSIX (posixSecondsToUTCTime) import Data.Time.Clock.POSIX (posixSecondsToUTCTime)
import Database.Esqueleto.Experimental (ConnectionPool)
import Database.Persist import Database.Persist
import Lens.Micro ((&), (+~), (.~), (?~), (^.), set) import Lens.Micro ((&), (+~), (.~), (?~), (^.), set)
import Lens.Micro.TH import Lens.Micro.TH
@ -36,17 +35,6 @@ import Zenith.GUI.Theme
import Zenith.Types hiding (ZcashAddress) import Zenith.Types hiding (ZcashAddress)
import Zenith.Utils (displayAmount, showAddress) import Zenith.Utils (displayAmount, showAddress)
data AppEvent
= AppInit
| ShowMsg !T.Text
| CloseMsg
| WalletClicked
| AccountClicked
| SetPool !ZcashPool
| SwitchQr !(Maybe QrCode)
| SwitchAddr !Int
deriving (Eq, Show)
data AppModel = AppModel data AppModel = AppModel
{ _configuration :: !Config { _configuration :: !Config
, _network :: !ZcashNet , _network :: !ZcashNet
@ -63,11 +51,19 @@ data AppModel = AppModel
, _balance :: !Integer , _balance :: !Integer
, _unconfBalance :: !(Maybe Integer) , _unconfBalance :: !(Maybe Integer)
, _selPool :: !ZcashPool , _selPool :: !ZcashPool
, _qrCodeWidget :: !(Maybe QrCode)
} deriving (Eq, Show) } deriving (Eq, Show)
makeLenses ''AppModel makeLenses ''AppModel
data AppEvent
= AppInit
| ShowMsg !T.Text
| CloseMsg
| WalletClicked
| AccountClicked
| SetPool !ZcashPool
deriving (Eq, Show)
remixArrowRightWideLine :: T.Text remixArrowRightWideLine :: T.Text
remixArrowRightWideLine = toGlyph 0xF496 remixArrowRightWideLine = toGlyph 0xF496
@ -172,10 +168,15 @@ buildUI wenv model = widgetTree
"addrScroll" "addrScroll"
]) `styleBasic` ]) `styleBasic`
[padding 3, radius 2, bgColor white] [padding 3, radius 2, bgColor white]
, addrQRCode , addrQRCode currentAddress (model ^. selPool)
] ]
addrQRCode :: WidgetNode AppModel AppEvent addrQRCode ::
addrQRCode = Maybe (Entity WalletAddress)
-> ZcashPool
-> WidgetNode AppModel AppEvent
addrQRCode wAddr zp =
case encodeText (defaultQRCodeOptions L) Utf8WithoutECI =<< dispAddr of
Just qr ->
box_ box_
[alignMiddle] [alignMiddle]
(hstack (hstack
@ -186,8 +187,9 @@ buildUI wenv model = widgetTree
(remixIcon remixShieldCheckFill `styleBasic` (remixIcon remixShieldCheckFill `styleBasic`
[ textSize 14 [ textSize 14
, padding 4 , padding 4
, styleIf (model ^. selPool == Orchard) (bgColor btnColor) , styleIf
, styleIf (model ^. selPool == Orchard) (textColor white) (model ^. selPool == Orchard)
(bgColor btnColor)
]) ])
, filler , filler
, box_ , box_
@ -195,8 +197,9 @@ buildUI wenv model = widgetTree
(remixIcon remixShieldLine `styleBasic` (remixIcon remixShieldLine `styleBasic`
[ textSize 14 [ textSize 14
, padding 4 , padding 4
, styleIf (model ^. selPool == Sapling) (bgColor btnColor) , styleIf
, styleIf (model ^. selPool == Sapling) (textColor white) (model ^. selPool == Sapling)
(bgColor btnColor)
]) ])
, filler , filler
, box_ , box_
@ -207,9 +210,6 @@ buildUI wenv model = widgetTree
, styleIf , styleIf
(model ^. selPool == Transparent) (model ^. selPool == Transparent)
(bgColor btnColor) (bgColor btnColor)
, styleIf
(model ^. selPool == Transparent)
(textColor white)
]) ])
] ]
, vstack , vstack
@ -218,38 +218,58 @@ buildUI wenv model = widgetTree
Orchard -> "Unified" Orchard -> "Unified"
Sapling -> "Legacy Shielded" Sapling -> "Legacy Shielded"
Transparent -> "Transparent" Transparent -> "Transparent"
Sprout -> "Unknown") `styleBasic` Sprout -> "Unknown")
[textColor white] , imageMem_
, box_ (T.pack $ show zp)
[alignMiddle]
(case model ^. qrCodeWidget of
Just qr ->
imageMem_
(qrCodeName qr)
(qrCodeBytes qr) (qrCodeBytes qr)
(Size (qrCodeSize qr)
(fromIntegral $ qrCodeHeight qr) [fitNone]
(fromIntegral $ qrCodeWidth qr)) ]
[fitWidth]
Nothing -> image_ "./assets/2620_color.png" [fitEither]) `styleBasic`
[bgColor white, height 100, width 100]
] `styleBasic`
[bgColor btnColor, border 2 btnColor]
, filler , filler
] `styleBasic` ])
[bgColor white]) Nothing ->
box_ [alignMiddle] (image_ "./assets/2620_color.png" [fitFill])
where
qrCodeImg :: QRImage -> Image PixelRGBA8
qrCodeImg qr = promoteImage (toImage 4 1 qr)
qrCodeSize :: QRImage -> Size
qrCodeSize qr =
Size
(fromIntegral $ imageWidth $ qrCodeImg qr)
(fromIntegral $ imageHeight $ qrCodeImg qr)
qrCodeBytes :: QRImage -> BS.ByteString
qrCodeBytes qr =
BS.pack $
pixelFold
(\bs _ _ (PixelRGBA8 i j k l) -> bs <> [i, j, k, l])
[]
(qrCodeImg qr)
dispAddr :: Maybe T.Text
dispAddr =
case zp of
Transparent ->
T.append "zcash:" . encodeTransparentReceiver (model ^. network) <$>
(t_rec =<<
(isValidUnifiedAddress .
E.encodeUtf8 . getUA . walletAddressUAddress . entityVal) =<<
wAddr)
Sapling ->
T.append "zcash:" <$>
(getSaplingFromUA .
E.encodeUtf8 . getUA . walletAddressUAddress . entityVal =<<
wAddr)
Orchard ->
T.append "zcash:" . getUA . walletAddressUAddress . entityVal <$>
wAddr
Sprout -> Nothing
addrRow :: Int -> Entity WalletAddress -> WidgetNode AppModel AppEvent addrRow :: Int -> Entity WalletAddress -> WidgetNode AppModel AppEvent
addrRow idx wAddr = addrRow idx wAddr =
box_ box_
[onClick $ SwitchAddr idx, alignLeft] [onClick $ ShowMsg ("You clicked address " <> showt idx), alignLeft]
(label (label
(walletAddressName (entityVal wAddr) <> (walletAddressName (entityVal wAddr) <>
": " <> showAddress (walletAddressUAddress $ entityVal wAddr))) `styleBasic` ": " <> showAddress (walletAddressUAddress $ entityVal wAddr))) `styleBasic`
[ padding 1 [padding 1, borderB 1 gray]
, borderB 1 gray
, styleIf (model ^. selAddr == idx) (borderL 2 btnHiLite)
, styleIf (model ^. selAddr == idx) (borderR 2 btnHiLite)
]
txBox = txBox =
boxShadow $ boxShadow $
box_ box_
@ -307,74 +327,6 @@ buildUI wenv model = widgetTree
alert CloseMsg $ alert CloseMsg $
hstack [filler, label $ fromMaybe "" (model ^. msg), filler] hstack [filler, label $ fromMaybe "" (model ^. msg), filler]
generateQRCodes :: Config -> IO ()
generateQRCodes config = do
let dbFilePath = c_dbPath config
pool <- runNoLoggingT $ initPool dbFilePath
addrs <- getExternalAddresses pool
mapM_ (checkExistingQrs pool) addrs
where
checkExistingQrs :: ConnectionPool -> Entity WalletAddress -> IO ()
checkExistingQrs pool wAddr = do
s <- getQrCodes pool (entityKey wAddr)
if not (null s)
then return ()
else do
generateOneQr pool Orchard wAddr
generateOneQr pool Sapling wAddr
generateOneQr pool Transparent wAddr
generateOneQr ::
ConnectionPool -> ZcashPool -> Entity WalletAddress -> IO ()
generateOneQr p zp wAddr =
case encodeText (defaultQRCodeOptions L) Utf8WithoutECI =<<
dispAddr zp (entityVal wAddr) of
Just qr -> do
_ <-
runNoLoggingT $
saveQrCode p $
QrCode
(entityKey wAddr)
zp
(qrCodeData qr)
(qrCodeH qr)
(qrCodeW qr)
(walletAddressName (entityVal wAddr) <> T.pack (show zp))
return ()
Nothing -> return ()
qrCodeImg :: QRImage -> Image PixelRGBA8
qrCodeImg qr = promoteImage (toImage 4 2 qr)
qrCodeH :: QRImage -> Int
qrCodeH qr = fromIntegral $ imageHeight $ qrCodeImg qr
qrCodeW :: QRImage -> Int
qrCodeW qr = fromIntegral $ imageWidth $ qrCodeImg qr
qrCodeData :: QRImage -> BS.ByteString
qrCodeData qr =
BS.pack $
pixelFold
(\bs _ _ (PixelRGBA8 i j k l) -> bs <> [i, j, k, l])
[]
(qrCodeImg qr)
dispAddr :: ZcashPool -> WalletAddress -> Maybe T.Text
dispAddr zp w =
case zp of
Transparent ->
T.append "zcash:" .
encodeTransparentReceiver
(maybe
TestNet
ua_net
((isValidUnifiedAddress .
E.encodeUtf8 . getUA . walletAddressUAddress)
w)) <$>
(t_rec =<<
(isValidUnifiedAddress . E.encodeUtf8 . getUA . walletAddressUAddress)
w)
Sapling ->
T.append "zcash:" <$>
(getSaplingFromUA . E.encodeUtf8 . getUA . walletAddressUAddress) w
Orchard -> Just $ (T.append "zcash:" . getUA . walletAddressUAddress) w
Sprout -> Nothing
handleEvent :: handleEvent ::
WidgetEnv AppModel AppEvent WidgetEnv AppModel AppEvent
-> WidgetNode AppModel AppEvent -> WidgetNode AppModel AppEvent
@ -387,31 +339,8 @@ handleEvent wenv node model evt =
ShowMsg t -> [Model $ model & msg ?~ t] ShowMsg t -> [Model $ model & msg ?~ t]
WalletClicked -> [Model $ model & msg ?~ "You clicked Wallet!"] WalletClicked -> [Model $ model & msg ?~ "You clicked Wallet!"]
AccountClicked -> [Model $ model & msg ?~ "You clicked Account!"] AccountClicked -> [Model $ model & msg ?~ "You clicked Account!"]
SetPool p -> SetPool p -> [Model $ model & selPool .~ p]
[ Model $ model & selPool .~ p
, Task $
SwitchQr <$> do
dbPool <- runNoLoggingT $ initPool $ c_dbPath $ model ^. configuration
case currentAddress of
Nothing -> return Nothing
Just wAddr -> getQrCode dbPool p $ entityKey wAddr
]
SwitchQr q -> [Model $ model & qrCodeWidget .~ q]
SwitchAddr i -> [Model $ model & selAddr .~ i, Event $ SetPool Orchard]
CloseMsg -> [Model $ model & msg .~ Nothing] CloseMsg -> [Model $ model & msg .~ Nothing]
where
currentWallet =
if null (model ^. wallets)
then Nothing
else Just ((model ^. wallets) !! (model ^. selWallet))
currentAccount =
if null (model ^. accounts)
then Nothing
else Just ((model ^. accounts) !! (model ^. selAcc))
currentAddress =
if null (model ^. addresses)
then Nothing
else Just ((model ^. addresses) !! (model ^. selAddr))
runZenithGUI :: Config -> IO () runZenithGUI :: Config -> IO ()
runZenithGUI config = do runZenithGUI config = do
@ -429,7 +358,6 @@ runZenithGUI config = do
Left e1 -> throwIO e1 Left e1 -> throwIO e1
Right chainInfo -> do Right chainInfo -> do
initDb dbFilePath initDb dbFilePath
generateQRCodes config
walList <- getWallets pool $ zgb_net chainInfo walList <- getWallets pool $ zgb_net chainInfo
accList <- accList <-
if not (null walList) if not (null walList)
@ -443,10 +371,6 @@ runZenithGUI config = do
if not (null addrList) if not (null addrList)
then getUserTx pool $ entityKey $ head addrList then getUserTx pool $ entityKey $ head addrList
else return [] else return []
qr <-
if not (null addrList)
then getQrCode pool Orchard $ entityKey $ head addrList
else return Nothing
let model = let model =
AppModel AppModel
config config
@ -463,8 +387,7 @@ runZenithGUI config = do
True True
314259000 314259000
(Just 300000) (Just 300000)
Orchard Transparent
qr
startApp model handleEvent buildUI params startApp model handleEvent buildUI params
Left e -> do Left e -> do
initDb dbFilePath initDb dbFilePath
@ -487,12 +410,10 @@ runZenithGUI config = do
314259000 314259000
(Just 30000) (Just 30000)
Orchard Orchard
Nothing
startApp model handleEvent buildUI params startApp model handleEvent buildUI params
where where
params = params =
[ appWindowTitle "Zenith - Zcash Full Node Wallet" [ appWindowTitle "Zenith - Zcash Full Node Wallet"
, appWindowState $ MainWindowNormal (1000, 600)
, appTheme zenithTheme , appTheme zenithTheme
, appFontDef "Regular" "./assets/Atkinson-Hyperlegible-Regular-102.ttf" --"./assets/DejaVuSansMono.ttf" , appFontDef "Regular" "./assets/Atkinson-Hyperlegible-Regular-102.ttf" --"./assets/DejaVuSansMono.ttf"
, appFontDef "Bold" "./assets/Atkinson-Hyperlegible-Bold-102.ttf" , appFontDef "Bold" "./assets/Atkinson-Hyperlegible-Bold-102.ttf"

View file

@ -143,9 +143,7 @@ data ZcashPool
| Sprout | Sprout
| Sapling | Sapling
| Orchard | Orchard
deriving (Show, Read, Eq, Generic, ToJSON) deriving (Show, Eq, Generic, ToJSON)
derivePersistField "ZcashPool"
instance FromJSON ZcashPool where instance FromJSON ZcashPool where
parseJSON = parseJSON =