Publish Zenith beta version #80

Merged
pitmutt merged 90 commits from dev041 into master 2024-05-09 19:15:41 +00:00
2 changed files with 22 additions and 2 deletions
Showing only changes of commit 22f889bf86 - Show all commits

View file

@ -1,6 +1,6 @@
{-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE OverloadedStrings #-}
-- Core wallet functionality for Zenith -- | Core wallet functionality for Zenith
module Zenith.Core where module Zenith.Core where
import Control.Exception (throwIO) import Control.Exception (throwIO)

View file

@ -19,13 +19,15 @@ module Zenith.DB where
import Control.Monad.IO.Class (liftIO) import Control.Monad.IO.Class (liftIO)
import qualified Data.ByteString as BS import qualified Data.ByteString as BS
import Data.HexString
import qualified Data.Text as T import qualified Data.Text as T
import Database.Persist import Database.Persist
import Database.Persist.Sqlite import Database.Persist.Sqlite
import Database.Persist.TH import Database.Persist.TH
import ZcashHaskell.Types (Scope(..), ZcashNet) import ZcashHaskell.Types (Scope(..), ZcashNet)
import Zenith.Types import Zenith.Types
( OrchardSpendingKeyDB(..) ( HexStringDB(..)
, OrchardSpendingKeyDB(..)
, PhraseDB(..) , PhraseDB(..)
, SaplingSpendingKeyDB(..) , SaplingSpendingKeyDB(..)
, ScopeDB(..) , ScopeDB(..)
@ -65,6 +67,18 @@ share
deriving Show Eq deriving Show Eq
|] |]
share
[mkPersist sqlSettings, mkMigrate "rawStorage"]
[persistLowerCase|
WalletTransaction
block Int
txId HexStringDB
conf Int
time Int
hex HexStringDB
deriving Show Eq
|]
-- * Database functions -- * Database functions
-- | Initializes the database -- | Initializes the database
initDb :: initDb ::
@ -73,6 +87,12 @@ initDb ::
initDb dbName = do initDb dbName = do
runSqlite dbName $ do runMigration migrateAll runSqlite dbName $ do runMigration migrateAll
-- | Initializes the raw data storage
initRawStore ::
T.Text -- ^ the database path
-> IO ()
initRawStore dbFilePath = runSqlite dbFilePath $ runMigration rawStorage
-- | Get existing wallets from database -- | Get existing wallets from database
getWallets :: T.Text -> ZcashNet -> IO [Entity ZcashWallet] getWallets :: T.Text -> ZcashNet -> IO [Entity ZcashWallet]
getWallets dbFp n = getWallets dbFp n =