polysemy-http: Polysemy Effects for HTTP clients

[ library, network ] [ Propose Tags ]
Versions [RSS] 0.1.0.0, 0.2.0.0, 0.2.0.1, 0.2.0.2, 0.2.0.3, 0.2.0.4, 0.3.0.0, 0.3.1.0, 0.4.0.0, 0.4.0.1, 0.4.0.2, 0.4.0.3, 0.4.0.4, 0.4.0.5, 0.4.0.6, 0.5.0.0, 0.6.0.0, 0.7.0.0, 0.8.0.0, 0.9.0.0, 0.10.0.0, 0.11.0.0, 0.12.0.0, 0.13.0.0, 0.13.0.1 (info)
Change log changelog.md
Dependencies aeson (>=1.4), ansi-terminal (>=0.10.3), base (>=4 && <5), bytestring, case-insensitive (>=1.2), composition (>=1.0.2), containers, data-default (>=0.7), either (>=5.0.1), http-client (>=0.6.4), http-client-tls (>=0.3.5), http-types (>=0.12.3), lens (>=4), polysemy (>=1.6), polysemy-log (>=0.2.2.4), polysemy-plugin (>=0.4), relude (>=0.7), string-interpolate (>=0.2.1), template-haskell, text, time [details]
License BSD-2-Clause-Patent
Copyright 2020 Torsten Schmits
Author Torsten Schmits
Maintainer haskell@tryp.io
Category Network
Home page https://github.com/tek/polysemy-http#readme
Bug tracker https://github.com/tek/polysemy-http/issues
Source repo head: git clone https://github.com/tek/polysemy-http
Uploaded by tek at 2021-11-13T23:46:01Z
Distributions
Reverse Dependencies 2 direct, 0 indirect [details]
Downloads 3119 total (52 in the last 30 days)
Rating (no votes yet) [estimated by Bayesian average]
Your Rating
  • λ
  • λ
  • λ
Status Docs uploaded by user
Build status unknown [no reports yet]

Readme for polysemy-http-0.5.0.0

[back to package description]

About

This Haskell library provides a Polysemy effect for running HTTP requests with http-client.

Example

import Polysemy (runM, resourceToIO)
import qualified Polysemy.Http as Http
import Polysemy.Http (interpretHttpNative, interpretLogStdout)

main :: IO ()
main = do
  result <- runM $
    resourceToIO $
    interpretLogStdout $
    interpretHttpNative $
    Http.request (Http.get "hackage.haskell.org" "package/polysemy-http")
  print result

API

Request

The effect constructor Http.request takes an argument of type Polysemy.Http.Data.Request.Request:

data Request =
  Request {
    _method :: Method,
    _host :: Host,
    _port :: Maybe Port,
    _tls :: Tls,
    _path :: Path,
    _headers :: [(HeaderName, HeaderValue)],
    _cookies :: CookieJar,
    _query :: [(QueryKey, Maybe QueryValue)],
    _body :: Body
  }

Most of these fields are just newtypes, except for Method, which is an enum:

data Method =
  Get | Post | ... | Custom Text

It has an IsString instance, so you can just write "GET" or "delete".

All Text newtypes have IsString as well, and they will be converted to CI and ByteString if needed when they are passed to http-client. Body is an LByteString newtype since that is what aeson typically produces. The port field is intended for nonstandard ports – if it is Nothing, the port will be determined from tls.

Response

Http.request returns Either HttpError (Response LByteString), with Polysemy.Http.Data.Response.Response looking like this:

data Response b =
  Response {
    _status :: Status,
    _body :: b,
    _headers :: [Header],
    _cookies :: CookieJar
  }

data Header =
  Header {
    name :: HeaderName,
    value :: HeaderValue
  }

Status is from http-types, because it has some helpful combinators. Its Header is just an alias, so this newtype is provided. The parameter b is intended to allow you to write interpreters that produce Text or something else, for example for [#testing].

Streaming

The higher-order constructor Http.stream opens and closes the request manually and passes the response to a handler function. The function streamResponse provides a simpler interface for this mechanism that runs a loop that passes individual chunks produced by http-client to a callback handler of type ∀ x . StreamEvent r c h x -> Sem r x that should look like this:

handle ::
  StreamEvent Double (IO ByteString) Int a ->
  Sem r a
handle = \case
  StreamEvent.Acquire (Response status body headers) ->
    pure 1
  StreamEvent.Chunk handle (StreamChunk c) ->
    pure ()
  StreamEvent.Result (Response status body headers) handle ->
    pure 5.5
  StreamEvent.Release handle ->
    pure ()

run :: Sem r Double
run =
  Http.streamResponse (Request.get "host.com" "path/to/file") handle

If you were e.g. to write the data to disk, you would open the file in the Acquire block, write the ByteString c in Chunk, and close the file in Release. The parameter h could then be Handle. The callbacks are wrapped in Resource.bracket, so Release is guaranteed to be called (as much as Resource is reliable). The Result block is called when the transfer is complete; its returned value is finally returned from streamHandler. The handle is an arbitrary identifier that the user can return from Acquire; it is not needed for the machinery and may be ().

Entity

The library also provides effects for request and response entity de/encoding, EntityDecode d m a and EntityEncode d m a, making it possible to abstract over json implementations or content types using interpreters. Since the effects are parameterized by the codec data type, one interpreter per type must be used.

Implementations for aeson are available as interpretEntityDecodeAeson and interpretEntityEncodeAeson:

import Polysemy (run)
import qualified Polysemy.Http as Http
import Polysemy.Http (interpretEntityDecodeAeson)

data Dat { a :: Maybe Int, b :: Text }
deriving (Show, FromJSON)

main :: IO
main =
  print $ run $ interpretEntityDecodeAeson $ Http.decode "{ \"b\": \"hello\" }"

There is not integration with the Http effect for this.

Testing

Polysemy makes it very easy to switch the native interpreter for a mock, and there is a convenience interpreter named interpretHttpPure that allows you to specify a list of responses and chunks that should be produced:

main :: IO ()
main = do
  result <- runM $
    resourceToIO $
    interpretLogStdout $
    interpretHttpPure [Response (toEnum 200) "foo" []] [] $
    Http.request (Http.get "hackage.haskell.org" "package/polysemy-http")
  print result