Merge pull request 'fix079: SQLite implementation' (#4) from fix079 into dev041

Reviewed-on: #4
This commit is contained in:
pitmutt 2024-01-23 15:58:31 +00:00 committed by Vergara Technologies LLC
commit 19ce971b96
Signed by: Vergara Technologies LLC
GPG Key ID: 99DB473BB4715618
4 changed files with 97 additions and 3 deletions

View File

@ -41,7 +41,9 @@ library:
- array
- base64-bytestring
- hexstring
- blake2
- persistent
- persistent-sqlite
- persistent-template
- zcash-haskell
executables:
@ -74,3 +76,7 @@ tests:
- -with-rtsopts=-N
dependencies:
- zenith
- hspec
- persistent
- persistent-sqlite
- persistent-template

View File

@ -1 +1,36 @@
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE EmptyDataDecls #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE QuasiQuotes #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE DerivingStrategies #-}
{-# LANGUAGE StandaloneDeriving #-}
{-# LANGUAGE UndecidableInstances #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE TypeOperators #-}
module Zenith.DB where
import qualified Data.ByteString as BS
import qualified Data.Text as T
import Database.Persist
import Database.Persist.Sqlite
import Database.Persist.TH
import ZcashHaskell.Types (Phrase)
share
[mkPersist sqlSettings, mkMigrate "migrateAll"]
[persistLowerCase|
ZcashWallet
seedPhrase Phrase
spendingKey BS.ByteString
tPrivateKey BS.ByteString
birthdayHeight Int
name T.Text
deriving Show
|]

View File

@ -1,2 +1,49 @@
{-# LANGUAGE OverloadedStrings #-}
import Control.Monad.IO.Class (liftIO)
import Database.Persist
import Database.Persist.Sqlite
import Test.Hspec
import Zenith.DB
import Zenith.DB
( EntityField(ZcashWalletId, ZcashWalletName)
, ZcashWallet(zcashWalletName)
)
main :: IO ()
main = putStrLn "Test suite not yet implemented"
main = do
hspec $ do
describe "Database tests" $ do
it "Create table" $ do
s <- runSqlite "test.db" $ do runMigration migrateAll
s `shouldBe` ()
it "insert wallet record" $ do
s <-
runSqlite "test.db" $ do
insert $
ZcashWallet
"one two three four five six seven eight nine ten eleven twelve"
"123456789"
"987654321"
2000000
"Main Wallet"
fromSqlKey s `shouldBe` 1
it "read wallet record" $ do
s <-
runSqlite "test.db" $ do
selectList [ZcashWalletBirthdayHeight >. 0] []
length s `shouldBe` 1
it "modify wallet record" $ do
s <-
runSqlite "test.db" $ do
let recId = toSqlKey 1 :: ZcashWalletId
update recId [ZcashWalletName =. "New Wallet"]
get recId
"New Wallet" `shouldBe` maybe "None" zcashWalletName s
it "delete wallet record" $ do
s <-
runSqlite "test.db" $ do
let recId = toSqlKey 1 :: ZcashWalletId
delete recId
get recId
"None" `shouldBe` maybe "None" zcashWalletName s

View File

@ -39,11 +39,13 @@ library
, array
, base >=4.7 && <5
, base64-bytestring
, blake2
, bytestring
, hexstring
, http-conduit
, http-types
, persistent
, persistent-sqlite
, persistent-template
, process
, regex-base
, regex-compat
@ -83,5 +85,9 @@ test-suite zenith-test
ghc-options: -threaded -rtsopts -with-rtsopts=-N
build-depends:
base >=4.7 && <5
, hspec
, persistent
, persistent-sqlite
, persistent-template
, zenith
default-language: Haskell2010