Skip to content

Commit

Permalink
draft an initial interface for a DB layer
Browse files Browse the repository at this point in the history
  • Loading branch information
KtorZ committed Mar 14, 2019
1 parent 847da46 commit 866c287
Show file tree
Hide file tree
Showing 3 changed files with 67 additions and 0 deletions.
2 changes: 2 additions & 0 deletions cardano-wallet.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -59,6 +59,7 @@ library
hs-source-dirs:
src
exposed-modules:
Cardano.DBLayer
Cardano.NetworkLayer
Cardano.NetworkLayer.HttpBridge
Cardano.NetworkLayer.HttpBridge.Api
Expand Down Expand Up @@ -154,6 +155,7 @@ test-suite unit
main-is:
Main.hs
other-modules:
Cardano.DBLayerSpec
Cardano.Wallet.AddressDerivationSpec
Cardano.Wallet.AddressDiscoverySpec
Cardano.Wallet.Binary.PackfileSpec
Expand Down
51 changes: 51 additions & 0 deletions src/Cardano/DBLayer.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,51 @@
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE ExistentialQuantification #-}
{-# LANGUAGE KindSignatures #-}
{-# LANGUAGE RankNTypes #-}

module Cardano.DBLayer
( DBLayer(..)
) where

import Cardano.Wallet
( Wallet )
import Control.Monad.Except
( ExceptT )
import Data.Word
( Word64 )
import GHC.TypeLits
( Symbol )


-- | A Database interface for storing various things in a DB. In practice,
-- we'll need some extra contraints on the wallet state that allows us to
-- serialize and unserialize it (e.g. @forall s. (Serialize s) => ...@)
data DBLayer m = forall s. DBLayer
-- Wallet checkpoints, checkpoints are handled as a bounded FIFO, where we
-- eventually store @k@ values (e.g. k=2160) at the same time.
{ enqueueCheckpoint -- Add a checkpoint on top of the queue
:: PrimaryKey "wallet"
-> Wallet s
-> ExceptT ErrEnqueueCheckpoint m ()
, dequeueCheckpoints -- Discard a number of checkpoints from the end
:: PrimaryKey "wallet"
-> Word64
-> ExceptT ErrDequeueCheckpoints m ()
, checkpoints --
:: PrimaryKey "wallet"
-> ExceptT ErrCheckpoints m [Wallet s]
}

-- | A primary key which can take many forms depending on the value. This may
-- become a type family as we move forward, but for now, it illustrate that
-- some queries are ran against some sort of store;
--
-- As a matter of fact, we may manipulate multiple wallets at the same time, so,
-- functions like 'enqueueCheckpoint' needs to be associated to a corresponding
-- wallet. Some other may not because they are information valid for all wallets
-- (like for instance, the last known network tip).
data PrimaryKey (resource :: Symbol)

data ErrEnqueueCheckpoint
data ErrDequeueCheckpoints
data ErrCheckpoints
14 changes: 14 additions & 0 deletions test/unit/Cardano/DBLayerSpec.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,14 @@
module Cardano.DBLayerSpec
( spec
) where

import Prelude

import Cardano.DBLayer
()
import Test.Hspec
( Spec )


spec :: Spec
spec = return ()

0 comments on commit 866c287

Please sign in to comment.