Skip to content

Commit

Permalink
Add store laws for UTxOHistory store.
Browse files Browse the repository at this point in the history
  • Loading branch information
paolino committed Mar 24, 2023
1 parent 53d3d99 commit 4901b92
Show file tree
Hide file tree
Showing 2 changed files with 57 additions and 0 deletions.
1 change: 1 addition & 0 deletions lib/wallet/cardano-wallet.cabal
Expand Up @@ -866,6 +866,7 @@ test-suite unit
Cardano.Wallet.DB.Sqlite.TypesSpec
Cardano.Wallet.DB.StateMachine
Cardano.Wallet.DB.Store.DeltaUTxO.ModelSpec
Cardano.Wallet.DB.Store.DeltaUTxO.StoreSpec
Cardano.Wallet.DB.Store.DeltaUTxO.TxOutCBORSpec
Cardano.Wallet.DB.Store.Meta.ModelSpec
Cardano.Wallet.DB.Store.Meta.StoreSpec
Expand Down
@@ -0,0 +1,56 @@
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE NoMonomorphismRestriction #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# OPTIONS_GHC -Wno-orphans #-}

module Cardano.Wallet.DB.Store.DeltaUTxO.StoreSpec (spec) where

import Prelude

import Cardano.DB.Sqlite
( ForeignKeysSetting (..) )
import Cardano.Wallet.DB.Arbitrary
()
import Cardano.Wallet.DB.Fixtures
( WalletProperty, logScale, withDBInMemory, withInitializedWalletProp )
import Cardano.Wallet.DB.Store.DeltaUTxO.Model
( DeltaUTxOHistory (AppendBlock, Prune, Rollback), UTxOHistory, empty )
import Cardano.Wallet.DB.Store.DeltaUTxO.ModelSpec
( genDelta, genSlot, genSlotNo, genUTxO )
import Cardano.Wallet.DB.Store.DeltaUTxO.Store
( mkStoreUTxOHistory )
import Fmt
( Buildable (..) )
import Test.DBVar
( prop_StoreUpdates )
import Test.Hspec
( Spec, around, describe, it )
import Test.QuickCheck
( Gen, frequency, property )

spec :: Spec
spec = around (withDBInMemory ForeignKeysEnabled) $ do
describe "DeltaUTxO store" $ do
it "respects store laws" $
property . prop_StoreMetaLaws

genDeltas :: UTxOHistory -> Gen DeltaUTxOHistory
genDeltas history =
frequency
[ (10, AppendBlock <$> genSlotNo history (1, 1, 4) <*> genDelta history)
, (3, Rollback <$> genSlot history (2, 4, 1))
, (5, Prune <$> genSlotNo history (1, 4, 1))
]

prop_StoreMetaLaws :: WalletProperty
prop_StoreMetaLaws = withInitializedWalletProp $ \wid runQ ->
prop_StoreUpdates
runQ
(mkStoreUTxOHistory wid)
(empty <$> genUTxO (empty mempty))
(logScale . genDeltas)

instance Buildable DeltaUTxOHistory where
build = build . show

0 comments on commit 4901b92

Please sign in to comment.