polysemy-http-0.7.0.0: Polysemy Effects for HTTP clients
Safe HaskellSafe-Inferred
LanguageHaskell2010

Polysemy.Http

Description

 
Synopsis

Documentation

A basic Polysemy effect abstracting HTTP requests:

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

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

Bracket a higher-order action with a Response that has been opened while its body hasn't been fetched.

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 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 Network.HTTP.Client implementation. BodyReader is an alias for IO ByteString; it is how http-client represents chunks. This uses the default interpreter for Manager.

interpretHttpPure Source #

Arguments

:: Member (Embed IO) r 
=> [Response LByteString]

When a request is made, one response is popped of the list and returned. If the list is exhausted, a 502 response is returned.

-> [ByteString]

Chunks used for streaming responses.

-> InterpretersFor [Http LByteString, State [Response LByteString], State [ByteString]] r 

In-Memory interpreter for Http.

Request and Response

data Method Source #

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

Instances

Instances details
FromJSON Method Source # 
Instance details

Defined in Polysemy.Http.Data.Request

ToJSON 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 #

Show Method Source # 
Instance details

Defined in Polysemy.Http.Data.Request

Eq Method Source # 
Instance details

Defined in Polysemy.Http.Data.Request

Methods

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

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

newtype Host Source #

Request host name.

Constructors

Host 

Fields

Instances

Instances details
FromJSON Host Source # 
Instance details

Defined in Polysemy.Http.Data.Request

ToJSON Host Source # 
Instance details

Defined in Polysemy.Http.Data.Request

IsString Host Source # 
Instance details

Defined in Polysemy.Http.Data.Request

Methods

fromString :: String -> Host #

Generic Host Source # 
Instance details

Defined in Polysemy.Http.Data.Request

Associated Types

type Rep Host :: Type -> Type #

Methods

from :: Host -> Rep Host x #

to :: Rep Host x -> Host #

Show Host Source # 
Instance details

Defined in Polysemy.Http.Data.Request

Methods

showsPrec :: Int -> Host -> ShowS #

show :: Host -> String #

showList :: [Host] -> ShowS #

Eq Host Source # 
Instance details

Defined in Polysemy.Http.Data.Request

Methods

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

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

type Rep Host Source # 
Instance details

Defined in Polysemy.Http.Data.Request

type Rep Host = D1 ('MetaData "Host" "Polysemy.Http.Data.Request" "polysemy-http-0.7.0.0-Fk2hH8oZ1SSB7dsjKCi0Cu" 'True) (C1 ('MetaCons "Host" 'PrefixI 'True) (S1 ('MetaSel ('Just "unHost") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)))

newtype Port Source #

Request port.

Constructors

Port 

Fields

Instances

Instances details
FromJSON Port Source # 
Instance details

Defined in Polysemy.Http.Data.Request

ToJSON Port Source # 
Instance details

Defined in Polysemy.Http.Data.Request

Enum Port Source # 
Instance details

Defined in Polysemy.Http.Data.Request

Methods

succ :: Port -> Port #

pred :: Port -> Port #

toEnum :: Int -> Port #

fromEnum :: Port -> Int #

enumFrom :: Port -> [Port] #

enumFromThen :: Port -> Port -> [Port] #

enumFromTo :: Port -> Port -> [Port] #

enumFromThenTo :: Port -> Port -> Port -> [Port] #

Generic Port Source # 
Instance details

Defined in Polysemy.Http.Data.Request

Associated Types

type Rep Port :: Type -> Type #

Methods

from :: Port -> Rep Port x #

to :: Rep Port x -> Port #

Num Port Source # 
Instance details

Defined in Polysemy.Http.Data.Request

Methods

(+) :: Port -> Port -> Port #

(-) :: Port -> Port -> Port #

(*) :: Port -> Port -> Port #

negate :: Port -> Port #

abs :: Port -> Port #

signum :: Port -> Port #

fromInteger :: Integer -> Port #

Read Port Source # 
Instance details

Defined in Polysemy.Http.Data.Request

Integral Port Source # 
Instance details

Defined in Polysemy.Http.Data.Request

Methods

quot :: Port -> Port -> Port #

rem :: Port -> Port -> Port #

div :: Port -> Port -> Port #

mod :: Port -> Port -> Port #

quotRem :: Port -> Port -> (Port, Port) #

divMod :: Port -> Port -> (Port, Port) #

toInteger :: Port -> Integer #

Real Port Source # 
Instance details

Defined in Polysemy.Http.Data.Request

Methods

toRational :: Port -> Rational #

Show Port Source # 
Instance details

Defined in Polysemy.Http.Data.Request

Methods

showsPrec :: Int -> Port -> ShowS #

show :: Port -> String #

showList :: [Port] -> ShowS #

Eq Port Source # 
Instance details

Defined in Polysemy.Http.Data.Request

Methods

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

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

Ord Port Source # 
Instance details

Defined in Polysemy.Http.Data.Request

Methods

compare :: Port -> Port -> Ordering #

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

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

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

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

max :: Port -> Port -> Port #

min :: Port -> Port -> Port #

type Rep Port Source # 
Instance details

Defined in Polysemy.Http.Data.Request

type Rep Port = D1 ('MetaData "Port" "Polysemy.Http.Data.Request" "polysemy-http-0.7.0.0-Fk2hH8oZ1SSB7dsjKCi0Cu" 'True) (C1 ('MetaCons "Port" 'PrefixI 'True) (S1 ('MetaSel ('Just "unPort") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int)))

newtype Tls Source #

A flag that indicates whether a request should use TLS.

Constructors

Tls 

Fields

Instances

Instances details
FromJSON Tls Source # 
Instance details

Defined in Polysemy.Http.Data.Request

ToJSON Tls Source # 
Instance details

Defined in Polysemy.Http.Data.Request

Generic Tls Source # 
Instance details

Defined in Polysemy.Http.Data.Request

Associated Types

type Rep Tls :: Type -> Type #

Methods

from :: Tls -> Rep Tls x #

to :: Rep Tls x -> Tls #

Show Tls Source # 
Instance details

Defined in Polysemy.Http.Data.Request

Methods

showsPrec :: Int -> Tls -> ShowS #

show :: Tls -> String #

showList :: [Tls] -> ShowS #

Eq Tls Source # 
Instance details

Defined in Polysemy.Http.Data.Request

Methods

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

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

type Rep Tls Source # 
Instance details

Defined in Polysemy.Http.Data.Request

type Rep Tls = D1 ('MetaData "Tls" "Polysemy.Http.Data.Request" "polysemy-http-0.7.0.0-Fk2hH8oZ1SSB7dsjKCi0Cu" 'True) (C1 ('MetaCons "Tls" 'PrefixI 'True) (S1 ('MetaSel ('Just "unTls") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool)))

newtype Path Source #

Rrequest path.

Constructors

Path 

Fields

Instances

Instances details
FromJSON Path Source # 
Instance details

Defined in Polysemy.Http.Data.Request

ToJSON Path Source # 
Instance details

Defined in Polysemy.Http.Data.Request

IsString Path Source # 
Instance details

Defined in Polysemy.Http.Data.Request

Methods

fromString :: String -> Path #

Monoid Path Source # 
Instance details

Defined in Polysemy.Http.Data.Request

Methods

mempty :: Path #

mappend :: Path -> Path -> Path #

mconcat :: [Path] -> Path #

Semigroup Path Source # 
Instance details

Defined in Polysemy.Http.Data.Request

Methods

(<>) :: Path -> Path -> Path #

sconcat :: NonEmpty Path -> Path #

stimes :: Integral b => b -> Path -> Path #

Generic Path Source # 
Instance details

Defined in Polysemy.Http.Data.Request

Associated Types

type Rep Path :: Type -> Type #

Methods

from :: Path -> Rep Path x #

to :: Rep Path x -> Path #

Show Path Source # 
Instance details

Defined in Polysemy.Http.Data.Request

Methods

showsPrec :: Int -> Path -> ShowS #

show :: Path -> String #

showList :: [Path] -> ShowS #

Eq Path Source # 
Instance details

Defined in Polysemy.Http.Data.Request

Methods

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

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

type Rep Path Source # 
Instance details

Defined in Polysemy.Http.Data.Request

type Rep Path = D1 ('MetaData "Path" "Polysemy.Http.Data.Request" "polysemy-http-0.7.0.0-Fk2hH8oZ1SSB7dsjKCi0Cu" 'True) (C1 ('MetaCons "Path" 'PrefixI 'True) (S1 ('MetaSel ('Just "unPath") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)))

newtype QueryKey Source #

The key of a query parameter.

Constructors

QueryKey 

Fields

Instances

Instances details
FromJSON QueryKey Source # 
Instance details

Defined in Polysemy.Http.Data.Request

ToJSON QueryKey Source # 
Instance details

Defined in Polysemy.Http.Data.Request

IsString QueryKey Source # 
Instance details

Defined in Polysemy.Http.Data.Request

Generic QueryKey Source # 
Instance details

Defined in Polysemy.Http.Data.Request

Associated Types

type Rep QueryKey :: Type -> Type #

Methods

from :: QueryKey -> Rep QueryKey x #

to :: Rep QueryKey x -> QueryKey #

Show QueryKey Source # 
Instance details

Defined in Polysemy.Http.Data.Request

Eq QueryKey Source # 
Instance details

Defined in Polysemy.Http.Data.Request

type Rep QueryKey Source # 
Instance details

Defined in Polysemy.Http.Data.Request

type Rep QueryKey = D1 ('MetaData "QueryKey" "Polysemy.Http.Data.Request" "polysemy-http-0.7.0.0-Fk2hH8oZ1SSB7dsjKCi0Cu" 'True) (C1 ('MetaCons "QueryKey" 'PrefixI 'True) (S1 ('MetaSel ('Just "unQueryKey") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)))

newtype QueryValue Source #

The value of a query parameter.

Constructors

QueryValue 

Fields

Instances

Instances details
FromJSON QueryValue Source # 
Instance details

Defined in Polysemy.Http.Data.Request

ToJSON QueryValue Source # 
Instance details

Defined in Polysemy.Http.Data.Request

IsString QueryValue Source # 
Instance details

Defined in Polysemy.Http.Data.Request

Generic QueryValue Source # 
Instance details

Defined in Polysemy.Http.Data.Request

Associated Types

type Rep QueryValue :: Type -> Type #

Show QueryValue Source # 
Instance details

Defined in Polysemy.Http.Data.Request

Eq QueryValue Source # 
Instance details

Defined in Polysemy.Http.Data.Request

type Rep QueryValue Source # 
Instance details

Defined in Polysemy.Http.Data.Request

type Rep QueryValue = D1 ('MetaData "QueryValue" "Polysemy.Http.Data.Request" "polysemy-http-0.7.0.0-Fk2hH8oZ1SSB7dsjKCi0Cu" 'True) (C1 ('MetaCons "QueryValue" 'PrefixI 'True) (S1 ('MetaSel ('Just "unQueryValue") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)))

data Request Source #

HTTP request parameters, used by Http.

Instances

Instances details
Generic Request Source # 
Instance details

Defined in Polysemy.Http.Data.Request

Associated Types

type Rep Request :: Type -> Type #

Methods

from :: Request -> Rep Request x #

to :: Rep Request x -> Request #

Show Request Source # 
Instance details

Defined in Polysemy.Http.Data.Request

Eq Request Source # 
Instance details

Defined in Polysemy.Http.Data.Request

Methods

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

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

HasRequest Request Source # 
Instance details

Defined in Polysemy.Http.Data.Request

type Rep 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 

Fields

Instances

Instances details
IsString Body Source # 
Instance details

Defined in Polysemy.Http.Data.Request

Methods

fromString :: String -> Body #

Generic Body Source # 
Instance details

Defined in Polysemy.Http.Data.Request

Associated Types

type Rep Body :: Type -> Type #

Methods

from :: Body -> Rep Body x #

to :: Rep Body x -> Body #

Show Body Source # 
Instance details

Defined in Polysemy.Http.Data.Request

Methods

showsPrec :: Int -> Body -> ShowS #

show :: Body -> String #

showList :: [Body] -> ShowS #

Eq Body Source # 
Instance details

Defined in Polysemy.Http.Data.Request

Methods

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

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

type Rep Body Source # 
Instance details

Defined in Polysemy.Http.Data.Request

type Rep Body = D1 ('MetaData "Body" "Polysemy.Http.Data.Request" "polysemy-http-0.7.0.0-Fk2hH8oZ1SSB7dsjKCi0Cu" 'True) (C1 ('MetaCons "Body" 'PrefixI 'True) (S1 ('MetaSel ('Just "unBody") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 LByteString)))

data Response b Source #

The response produced by Http.

Constructors

Response Status b [Header] CookieJar 

Instances

Instances details
Show (Response BodyReader) Source # 
Instance details

Defined in Polysemy.Http.Data.Response

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 #

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 #

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.

newtype HeaderName Source #

The name of a header.

Constructors

HeaderName 

Fields

Instances

Instances details
FromJSON HeaderName Source # 
Instance details

Defined in Polysemy.Http.Data.Header

ToJSON HeaderName Source # 
Instance details

Defined in Polysemy.Http.Data.Header

IsString HeaderName Source # 
Instance details

Defined in Polysemy.Http.Data.Header

Generic HeaderName Source # 
Instance details

Defined in Polysemy.Http.Data.Header

Associated Types

type Rep HeaderName :: Type -> Type #

Show HeaderName Source # 
Instance details

Defined in Polysemy.Http.Data.Header

Eq HeaderName Source # 
Instance details

Defined in Polysemy.Http.Data.Header

type Rep HeaderName Source # 
Instance details

Defined in Polysemy.Http.Data.Header

type Rep HeaderName = D1 ('MetaData "HeaderName" "Polysemy.Http.Data.Header" "polysemy-http-0.7.0.0-Fk2hH8oZ1SSB7dsjKCi0Cu" 'True) (C1 ('MetaCons "HeaderName" 'PrefixI 'True) (S1 ('MetaSel ('Just "unHeaderName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)))

newtype HeaderValue Source #

The value of a header.

Constructors

HeaderValue 

Fields

Instances

Instances details
FromJSON HeaderValue Source # 
Instance details

Defined in Polysemy.Http.Data.Header

ToJSON HeaderValue Source # 
Instance details

Defined in Polysemy.Http.Data.Header

IsString HeaderValue Source # 
Instance details

Defined in Polysemy.Http.Data.Header

Generic HeaderValue Source # 
Instance details

Defined in Polysemy.Http.Data.Header

Associated Types

type Rep HeaderValue :: Type -> Type #

Show HeaderValue Source # 
Instance details

Defined in Polysemy.Http.Data.Header

Eq HeaderValue Source # 
Instance details

Defined in Polysemy.Http.Data.Header

type Rep HeaderValue Source # 
Instance details

Defined in Polysemy.Http.Data.Header

type Rep HeaderValue = D1 ('MetaData "HeaderValue" "Polysemy.Http.Data.Header" "polysemy-http-0.7.0.0-Fk2hH8oZ1SSB7dsjKCi0Cu" 'True) (C1 ('MetaCons "HeaderValue" 'PrefixI 'True) (S1 ('MetaSel ('Just "unHeaderValue") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)))

data Header Source #

An HTTP header.

Constructors

Header 

Instances

Instances details
FromJSON Header Source # 
Instance details

Defined in Polysemy.Http.Data.Header

ToJSON Header Source # 
Instance details

Defined in Polysemy.Http.Data.Header

Generic Header Source # 
Instance details

Defined in Polysemy.Http.Data.Header

Associated Types

type Rep Header :: Type -> Type #

Methods

from :: Header -> Rep Header x #

to :: Rep Header x -> Header #

Show Header Source # 
Instance details

Defined in Polysemy.Http.Data.Header

Eq Header Source # 
Instance details

Defined in Polysemy.Http.Data.Header

Methods

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

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

type Rep Header Source # 
Instance details

Defined in Polysemy.Http.Data.Header

type Rep Header = D1 ('MetaData "Header" "Polysemy.Http.Data.Header" "polysemy-http-0.7.0.0-Fk2hH8oZ1SSB7dsjKCi0Cu" 'False) (C1 ('MetaCons "Header" 'PrefixI 'True) (S1 ('MetaSel ('Just "name") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 HeaderName) :*: S1 ('MetaSel ('Just "value") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 HeaderValue)))

withPort :: Maybe Port -> Tls -> Method -> Host -> Path -> Body -> Request Source #

Create a request with empty headers, query and cookies.

withTls :: Tls -> Method -> Host -> Path -> Body -> Request Source #

Create a request with default port and empty headers, query and cookies.

simple :: Method -> Host -> Path -> Body -> Request Source #

Create a TLS request with default port and empty headers, query and cookies.

get :: Host -> Path -> Request Source #

Create a TLS GET request with default port and empty headers, query and cookies.

post :: Host -> Path -> Body -> Request Source #

Create a TLS POST request with default port and empty headers, query and cookies.

put :: Host -> Path -> Body -> Request Source #

Create a TLS PUT request with default port and empty headers, query and cookies.

delete :: Host -> Path -> Request Source #

Create a TLS DELETE request with default port and empty headers, query and cookies.

fromUrl :: Method -> Body -> Text -> Either Text Request Source #

Parse the URL and create a request or return a parse error.

getUrl :: Text -> Either Text Request Source #

Parse URL for a GET.

postUrl :: Body -> Text -> Either Text Request Source #

Parse URL for a POST.

putUrl :: Body -> Text -> Either Text Request Source #

Parse URL for a PUT.

deleteUrl :: Text -> Either Text Request Source #

Parse URL for a DELETE.

cookie :: Text -> Text -> Text -> Cookie Source #

Create a cookie with default values.

addCookies :: [Cookie] -> Request -> Request Source #

Add multiple cookies to a request.

addCookie :: Text -> Text -> Text -> Request -> Request Source #

Add a cookie to a request, using default values.

data HttpError Source #

Indicates a critical error caused by an exception in the http-client backend.

Constructors

ChunkFailed Text 
Internal Text 

Instances

Instances details
Show HttpError Source # 
Instance details

Defined in Polysemy.Http.Data.HttpError

Eq HttpError Source # 
Instance details

Defined in Polysemy.Http.Data.HttpError

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.

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.

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
Show EntityError Source # 
Instance details

Defined in Polysemy.Http.Effect.Entity

Eq EntityError Source # 
Instance details

Defined in Polysemy.Http.Effect.Entity

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

Interpreter for EntityEncode that uses Aeson and a different codec type. The first parameter is the conversion function.

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

Interpreter for EntityEncode that uses Aeson.

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

Interpreter for EntityDecode that uses Aeson and a different codec type. The first parameter is the conversion function.

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.

interpretManager :: Member (Embed IO) r => InterpreterFor Manager r Source #

Trivial interpreter with a globally shared Manager instance.

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

Make a request, setting the content-type header to application/json