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

Commit

Permalink
[CBR-179] Move middlewares to dedicated module
Browse files Browse the repository at this point in the history
  • Loading branch information
akegalj authored and KtorZ committed Sep 14, 2018
1 parent c536af4 commit dcce5c1
Show file tree
Hide file tree
Showing 5 changed files with 58 additions and 51 deletions.
1 change: 1 addition & 0 deletions wallet-new/cardano-sl-wallet-new.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -134,6 +134,7 @@ library
Cardano.Wallet.Orphans.Bi
Cardano.Wallet.Server
Cardano.Wallet.Server.CLI
Cardano.Wallet.Server.Middlewares
Cardano.Wallet.Server.Plugins
Cardano.Wallet.Server.Plugins.AcidState
Cardano.Wallet.Server.LegacyPlugins
Expand Down
5 changes: 3 additions & 2 deletions wallet-new/server/Main.hs
Original file line number Diff line number Diff line change
Expand Up @@ -50,6 +50,7 @@ import Cardano.Wallet.Server.CLI (ChooseWalletBackend (..),
getWalletNodeOptions, walletDbPath, walletFlushDb,
walletRebuildDb)
import qualified Cardano.Wallet.Server.LegacyPlugins as LegacyPlugins
import Cardano.Wallet.Server.Middlewares (throttleMiddleware)
import qualified Cardano.Wallet.Server.Plugins as Plugins
import Cardano.Wallet.WalletLayer (PassiveWalletLayer)
import qualified Cardano.Wallet.WalletLayer.Kernel as WalletLayer.Kernel
Expand Down Expand Up @@ -107,7 +108,7 @@ actionWithLegacyWallet coreConfig walletConfig txpConfig sscParams nodeParams nt
plugins ntpStatus =
mconcat [ LegacyPlugins.conversation wArgs
, LegacyPlugins.legacyWalletBackend coreConfig txpConfig wArgs ntpStatus
[ LegacyPlugins.throttleMiddleware (ccThrottle walletConfig)
[ throttleMiddleware (ccThrottle walletConfig)
]
, LegacyPlugins.walletDocumentation wArgs
, LegacyPlugins.acidCleanupWorker wArgs
Expand Down Expand Up @@ -175,7 +176,7 @@ actionWithWallet coreConfig walletConfig txpConfig sscParams nodeParams ntpConfi
-- The actual wallet backend server.
[ Plugins.apiServer pm params w
-- Throttle requests.
[ Plugins.throttleMiddleware (ccThrottle walletConfig)
[ throttleMiddleware (ccThrottle walletConfig)
]

-- The corresponding wallet documention, served as a different
Expand Down
34 changes: 3 additions & 31 deletions wallet-new/src/Cardano/Wallet/Server/LegacyPlugins.hs
Original file line number Diff line number Diff line change
Expand Up @@ -13,7 +13,6 @@ module Cardano.Wallet.Server.LegacyPlugins (
, walletDocumentation
, resubmitterPlugin
, notifierPlugin
, throttleMiddleware
) where

import Universum
Expand All @@ -24,6 +23,7 @@ import qualified Cardano.Wallet.API.V1.Types as V1
import qualified Cardano.Wallet.LegacyServer as LegacyServer
import Cardano.Wallet.Server.CLI (WalletBackendParams (..),
isDebugMode, walletAcidInterval, walletDbOptions)
import Cardano.Wallet.Server.Middlewares (withMiddlewares)
import qualified Pos.Wallet.Web.Error.Types as V0

import Control.Exception (fromException)
Expand All @@ -33,7 +33,6 @@ import Network.HTTP.Types.Status (badRequest400)
import Network.Wai (Application, Middleware, Response, responseLBS)
import Network.Wai.Handler.Warp (defaultSettings,
setOnExceptionResponse)
import qualified Network.Wai.Middleware.Throttle as Throttle
import Ntp.Client (NtpStatus)
import Pos.Chain.Txp (TxpConfiguration)
import Pos.Infra.Diffusion.Types (Diffusion (..))
Expand All @@ -54,8 +53,7 @@ import Cardano.NodeIPC (startNodeJsIPC)
import Pos.Configuration (walletProductionApi,
walletTxCreationDisabled)
import Pos.Infra.Shutdown.Class (HasShutdownContext (shutdownContext))
import Pos.Launcher.Configuration (HasConfigurations,
ThrottleSettings (..))
import Pos.Launcher.Configuration (HasConfigurations)
import Pos.Util.CompileInfo (HasCompileInfo)
import Pos.Wallet.Web.Mode (WalletWebMode)
import Pos.Wallet.Web.Server.Launcher (walletDocumentationImpl,
Expand Down Expand Up @@ -103,11 +101,7 @@ walletDocumentation WalletBackendParams {..} = pure $ \_ ->
application :: WalletWebMode Application
application = do
let app = Servant.serve API.walletDocAPI LegacyServer.walletDocServer
return $
withMiddlewares
[ throttleMiddleware Nothing
]
app
return $ withMiddlewares [] app
tls =
if isDebugMode walletRunMode then Nothing else walletTLSParams

Expand Down Expand Up @@ -215,25 +209,3 @@ syncWalletWorker :: Core.Config -> Plugin WalletWebMode
syncWalletWorker coreConfig = pure $ const $
modifyLoggerName (const "syncWalletWorker") $
(view (lensOf @SyncQueue) >>= processSyncRequest coreConfig)

-- | "Attaches" the middlewares to this 'Application'.
withMiddlewares :: [Middleware] -> Application -> Application
withMiddlewares = flip $ foldr ($)

-- | A @Middleware@ to throttle requests.
throttleMiddleware :: Maybe ThrottleSettings -> Middleware
throttleMiddleware Nothing app = app
throttleMiddleware (Just ts) app = \req respond -> do
throttler <- Throttle.initThrottler
Throttle.throttle throttleSettings throttler app req respond
where
throttleSettings = Throttle.defaultThrottleSettings
{ Throttle.onThrottled = \microsTilRetry ->
let
err = V1.RequestThrottled microsTilRetry
in
responseLBS (V1.toHttpErrorStatus err) [applicationJson] (encode err)
, Throttle.throttleRate = fromIntegral $ tsRate ts
, Throttle.throttlePeriod = fromIntegral $ tsPeriod ts
, Throttle.throttleBurst = fromIntegral $ tsBurst ts
}
42 changes: 42 additions & 0 deletions wallet-new/src/Cardano/Wallet/Server/Middlewares.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,42 @@
{- | A collection of middlewares used by this edge node.
@Middleware@ is a component that sits between the server and application.
It can do such tasks as GZIP encoding or response caching.
-}

module Cardano.Wallet.Server.Middlewares
( withMiddlewares
, throttleMiddleware
) where

import Universum

import Data.Aeson (encode)
import Network.Wai (Application, Middleware, responseLBS)
import qualified Network.Wai.Middleware.Throttle as Throttle

import Cardano.Wallet.API.V1.Headers (applicationJson)
import qualified Cardano.Wallet.API.V1.Types as V1

import Pos.Launcher.Configuration (ThrottleSettings (..))

-- | "Attaches" the middlewares to this 'Application'.
withMiddlewares :: [Middleware] -> Application -> Application
withMiddlewares = flip $ foldr ($)

-- | A @Middleware@ to throttle requests.
throttleMiddleware :: Maybe ThrottleSettings -> Middleware
throttleMiddleware Nothing app = app
throttleMiddleware (Just ts) app = \req respond -> do
throttler <- Throttle.initThrottler
Throttle.throttle throttleSettings throttler app req respond
where
throttleSettings = Throttle.defaultThrottleSettings
{ Throttle.onThrottled = \microsTilRetry ->
let
err = V1.RequestThrottled microsTilRetry
in
responseLBS (V1.toHttpErrorStatus err) [applicationJson] (encode err)
, Throttle.throttleRate = fromIntegral $ tsRate ts
, Throttle.throttlePeriod = fromIntegral $ tsPeriod ts
, Throttle.throttleBurst = fromIntegral $ tsBurst ts
}
27 changes: 9 additions & 18 deletions wallet-new/src/Cardano/Wallet/Server/Plugins.hs
Original file line number Diff line number Diff line change
Expand Up @@ -16,27 +16,24 @@ import Universum

import Data.Acid (AcidState)

import Network.Wai (Application, Middleware, responseLBS)
import Network.Wai (Application, Middleware)
import Network.Wai.Handler.Warp (defaultSettings)
import qualified Network.Wai.Middleware.Throttle as Throttle

import Cardano.NodeIPC (startNodeJsIPC)
import Cardano.Wallet.API as API
import Cardano.Wallet.API.V1.Headers (applicationJson)
import qualified Cardano.Wallet.API.V1.Types as V1
import Cardano.Wallet.Kernel (DatabaseMode (..), PassiveWallet)
import Cardano.Wallet.Server.CLI (NewWalletBackendParams (..),
WalletBackendParams (..), getWalletDbOptions, isDebugMode,
walletAcidInterval)
import Cardano.Wallet.Server.Middlewares (withMiddlewares)
import Cardano.Wallet.WalletLayer (ActiveWalletLayer,
PassiveWalletLayer)
import Pos.Chain.Update (cpsSoftwareVersion)
import Pos.Crypto (ProtocolMagic)
import Pos.Infra.Diffusion.Types (Diffusion (..))
import Pos.Infra.Shutdown (HasShutdownContext (shutdownContext),
ShutdownContext)
import Pos.Launcher.Configuration (HasConfigurations,
ThrottleSettings (..))
import Pos.Launcher.Configuration (HasConfigurations)
import Pos.Util.CompileInfo (HasCompileInfo)
import Pos.Util.Wlog (logInfo, modifyLoggerName, usingLoggerName)
import Pos.Web (serveDocImpl, serveImpl)
Expand All @@ -49,7 +46,6 @@ import Cardano.Wallet.Server.Plugins.AcidState
(createAndArchiveCheckpoints)
import qualified Cardano.Wallet.WalletLayer as WalletLayer
import qualified Cardano.Wallet.WalletLayer.Kernel as WalletLayer.Kernel
import Data.Aeson (encode)
import qualified Data.ByteString.Char8 as BS8
import qualified Servant

Expand Down Expand Up @@ -99,11 +95,6 @@ apiServer protocolMagic (NewWalletBackendParams WalletBackendParams{..}) (passiv
portCallback ctx =
usingLoggerName "NodeIPC" . flip runReaderT ctx . startNodeJsIPC

-- | "Attaches" the middlewares to this 'Application'.
withMiddlewares :: [Middleware] -> Application -> Application
withMiddlewares = flip $ foldr ($)


-- | A @Plugin@ to serve the wallet documentation
docServer
:: (HasConfigurations, HasCompileInfo)
Expand Down Expand Up @@ -145,12 +136,12 @@ acidStateSnapshots :: AcidState db
-> DatabaseMode
-> Plugin Kernel.WalletMode
acidStateSnapshots dbRef params dbMode = pure $ \_diffusion -> do
let opts = getWalletDbOptions params
modifyLoggerName (const "acid-state-checkpoint-plugin") $
createAndArchiveCheckpoints
dbRef
(walletAcidInterval opts)
dbMode
let opts = getWalletDbOptions params
modifyLoggerName (const "acid-state-checkpoint-plugin") $
createAndArchiveCheckpoints
dbRef
(walletAcidInterval opts)
dbMode

-- | A @Plugin@ to store updates proposal received from the blockchain
updateWatcher :: Plugin Kernel.WalletMode
Expand Down

0 comments on commit dcce5c1

Please sign in to comment.