| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Polysemy.Http
Synopsis
- data Http c :: Effect
- request :: forall c r. Member (Http c) r => Request -> Sem r (Either HttpError (Response LByteString))
- stream :: forall c r a. Member (Http c) r => Request -> (Response c -> Sem r (Either HttpError a)) -> Sem r (Either HttpError a)
- interpretHttpNative :: Members [Embed IO, Log, Resource] r => InterpreterFor (Http BodyReader) r
- interpretHttpStrict :: Members [Embed IO, Error HttpError] r => [Response LByteString] -> [ByteString] -> InterpreterFor (Http Int) r
- data Request = Request {}
- newtype Body = Body LByteString
- newtype QueryValue = QueryValue Text
- newtype QueryKey = QueryKey Text
- newtype Path = Path Text
- newtype Tls = Tls Bool
- newtype Port = Port Int
- newtype Host = Host Text
- data Method
- data Response b = Response {}
- 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
- data Header = Header HeaderName HeaderValue
- newtype HeaderValue = HeaderValue Text
- newtype HeaderName = HeaderName Text
- get :: Host -> Path -> Request
- post :: Host -> Path -> Body -> Request
- put :: Host -> Path -> Body -> Request
- delete :: Host -> Path -> Request
- getUrl :: Text -> Either Text Request
- postUrl :: Body -> Text -> Either Text Request
- putUrl :: Body -> Text -> Either Text Request
- deleteUrl :: Text -> Either Text Request
- streamResponse :: Members [Http c, Error HttpError, Resource] r => Request -> (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 => 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 LByteString
- 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
- interpretEntityEncodeAeson :: ToJSON d => Sem (EntityEncode d ': r) a -> Sem r a
- interpretEntityDecodeAeson :: FromJSON d => Sem (EntityDecode d ': r) a -> Sem r a
- data Manager :: Effect
- data Log :: Effect
- interpretLogNull :: InterpreterFor Log r
- interpretLogStdout :: Member (Embed IO) r => Sem (Log ': r) a -> Sem r a
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
| type DefiningModule Http Source # | |
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 using the native Http BodyReaderClient implementation.
BodyReader is an alias for , it is how http-client represents chunks.
This uses the default interpreter for IO ByteStringManager.
interpretHttpStrict :: Members [Embed IO, Error HttpError] r => [Response LByteString] -> [ByteString] -> InterpreterFor (Http Int) r Source #
Request and Response
HTTP request parameters, used by Http.
Constructors
| Request | |
Instances
| Eq Request Source # | |
| Show Request Source # | |
| HasRequest Request Source # | |
Defined in Polysemy.Http.Data.Request Methods request :: Lens' Request Request Source # body :: Lens' Request Body Source # headers :: Lens' Request [(HeaderName, HeaderValue)] Source # host :: Lens' Request Host Source # method :: Lens' Request Method Source # path :: Lens' Request Path Source # port :: Lens' Request (Maybe Port) Source # query :: Lens' Request [(QueryKey, Maybe QueryValue)] Source # | |
Request body, using LByteString because it is what encode produces.
Constructors
| Body LByteString |
newtype QueryValue Source #
The value of a query parameter.
Constructors
| QueryValue Text |
Instances
| Eq QueryValue Source # | |
Defined in Polysemy.Http.Data.Request | |
| Show QueryValue Source # | |
Defined in Polysemy.Http.Data.Request Methods showsPrec :: Int -> QueryValue -> ShowS # show :: QueryValue -> String # showList :: [QueryValue] -> ShowS # | |
| IsString QueryValue Source # | |
Defined in Polysemy.Http.Data.Request Methods fromString :: String -> QueryValue # | |
The key of a query parameter.
Rrequest path.
A flag that indicates whether a request should use TLS.
Request port.
Request host name.
All standard HTTP methods, mirroring those from Types, plus a constructor for arbitrary strings.
The response produced by Http.
Constructors
| Response | |
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 HeaderValue Source #
The value of a header.
Constructors
| HeaderValue Text |
Instances
| Eq HeaderValue Source # | |
Defined in Polysemy.Http.Data.Header | |
| Show HeaderValue Source # | |
Defined in Polysemy.Http.Data.Header Methods showsPrec :: Int -> HeaderValue -> ShowS # show :: HeaderValue -> String # showList :: [HeaderValue] -> ShowS # | |
| IsString HeaderValue Source # | |
Defined in Polysemy.Http.Data.Header Methods fromString :: String -> HeaderValue # | |
newtype HeaderName Source #
The name of a header.
Constructors
| HeaderName Text |
Instances
| Eq HeaderName Source # | |
Defined in Polysemy.Http.Data.Header | |
| Show HeaderName Source # | |
Defined in Polysemy.Http.Data.Header Methods showsPrec :: Int -> HeaderName -> ShowS # show :: HeaderName -> String # showList :: [HeaderName] -> ShowS # | |
| IsString HeaderName Source # | |
Defined in Polysemy.Http.Data.Header Methods fromString :: String -> HeaderName # | |
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") 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.
Instances
| type DefiningModule EntityDecode Source # | |
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
| type DefiningModule EntityEncode Source # | |
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 ()
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
| Eq EntityError Source # | |
Defined in Polysemy.Http.Data.Entity | |
| Show EntityError Source # | |
Defined in Polysemy.Http.Data.Entity Methods showsPrec :: Int -> EntityError -> ShowS # show :: EntityError -> String # showList :: [EntityError] -> ShowS # | |
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
| type DefiningModule Manager Source # | |
Defined in Polysemy.Http.Data.Manager type DefiningModule Manager = "Polysemy.Http.Data.Manager" | |
Logging
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