Skip to content

Commit

Permalink
[RSC-233] Remove Mintette.Worker
Browse files Browse the repository at this point in the history
  • Loading branch information
gromakovsky committed Sep 20, 2016
1 parent 3ebccea commit cb02b66
Show file tree
Hide file tree
Showing 12 changed files with 38 additions and 126 deletions.
9 changes: 3 additions & 6 deletions bench/Bench/RSCoin/Local/InfraThreads.hs
Original file line number Diff line number Diff line change
Expand Up @@ -12,11 +12,9 @@ import System.FilePath ((</>))

import qualified RSCoin.Bank as B
import RSCoin.Core (ContextArgument (CADefault),
Mintette (Mintette), PublicKey,
SecretKey, Severity (Warning),
defaultEpochDelta, defaultPort,
localhost, testBankSecretKey,
testNotarySecretKey)
Mintette (Mintette), PublicKey, SecretKey,
Severity (Warning), defaultPort, localhost,
testBankSecretKey, testNotarySecretKey)
import qualified RSCoin.Mintette as M
import qualified RSCoin.Notary as N

Expand All @@ -41,7 +39,6 @@ mintetteThread :: Int -> FilePath -> SecretKey -> IO ()
mintetteThread mintetteId benchDir sk =
M.launchMintetteReal
False
defaultEpochDelta
port
(M.mkRuntimeEnv 100000 sk)
dbPath
Expand Down
2 changes: 1 addition & 1 deletion rscoin-core
1 change: 0 additions & 1 deletion rscoin.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -43,7 +43,6 @@ library
, RSCoin.Mintette.Launcher
, RSCoin.Mintette.Server
, RSCoin.Mintette.Storage
, RSCoin.Mintette.Worker

, RSCoin.Notary
, RSCoin.Notary.AcidState
Expand Down
1 change: 0 additions & 1 deletion src/Deploy/Config.hs
Original file line number Diff line number Diff line change
Expand Up @@ -20,7 +20,6 @@ data DeployConfig = DeployConfig
, dcMintettes :: !Word
, dcExplorers :: !Word
, dcPeriod :: !Word
, dcEpoch :: !Word
, dcGlobalSeverity :: !Severity
, dcBankSeverity :: !(Maybe Severity)
, dcNotarySeverity :: !(Maybe Severity)
Expand Down
4 changes: 1 addition & 3 deletions src/Deploy/Main.hs
Original file line number Diff line number Diff line change
Expand Up @@ -53,7 +53,6 @@ getConfigPath =
data CommonParams = CommonParams
{ cpBaseDir :: !FilePath
, cpPeriod :: !Millisecond
, cpEpoch :: !Millisecond
, cpRebuild :: !Bool
} deriving (Show)

Expand Down Expand Up @@ -88,7 +87,7 @@ startMintette CommonParams{..} idx = do
(sk,pk) <- getKeys workingDir
let env = M.mkRuntimeEnv 1000000000 sk
start =
M.launchMintetteReal cpRebuild cpEpoch port env (Just dbDir) contextArgument
M.launchMintetteReal cpRebuild port env (Just dbDir) contextArgument
(, pk) <$> forkIO start

startExplorer
Expand Down Expand Up @@ -229,7 +228,6 @@ main = do
CommonParams
{ cpBaseDir = deployDir
, cpPeriod = fromIntegral dcPeriod
, cpEpoch = fromIntegral dcEpoch
, cpRebuild = False
}
mintetteIndices = [1 .. dcMintettes]
Expand Down
8 changes: 3 additions & 5 deletions src/Mintette/Main.hs
Original file line number Diff line number Diff line change
Expand Up @@ -3,10 +3,9 @@
import Control.Exception (SomeException)
import Control.Monad.Catch (throwM, try)
import Data.Monoid ((<>))
import Data.Time.Units (Second)

import RSCoin.Core (initLogging, keyGen, readSecretKey,
writePublicKey, writeSecretKey)
import RSCoin.Core (initLogging, keyGen, readSecretKey, writePublicKey,
writeSecretKey)
import qualified RSCoin.Mintette as M

import qualified MintetteOptions as Opts
Expand Down Expand Up @@ -46,9 +45,8 @@ mainServe ctxArg Opts.ServeOptions {..} Opts.Options {..} = do
if cloMemMode
then Nothing
else Just cloPath
epochDelta = fromInteger cloEpochDelta :: Second
env = M.mkRuntimeEnv cloActionLogsLimit sk
M.launchMintetteReal cloRebuildDB epochDelta cloPort env dbPath ctxArg
M.launchMintetteReal cloRebuildDB cloPort env dbPath ctxArg

mainDumpStatistics :: M.ContextArgument -> Opts.Options -> IO ()
mainDumpStatistics ctxArg Opts.Options {..} = do
Expand Down
19 changes: 5 additions & 14 deletions src/Mintette/MintetteOptions.hs
Original file line number Diff line number Diff line change
Expand Up @@ -8,18 +8,16 @@ module MintetteOptions
, getOptions
) where

import Options.Applicative (Parser, auto, command, execParser,
fullDesc, help, helper, info, long,
metavar, option, progDesc, short,
showDefault, subparser, switch, value,
(<>))
import Options.Applicative (Parser, auto, command, execParser, fullDesc,
help, helper, info, long, metavar, option,
progDesc, short, showDefault, subparser, switch,
value, (<>))
import System.FilePath ((</>))

import Serokell.Util.OptParse (strOption)

import RSCoin.Core (Severity (Error), configDirectory,
defaultConfigurationPath,
defaultEpochDelta, defaultPort,
defaultConfigurationPath, defaultPort,
defaultSecretKeyPath)

data Command
Expand All @@ -28,7 +26,6 @@ data Command

data ServeOptions = ServeOptions
{ cloPort :: Int
, cloEpochDelta :: Integer
, cloSecretKeyPath :: FilePath
, cloAutoCreateKey :: Bool
, cloActionLogsLimit :: Word
Expand Down Expand Up @@ -58,12 +55,6 @@ commandParser defaultSKPath =
option
auto
(short 'p' <> long "port" <> value defaultPort <> showDefault) <*>
option
auto
(long "epoch-delta" <> value (toInteger defaultEpochDelta) <>
showDefault <>
help "Epoch length in seconds" <>
metavar "INT") <*>
strOption
(long "sk" <> value defaultSKPath <> metavar "FILEPATH" <>
help "Path to the secret key" <>
Expand Down
1 change: 0 additions & 1 deletion src/RSCoin/Mintette.hs
Original file line number Diff line number Diff line change
Expand Up @@ -11,4 +11,3 @@ import RSCoin.Mintette.Env as Exports
import RSCoin.Mintette.Error as Exports
import RSCoin.Mintette.Launcher as Exports
import RSCoin.Mintette.Server as Exports
import RSCoin.Mintette.Worker as Exports
31 changes: 10 additions & 21 deletions src/RSCoin/Mintette/Launcher.hs
Original file line number Diff line number Diff line change
Expand Up @@ -11,21 +11,16 @@ module RSCoin.Mintette.Launcher
import Control.Monad.Catch (bracket)
import Control.Monad.Trans (MonadIO (liftIO))
import qualified Data.Text.IO as TIO
import Data.Time.Units (TimeUnit)
import Formatting (int, sformat, stext, (%))

import Control.TimeWarp.Timed (fork_)
import RSCoin.Core (ContextArgument (..), RealMode,
mintetteLoggerName,
runRealModeUntrusted)
mintetteLoggerName, runRealModeUntrusted)

import RSCoin.Mintette.Acidic (GetPeriodId (..), closeState,
getStatistics, openMemState,
openState)
import RSCoin.Mintette.Acidic (GetPeriodId (..), closeState, getStatistics,
openMemState, openState)
import RSCoin.Mintette.AcidState (State, query)
import RSCoin.Mintette.Env (RuntimeEnv)
import RSCoin.Mintette.Server (serve)
import RSCoin.Mintette.Worker (runWorkerWithDelta)

mintetteWrapperReal :: Bool
-> Maybe FilePath
Expand All @@ -38,23 +33,17 @@ mintetteWrapperReal deleteIfExists dbPath ca action = do
action

launchMintetteReal
:: (Show t, Num t, Integral t, TimeUnit t)
=> Bool -> t -> Int -> RuntimeEnv -> Maybe FilePath -> ContextArgument -> IO ()
launchMintetteReal deleteIfExists epochDelta port env dbPath ctxArg =
mintetteWrapperReal deleteIfExists dbPath ctxArg $
\st -> do
fork_ $ runWorkerWithDelta epochDelta env st
serve port st env
::
Bool -> Int -> RuntimeEnv -> Maybe FilePath -> ContextArgument -> IO ()
launchMintetteReal deleteIfExists port env dbPath ctxArg =
mintetteWrapperReal deleteIfExists dbPath ctxArg $ \st -> serve port st env

dumpStorageStatistics :: Bool -> FilePath -> ContextArgument -> IO ()
dumpStorageStatistics deleteIfExists dbPath ctxArg =
mintetteWrapperReal deleteIfExists (Just dbPath) ctxArg impl
where
impl st = do
pId <- query st GetPeriodId
liftIO .
TIO.putStrLn .
sformat
("Storage statistics (period id is " % int % "):\n" % stext)
pId =<<
getStatistics st
liftIO . TIO.putStrLn .
sformat ("Storage statistics (period id is " % int % "):\n" % stext)
pId =<< getStatistics st
50 changes: 0 additions & 50 deletions src/RSCoin/Mintette/Worker.hs

This file was deleted.

7 changes: 2 additions & 5 deletions test/Test/RSCoin/Full/Mintette.hs
Original file line number Diff line number Diff line change
Expand Up @@ -11,10 +11,8 @@ import Control.Lens (view, (^.))
import qualified RSCoin.Core as C
import qualified RSCoin.Mintette as M

import Test.RSCoin.Full.Context (MintetteInfo, port,
secretKey, state)
import Test.RSCoin.Full.Mintette.Config (MintetteConfig,
malfunctioningConfig)
import Test.RSCoin.Full.Context (MintetteInfo, port, secretKey, state)
import Test.RSCoin.Full.Mintette.Config (MintetteConfig, malfunctioningConfig)
import qualified Test.RSCoin.Full.Mintette.Server as FM

initialization
Expand All @@ -30,7 +28,6 @@ initialization conf forkTmp m = do
Nothing -> M.serve
Just s -> FM.serve s
forkTmp $ runner <$> view port <*> view state <*> pure env $ m
forkTmp $ M.runWorker env <$> view state $ m

defaultMintetteInit
:: C.WorkMode m
Expand Down
31 changes: 13 additions & 18 deletions test/Test/RSCoin/Full/Mintette/Storage.hs
Original file line number Diff line number Diff line change
Expand Up @@ -5,14 +5,15 @@
{-# LANGUAGE TupleSections #-}

-- | Storage for mintette's data (configurable).
-- WARNING: this module is outdated! Rewrite it when needed.

module Test.RSCoin.Full.Mintette.Storage
( checkNotDoubleSpent
, commitTx
) where

import Control.Lens (at, use, uses, view, (%=),
(.=), (<>=), _1)
import Control.Lens (at, use, uses, view, (%=), (.=), (<>=),
_1)
import Control.Monad (unless, when)
import Control.Monad.Catch (MonadThrow (throwM))
import Control.Monad.Reader (ReaderT)
Expand All @@ -23,26 +24,20 @@ import Data.Maybe (fromJust, fromMaybe, isJust)
import qualified Data.Set as S
import Safe (atMay)

import RSCoin.Core (AddrId, SecretKey,
Transaction (..),
TxStrategy (..),
computeOutputAddrids,
derivePublicKey,
isStrategyCompleted,
mkCheckConfirmation, owners,
sign,
import RSCoin.Core (AddrId, SecretKey, Transaction (..),
TxStrategy (..), computeOutputAddrids,
derivePublicKey, isStrategyCompleted,
mkCheckConfirmation, owners, sign,
verifyCheckConfirmation)
import qualified RSCoin.Core as C
import RSCoin.Mintette.Env (RuntimeEnv, reSecretKey)
import RSCoin.Mintette.Error (MintetteError (..))
import RSCoin.Mintette.Storage (Storage, addresses,
checkIsActive, checkTxSum,
curMintetteId, dpk,
getLogHead, logHeads,
logSize, mintettes, periodId,
pset, pushLogEntry,
readerToState, txset, utxo,
utxoAdded, utxoDeleted)
import RSCoin.Mintette.Storage (Storage, addresses, checkIsActive,
checkTxSum, curMintetteId, dpk,
getLogHead, logHeads, logSize,
mintettes, periodId, pset,
pushLogEntry, readerToState, txset,
utxo, utxoAdded, utxoDeleted)

import Test.RSCoin.Full.Mintette.Config (MintetteConfig (..))

Expand Down

0 comments on commit cb02b66

Please sign in to comment.