Skip to content
This repository has been archived by the owner on Aug 18, 2020. It is now read-only.

Commit

Permalink
Merge pull request #3389 from input-output-hk/CHW-1-public-key
Browse files Browse the repository at this point in the history
[CHW] Support of root public key for external wallets.
  • Loading branch information
Denis Shevchenko committed Aug 15, 2018
2 parents a9a22fb + c892382 commit 26d5306
Show file tree
Hide file tree
Showing 15 changed files with 373 additions and 34 deletions.
4 changes: 4 additions & 0 deletions lib/cardano-sl.cabal
Expand Up @@ -85,6 +85,8 @@ library
-- Utilities/helpers
Pos.Util.Config
Pos.Util.OutboundQueue
Pos.Util.UserKeyError
Pos.Util.UserPublic
Pos.Util.UserSecret

Pos.Web
Expand Down Expand Up @@ -277,6 +279,8 @@ test-suite cardano-test
-- Everything else
Test.Pos.Block.Arbitrary.Message
Test.Pos.Block.CborSpec
Test.Pos.Cbor.Arbitrary.UserPublic
Test.Pos.Cbor.Arbitrary.UserSecret
Test.Pos.Cbor.CborSpec
Test.Pos.ConstantsSpec
Test.Pos.Diffusion.BlockSpec
Expand Down
6 changes: 6 additions & 0 deletions lib/src/Pos/Client/CLI/NodeOptions.hs
Expand Up @@ -40,6 +40,7 @@ data CommonNodeArgs = CommonNodeArgs
, cnaAssetLockPath :: !(Maybe FilePath)
-- these two arguments are only used in development mode
, devGenesisSecretI :: !(Maybe Int)
, publicKeyfilePath :: !FilePath
, keyfilePath :: !FilePath
, networkConfigOpts :: !NetworkConfigOpts
-- ^ Network configuration
Expand Down Expand Up @@ -80,6 +81,11 @@ commonNodeArgsParser = do
long "genesis-secret" <>
metavar "INT" <>
help "Used genesis secret key index."
publicKeyfilePath <- strOption $
long "pubkeyfile" <>
metavar "FILEPATH" <>
value "public.key" <>
help "Path to file with public key (we use it for external wallets)."
keyfilePath <- strOption $
long "keyfile" <>
metavar "FILEPATH" <>
Expand Down
3 changes: 3 additions & 0 deletions lib/src/Pos/Client/CLI/Params.hs
Expand Up @@ -25,6 +25,7 @@ import Pos.Crypto (VssKeyPair)
import Pos.Infra.Network.CLI (intNetworkConfigOpts)
import Pos.Launcher.Param (BaseParams (..), LoggingParams (..),
NodeParams (..))
import Pos.Util.UserPublic (peekUserPublic)
import Pos.Util.UserSecret (peekUserSecret)
import Pos.Util.Util (eitherToThrow)

Expand Down Expand Up @@ -68,6 +69,7 @@ getNodeParams ::
getNodeParams defaultLoggerName cArgs@CommonNodeArgs{..} NodeArgs{..} = do
(primarySK, userSecret) <-
prepareUserSecret cArgs =<< peekUserSecret (getKeyfilePath cArgs)
userPublic <- peekUserPublic publicKeyfilePath
npNetworkConfig <- intNetworkConfigOpts networkConfigOpts
npBehaviorConfig <- case behaviorConfigPath of
Nothing -> pure def
Expand All @@ -76,6 +78,7 @@ getNodeParams defaultLoggerName cArgs@CommonNodeArgs{..} NodeArgs{..} = do
{ npDbPathM = dbPath
, npRebuildDb = rebuildDB
, npSecretKey = primarySK
, npUserPublic = userPublic
, npUserSecret = userSecret
, npBaseParams = getBaseParams defaultLoggerName cArgs
, npJLFile = jlPath
Expand Down
6 changes: 6 additions & 0 deletions lib/src/Pos/Context/Context.hs
Expand Up @@ -50,6 +50,7 @@ import Pos.Launcher.Param (BaseParams (..), NodeParams (..))
import Pos.Network.Block.RetrievalQueue (BlockRetrievalQueue,
BlockRetrievalQueueTag)
import Pos.Util.Lens (postfixLFields)
import Pos.Util.UserPublic (HasUserPublic (..), UserPublic)
import Pos.Util.UserSecret (HasUserSecret (..), UserSecret)
import Pos.Util.Util (HasLens (..))

Expand Down Expand Up @@ -83,6 +84,8 @@ data NodeContext = NodeContext
-- Stored hash is a hash of last applied block.
, ncStateLockMetrics :: !(StateLockMetrics MemPoolModifyReason)
-- ^ A set of callbacks for 'StateLock'.
, ncUserPublic :: !(TVar UserPublic)
-- ^ Public keys (and path to file) which are used to identify external wallets.
, ncUserSecret :: !(TVar UserSecret)
-- ^ Secret keys (and path to file) which are used to send transactions
, ncBlockRetrievalQueue :: !BlockRetrievalQueue
Expand Down Expand Up @@ -153,6 +156,9 @@ instance HasShutdownContext NodeContext where
instance HasLens UpdateContext NodeContext UpdateContext where
lensOf = ncUpdateContext_L

instance HasUserPublic NodeContext where
userPublic = ncUserPublic_L

instance HasUserSecret NodeContext where
userSecret = ncUserSecret_L

Expand Down
2 changes: 2 additions & 0 deletions lib/src/Pos/Launcher/Param.hs
Expand Up @@ -25,6 +25,7 @@ import Pos.Infra.DHT.Real.Param (KademliaParams)
import Pos.Infra.Network.Types (NetworkConfig)
import Pos.Infra.Statistics (EkgParams, StatsdParams)
import Pos.Util.Lens (postfixLFields)
import Pos.Util.UserPublic (UserPublic)
import Pos.Util.UserSecret (UserSecret)
import Pos.Util.Util (HasLens (..))

Expand All @@ -51,6 +52,7 @@ data NodeParams = NodeParams
{ npDbPathM :: !(Maybe FilePath) -- ^ Path to node's database
, npRebuildDb :: !Bool -- ^ @True@ if data-base should be rebuilt
, npSecretKey :: !SecretKey -- ^ Primary secret key of node
, npUserPublic :: !UserPublic -- ^ All node public keys
, npUserSecret :: !UserSecret -- ^ All node secret keys
, npBaseParams :: !BaseParams -- ^ See 'BaseParams'
, npJLFile :: !(Maybe FilePath) -- ^ File to use for JSON logging.
Expand Down
2 changes: 2 additions & 0 deletions lib/src/Pos/Launcher/Resource.hs
Expand Up @@ -284,6 +284,8 @@ allocateNodeContext ancd txpSettings ekgStore = do
logDebug "Created slotting context"
putSlotting ncSlottingVar ncSlottingContext
logDebug "Filled slotting future"
ncUserPublic <- newTVarIO $ npUserPublic
logDebug "Created UserPublic variable"
ncUserSecret <- newTVarIO $ npUserSecret
logDebug "Created UserSecret variable"
ncBlockRetrievalQueue <- liftIO $ newTBQueueIO blockRetrievalQueueSize
Expand Down
28 changes: 28 additions & 0 deletions lib/src/Pos/Util/UserKeyError.hs
@@ -0,0 +1,28 @@
-- | Possible errors with files which stores secret and public keys.

module Pos.Util.UserKeyError
( UserKeyType (..)
, UserKeyError (..)
, KeyError (..)
) where

import Universum

import Control.Exception.Safe (Exception)

-- | 'PublicKey' is for external wallets, 'SecretKey' is for internal wallets.
data UserKeyType
= Public
| Secret
deriving Show

data UserKeyError
= NotWritable
| AlreadyLocked
| IncorrectLock
deriving Show

data KeyError = KeyError UserKeyType UserKeyError
deriving Show

instance Exception KeyError
242 changes: 242 additions & 0 deletions lib/src/Pos/Util/UserPublic.hs
@@ -0,0 +1,242 @@
{-# LANGUAGE CPP #-}

-- | Public key file storage and management functions based on file
-- locking.

#if !defined(mingw32_HOST_OS)
#define POSIX
#endif

module Pos.Util.UserPublic
( WalletUserPublic (..)
, wupWalletName
, wupAccounts
, wupAddrs

, UserPublic
, upKeys
, upWallet
, HasUserPublic(..)
, initializeUserPublic
, peekUserPublic
, takeUserPublic
, writeUserPublic
, writeUserPublicRelease
) where

import qualified Prelude
import Universum

import Control.Exception.Safe (finally)
import Control.Lens (makeLenses, to)
import qualified Data.ByteString as BS
import Data.Default (Default (..))
import Formatting (Format, bprint, build, formatToString, later, (%))
import qualified Formatting.Buildable
import Serokell.Util.Text (listJson)
import System.Directory (doesFileExist)
import System.Directory (renameFile)
import System.FileLock (FileLock, SharedExclusive (..), lockFile,
unlockFile, withFileLock)
import System.FilePath (takeDirectory, takeFileName)
import System.IO (hClose, openBinaryTempFile)

import Pos.Binary.Class (Bi (..), Cons (..), Field (..), decodeFull',
deriveSimpleBi, encodeListLen, enforceSize, serialize')
import Pos.Crypto (PublicKey)
import Pos.Util.UserKeyError (KeyError (..), UserKeyError (..),
UserKeyType (..))

import Test.Pos.Crypto.Arbitrary ()

#ifdef POSIX
import Formatting (oct, sformat)
import qualified System.Posix.Files as PSX
import qualified System.Posix.Types as PSX (FileMode)
import System.Wlog (WithLogger, logWarning)
#endif

-- Because of the Formatting import
{-# ANN module ("HLint: ignore Use fewer imports" :: Text) #-}

-- | Describes HD wallets keyfile content
data WalletUserPublic = WalletUserPublic
{ _wupWalletName :: Text -- ^ name of wallet
, _wupAccounts :: [(Word32, Text)] -- ^ accounts coordinates and names
, _wupAddrs :: [(Word32, Word32)] -- ^ addresses coordinates
} deriving (Eq, Generic, Show)

makeLenses ''WalletUserPublic

instance Buildable WalletUserPublic where
build WalletUserPublic{..} =
bprint ("{ wallet name = "%build%
", accounts = "%pairsF%", addresses = "%pairsF%" }")
_wupWalletName
_wupAccounts
_wupAddrs
where
pairsF :: (Buildable a, Buildable b) => Format r ([(a, b)] -> r)
pairsF = later $ mconcat . map (uncurry $ bprint ("("%build%", "%build%")"))

deriveSimpleBi ''WalletUserPublic [
Cons 'WalletUserPublic [
Field [| _wupWalletName :: Text |],
Field [| _wupAccounts :: [(Word32, Text)] |],
Field [| _wupAddrs :: [(Word32, Word32)] |]
]]

-- | User public data.
data UserPublic = UserPublic
{ _upKeys :: [PublicKey]
, _upWallet :: Maybe WalletUserPublic
, _upPath :: FilePath
, _upLock :: Maybe FileLock
} deriving (Eq, Generic)

makeLenses ''UserPublic

class HasUserPublic ctx where
-- if you're going to mock this TVar, look how it's done for peer state.
userPublic :: Lens' ctx (TVar UserPublic)

-- | Show instance to be able to include it into NodeParams
instance Show UserPublic where
show UserPublic {..} =
formatToString
("UserPublic { _upKeys = "%listJson%
", _upPath = "%build%", _upWallet = "%build%"}")
_upKeys
_upPath
_upWallet

-- | Path of lock file for the provided path.
lockFilePath :: FilePath -> FilePath
lockFilePath = (<> ".lock")

-- | Checks if this user public instance can be dumped back to
-- file. If not, using 'writeUserPublic' and 'writeUserPublicRelease'
-- will result in error.
canWrite :: UserPublic -> Bool
canWrite up = up ^. upLock . to isJust

instance Default UserPublic where
def = UserPublic [] Nothing "" Nothing

instance Bi UserPublic where
encode us = encodeListLen 2 <> encode (_upKeys us)
<> encode (_upWallet us)
decode = do
enforceSize "UserPublic" 2
pKeys <- decode
wallet <- decode
return $ def
& upKeys .~ pKeys
& upWallet .~ wallet

-- | WithLogger is only needed on posix platforms
#ifdef POSIX
type MonadMaybeLog m = (MonadIO m, WithLogger m)
#else
type MonadMaybeLog m = MonadIO m
#endif

#ifdef POSIX
-- | Constant that defines file mode 600 (readable & writable only by owner).
mode600 :: PSX.FileMode
mode600 = PSX.unionFileModes PSX.ownerReadMode PSX.ownerWriteMode

-- | Return only the access part of the file mode (like owner:rw-, etc).
getAccessMode :: (MonadIO m) => FilePath -> m PSX.FileMode
getAccessMode path = do
mode <- liftIO $ PSX.fileMode <$> PSX.getFileStatus path
return $ PSX.intersectFileModes mode PSX.accessModes

-- | Set mode 600 on a given file, regardless of its current mode.
setMode600 :: (MonadIO m) => FilePath -> m ()
setMode600 path = liftIO $ PSX.setFileMode path mode600

ensureModeIs600 :: MonadMaybeLog m => FilePath -> m ()
ensureModeIs600 path = do
accessMode <- getAccessMode path
unless (accessMode == mode600) $ do
logWarning $
sformat ("Key file at "%build%" has access mode "%oct%" instead of 600. Fixing it automatically.")
path accessMode
setMode600 path
#endif

-- | Create user public file at the given path, but only when one doesn't
-- already exist.
initializeUserPublic :: MonadMaybeLog m => FilePath -> m ()
initializeUserPublic publicPath = do
exists <- liftIO $ doesFileExist publicPath
#ifdef POSIX
if exists
then ensureModeIs600 publicPath
else do
createEmptyFile publicPath
setMode600 publicPath
#else
unless exists $ createEmptyFile publicPath
#endif
where
createEmptyFile :: (MonadIO m) => FilePath -> m ()
createEmptyFile = liftIO . flip writeFile mempty

-- | Reads user public from the given file.
-- If the file does not exist/is empty, returns empty user public
peekUserPublic :: MonadMaybeLog m => FilePath -> m UserPublic
peekUserPublic path = do
initializeUserPublic path
withReadLock path $ do
content <- decodeFull' <$> BS.readFile path
pure $ either (const def) identity content & upPath .~ path

-- | Read user public putting an exclusive lock on it. To unlock, use
-- 'writeUserPublicRelease'.
takeUserPublic :: MonadMaybeLog m => FilePath -> m UserPublic
takeUserPublic path = do
initializeUserPublic path
liftIO $ do
lock <- lockFile (lockFilePath path) Exclusive
content <- decodeFull' <$> BS.readFile path
pure $ either (const def) identity content
& upPath .~ path
& upLock .~ Just lock

-- | Writes user public.
writeUserPublic :: (MonadIO m) => UserPublic -> m ()
writeUserPublic up
| canWrite up = liftIO $ throwM $ KeyError Public AlreadyLocked
| otherwise = liftIO $ withFileLock (lockFilePath $ up ^. upPath) Exclusive $ const $ writeRaw up

-- | Writes user public and releases the lock. UserPublic can't be
-- used after this function call anymore.
writeUserPublicRelease :: (MonadIO m, MonadThrow m) => UserPublic -> m ()
writeUserPublicRelease up
| not (canWrite up) = throwM $ KeyError Public NotWritable
| otherwise = liftIO $ do
writeRaw up
case (up ^. upLock) of
Nothing -> throwM $ KeyError Public IncorrectLock
Just lock -> unlockFile lock

-- | Helper for writing public to file
writeRaw :: UserPublic -> IO ()
writeRaw up = do
let path = up ^. upPath
-- On POSIX platforms, openBinaryTempFile guarantees that the file
-- will be created with mode 600.
-- If openBinaryTempFile throws, we want to propagate this exception,
-- hence no handler.
(tempPath, tempHandle) <-
openBinaryTempFile (takeDirectory path) (takeFileName path)

BS.hPut tempHandle (serialize' up) `finally` hClose tempHandle

renameFile tempPath path

-- | Helper for taking shared lock on file
withReadLock :: MonadIO m => FilePath -> IO a -> m a
withReadLock path = liftIO . withFileLock (lockFilePath path) Shared . const

0 comments on commit 26d5306

Please sign in to comment.