I ended up playing around a bit with the Network.HTTP
module. My goal was to make a one-liner to load test an HTTP service I work on. I wanted to see how far I could towards doing what I normally do in ab
, but in Haskell.
Here’s the one-liner for use with GHCi:
import Network.HTTP
import Control.Monad
mapM_ (\x -> replicateM_ 100 (simpleHTTP (getRequest "http://localhost:8000/"){rqBody="waa", rqHeaders=[Header (HdrCustom "x-project-id") (show x)]}) >> print x) [1..150]
--
Let’s break it down:
mapM_ :: Monad m => (a -> m b) -> [a] -> m ()
mapM_ (some action) [1..150] {-- apply the action with each
integer as input --}
(>>) :: Monad m => m a -> m b -> m b
(\x -> (action x) >> print x) {-- take a value, do something with it,
discard the result, then print it --}
replicateM_ :: Monad m => Int -> m a -> m ()
(\x -> (replicateM_ 100 $ (action x)) -- replicate the action 100 times
simpleHTTP :: HStream ty =>
Request ty -> IO (Network.Stream.Result (Response ty))
(\x -> simpleHTTP (... x)) {-- the action is an HTTP request
consisting of... --}
-- and this is what a Request looks like
data Request a
= Request {rqURI :: Network.URI.URI,
rqMethod :: RequestMethod,
rqHeaders :: [Header],
rqBody :: a}
rqBody :: Request a -> a
rqHeaders :: Request a -> [Header]
-- modify the initial request body
(\x -> {rqBody="waaa", rqHeaders=[... x]} {-- with a particular body and
headers --}
-- modify the initial request headers: {x-project-id: x}
HdrCustom :: String -> HeaderName
(\x -> rqHeaders=[Header (HdrCustom "x-project-id") (show x)])
And now for a decomposed module:
module Main where
import Network.HTTP
import Network.Stream (Result)
import Control.Monad (replicateM_)
request :: Show a => a -> IO (Result (Response String))
request proj = simpleHTTP $ bldRequest (show proj)
where bldRequest project = (getRequest url){ rqBody="waaa"
, rqHeaders=mkHeaders project
}
mkHeaders project = [Header (HdrCustom "x-project-id") project]
url = "http://localhost:8000"
main :: IO ()
main = mapM_ (replicateM_ 100 . request) [1..150]
It was surprisingly fun to tinker and get to this. It took several GHCi experiments. The output from running this in GHCi looks like:
It was also fun to realize how easy it was to modify by taking advantage of GHCi’s readline support. I’d hit <up>
, and I could modify any of:
[1..150]
replicateM_ 100
rqBody="waaa"
>> print x
This exercise gave me a chance to work with simple HTTP in Haskell and to fiddle with monadic I/O. The experience on a whole was pleasant.
I leave you with this thought: Never underestimate the power of a good REPL when learning a new language/library/module/system.