Skip to content

Commit 5058fb5

Browse files
committed
[RSC-154] Rewrite Notary to accept maybe master
This commit introduces changes in notary interface to ease testing of Notary. Now Notary contains list of master keys he trust. If this list is empty then Notary trust everyone. Also because of this list our Notary is now more DoS resistant.
1 parent 7b54672 commit 5058fb5

File tree

14 files changed

+130
-92
lines changed

14 files changed

+130
-92
lines changed

bench/Bench/RSCoin/Local/InfraThreads.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -53,6 +53,6 @@ notaryThread :: FilePath -> IO ()
5353
notaryThread benchDir =
5454
runRealModeUntrusted notaryLoggerName B.CADefault $
5555
bracket
56-
(liftIO $ N.openState $ benchDir </> "notary-db")
56+
(liftIO $ N.openState (benchDir </> "notary-db") [])
5757
(liftIO . N.closeState)
5858
N.serveNotary

src/Deploy/Main.hs

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -108,6 +108,7 @@ startNotary severity CommonParams{..} = do
108108
(Just dbDir)
109109
contextArgument
110110
8090
111+
[]
111112
Cherepakha.mkdir workingDirDeprecated
112113
forkIO start
113114

src/Notary/Main.hs

Lines changed: 12 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -1,6 +1,9 @@
11
module Main where
22

3-
import RSCoin.Core (initLogging)
3+
import Control.Monad (when)
4+
import Data.Maybe (mapMaybe)
5+
6+
import RSCoin.Core (constructPublicKey, initLogging, logWarning)
47
import qualified RSCoin.Notary as N
58

69
import qualified NotaryOptions as Opts
@@ -9,12 +12,16 @@ main :: IO ()
912
main = do
1013
Opts.Options{..} <- Opts.getOptions
1114
initLogging cliLogSeverity
12-
let dbPath =
13-
if cliMemMode
14-
then Nothing
15-
else Just cliPath
15+
let dbPath = if cliMemMode
16+
then Nothing
17+
else Just cliPath
18+
let trustedKeys = mapMaybe constructPublicKey cliTrustedKeys
19+
when (length trustedKeys < length cliTrustedKeys) $
20+
logWarning "Not all keys were parsed!"
21+
1622
N.launchNotaryReal
1723
cliLogSeverity
1824
dbPath
1925
(N.CACustomLocation cliConfigPath)
2026
cliWebPort
27+
trustedKeys

src/Notary/NotaryOptions.hs

Lines changed: 7 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -5,7 +5,8 @@ module NotaryOptions
55
, getOptions
66
) where
77

8-
import Options.Applicative (Parser, auto, execParser, fullDesc,
8+
import Data.Text (Text)
9+
import Options.Applicative (Parser, auto, execParser, fullDesc, many,
910
help, helper, info, long, metavar,
1011
option, progDesc, short, showDefault,
1112
switch, value, (<>))
@@ -22,6 +23,7 @@ data Options = Options
2223
, cliMemMode :: Bool
2324
, cliWebPort :: Int
2425
, cliConfigPath :: FilePath
26+
, cliTrustedKeys :: [Text]
2527
} deriving Show
2628

2729
optionsParser :: FilePath -> FilePath -> Parser Options
@@ -45,7 +47,10 @@ optionsParser configDir defaultConfigPath =
4547
(long "config-path" <> help "Path to configuration file" <>
4648
value defaultConfigPath <>
4749
showDefault <>
48-
metavar "FILEPATH")
50+
metavar "FILEPATH") <*>
51+
many (strOption $ long "trust-keys" <> metavar "[PUBLIC KEY]" <>
52+
help "Public keys notary will trust as master keys. If not specifed \
53+
\then notary will trust any key")
4954

5055
getOptions :: IO Options
5156
getOptions = do

src/RSCoin/Core/Communication.hs

Lines changed: 4 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -290,9 +290,9 @@ allocateMultisignatureAddress
290290
-> PartyAddress
291291
-> AllocationStrategy
292292
-> Signature
293-
-> (PublicKey, Signature)
293+
-> Maybe (PublicKey, Signature)
294294
-> m ()
295-
allocateMultisignatureAddress msAddr partyAddr allocStrat signature masterCheck = do
295+
allocateMultisignatureAddress msAddr partyAddr allocStrat signature mMasterCheck = do
296296
L.logInfo $ sformat
297297
( "Allocate new ms address: " % build % "\n,"
298298
% "from party address: " % build % "\n"
@@ -304,9 +304,9 @@ allocateMultisignatureAddress msAddr partyAddr allocStrat signature masterCheck
304304
partyAddr
305305
allocStrat
306306
signature
307-
(pairBuilder masterCheck)
307+
(pairBuilder <$> mMasterCheck)
308308
callNotary $ P.call (P.RSCNotary P.AllocateMultisig)
309-
msAddr partyAddr allocStrat signature masterCheck
309+
msAddr partyAddr allocStrat signature mMasterCheck
310310

311311
queryNotaryCompleteMSAddresses :: WorkMode m => m [(Address, TxStrategy)]
312312
queryNotaryCompleteMSAddresses = do

src/RSCoin/Notary/AcidState.hs

Lines changed: 8 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -30,18 +30,21 @@ import Data.Acid (AcidState, closeAcidState, makeAcidic,
3030
import Data.Acid.Memory (openMemoryState)
3131
import Data.SafeCopy (base, deriveSafeCopy)
3232

33-
import RSCoin.Notary.Storage (Storage)
33+
import RSCoin.Core (PublicKey)
34+
import RSCoin.Notary.Storage (Storage (..))
3435
import qualified RSCoin.Notary.Storage as S
3536

3637
type RSCoinNotaryState = AcidState Storage
3738

3839
$(deriveSafeCopy 0 'base ''Storage)
3940

40-
openState :: FilePath -> IO RSCoinNotaryState
41-
openState fp = openLocalStateFrom fp S.emptyNotaryStorage
41+
openState :: FilePath -> [PublicKey] -> IO RSCoinNotaryState
42+
openState fp trustedKeys =
43+
openLocalStateFrom fp S.emptyNotaryStorage { _masterKeys = trustedKeys }
4244

43-
openMemState :: IO RSCoinNotaryState
44-
openMemState = openMemoryState S.emptyNotaryStorage
45+
openMemState :: [PublicKey] -> IO RSCoinNotaryState
46+
openMemState trustedKeys =
47+
openMemoryState S.emptyNotaryStorage { _masterKeys = trustedKeys }
4548

4649
closeState :: RSCoinNotaryState -> IO ()
4750
closeState = closeAcidState

src/RSCoin/Notary/Error.hs

Lines changed: 6 additions & 10 deletions
Original file line numberDiff line numberDiff line change
@@ -26,7 +26,6 @@ data NotaryError
2626
-- PeriodId supplied -- actual periodId known to Notary
2727
| NEBlocked -- ^ User has reached limit number of attempts for multisig allocation
2828
| NEInvalidArguments Text -- ^ Generic exception for invalid arguments
29-
| NEInvalidChain Text -- ^ Invalid chain of certificates provided @TODO: Deprecated
3029
| NEInvalidSignature -- ^ Invalid signature provided
3130
| NEStrategyNotSupported Text -- ^ Address's strategy is not supported, with name provided
3231
| NEUnrelatedSignature Text -- ^ Signature provided doesn't correspond to any of address' parties
@@ -41,7 +40,6 @@ instance Buildable NotaryError where
4140
build (NEAddrIdNotInUtxo pId) = bprint ("NEAddrIdNotInUtxo, notary's periodId " % int) pId
4241
build NEBlocked = "NEBlocked"
4342
build (NEInvalidArguments msg) = bprint ("NEInvalidArguments: " % stext) msg
44-
build (NEInvalidChain msg) = bprint ("NEInvalidChain: " % stext) msg
4543
build NEInvalidSignature = "NEInvalidSignature"
4644
build (NEStrategyNotSupported s) = bprint ("NEStrategyNotSupported, strategy " % stext) s
4745
build (NEUnrelatedSignature msg) = bprint ("NEUnrelatedSignature: " % stext) msg
@@ -56,10 +54,9 @@ instance MessagePack NotaryError where
5654
toObject (NEAddrIdNotInUtxo pId) = toObj (1, pId)
5755
toObject NEBlocked = toObj (2, ())
5856
toObject (NEInvalidArguments msg) = toObj (3, msg)
59-
toObject (NEInvalidChain msg) = toObj (4, msg)
60-
toObject NEInvalidSignature = toObj (5, ())
61-
toObject (NEStrategyNotSupported s) = toObj (6, s)
62-
toObject (NEUnrelatedSignature msg) = toObj (7, msg)
57+
toObject NEInvalidSignature = toObj (4, ())
58+
toObject (NEStrategyNotSupported s) = toObj (5, s)
59+
toObject (NEUnrelatedSignature msg) = toObj (6, msg)
6360

6461
fromObject obj = do
6562
(i, payload) <- fromObject obj
@@ -68,8 +65,7 @@ instance MessagePack NotaryError where
6865
1 -> NEAddrIdNotInUtxo <$> fromObject payload
6966
2 -> pure NEBlocked
7067
3 -> NEInvalidArguments <$> fromObject payload
71-
4 -> NEInvalidChain <$> fromObject payload
72-
5 -> pure NEInvalidSignature
73-
6 -> NEStrategyNotSupported <$> fromObject payload
74-
7 -> NEUnrelatedSignature <$> fromObject payload
68+
4 -> pure NEInvalidSignature
69+
5 -> NEStrategyNotSupported <$> fromObject payload
70+
6 -> NEUnrelatedSignature <$> fromObject payload
7571
_ -> Nothing

src/RSCoin/Notary/Launcher.hs

Lines changed: 9 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -11,7 +11,7 @@ import Network.Wai (Middleware)
1111
import Network.Wai.Handler.Warp (run)
1212
import Network.Wai.Middleware.RequestLogger (logStdout, logStdoutDev)
1313

14-
import RSCoin.Core (Severity (..),
14+
import RSCoin.Core (PublicKey, Severity (..),
1515
notaryLoggerName)
1616
import RSCoin.Notary.AcidState (RSCoinNotaryState,
1717
closeState, openMemState,
@@ -22,11 +22,16 @@ import RSCoin.Timed (ContextArgument (..),
2222
fork_,
2323
runRealModeUntrusted)
2424

25-
launchNotaryReal :: Severity -> Maybe FilePath -> ContextArgument -> Int -> IO ()
26-
launchNotaryReal logSeverity dbPath ca webPort = do
25+
launchNotaryReal :: Severity
26+
-> Maybe FilePath
27+
-> ContextArgument
28+
-> Int
29+
-> [PublicKey]
30+
-> IO ()
31+
launchNotaryReal logSeverity dbPath ca webPort trustedKeys = do
2732
let openAction = maybe openMemState openState dbPath
2833
runRealModeUntrusted notaryLoggerName ca $
29-
bracket (liftIO openAction) (liftIO . closeState) $
34+
bracket (liftIO $ openAction trustedKeys) (liftIO . closeState) $
3035
\st -> do
3136
fork_ $ serveNotary st
3237
launchWeb webPort logSeverity st

src/RSCoin/Notary/Server.hs

Lines changed: 4 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -181,13 +181,13 @@ handleAllocateMultisig
181181
-> C.PartyAddress
182182
-> C.AllocationStrategy
183183
-> C.Signature
184-
-> (C.PublicKey, C.Signature)
184+
-> Maybe (C.PublicKey, C.Signature)
185185
-> m ()
186-
handleAllocateMultisig st msAddr partyAddr allocStrat signature masterCheck = toServer $ do
186+
handleAllocateMultisig st msAddr partyAddr allocStrat signature mMasterCheck = toServer $ do
187187
C.logDebug "Begining allocation MS address..."
188188
C.logDebug $
189-
sformat ("SigPair: " % build % ", Chain: " % build) signature (pairBuilder masterCheck)
190-
update' st $ AllocateMSAddress msAddr partyAddr allocStrat signature masterCheck
189+
sformat ("SigPair: " % build % ", Chain: " % build) signature (pairBuilder <$> mMasterCheck)
190+
update' st $ AllocateMSAddress msAddr partyAddr allocStrat signature mMasterCheck
191191

192192
-- @TODO: get query only in Debug mode
193193
currentMSAddresses <- query' st QueryAllMSAdresses

src/RSCoin/Notary/Storage.hs

Lines changed: 23 additions & 12 deletions
Original file line numberDiff line numberDiff line change
@@ -5,7 +5,7 @@
55
-- | Storage for Notary's data.
66

77
module RSCoin.Notary.Storage
8-
( Storage
8+
( Storage (_masterKeys)
99
, acquireSignatures
1010
, addSignedTransaction
1111
, allocateMSAddress
@@ -77,6 +77,10 @@ data Storage = Storage
7777
-- | Mapping between addrid and address.
7878
, _utxo :: !Utxo
7979

80+
-- | Trusted master keys to check for signatures in MS address allocation &
81+
-- transaction signing.
82+
, _masterKeys :: ![PublicKey] -- @TODO: replace with HashSet
83+
8084
-- | Last periodId, known to Notary.
8185
, _periodId :: !PeriodId
8286
} deriving (Show)
@@ -93,6 +97,7 @@ emptyNotaryStorage =
9397
, _periodStats = M.empty
9498
, _addresses = M.empty
9599
, _utxo = M.empty
100+
, _masterKeys = []
96101
, _periodId = -1
97102
}
98103

@@ -158,20 +163,20 @@ addSignedTransaction tx addr sg@(sigAddr, sig) = do
158163
-- | Allocate new multisignature address by chosen strategy and
159164
-- given chain of certificates.
160165
allocateMSAddress
161-
:: MSAddress -- ^ New multisig address itself
162-
-> PartyAddress -- ^ Address of party who call this
163-
-> AllocationStrategy -- ^ Strategy for MS address allocation
164-
-> Signature -- ^ 'Signature' of @(msAddr, argStrategy)@
165-
-> (PublicKey, Signature) -- ^ Party address authorization.
166-
-- 1. cold master public key
167-
-- 2. signature of party by master key
166+
:: MSAddress -- ^ New multisig address itself
167+
-> PartyAddress -- ^ Address of party who call this
168+
-> AllocationStrategy -- ^ Strategy for MS address allocation
169+
-> Signature -- ^ 'Signature' of @(msAddr, argStrategy)@
170+
-> Maybe (PublicKey, Signature) -- ^ Party address authorization.
171+
-- 1. cold master public key
172+
-- 2. signature of party by master key
168173
-> Update Storage ()
169174
allocateMSAddress
170175
msAddr
171176
argPartyAddress
172177
argStrategy@AllocationStrategy{..}
173178
requestSig
174-
(masterPk, masterSlaveSig)
179+
mMasterSlavePair
175180
= do
176181
-- too many checks :( I wish I know which one we shouldn't check
177182
-- but order of checks matters!!!
@@ -181,18 +186,24 @@ allocateMSAddress
181186
TrustParty{..} -> hotTrustKey
182187
UserParty{..} -> partyPk
183188

184-
unless (verify masterPk masterSlaveSig slavePk) $
185-
throwM $ NEUnrelatedSignature "partyAddr not signed with masterPk"
189+
trustedKeys <- use masterKeys
190+
unless (null trustedKeys) $ case mMasterSlavePair of
191+
Nothing -> throwM $ NEInvalidArguments "You should provide master pk and slave signature"
192+
Just (masterPk, masterSlaveSig) -> do
193+
unless (verify masterPk masterSlaveSig slavePk) $
194+
throwM $ NEUnrelatedSignature "partyAddr not signed with masterPk"
195+
when (masterPk `notElem` trustedKeys) $
196+
throwM $ NEInvalidArguments "provided master pk is not a trusted key"
186197
unless (verify slavePk requestSig signedData) $
187198
throwM $ NEUnrelatedSignature $ sformat
188199
("(msAddr, strategy) not signed with proper sk for pk: " % build) slavePk
189-
-- @TODO: check if master in rootPks (DOS otherwise)
190200
when (_sigNumber <= 0) $
191201
throwM $ NEInvalidArguments "required number of signatures should be positive"
192202
when (_sigNumber > HS.size _allParties) $
193203
throwM $ NEInvalidArguments "required number of signatures is greater then party size"
194204
unless (partyToAllocation argPartyAddress `HS.member` _allParties) $
195205
throwM $ NEInvalidArguments "party address not in set of addresses"
206+
196207
guardMaxAttemps partyAddr
197208

198209
mMSAddressInfo <- uses allocationStrategyPool $ M.lookup msAddr

0 commit comments

Comments
 (0)