Skip to content

Commit

Permalink
reorganize shared wallet code
Browse files Browse the repository at this point in the history
reshuffle shared wallet code
  • Loading branch information
paweljakubas committed Apr 6, 2021
1 parent c3979c4 commit d493191
Show file tree
Hide file tree
Showing 11 changed files with 109 additions and 58 deletions.
7 changes: 4 additions & 3 deletions lib/core/cardano-wallet-core.cabal
Expand Up @@ -143,6 +143,9 @@ library
Cardano.Pool.DB.Sqlite
Cardano.Pool.DB.Sqlite.TH
Cardano.Pool.Metadata
Cardano.SharedWallet.DB.Sqlite.TH
Cardano.SharedWallet.Script
Cardano.SharedWallet.Shared
Cardano.Wallet
Cardano.Wallet.Api
Cardano.Wallet.Api.Client
Expand Down Expand Up @@ -171,8 +174,6 @@ library
Cardano.Wallet.Primitive.Slotting
Cardano.Wallet.Primitive.AddressDiscovery.Random
Cardano.Wallet.Primitive.AddressDiscovery.Sequential
Cardano.Wallet.Primitive.AddressDiscovery.Shared
Cardano.Wallet.Primitive.AddressDiscovery.Script
Cardano.Wallet.Primitive.SyncProgress
Cardano.Wallet.Primitive.CoinSelection.MA.RoundRobin
Cardano.Wallet.Primitive.Model
Expand Down Expand Up @@ -331,6 +332,7 @@ test-suite unit
Cardano.Pool.DB.MVarSpec
Cardano.Pool.DB.Properties
Cardano.Pool.DB.SqliteSpec
Cardano.SharedWallet.SharedSpec
Cardano.Wallet.Api.Malformed
Cardano.Wallet.Api.Server.TlsSpec
Cardano.Wallet.Api.ServerSpec
Expand All @@ -352,7 +354,6 @@ test-suite unit
Cardano.Wallet.Primitive.AddressDerivationSpec
Cardano.Wallet.Primitive.AddressDiscovery.RandomSpec
Cardano.Wallet.Primitive.AddressDiscovery.SequentialSpec
Cardano.Wallet.Primitive.AddressDiscovery.SharedSpec
Cardano.Wallet.Primitive.AddressDiscoverySpec
Cardano.Wallet.Primitive.CoinSelection.MA.RoundRobinSpec
Cardano.Wallet.Primitive.ModelSpec
Expand Down
1 change: 1 addition & 0 deletions lib/core/src/Cardano/SharedWallet/.#Script.hs
83 changes: 83 additions & 0 deletions lib/core/src/Cardano/SharedWallet/DB/Sqlite/TH.hs
@@ -0,0 +1,83 @@
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE QuasiQuotes #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE UndecidableInstances #-}

-- |
-- Copyright: © 2018-2021 IOHK
-- License: Apache-2.0
--
-- Auto-generated Sqlite & Persistent machinery via Template-Haskell. This has
-- been moved into a separate file so that we can treat it slightly differently
-- when computing code-coverage.

module Cardano.SharedWallet.DB.Sqlite.TH where

import Prelude

import Cardano.Address.Script
( Cosigner, Script )
import Cardano.SharedWallet.Script
( CredentialType )
import Cardano.Wallet.DB.Sqlite.Types
( BlockId, sqlSettings' )
import Data.Text
( Text )
import Data.Time.Clock
( UTCTime )
import Data.Word
( Word32, Word8 )
import Database.Persist.Class
( AtLeastOneUniqueKey (..), OnlyOneUniqueKey (..) )
import Database.Persist.TH
( mkDeleteCascade, mkMigrate, mkPersist, persistLowerCase, share )
import GHC.Generics
( Generic (..) )

import qualified Cardano.Wallet.Primitive.AddressDiscovery.Sequential as W
import qualified Cardano.Wallet.Primitive.Types as W
import qualified Data.ByteString.Char8 as B8

share
[ mkPersist sqlSettings'
, mkDeleteCascade sqlSettings'
, mkMigrate "migrateAll"
]
[persistLowerCase|

-- Shared Wallet
SharedWallet
sharedWalletWalletId W.WalletId sql=wallet_id
sharedWalletCreationTime UTCTime sql=creation_time
sharedWalletUpdateTime UTCTime Maybe sql=update_time
sharedWalletName Text sql=name
sharedWalletAccountXPub B8.ByteString sql=account_xpub
sharedWalletAccountIndex Word32 sql=account_ix
sharedWalletScriptGap W.AddressPoolGap sql=pool_gap
sharedWalletPaymentScript (Script Cosigner) sql=payment_script
sharedWalletDelegationScript (Script Cosigner) Maybe sql=delegation_script
sharedWalletGenesisHash BlockId sql=genesis_hash
sharedWalletGenesisStart UTCTime sql=genesis_start

Primary sharedWalletWalletId
deriving Show Generic

CosignerKey
cosignerKeyWalletId W.WalletId sql=wallet_id
cosignerKeyCreationTime UTCTime sql=creation_time
cosignerKeyCredential CredentialType sql=credential
cosignerKeyAccountXPub B8.ByteString sql=account_xpub
cosignerKeyIndex Word8 sql=cosigner_ix

Primary
cosignerKeyWalletId
cosignerKeyCredential
cosignerKeyIndex
Foreign SharedWallet fk_shared_wallet_cosigner_key cosignerKeyWalletId ! ON DELETE CASCADE
deriving Show Generic
|]
Expand Up @@ -19,7 +19,7 @@
-- An implementation of shared script state using
-- scheme specified in CIP-1854 Multi-signature Wallets..

module Cardano.Wallet.Primitive.AddressDiscovery.Script
module Cardano.SharedWallet.Script
(
CredentialType (..)
, keyHashFromAccXPubIx
Expand Down
Expand Up @@ -21,7 +21,7 @@
-- An implementation of shared script state using
-- scheme specified in CIP-1854 Multi-signature Wallets.

module Cardano.Wallet.Primitive.AddressDiscovery.Shared
module Cardano.SharedWallet.Shared
(
-- ** State
SharedState (..)
Expand All @@ -46,6 +46,8 @@ import Cardano.Address.Script
)
import Cardano.Crypto.Wallet
( XPub )
import Cardano.SharedWallet.Script
( keyHashFromAccXPubIx )
import Cardano.Wallet.Primitive.AddressDerivation
( Depth (..)
, DerivationPrefix (..)
Expand All @@ -59,8 +61,6 @@ import Cardano.Wallet.Primitive.AddressDerivation
)
import Cardano.Wallet.Primitive.AddressDiscovery
( coinTypeAda )
import Cardano.Wallet.Primitive.AddressDiscovery.Script
( keyHashFromAccXPubIx )
import Cardano.Wallet.Primitive.AddressDiscovery.Sequential
( AddressPool
, AddressPoolGap
Expand Down
37 changes: 1 addition & 36 deletions lib/core/src/Cardano/Wallet/DB/Sqlite/TH.hs
Expand Up @@ -27,22 +27,18 @@ module Cardano.Wallet.DB.Sqlite.TH where

import Prelude

import Cardano.Address.Script
( Cosigner, Script )
import Cardano.Slotting.Slot
( SlotNo )
import Cardano.Wallet.DB.Sqlite.Types
( BlockId, HDPassphrase, TxId, sqlSettings' )
import Cardano.Wallet.Primitive.AddressDiscovery.Script
( CredentialType )
import Data.Quantity
( Percentage (..) )
import Data.Text
( Text )
import Data.Time.Clock
( UTCTime )
import Data.Word
( Word16, Word32, Word64, Word8 )
( Word16, Word32, Word64 )
import Database.Persist.Class
( AtLeastOneUniqueKey (..), OnlyOneUniqueKey (..) )
import Database.Persist.TH
Expand Down Expand Up @@ -379,35 +375,4 @@ RndStatePendingAddress
rndStatePendingAddressAddress
Foreign Wallet OnDeleteCascade rnd_state_pending_address rndStatePendingAddressWalletId
deriving Show Generic

-- Shared Wallet
SharedWallet
sharedWalletWalletId W.WalletId sql=wallet_id
sharedWalletCreationTime UTCTime sql=creation_time
sharedWalletUpdateTime UTCTime Maybe sql=update_time
sharedWalletName Text sql=name
sharedWalletAccountXPub B8.ByteString sql=account_xpub
sharedWalletAccountIndex Word32 sql=account_ix
sharedWalletScriptGap W.AddressPoolGap sql=pool_gap
sharedWalletPaymentScript (Script Cosigner) sql=payment_script
sharedWalletDelegationScript (Script Cosigner) Maybe sql=delegation_script
sharedWalletGenesisHash BlockId sql=genesis_hash
sharedWalletGenesisStart UTCTime sql=genesis_start

Primary sharedWalletWalletId
deriving Show Generic

CosignerKey
cosignerKeyWalletId W.WalletId sql=wallet_id
cosignerKeyCreationTime UTCTime sql=creation_time
cosignerKeyCredential CredentialType sql=credential
cosignerKeyAccountXPub B8.ByteString sql=account_xpub
cosignerKeyIndex Word8 sql=cosigner_ix

Primary
cosignerKeyWalletId
cosignerKeyCredential
cosignerKeyIndex
Foreign SharedWallet fk_shared_wallet_cosigner_key cosignerKeyWalletId ! ON DELETE CASCADE
deriving Show Generic
|]
4 changes: 2 additions & 2 deletions lib/core/src/Cardano/Wallet/DB/Sqlite/Types.hs
Expand Up @@ -30,12 +30,12 @@ import Cardano.Api.Typed
, metadataFromJson
, metadataToJson
)
import Cardano.SharedWallet.Script
( CredentialType )
import Cardano.Slotting.Slot
( SlotNo (..) )
import Cardano.Wallet.Primitive.AddressDerivation
( Passphrase (..), PassphraseScheme (..), Role (..) )
import Cardano.Wallet.Primitive.AddressDiscovery.Script
( CredentialType )
import Cardano.Wallet.Primitive.AddressDiscovery.Sequential
( AddressPoolGap (..)
, DerivationPrefix
Expand Down
Expand Up @@ -110,7 +110,7 @@ import Cardano.Wallet.Primitive.AddressDiscovery
, KnownAddresses (..)
, coinTypeAda
)
import Cardano.Wallet.Primitive.AddressDiscovery.Script
import Cardano.SharedWallet.Script
( constructAddressFromIx )
import Cardano.Wallet.Primitive.Types
( invariant )
Expand Down
Expand Up @@ -9,7 +9,7 @@

{-# OPTIONS_GHC -fno-warn-orphans #-}

module Cardano.Wallet.Primitive.AddressDiscovery.SharedSpec
module Cardano.SharedWallet.SharedSpec
( spec
) where

Expand All @@ -24,6 +24,14 @@ import Cardano.Address.Script
, ValidationLevel (..)
, validateScriptTemplate
)
import Cardano.SharedWallet.Script
( constructAddressFromIx
, keyHashFromAccXPubIx
, liftDelegationAddress
, liftPaymentAddress
)
import Cardano.SharedWallet.Shared
( SharedState (..), isShared, newSharedState )
import Cardano.Wallet.Gen
( genNatural, genScript )
import Cardano.Wallet.Primitive.AddressDerivation
Expand All @@ -36,16 +44,8 @@ import Cardano.Wallet.Primitive.AddressDerivation
)
import Cardano.Wallet.Primitive.AddressDerivation.Shelley
( ShelleyKey (..), unsafeGenerateKeyFromSeed )
import Cardano.Wallet.Primitive.AddressDiscovery.Script
( constructAddressFromIx
, keyHashFromAccXPubIx
, liftDelegationAddress
, liftPaymentAddress
)
import Cardano.Wallet.Primitive.AddressDiscovery.Sequential
( AddressPoolGap (..), addresses, mkUnboundedAddressPoolGap )
import Cardano.Wallet.Primitive.AddressDiscovery.Shared
( SharedState (..), isShared, newSharedState )
import Cardano.Wallet.Primitive.Types.Address
( AddressState (..) )
import Cardano.Wallet.Unsafe
Expand Down
4 changes: 2 additions & 2 deletions lib/core/test/unit/Cardano/Wallet/Api/TypesSpec.hs
Expand Up @@ -47,6 +47,8 @@ import Cardano.Mnemonic
, entropyToMnemonic
, mkEntropy
)
import Cardano.SharedWallet.Shared
( retrieveAllCosigners )
import Cardano.Wallet.Api
( Api )
import Cardano.Wallet.Api.Types
Expand Down Expand Up @@ -174,8 +176,6 @@ import Cardano.Wallet.Primitive.AddressDerivationSpec
()
import Cardano.Wallet.Primitive.AddressDiscovery.Sequential
( AddressPoolGap, getAddressPoolGap )
import Cardano.Wallet.Primitive.AddressDiscovery.Shared
( retrieveAllCosigners )
import Cardano.Wallet.Primitive.SyncProgress
( SyncProgress (..) )
import Cardano.Wallet.Primitive.Types
Expand Down
3 changes: 2 additions & 1 deletion lib/shelley/src/Cardano/Wallet/Shelley/Api/Server.hs
Expand Up @@ -490,11 +490,12 @@ server byron icarus shelley spl ntp =

sharedWallets :: Server SharedWallets
sharedWallets =
postSharedWallet :<|> getSharedWallet :<|> patchSharedWallet
postSharedWallet :<|> getSharedWallet :<|> patchSharedWallet :<|> deleteSharedWallet
where
postSharedWallet = pure $ throwError err501
getSharedWallet = pure $ throwError err501
patchSharedWallet _ = pure $ throwError err501
deleteSharedWallet = pure $ throwError err501

postAnyAddress
:: NetworkId
Expand Down

0 comments on commit d493191

Please sign in to comment.