polysemy-http-0.1.0.0: Polysemy effect for http-client
Safe HaskellNone
LanguageHaskell2010

Polysemy.Http

Synopsis

Documentation

A basic Polysemy effect abstracting HTTP requests:

import Polysemy (resourceToIO, runM)
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

data Http c :: Effect Source #

The main effect for HTTP requests. The parameter c determines the representation of raw chunks.

Instances

Instances details
type DefiningModule Http Source # 
Instance details

Defined in Polysemy.Http.Data.Http

type DefiningModule Http = "Polysemy.Http.Data.Http"

request :: forall c r. Member (Http c) r => Request -> Sem r (Either HttpError (Response LByteString)) Source #

Synchronously run an HTTP request and return the response.

stream :: forall c r a. Member (Http c) r => Request -> (Response c -> Sem r (Either HttpError a)) -> Sem r (Either HttpError a) Source #

Open a connection without consuming data and pass the response to a handler for custom transmission. The intended purpose is to allow streaming transfers.

Interpreters

interpretHttpNative :: Members [Embed IO, Log, Resource] r => InterpreterFor (Http BodyReader) r Source #

Interpret Http BodyReader using the native Client implementation. BodyReader is an alias for IO ByteString, it is how http-client represents chunks. This uses the default interpreter for Manager.

interpretHttpStrict :: Members [Embed IO, Error HttpError] r => [Response LByteString] -> [ByteString] -> InterpreterFor (Http Int) r Source #

In-Memory interpreter for Http. The first parameter is a list of Response. When a request is made, one response is popped of the head and returned. If the list is exhausted, a 502 response is returned.

Request and Response

data Request Source #

HTTP request parameters, used by Http.

Instances

Instances details
Eq Request Source # 
Instance details

Defined in Polysemy.Http.Data.Request

Methods

(==) :: Request -> Request -> Bool #

(/=) :: Request -> Request -> Bool #

Show Request Source # 
Instance details

Defined in Polysemy.Http.Data.Request

HasRequest Request Source # 
Instance details

Defined in Polysemy.Http.Data.Request

newtype Body Source #

Request body, using LByteString because it is what encode produces.

Constructors

Body LByteString 

Instances

Instances details
Eq Body Source # 
Instance details

Defined in Polysemy.Http.Data.Request

Methods

(==) :: Body -> Body -> Bool #

(/=) :: Body -> Body -> Bool #

Show Body Source # 
Instance details

Defined in Polysemy.Http.Data.Request

Methods

showsPrec :: Int -> Body -> ShowS #

show :: Body -> String #

showList :: [Body] -> ShowS #

IsString Body Source # 
Instance details

Defined in Polysemy.Http.Data.Request

Methods

fromString :: String -> Body #

newtype QueryValue Source #

The value of a query parameter.

Constructors

QueryValue Text 

Instances

Instances details
Eq QueryValue Source # 
Instance details

Defined in Polysemy.Http.Data.Request

Show QueryValue Source # 
Instance details

Defined in Polysemy.Http.Data.Request

IsString QueryValue Source # 
Instance details

Defined in Polysemy.Http.Data.Request

newtype QueryKey Source #

The key of a query parameter.

Constructors

QueryKey Text 

Instances

Instances details
Eq QueryKey Source # 
Instance details

Defined in Polysemy.Http.Data.Request

Show QueryKey Source # 
Instance details

Defined in Polysemy.Http.Data.Request

IsString QueryKey Source # 
Instance details

Defined in Polysemy.Http.Data.Request

newtype Path Source #

Rrequest path.

Constructors

Path Text 

Instances

Instances details
Eq Path Source # 
Instance details

Defined in Polysemy.Http.Data.Request

Methods

(==) :: Path -> Path -> Bool #

(/=) :: Path -> Path -> Bool #

Show Path Source # 
Instance details

Defined in Polysemy.Http.Data.Request

Methods

showsPrec :: Int -> Path -> ShowS #

show :: Path -> String #

showList :: [Path] -> ShowS #

IsString Path Source # 
Instance details

Defined in Polysemy.Http.Data.Request

Methods

fromString :: String -> Path #

newtype Tls Source #

A flag that indicates whether a request should use TLS.

Constructors

Tls Bool 

Instances

Instances details
Eq Tls Source # 
Instance details

Defined in Polysemy.Http.Data.Request

Methods

(==) :: Tls -> Tls -> Bool #

(/=) :: Tls -> Tls -> Bool #

Show Tls Source # 
Instance details

Defined in Polysemy.Http.Data.Request

Methods

showsPrec :: Int -> Tls -> ShowS #

show :: Tls -> String #

showList :: [Tls] -> ShowS #

newtype Port Source #

Request port.

Constructors

Port Int 

Instances

Instances details
Eq Port Source # 
Instance details

Defined in Polysemy.Http.Data.Request

Methods

(==) :: Port -> Port -> Bool #

(/=) :: Port -> Port -> Bool #

Show Port Source # 
Instance details

Defined in Polysemy.Http.Data.Request

Methods

showsPrec :: Int -> Port -> ShowS #

show :: Port -> String #

showList :: [Port] -> ShowS #

newtype Host Source #

Request host name.

Constructors

Host Text 

Instances

Instances details
Eq Host Source # 
Instance details

Defined in Polysemy.Http.Data.Request

Methods

(==) :: Host -> Host -> Bool #

(/=) :: Host -> Host -> Bool #

Show Host Source # 
Instance details

Defined in Polysemy.Http.Data.Request

Methods

showsPrec :: Int -> Host -> ShowS #

show :: Host -> String #

showList :: [Host] -> ShowS #

IsString Host Source # 
Instance details

Defined in Polysemy.Http.Data.Request

Methods

fromString :: String -> Host #

data Method Source #

All standard HTTP methods, mirroring those from Types, plus a constructor for arbitrary strings.

Instances

Instances details
Eq Method Source # 
Instance details

Defined in Polysemy.Http.Data.Request

Methods

(==) :: Method -> Method -> Bool #

(/=) :: Method -> Method -> Bool #

Show Method Source # 
Instance details

Defined in Polysemy.Http.Data.Request

IsString Method Source # 
Instance details

Defined in Polysemy.Http.Data.Request

Methods

fromString :: String -> Method #

data Response b Source #

The response produced by Http.

Constructors

Response 

Fields

  • status :: Status

    Uses the type from HTTP for convenience

  • body :: b

    parameterized in the body to allow different interpreters to use other representations.

  • headers :: [Header]

    Does not use the type from HTTP because it is an alias.

Instances

Instances details
Eq b => Eq (Response b) Source # 
Instance details

Defined in Polysemy.Http.Data.Response

Methods

(==) :: Response b -> Response b -> Bool #

(/=) :: Response b -> Response b -> Bool #

Show b => Show (Response b) Source # 
Instance details

Defined in Polysemy.Http.Data.Response

Methods

showsPrec :: Int -> Response b -> ShowS #

show :: Response b -> String #

showList :: [Response b] -> ShowS #

Show (Response BodyReader) Source # 
Instance details

Defined in Polysemy.Http.Data.Response

Methods

showsPrec :: Int -> Response BodyReader -> ShowS #

show :: Response BodyReader -> String #

showList :: [Response BodyReader] -> ShowS #

pattern Server :: Status -> b -> [Header] -> Response b Source #

Match on a response with a 5xx status.

pattern Client :: Status -> b -> [Header] -> Response b Source #

Match on a response with a 4xx status.

pattern Redirect :: Status -> b -> [Header] -> Response b Source #

Match on a response with a 3xx status.

pattern Success :: Status -> b -> [Header] -> Response b Source #

Match on a response with a 2xx status.

pattern Info :: Status -> b -> [Header] -> Response b Source #

Match on a response with a 1xx status.

data Header Source #

An HTTP header.

Instances

Instances details
Eq Header Source # 
Instance details

Defined in Polysemy.Http.Data.Header

Methods

(==) :: Header -> Header -> Bool #

(/=) :: Header -> Header -> Bool #

Show Header Source # 
Instance details

Defined in Polysemy.Http.Data.Header

newtype HeaderValue Source #

The value of a header.

Constructors

HeaderValue Text 

Instances

Instances details
Eq HeaderValue Source # 
Instance details

Defined in Polysemy.Http.Data.Header

Show HeaderValue Source # 
Instance details

Defined in Polysemy.Http.Data.Header

IsString HeaderValue Source # 
Instance details

Defined in Polysemy.Http.Data.Header

newtype HeaderName Source #

The name of a header.

Constructors

HeaderName Text 

Instances

Instances details
Eq HeaderName Source # 
Instance details

Defined in Polysemy.Http.Data.Header

Show HeaderName Source # 
Instance details

Defined in Polysemy.Http.Data.Header

IsString HeaderName Source # 
Instance details

Defined in Polysemy.Http.Data.Header

Streaming

streamResponse :: Members [Http c, Error HttpError, Resource] r => Request -> (forall x. StreamEvent o c h x -> Sem r x) -> Sem r o Source #

Initiate a request and stream the response, calling process after connecting, for every chunk, after closing the connection, and for the return value. StreamEvent is used to indicate the stage of the request cycle.

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 ()
>>> runInterpreters $ streamResponse (Http.get "host.com" "path/to/file") handle
5.5

data StreamEvent r c h a where Source #

Control algebra for streaming requests. r is the final return type of the stream handler, after the request is processed to completion. c is the raw chunk data type h is the handle type that identifies the active request. It is entirely controlled by the consumer and may be empty.

Constructors

Acquire :: Response c -> StreamEvent r c h h

Used when calling the handler after the request has been initiated, but no data has been read.

Chunk :: h -> StreamChunk -> StreamEvent r c h ()

Used when calling the handler for each received chunk.

Result :: Response c -> h -> StreamEvent r c h r

Used when calling the handler after the request has finished transferring. It should return the final result.

Release :: h -> StreamEvent r c h ()

Used to finalize the transfer, e.g. for resource cleanup.

Entity

data EntityDecode d :: Effect Source #

Abstraction of json decoding, potentially usable for other content types like xml.

Instances

Instances details
type DefiningModule EntityDecode Source # 
Instance details

Defined in Polysemy.Http.Data.Entity

type DefiningModule EntityDecode = "Polysemy.Http.Data.Entity"

decode :: forall d r. Member (EntityDecode d) r => LByteString -> Sem r (Either EntityError d) Source #

Lazily decode a LByteString to a value of type d

decodeStrict :: forall d r. Member (EntityDecode d) r => ByteString -> Sem r (Either EntityError d) Source #

Strictly decode a ByteString to a value of type d

data EntityEncode d :: Effect Source #

Abstraction of json encoding, potentially usable for other content types like xml.

Instances

Instances details
type DefiningModule EntityEncode Source # 
Instance details

Defined in Polysemy.Http.Data.Entity

type DefiningModule EntityEncode = "Polysemy.Http.Data.Entity"

encode :: forall d r. Member (EntityEncode d) r => d -> Sem r LByteString Source #

Lazily encode a value of type d to a LByteString

encodeStrict :: forall d r. Member (EntityEncode d) r => d -> Sem r ByteString Source #

Strictly encode a value of type d to a ByteString

type family Entities es r :: Constraint where ... Source #

Convenience constraint for requiring multiple entity effects, to be used like Members.

foo :: Entities [Encode Int, Decode Double] r => Sem r ()

Equations

Entities '[] r = () 
Entities (Encode d ': ds) r = (Member (EntityEncode d) r, Entities ds r) 
Entities (Decode d ': ds) r = (Member (EntityDecode d) r, Entities ds r) 

data Decode a Source #

Marker type to be used with Entities

data Encode a Source #

Marker type to be used with Entities

type family Decoders ds r :: Constraint where ... Source #

Convenience constraint for requiring multiple decoders.

foo :: Decoders [Int, Double] r => Sem r ()

Equations

Decoders '[] r = () 
Decoders (d ': ds) r = (Member (EntityDecode d) r, Decoders ds r) 

type family Encoders es r :: Constraint where ... Source #

Convenience constraint for requiring multiple encoders.

foo :: Encoders [Int, Double] r => Sem r ()

Equations

Encoders '[] r = () 
Encoders (d ': ds) r = (Member (EntityEncode d) r, Encoders ds r) 

data EntityError Source #

Generic error type for decoders.

Constructors

EntityError Text Text 

Instances

Instances details
Eq EntityError Source # 
Instance details

Defined in Polysemy.Http.Data.Entity

Show EntityError Source # 
Instance details

Defined in Polysemy.Http.Data.Entity

interpretEntityEncodeAeson :: ToJSON d => Sem (EntityEncode d ': r) a -> Sem r a Source #

Interpreter for EntityEncode that uses Aeson.

interpretEntityDecodeAeson :: FromJSON d => Sem (EntityDecode d ': r) a -> Sem r a Source #

Interpreter for EntityDecode that uses Aeson.

Utilities

Connection Pool

data Manager :: Effect Source #

This effect abstracts the creation of a Manager in order to allow pool sharing in a flexible way.

Instances

Instances details
type DefiningModule Manager Source # 
Instance details

Defined in Polysemy.Http.Data.Manager

type DefiningModule Manager = "Polysemy.Http.Data.Manager"

Logging

data Log :: Effect Source #

An effect that wraps Log for less boilerplate. Constructors are manual because HasCallStack is always in scope.

interpretLogNull :: InterpreterFor Log r Source #

No-op interpreter for Log

interpretLogStdout :: Member (Embed IO) r => Sem (Log ': r) a -> Sem r a Source #

Default interpreter for Log that uses Log to print to stdout