wrecker-0.1.1.1: A HTTP Performance Benchmarker

Safe HaskellNone
LanguageHaskell2010

Wrecker

Description

wrecker is a library for creating HTTP benchmarks. It is designed for benchmarking a series of HTTP request were the output of previous requests are used as inputs to the next request. This is useful for complex API profiling situations.

wrecker does not provide any mechanism for making HTTP calls. It works with any HTTP client that produces a HttpException during failure (so http-client and wreq will work out of the box).

See the documentation for examples of how to use wrecker with benchmarking scripts.

Synopsis

Documentation

data Recorder Source #

An opaque type for recording actions for profiling. No means are provided for creating a Recorder directly. To obtain a Recorder use either run or defaultMain.

defaultMain :: [(String, Recorder -> IO ())] -> IO () Source #

defaultMain is typically the main entry point for wrecker benchmarks. defaultMain will parse all command line arguments and then call run with the correct Options.

import Wrecker
import Your.Performance.Scripts (landingPage, purchase)

main :: IO ()
main = defaultMain
 [ ("loginReshare", loginReshare)
 , ("purchase"    , purchase    )
 ]

To see the options defaultMain can parse call `--help`

$ wrecker-based-app --help

wrecker - HTTP stress tester and benchmarker

Usage: example [--concurrency ARG] [--bin-count ARG] ([--run-count ARG] |
               [--run-timed ARG]) [--timeout-time ARG] [--display-mode ARG]
               [--log-level ARG] [--match ARG] [--request-name-size ARG]
               [--output-path ARG] [--silent]
 Welcome to wrecker

Available options:
 -h,--help                Show this help text
 --concurrency ARG        Number of threads for concurrent requests
 --bin-count ARG          Number of bins for latency histogram
 --run-count ARG          number of times to repeat
 --run-timed ARG          number of seconds to repeat
 --timeout-time ARG       How long to wait for all requests to finish
 --display-mode ARG       Display results interactively
 --log-level ARG          Display results interactively
 --match ARG              Only run tests that match the glob
 --request-name-size ARG  Request name size for the terminal display
 --output-path ARG        Save a JSON file of the the statistics to given path
 --silent                 Disable all output

record :: forall a. Recorder -> String -> IO a -> IO a Source #

record is how HTTP actions are profiled. Wrap each action of interest in a call to record.

import Network.Wreq.Session
import Data.Aeson

loginReshare :: Recorder -> IO ()
loginReshare recorder = withSession $ \session -> do
  let rc = record recorder

  Object user <- rc "login"
               $ asJSON
            =<< ( post session "https://somesite.com/login"
                $ object [ "email"    .= "example@example.com"
                         , "password" .= "12345678"
                        ]
                )
  let Just feedUrl = H.lookup "feed" user
  itemRef : _ <- rc "get feed"
               $ asJSON
             =<< ( post session feedUrl
                 $ object [ "email"    .= "example@example.com"
                          , "password" .= "12345678"
                          ]
                 )
  rc "reshare" $ post session "https://somesite.com/share"
               $ object [ "type" : "reshare"
                        , "ref"  : itemRef
                        ]

In this case the loginReshare script would record three actions: "login", "get feed" and "reshare".

record measures the elapsed time of the call, and catches HttpException in the case of failure. This means failures must be thrown if they are to be properly recorded.

run :: Options -> [(String, Recorder -> IO ())] -> IO (HashMap String AllStats) Source #

run is the a lower level entry point, compared to defaultMain. Unlike defaultMain no command line argument parsing is performed. Instead, Options are directly passed in. defaultOptions can be used as a default argument for run.

Like defaultMain, run creates a Recorder and passes it each benchmark.

data Options Source #

Constructors

Options 

Fields

data RunType Source #

There are two typical ways to invoke wrecker. RunCount will execute each a script n times, where n is the parameter for RunCount. Alternatively, wrecker can run for specified time with RunTimed.

Constructors

RunCount Int 
RunTimed Int 

data DisplayMode Source #

DisplayMode controls how results are displayed in the console. The default is NonInterative which returns the final results at the end of the program. Interactive will show partial results as the program updates.

defaultOptions :: Options Source #

defaultOptions provides sensible default for the Options types

runParser :: IO Options Source #

Run the command line parse and return the Options

runParser can parse the following options

$ wrecker-based-app --help

wrecker - HTTP stress tester and benchmarker

Usage: example [--concurrency ARG] [--bin-count ARG] ([--run-count ARG] |
               [--run-timed ARG]) [--timeout-time ARG] [--display-mode ARG]
               [--log-level ARG] [--match ARG] [--request-name-size ARG]
               [--output-path ARG] [--silent]
 Welcome to wrecker

Available options:
 -h,--help                Show this help text
 --concurrency ARG        Number of threads for concurrent requests
 --bin-count ARG          Number of bins for latency histogram
 --run-count ARG          number of times to repeat
 --run-timed ARG          number of seconds to repeat
 --timeout-time ARG       How long to wait for all requests to finish
 --display-mode ARG       Display results interactively
 --log-level ARG          Display results interactively
 --match ARG              Only run tests that match the glob
 --request-name-size ARG  Request name size for the terminal display
 --output-path ARG        Save a JSON file of the the statistics to given path
 --silent                 Disable all output

data AllStats Source #

AllStats has all of the ... stats. This type stores all of the information wrecker uses to display metrics to the user.

Constructors

AllStats 

Fields

Instances

Eq AllStats Source # 
Show AllStats Source # 
ToJSON AllStats Source # 

Methods

toJSON :: AllStats -> Value

toEncoding :: AllStats -> Encoding

toJSONList :: [AllStats] -> Value

toEncodingList :: [AllStats] -> Encoding

newStandaloneRecorder :: IO (NextRef AllStats, Thread, Recorder) Source #

Typically wrecker will control benchmarking actions. Howeve,r in some situations a benchmark might require more control.

To facilitate more complex scenarios wrecker provide newStandaloneRecorder which provides a Recorder and Thread that processes the events, and a reference to the current stats.