{-# options_haddock prune #-}
module Polysemy.Http.Http where
import qualified Data.ByteString as ByteString
import Polysemy.Http.Data.HttpError (HttpError)
import Polysemy.Http.Data.Request (Request)
import Polysemy.Http.Data.Response (Response (Response))
import Polysemy.Http.Data.StreamChunk (StreamChunk (StreamChunk))
import qualified Polysemy.Http.Data.StreamEvent as StreamEvent
import Polysemy.Http.Data.StreamEvent (StreamEvent)
import qualified Polysemy.Http.Effect.Http as Http
import Polysemy.Http.Effect.Http (Http)
streamLoop ::
Members [Http c, Error HttpError] r =>
Maybe Int ->
(∀ x . StreamEvent o c h x -> Sem r x) ->
Response c ->
h ->
Sem r o
streamLoop :: forall c (r :: EffectRow) o h.
Members '[Http c, Error HttpError] r =>
Maybe Int
-> (forall x. StreamEvent o c h x -> Sem r x)
-> Response c
-> h
-> Sem r o
streamLoop Maybe Int
chunkSize forall x. StreamEvent o c h x -> Sem r x
process response :: Response c
response@(Response Status
_ c
body [Header]
_ CookieJar
_) h
handle =
Sem r o
spin
where
spin :: Sem r o
spin =
ByteString -> Sem r o
handleChunk (ByteString -> Sem r o) -> Sem r ByteString -> Sem r o
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Either HttpError ByteString -> Sem r ByteString
forall e (r :: EffectRow) a.
Member (Error e) r =>
Either e a -> Sem r a
fromEither (Either HttpError ByteString -> Sem r ByteString)
-> Sem r (Either HttpError ByteString) -> Sem r ByteString
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Maybe Int -> c -> Sem r (Either HttpError ByteString)
forall c (r :: EffectRow).
Member (Http c) r =>
Maybe Int -> c -> Sem r (Either HttpError ByteString)
Http.consumeChunk Maybe Int
chunkSize c
body
handleChunk :: ByteString -> Sem r o
handleChunk (ByteString -> Bool
ByteString.null -> Bool
True) =
StreamEvent o c h o -> Sem r o
forall x. StreamEvent o c h x -> Sem r x
process (Response c -> h -> StreamEvent o c h o
forall c h r. Response c -> h -> StreamEvent r c h r
StreamEvent.Result Response c
response h
handle)
handleChunk !ByteString
chunk = do
StreamEvent o c h () -> Sem r ()
forall x. StreamEvent o c h x -> Sem r x
process (h -> StreamChunk -> StreamEvent o c h ()
forall h r c. h -> StreamChunk -> StreamEvent r c h ()
StreamEvent.Chunk h
handle (ByteString -> StreamChunk
StreamChunk ByteString
chunk))
Sem r o
spin
streamHandler ::
∀ o r c h .
Members [Http c, Error HttpError, Resource] r =>
Maybe Int ->
(∀ x . StreamEvent o c h x -> Sem r x) ->
Response c ->
Sem r o
streamHandler :: forall o (r :: EffectRow) c h.
Members '[Http c, Error HttpError, Resource] r =>
Maybe Int
-> (forall x. StreamEvent o c h x -> Sem r x)
-> Response c
-> Sem r o
streamHandler Maybe Int
chunkSize forall x. StreamEvent o c h x -> Sem r x
process Response c
response =
Sem r h -> (h -> Sem r ()) -> (h -> Sem r o) -> Sem r o
forall (r :: EffectRow) a c b.
Member Resource r =>
Sem r a -> (a -> Sem r c) -> (a -> Sem r b) -> Sem r b
bracket Sem r h
acquire h -> Sem r ()
release (Maybe Int
-> (forall x. StreamEvent o c h x -> Sem r x)
-> Response c
-> h
-> Sem r o
forall c (r :: EffectRow) o h.
Members '[Http c, Error HttpError] r =>
Maybe Int
-> (forall x. StreamEvent o c h x -> Sem r x)
-> Response c
-> h
-> Sem r o
streamLoop Maybe Int
chunkSize StreamEvent o c h x -> Sem r x
forall x. StreamEvent o c h x -> Sem r x
process Response c
response)
where
acquire :: Sem r h
acquire =
StreamEvent o c h h -> Sem r h
forall x. StreamEvent o c h x -> Sem r x
process (Response c -> StreamEvent o c h h
forall c r h. Response c -> StreamEvent r c h h
StreamEvent.Acquire Response c
response)
release :: h -> Sem r ()
release h
handle =
StreamEvent o c h () -> Sem r ()
forall x. StreamEvent o c h x -> Sem r x
process (h -> StreamEvent o c h ()
forall h r c. h -> StreamEvent r c h ()
StreamEvent.Release h
handle)
streamResponse ::
Members [Http c, Error HttpError, Resource] r =>
Request ->
Maybe Int ->
(∀ x . StreamEvent o c h x -> Sem r x) ->
Sem r o
streamResponse :: forall c (r :: EffectRow) o h.
Members '[Http c, Error HttpError, Resource] r =>
Request
-> Maybe Int
-> (forall x. StreamEvent o c h x -> Sem r x)
-> Sem r o
streamResponse Request
request Maybe Int
chunkSize forall x. StreamEvent o c h x -> Sem r x
process =
Either HttpError o -> Sem r o
forall e (r :: EffectRow) a.
Member (Error e) r =>
Either e a -> Sem r a
fromEither (Either HttpError o -> Sem r o)
-> (Either HttpError (Either HttpError o) -> Either HttpError o)
-> Either HttpError (Either HttpError o)
-> Sem r o
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Either HttpError (Either HttpError o) -> Either HttpError o
forall (m :: * -> *) a. Monad m => m (m a) -> m a
join (Either HttpError (Either HttpError o) -> Sem r o)
-> Sem r (Either HttpError (Either HttpError o)) -> Sem r o
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Request
-> (Response c -> Sem r (Either HttpError o))
-> Sem r (Either HttpError (Either HttpError o))
forall c (r :: EffectRow) a.
Member (Http c) r =>
Request -> (Response c -> Sem r a) -> Sem r (Either HttpError a)
Http.response Request
request (Sem (Error HttpError : r) o -> Sem r (Either HttpError o)
forall e (r :: EffectRow) a.
Sem (Error e : r) a -> Sem r (Either e a)
runError (Sem (Error HttpError : r) o -> Sem r (Either HttpError o))
-> (Response c -> Sem (Error HttpError : r) o)
-> Response c
-> Sem r (Either HttpError o)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Maybe Int
-> (forall x. StreamEvent o c h x -> Sem (Error HttpError : r) x)
-> Response c
-> Sem (Error HttpError : r) o
forall o (r :: EffectRow) c h.
Members '[Http c, Error HttpError, Resource] r =>
Maybe Int
-> (forall x. StreamEvent o c h x -> Sem r x)
-> Response c
-> Sem r o
streamHandler Maybe Int
chunkSize (Sem r x -> Sem (Error HttpError : r) x
forall (e :: (* -> *) -> * -> *) (r :: EffectRow) a.
Sem r a -> Sem (e : r) a
raise (Sem r x -> Sem (Error HttpError : r) x)
-> (StreamEvent o c h x -> Sem r x)
-> StreamEvent o c h x
-> Sem (Error HttpError : r) x
forall b c a. (b -> c) -> (a -> b) -> a -> c
. StreamEvent o c h x -> Sem r x
forall x. StreamEvent o c h x -> Sem r x
process))