freckle-app-1.15.2.0: Haskell application toolkit used at Freckle
Safe HaskellSafe-Inferred
LanguageHaskell2010

Freckle.App.Test.Http

Description

Implements stubbing of an HTTP request function

Synopsis

Documentation

Stubbing is accomplished by holding a list of HttpStub somewhere, which defines how to respond to requests that match. The simplest way to do so is to use the IsString instance:

stubs :: [HttpStub]
stubs =
  [ "https://example.com"
  ]

You can now use,

httpStubbed stubs :: Request -> Response ByteString

Anywhere you need an HTTP requesting function and it will respond 200 with an empty body for any GET requests made to this domain.

Stubbed responses can be modified through lenses:

stubs :: [HttpStub]
stubs =
  [ "https://example.com"
      & statusL .~ status400
      & bodyL .~ "Let's test a Bad Request"
  ]

The string is passed to parseRequest_, so anything valid there is valid here, such as setting the method:

data MyItem = MyItem
  { -- ...
  }
  deriving stock Generic
  deriving anyclass ToJSON

stubs :: [HttpStub]
stubs =
  [ "POST https://example.com/items"
      & json [MyItem]
      -- ^ Now matches requests with JSON in the Accept Header only
      --   Responds with Content-Type JSON
      --   Responds with a body of the JSON-encoded items
  ]

MonadHttp

Once we have the stubs, we can set up a MonadHttp context that uses it:

data TestApp = TestApp
  { appHttpStubs :: [HttpStubs]
  }

-- Assume TestAppT is a ReaderT TestApp
instance MonadHttp (TestAppT m a) where
  httpLbs req = do
    stubs <- asks appHttpStubs
    pure $ httpStubbed stubs req

Additionally, there are tools for DerivingVia or running things in a concrete HttpStubsT stack.

Handling Un-stubbed Requests

When no stubs match a given request, we call error -- this seems uncouth, but is actually the best possible behavior for the intended use-case in (e.g.) HSpec:

One other reasonable behavior would be to respond 404 to any un-matched requests. This can be accomplished by adding a "match anything" stub at the end:

stubs :: [HttpStub]
stubs =
  [ -- ...
  , -- ...
  , httpStub "Anything" MatchAnything
      & statusL .~ status404
      & bodyL .~ "Not found"
  ]

httpStubbed :: HasCallStack => [HttpStub] -> Request -> Response ByteString Source #

Respond to a Request with the first HttpStub to match

If no stubs match, error is used. If you'd rather experience a 404, add a final stub for any request that does that:

stubs :: [HttpStub]
stubs =
  [ -- ...
  , -- ...
  , httpStub "Anything" MatchAnything
      & statusL .~ status404
      & bodyL .~ "Not found"
  ]

Defining stubs

data HttpStub Source #

Constructors

HttpStub 

Fields

Instances

Instances details
IsString HttpStub Source # 
Instance details

Defined in Freckle.App.Test.Http

HasHttpStubs [HttpStub] Source # 
Instance details

Defined in Freckle.App.Test.Http

Monad m => MonadReader [HttpStub] (HttpStubsT m) Source # 
Instance details

Defined in Freckle.App.Test.Http

Methods

ask :: HttpStubsT m [HttpStub] #

local :: ([HttpStub] -> [HttpStub]) -> HttpStubsT m a -> HttpStubsT m a #

reader :: ([HttpStub] -> a) -> HttpStubsT m a #

httpStub :: String -> MatchRequest -> HttpStub Source #

Respond 200 with empty body for matching requests

httpStubUrl :: String -> HttpStub Source #

Respond 200 with empty body for requests parsed from the given URL

Stub modifiers

Response modifiers

Response helpers

json :: ToJSON a => a -> HttpStub -> HttpStub Source #

Modify the stub to match JSON requests and respond with the given value

FileSystem stubs

loadHttpStubsDirectory :: FilePath -> IO [HttpStub] Source #

Load stubs from the filesystem

Within the given directory, files are expected to be named for scheme, then host, then pathportquery.

Given,

files/
  https/
    www.example.com/
      hello                  => Hello
      world                  => World
  http/
    localhost:3000/
      hello?world=1          => "Hello 2"

Then loadHttpStubsDirectory "files" is equivalent to,

[ stubUrl "https://www.example.com/hello" & bodyL .~ "Hello"
, stubUrl "https://www.example.com/world" & bodyL .~ "World"
, stubUrl "http://localhost:3000/hello?world=1" & bodyL .~ "Hello 2"
]

NB. This function currently abuses the fact that / within filenames is the same for URLs, and so will not work on Windows. Patches welcome.

MonadHttp instances

For use with DerivingVia

class HasHttpStubs env where Source #

Methods

httpStubsL :: Lens' env [HttpStub] Source #

Instances

Instances details
HasHttpStubs [HttpStub] Source # 
Instance details

Defined in Freckle.App.Test.Http

newtype ReaderHttpStubs m a Source #

Constructors

ReaderHttpStubs 

Fields

Instances

Instances details
MonadReader env m => MonadReader env (ReaderHttpStubs m) Source # 
Instance details

Defined in Freckle.App.Test.Http

Methods

ask :: ReaderHttpStubs m env #

local :: (env -> env) -> ReaderHttpStubs m a -> ReaderHttpStubs m a #

reader :: (env -> a) -> ReaderHttpStubs m a #

Applicative m => Applicative (ReaderHttpStubs m) Source # 
Instance details

Defined in Freckle.App.Test.Http

Functor m => Functor (ReaderHttpStubs m) Source # 
Instance details

Defined in Freckle.App.Test.Http

Methods

fmap :: (a -> b) -> ReaderHttpStubs m a -> ReaderHttpStubs m b #

(<$) :: a -> ReaderHttpStubs m b -> ReaderHttpStubs m a #

Monad m => Monad (ReaderHttpStubs m) Source # 
Instance details

Defined in Freckle.App.Test.Http

(MonadReader env m, HasHttpStubs env) => MonadHttp (ReaderHttpStubs m) Source # 
Instance details

Defined in Freckle.App.Test.Http

Concrete transformer

data HttpStubsT m a Source #

Instances

Instances details
Applicative m => Applicative (HttpStubsT m) Source # 
Instance details

Defined in Freckle.App.Test.Http

Methods

pure :: a -> HttpStubsT m a #

(<*>) :: HttpStubsT m (a -> b) -> HttpStubsT m a -> HttpStubsT m b #

liftA2 :: (a -> b -> c) -> HttpStubsT m a -> HttpStubsT m b -> HttpStubsT m c #

(*>) :: HttpStubsT m a -> HttpStubsT m b -> HttpStubsT m b #

(<*) :: HttpStubsT m a -> HttpStubsT m b -> HttpStubsT m a #

Functor m => Functor (HttpStubsT m) Source # 
Instance details

Defined in Freckle.App.Test.Http

Methods

fmap :: (a -> b) -> HttpStubsT m a -> HttpStubsT m b #

(<$) :: a -> HttpStubsT m b -> HttpStubsT m a #

Monad m => Monad (HttpStubsT m) Source # 
Instance details

Defined in Freckle.App.Test.Http

Methods

(>>=) :: HttpStubsT m a -> (a -> HttpStubsT m b) -> HttpStubsT m b #

(>>) :: HttpStubsT m a -> HttpStubsT m b -> HttpStubsT m b #

return :: a -> HttpStubsT m a #

Monad m => MonadHttp (HttpStubsT m) Source # 
Instance details

Defined in Freckle.App.Test.Http

Monad m => MonadReader [HttpStub] (HttpStubsT m) Source # 
Instance details

Defined in Freckle.App.Test.Http

Methods

ask :: HttpStubsT m [HttpStub] #

local :: ([HttpStub] -> [HttpStub]) -> HttpStubsT m a -> HttpStubsT m a #

reader :: ([HttpStub] -> a) -> HttpStubsT m a #