From 0d70a6c960518d5f9a1cc80a34834905d8490714 Mon Sep 17 00:00:00 2001 From: Connor Clark Date: Tue, 26 Jul 2016 15:48:25 -0700 Subject: [PATCH] Criterion benchmarks (#50) * begin bench executable * tweak benchmark, fork serverLoop for interruptibility * client streaming benchmarks * add server streaming handler * server streaming benchmark * bidi streaming benchmark * cleanup, create benchmark html * improve error messages * benchmarks: add bounds, remove -g, add -O2 * eliminate explicit sleep at shutdown * bump protobuf-wire version * remove superfluous parens, remove benchmarks.html --- .gitignore | 1 + bench/Bench.hs | 167 +++ benchmarks.html | 1074 ----------------- grpc-haskell.cabal | 22 +- .../GRPC/HighLevel/Server/Unregistered.hs | 5 +- stack.yaml | 2 +- 6 files changed, 193 insertions(+), 1078 deletions(-) create mode 100644 bench/Bench.hs delete mode 100644 benchmarks.html diff --git a/.gitignore b/.gitignore index 178d31e..3e4307f 100644 --- a/.gitignore +++ b/.gitignore @@ -5,3 +5,4 @@ dist *.o examples/echo/echo-cpp/echo-client examples/echo/echo-cpp/echo-server +benchmarks.html diff --git a/bench/Bench.hs b/bench/Bench.hs new file mode 100644 index 0000000..27b6497 --- /dev/null +++ b/bench/Bench.hs @@ -0,0 +1,167 @@ +{-# LANGUAGE DeriveGeneric #-} +{-# LANGUAGE LambdaCase #-} +{-# LANGUAGE OverloadedStrings #-} +{-# LANGUAGE DataKinds #-} +{-# LANGUAGE BangPatterns #-} + +import Control.Concurrent +import Control.Concurrent.Async +import Control.Exception (bracket) +import Control.Monad +import Criterion.Main +import Criterion.Types (Config(..)) +import qualified Data.ByteString.Lazy as BL +import Data.Word +import Data.Protobuf.Wire.Class +import Data.Protobuf.Wire.Types +import GHC.Generics (Generic) +import Network.GRPC.HighLevel.Server hiding (serverLoop) +import Network.GRPC.HighLevel.Server.Unregistered (serverLoop) +import Network.GRPC.LowLevel +import System.Random (randomRIO) + +data AddRequest = AddRequest {addX :: Fixed Word32 + , addY :: Fixed Word32} + deriving (Show, Eq, Ord, Generic) +instance Message AddRequest + +data AddResponse = AddResponse (Fixed Word32) + deriving (Show, Eq, Ord, Generic) +instance Message AddResponse + +addMethod :: MethodName +addMethod = MethodName "/unary" + +addClientStreamMethod :: MethodName +addClientStreamMethod = MethodName "/clientstream" + +addServerStreamMethod :: MethodName +addServerStreamMethod = MethodName "/serverstream" + +addBiDiMethod :: MethodName +addBiDiMethod = MethodName "/bidistream" + +addHandler :: Handler 'Normal +addHandler = + UnaryHandler addMethod $ + \c -> do + let b = payload c + return ( AddResponse $ addX b + addY b + , metadata c + , StatusOk + , StatusDetails "" + ) + +addClientStreamHandler :: Handler 'ClientStreaming +addClientStreamHandler = + ClientStreamHandler addClientStreamMethod $ + \_ recv -> do + answer <- go recv 0 + return (Just answer, mempty, StatusOk, "") + where go recv !i = do + req <- recv + case req of + Left _ -> return $ AddResponse i + Right Nothing -> return $ AddResponse i + Right (Just (AddRequest x y)) -> go recv (i+x+y) + +addServerStreamHandler :: Handler 'ServerStreaming +addServerStreamHandler = + ServerStreamHandler addServerStreamMethod $ + \c send -> do + let AddRequest (Fixed x) y = payload c + replicateM_ (fromIntegral x) $ send $ AddResponse y + return (mempty, StatusOk, "") + +addBiDiHandler :: Handler 'BiDiStreaming +addBiDiHandler = BiDiStreamHandler addBiDiMethod (go 0) + where go :: Fixed Word32 -> ServerRWHandler AddRequest AddResponse + go !i c recv send = do + req <- recv + case req of + Left _ -> return (mempty, StatusOk, "") + Right Nothing -> return (mempty, StatusOk, "") + Right (Just (AddRequest x y)) -> do + let curr = i + x + y + void $ send $ AddResponse curr + go curr c recv send + + +serverOpts :: ServerOptions +serverOpts = + defaultOptions{optNormalHandlers = [addHandler] + , optClientStreamHandlers = [addClientStreamHandler] + , optServerStreamHandlers = [addServerStreamHandler] + , optBiDiStreamHandlers = [addBiDiHandler]} + +threadDelaySecs :: Int -> IO () +threadDelaySecs = threadDelay . (* 10^(6::Int)) + +main :: IO () +main = bracket startServer stopServer $ const $ withGRPC $ \grpc -> + withClient grpc (ClientConfig "localhost" 50051 []) $ \c -> do + rmAdd <- clientRegisterMethodNormal c addMethod + rmClientStream <- clientRegisterMethodClientStreaming c addClientStreamMethod + rmServerStream <- clientRegisterMethodServerStreaming c addServerStreamMethod + rmBiDiStream <- clientRegisterMethodBiDiStreaming c addBiDiMethod + defaultMainWith + defaultConfig{reportFile = Just "benchmarks.html"} + [ bench "unary request" $ nfIO (addRequest c rmAdd) + , bench "client stream: 100 messages" $ nfIO (addClientStream c rmClientStream 100) + , bench "client stream: 1k messages" $ nfIO (addClientStream c rmClientStream 1000) + , bench "client stream: 10k messages" $ nfIO (addClientStream c rmClientStream 10000) + , bench "server stream: 100 messages" $ nfIO (addServerStream c rmServerStream 100) + , bench "server stream: 1k messages" $ nfIO (addServerStream c rmServerStream 1000) + , bench "server stream: 10k messages" $ nfIO (addServerStream c rmServerStream 10000) + , bench "bidi stream: 50 messages up, 50 down" $ nfIO (bidiStream c rmBiDiStream 50) + , bench "bidi stream: 500 message up, 500 down" $ nfIO (bidiStream c rmBiDiStream 500) + , bench "bidi stream: 5000 messages up, 5000 down" $ nfIO (bidiStream c rmBiDiStream 5000)] + + where startServer = do + sThrd <- async $ serverLoop serverOpts + threadDelaySecs 1 + return sThrd + + stopServer sThrd = cancel sThrd >> void (waitCatch sThrd) + + encode = BL.toStrict . toLazyByteString + + addRequest c rmAdd = do + x <- liftM Fixed $ randomRIO (0,1000) + y <- liftM Fixed $ randomRIO (0,1000) + let addEnc = BL.toStrict . toLazyByteString $ AddRequest x y + clientRequest c rmAdd 5 addEnc mempty >>= \case + Left e -> fail $ "Got client error on add request: " ++ show e + Right r -> case fromByteString (rspBody r) of + Left e -> fail $ "failed to decode add response: " ++ show e + Right dec + | dec == AddResponse (x + y) -> return () + | otherwise -> fail $ "Got wrong add answer: " ++ show dec ++ "; expected: " ++ show x ++ " + " ++ show y ++ " = " ++ show (x+y) + + addClientStream c rm i = do + let msg = encode $ AddRequest 1 0 + Right (Just r,_,_,_,_) <- clientWriter c rm 5 mempty $ \send -> do + replicateM_ i $ send msg + let decoded = fromByteString r + when (decoded /= Right (AddResponse (fromIntegral i))) $ + fail $ "clientStream: bad answer: " ++ show decoded ++ "; expected: " ++ show i + + addServerStream c rm i = do + let msg = encode $ AddRequest (fromIntegral i) 2 + Right (_, _, sd) <- clientReader c rm 5 msg mempty $ \_ recv -> + replicateM_ i $ do + Right (Just bs) <- recv + let Right decoded = fromByteString bs + when (decoded /= AddResponse 2) $ + fail $ "serverStream: bad response of " ++ show decoded ++ "; expected 2." + when (sd /= mempty) $ fail $ "bad status details: " ++ show sd + + bidiStream c rm i = do + Right (_, _, sd) <- clientRW c rm 5 mempty $ \_ recv send -> + forM_ (take i [2,4..]) $ \n -> do + void $ send $ encode $ AddRequest 1 1 + Right (Just bs) <- recv + let Right decoded = fromByteString bs + when (decoded /= AddResponse n) $ + fail $ "bidiStream: got: " ++ show decoded ++ "expected: " ++ show n + when (sd /= mempty) $ fail $ "bad StatusDetails: " ++ show sd diff --git a/benchmarks.html b/benchmarks.html deleted file mode 100644 index 336605b..0000000 --- a/benchmarks.html +++ /dev/null @@ -1,1074 +0,0 @@ - - - - - criterion report - - - - - - - -
-
-

criterion performance measurements

- -

overview

- -

want to understand this report?

- -
- -

unary request

- - - - - - - - -
- - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
lower boundestimateupper bound
OLS regressionxxxxxxxxx
R² goodness-of-fitxxxxxxxxx
Mean execution time1.1127952052099233e-41.1157779769569623e-41.1222578474109467e-4
Standard deviation7.006642862776891e-71.6019470204849632e-63.0016649862884594e-6
- - -

Outlying measurements have slight - (8.197243287309262e-2%) - effect on estimated standard deviation.

-
-

client stream: 100 messages

- - - - - - - - -
- - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
lower boundestimateupper bound
OLS regressionxxxxxxxxx
R² goodness-of-fitxxxxxxxxx
Mean execution time1.1145656673217617e-31.1225264180385309e-31.136100231001483e-3
Standard deviation2.1175077057984874e-53.660369985889931e-56.0245576168224164e-5
- - -

Outlying measurements have moderate - (0.2100730004584609%) - effect on estimated standard deviation.

-
-

client stream: 1k messages

- - - - - - - - -
- - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
lower boundestimateupper bound
OLS regressionxxxxxxxxx
R² goodness-of-fitxxxxxxxxx
Mean execution time1.0274288101958585e-21.0341389459833119e-21.0418416003070792e-2
Standard deviation1.5974251878414234e-42.0913496502759373e-42.889361409397357e-4
- - -

Outlying measurements have slight - (3.222222222222209e-2%) - effect on estimated standard deviation.

-
-

client stream: 10k messages

- - - - - - - - -
- - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
lower boundestimateupper bound
OLS regressionxxxxxxxxx
R² goodness-of-fitxxxxxxxxx
Mean execution time0.10351395223852060.10443575532386540.10589733927787692
Standard deviation8.693634002187114e-41.7581790983451108e-32.6984798923229657e-3
- - -

Outlying measurements have slight - (9.876543209876533e-2%) - effect on estimated standard deviation.

-
-

server stream: 100 messages

- - - - - - - - -
- - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
lower boundestimateupper bound
OLS regressionxxxxxxxxx
R² goodness-of-fitxxxxxxxxx
Mean execution time1.00500185533956e-31.0219297837648412e-31.038431407924066e-3
Standard deviation4.534639216316358e-55.8708277292223296e-57.292687430223964e-5
- - -

Outlying measurements have moderate - (0.4697581699045145%) - effect on estimated standard deviation.

-
-

server stream: 1k messages

- - - - - - - - -
- - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
lower boundestimateupper bound
OLS regressionxxxxxxxxx
R² goodness-of-fitxxxxxxxxx
Mean execution time8.263458511284804e-38.29655676830788e-38.338747504141219e-3
Standard deviation7.989147957982453e-51.1338955133128914e-41.6239809568186118e-4
- - -

Outlying measurements have slight - (2.938475665748384e-2%) - effect on estimated standard deviation.

-
-

server stream: 10k messages

- - - - - - - - -
- - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
lower boundestimateupper bound
OLS regressionxxxxxxxxx
R² goodness-of-fitxxxxxxxxx
Mean execution time8.139915127469478e-28.203977915769449e-28.294207157255142e-2
Standard deviation8.712272680628149e-41.303323554210239e-31.75288845055683e-3
- - -

Outlying measurements have slight - (9.000000000000001e-2%) - effect on estimated standard deviation.

-
-

bidi stream: 50 messages up, 50 down

- - - - - - - - -
- - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
lower boundestimateupper bound
OLS regressionxxxxxxxxx
R² goodness-of-fitxxxxxxxxx
Mean execution time3.6837263323658102e-33.690185989917211e-33.7016024806948455e-3
Standard deviation1.87435230068336e-52.7406270029965376e-53.868689618608243e-5
- - -

Outlying measurements have slight - (2.1266540642722116e-2%) - effect on estimated standard deviation.

-
-

bidi stream: 500 message up, 500 down

- - - - - - - - -
- - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
lower boundestimateupper bound
OLS regressionxxxxxxxxx
R² goodness-of-fitxxxxxxxxx
Mean execution time3.539779838485038e-23.5467452958929724e-23.5585300045038584e-2
Standard deviation1.1602363892840695e-41.603301186146598e-42.1296560804213925e-4
- - -

Outlying measurements have slight - (5.8593749999999986e-2%) - effect on estimated standard deviation.

-
-

bidi stream: 5000 messages up, 5000 down

- - - - - - - - -
- - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
lower boundestimateupper bound
OLS regressionxxxxxxxxx
R² goodness-of-fitxxxxxxxxx
Mean execution time0.35194120436214790.352078467508753430.3521320771337429
Standard deviation0.01.2712910344311448e-41.4489214967143587e-4
- - -

Outlying measurements have moderate - (0.1875%) - effect on estimated standard deviation.

-
- -

understanding this report

- -

In this report, each function benchmarked by criterion is assigned - a section of its own. The charts in each section are active; if - you hover your mouse over data points and annotations, you will see - more details.

- -
    -
  • The chart on the left is a - kernel - density estimate (also known as a KDE) of time - measurements. This graphs the probability of any given time - measurement occurring. A spike indicates that a measurement of a - particular time occurred; its height indicates how often that - measurement was repeated.
  • - -
  • The chart on the right is the raw data from which the kernel - density estimate is built. The x axis indicates the - number of loop iterations, while the y axis shows measured - execution time for the given number of loop iterations. The - line behind the values is the linear regression prediction of - execution time for a given number of iterations. Ideally, all - measurements will be on (or very near) this line.
  • -
- -

Under the charts is a small table. - The first two rows are the results of a linear regression run - on the measurements displayed in the right-hand chart.

- -
    -
  • OLS regression indicates the - time estimated for a single loop iteration using an ordinary - least-squares regression model. This number is more accurate - than the mean estimate below it, as it more effectively - eliminates measurement overhead and other constant factors.
  • -
  • R² goodness-of-fit is a measure of how - accurately the linear regression model fits the observed - measurements. If the measurements are not too noisy, R² - should lie between 0.99 and 1, indicating an excellent fit. If - the number is below 0.99, something is confounding the accuracy - of the linear model.
  • -
  • Mean execution time and standard deviation are - statistics calculated from execution time - divided by number of iterations.
  • -
- -

We use a statistical technique called - the bootstrap - to provide confidence intervals on our estimates. The - bootstrap-derived upper and lower bounds on estimates let you see - how accurate we believe those estimates to be. (Hover the mouse - over the table headers to see the confidence levels.)

- -

A noisy benchmarking environment can cause some or many - measurements to fall far from the mean. These outlying - measurements can have a significant inflationary effect on the - estimate of the standard deviation. We calculate and display an - estimate of the extent to which the standard deviation has been - inflated by outliers.

- - - -
-
- - - diff --git a/grpc-haskell.cabal b/grpc-haskell.cabal index eee67ee..75cd945 100644 --- a/grpc-haskell.cabal +++ b/grpc-haskell.cabal @@ -36,10 +36,10 @@ library , proto3-wire , protobuf-wire - , async + , async ==2.1.* , tasty >= 0.11 && <0.12 , tasty-hunit >= 0.9 && <0.10 - , safe + , safe ==0.3.* , vector c-sources: @@ -198,3 +198,21 @@ test-suite test if flag(debug) CPP-Options: -DDEBUG CC-Options: -DGRPC_HASKELL_DEBUG + +benchmark bench + type: exitcode-stdio-1.0 + build-depends: + base ==4.8.* + , grpc-haskell + , async ==2.1.* + , criterion ==1.1.* + , protobuf-wire + , bytestring ==0.10.* + , random >=1.0.0 + hs-source-dirs: bench + main-is: Bench.hs + ghc-options: -Wall -O2 -threaded -rtsopts -with-rtsopts=-N + if flag(debug) + CPP-Options: -DDEBUG + CC-Options: -DGRPC_HASKELL_DEBUG + default-language: Haskell2010 diff --git a/src/Network/GRPC/HighLevel/Server/Unregistered.hs b/src/Network/GRPC/HighLevel/Server/Unregistered.hs index 0ad8990..31cfc21 100644 --- a/src/Network/GRPC/HighLevel/Server/Unregistered.hs +++ b/src/Network/GRPC/HighLevel/Server/Unregistered.hs @@ -8,6 +8,7 @@ module Network.GRPC.HighLevel.Server.Unregistered where +import Control.Concurrent import Control.Arrow import qualified Control.Exception as CE import Control.Monad @@ -81,7 +82,9 @@ dispatchLoop server meta hN hC hS hB = serverLoop :: ServerOptions -> IO () serverLoop ServerOptions{..} = - withGRPC $ \grpc -> + -- We run the loop in a new thread so that we can kill the serverLoop thread. + -- Without this fork, we block on a foreign call, which can't be interrupted. + void $ forkIO $ withGRPC $ \grpc -> withServer grpc config $ \server -> do dispatchLoop server optInitialMetadata diff --git a/stack.yaml b/stack.yaml index b37a35b..0e56867 100644 --- a/stack.yaml +++ b/stack.yaml @@ -9,7 +9,7 @@ packages: - '.' - location: git: git@github.mv.awakenetworks.net:awakenetworks/protobuf-wire.git - commit: 62aa5b92f21883d14bf8d3beed5645f84da01ad6 + commit: 676a99af41a664660d269c475832301873062a37 extra-dep: true - location: git: git@github.com:awakenetworks/proto3-wire.git