| Safe Haskell | Safe-Inferred |
|---|---|
| Language | Haskell2010 |
Polysemy.Http
Description
Synopsis
- data Http c :: Effect
- response :: forall c r a. Member (Http c) r => Request -> (Response c -> Sem r a) -> Sem r (Either HttpError a)
- request :: forall c r. Member (Http c) r => Request -> Sem r (Either HttpError (Response LByteString))
- interpretHttpNative :: Members [Embed IO, Log, Resource] r => InterpreterFor (Http BodyReader) r
- interpretHttpPure :: Member (Embed IO) r => [Response LByteString] -> [ByteString] -> InterpretersFor [Http LByteString, State [Response LByteString], State [ByteString]] r
- data Method
- newtype Host = Host {}
- newtype Port = Port {}
- newtype Tls = Tls {}
- newtype Path = Path {}
- newtype QueryKey = QueryKey {
- unQueryKey :: Text
- newtype QueryValue = QueryValue {
- unQueryValue :: Text
- data Request = Request Method Host (Maybe Port) Tls Path [(HeaderName, HeaderValue)] CookieJar [(QueryKey, Maybe QueryValue)] Body
- newtype Body = Body {
- unBody :: ByteString
- data Response b = Response Status b [Header] CookieJar
- pattern Server :: Status -> b -> [Header] -> Response b
- pattern Client :: Status -> b -> [Header] -> Response b
- pattern Redirect :: Status -> b -> [Header] -> Response b
- pattern Success :: Status -> b -> [Header] -> Response b
- pattern Info :: Status -> b -> [Header] -> Response b
- newtype HeaderName = HeaderName {
- unHeaderName :: Text
- newtype HeaderValue = HeaderValue {}
- data Header = Header {
- name :: HeaderName
- value :: HeaderValue
- withPort :: Maybe Port -> Tls -> Method -> Host -> Path -> Body -> Request
- withTls :: Tls -> Method -> Host -> Path -> Body -> Request
- simple :: Method -> Host -> Path -> Body -> Request
- get :: Host -> Path -> Request
- post :: Host -> Path -> Body -> Request
- put :: Host -> Path -> Body -> Request
- delete :: Host -> Path -> Request
- fromUrl :: Method -> Body -> Text -> Either Text Request
- getUrl :: Text -> Either Text Request
- postUrl :: Body -> Text -> Either Text Request
- putUrl :: Body -> Text -> Either Text Request
- deleteUrl :: Text -> Either Text Request
- cookie :: Text -> Text -> Text -> Cookie
- addCookies :: [Cookie] -> Request -> Request
- addCookie :: Text -> Text -> Text -> Request -> Request
- data HttpError
- streamResponse :: Members [Http c, Error HttpError, Resource] r => Request -> Maybe Int -> (forall x. StreamEvent o c h x -> Sem r x) -> Sem r o
- data StreamEvent r c h a where
- Acquire :: Response c -> StreamEvent r c h h
- Chunk :: h -> StreamChunk -> StreamEvent r c h ()
- Result :: Response c -> h -> StreamEvent r c h r
- Release :: h -> StreamEvent r c h ()
- data EntityDecode d :: Effect
- decode :: forall d r. Member (EntityDecode d) r => ByteString -> Sem r (Either EntityError d)
- decodeLazy :: forall d r. Member (EntityDecode d) r => LByteString -> Sem r (Either EntityError d)
- decodeStrict :: forall d r. Member (EntityDecode d) r => ByteString -> Sem r (Either EntityError d)
- data EntityEncode d :: Effect
- encode :: forall d r. Member (EntityEncode d) r => d -> Sem r ByteString
- encodeStrict :: forall d r. Member (EntityEncode d) r => d -> Sem r ByteString
- type family Entities es r :: Constraint where ...
- data Decode a
- data Encode a
- type family Decoders ds r :: Constraint where ...
- type family Encoders es r :: Constraint where ...
- data EntityError = EntityError Text Text
- interpretEntityEncodeAesonAs :: ToJSON j => (d -> j) -> Sem (EntityEncode d ': r) a -> Sem r a
- interpretEntityEncodeAeson :: ToJSON d => Sem (EntityEncode d ': r) a -> Sem r a
- interpretEntityDecodeAesonWith :: FromJSON j => (j -> Sem r (Either Text d)) -> Sem (EntityDecode d ': r) a -> Sem r a
- interpretEntityDecodeAesonAs :: FromJSON j => (j -> d) -> Sem (EntityDecode d ': r) a -> Sem r a
- interpretEntityDecodeAeson :: FromJSON d => Sem (EntityDecode d ': r) a -> Sem r a
- data Manager :: Effect
- interpretManager :: Member (Embed IO) r => InterpreterFor Manager r
- jsonRequest :: Member (Http c) r => Request -> Sem r (Either HttpError (Response LByteString))
Documentation
A basic Polysemy effect abstracting HTTP requests:
import Polysemy (resourceToIO, runM)
import 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.
Interpreters
interpretHttpNative :: Members [Embed IO, Log, Resource] r => InterpreterFor (Http BodyReader) r Source #
Interpret using the native Network.HTTP.Client implementation.
Http BodyReaderBodyReader is an alias for ; it is how http-client represents chunks.
This uses the default interpreter for IO ByteStringManager.
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
All standard HTTP methods, mirroring those from Types, plus a constructor for arbitrary strings.
Request host name.
Instances
Request port.
Instances
| FromJSON Port Source # | |
| ToJSON Port Source # | |
Defined in Polysemy.Http.Data.Request | |
| Enum Port Source # | |
| Generic Port Source # | |
| Num Port Source # | |
| Read Port Source # | |
| Integral Port Source # | |
| Real Port Source # | |
Defined in Polysemy.Http.Data.Request Methods toRational :: Port -> Rational # | |
| Show Port Source # | |
| Eq Port Source # | |
| Ord Port Source # | |
| type Rep Port Source # | |
Defined in Polysemy.Http.Data.Request | |
A flag that indicates whether a request should use TLS.
Rrequest path.
Instances
| FromJSON Path Source # | |
| ToJSON Path Source # | |
Defined in Polysemy.Http.Data.Request | |
| IsString Path Source # | |
Defined in Polysemy.Http.Data.Request Methods fromString :: String -> Path # | |
| Monoid Path Source # | |
| Semigroup Path Source # | |
| Generic Path Source # | |
| Show Path Source # | |
| Eq Path Source # | |
| type Rep Path Source # | |
Defined in Polysemy.Http.Data.Request | |
The key of a query parameter.
Constructors
| QueryKey | |
Fields
| |
Instances
| FromJSON QueryKey Source # | |
| ToJSON QueryKey Source # | |
Defined in Polysemy.Http.Data.Request | |
| IsString QueryKey Source # | |
Defined in Polysemy.Http.Data.Request Methods fromString :: String -> QueryKey # | |
| Generic QueryKey Source # | |
| Show QueryKey Source # | |
| Eq QueryKey Source # | |
| type Rep QueryKey Source # | |
Defined in Polysemy.Http.Data.Request | |
newtype QueryValue Source #
The value of a query parameter.
Constructors
| QueryValue | |
Fields
| |
Instances
HTTP request parameters, used by Http.
Constructors
| Request Method Host (Maybe Port) Tls Path [(HeaderName, HeaderValue)] CookieJar [(QueryKey, Maybe QueryValue)] Body |
Instances
Request body.
Constructors
| Body | |
Fields
| |
Instances
| IsString Body Source # | |
Defined in Polysemy.Http.Data.Request Methods fromString :: String -> Body # | |
| Generic Body Source # | |
| Show Body Source # | |
| Eq Body Source # | |
| type Rep Body Source # | |
Defined in Polysemy.Http.Data.Request type Rep Body = D1 ('MetaData "Body" "Polysemy.Http.Data.Request" "polysemy-http-0.11.0.0-KwdjpKcptzS4j0Fq88wQVf" 'True) (C1 ('MetaCons "Body" 'PrefixI 'True) (S1 ('MetaSel ('Just "unBody") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ByteString))) | |
The response produced by Http.
Instances
| Generic (Response b) Source # | |
| Show (Response BodyReader) Source # | |
Defined in Polysemy.Http.Data.Response | |
| Show b => Show (Response b) Source # | |
| Eq b => Eq (Response b) Source # | |
| type Rep (Response b) Source # | |
Defined in Polysemy.Http.Data.Response type Rep (Response b) = D1 ('MetaData "Response" "Polysemy.Http.Data.Response" "polysemy-http-0.11.0.0-KwdjpKcptzS4j0Fq88wQVf" 'False) (C1 ('MetaCons "Response" 'PrefixI 'True) ((S1 ('MetaSel ('Just "status") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Status) :*: S1 ('MetaSel ('Just "body") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 b)) :*: (S1 ('MetaSel ('Just "headers") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Header]) :*: S1 ('MetaSel ('Just "cookies") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 CookieJar)))) | |
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
newtype HeaderValue Source #
The value of a header.
Constructors
| HeaderValue | |
Fields | |
Instances
An HTTP header.
Constructors
| Header | |
Fields
| |
Instances
| FromJSON Header Source # | |
| ToJSON Header Source # | |
Defined in Polysemy.Http.Data.Header | |
| Generic Header Source # | |
| Show Header Source # | |
| Eq Header Source # | |
| type Rep Header Source # | |
Defined in Polysemy.Http.Data.Header type Rep Header = D1 ('MetaData "Header" "Polysemy.Http.Data.Header" "polysemy-http-0.11.0.0-KwdjpKcptzS4j0Fq88wQVf" '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.
addCookie :: Text -> Text -> Text -> Request -> Request Source #
Add a cookie to a request, using default values.
Indicates a critical error caused by an exception in the http-client backend.
Constructors
| ChunkFailed Text | |
| Internal Text |
Streaming
streamResponse :: Members [Http c, Error HttpError, Resource] r => Request -> Maybe Int -> (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.
The optional Int argument defines the minimal chunk size that is read for each callback. If it is Nothing, the
stream reads what is available.
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") handle5.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 => ByteString -> Sem r (Either EntityError d) Source #
Strictly decode a ByteString to a value of type d
decodeLazy :: 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 ByteString Source #
Strictly encode a value of type d to a ByteString
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 ()
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
| Show EntityError Source # | |
Defined in Polysemy.Http.Effect.Entity Methods showsPrec :: Int -> EntityError -> ShowS # show :: EntityError -> String # showList :: [EntityError] -> ShowS # | |
| Eq EntityError Source # | |
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.
interpretEntityDecodeAesonWith :: FromJSON j => (j -> Sem r (Either Text 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 effectful conversion function.
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.