{-# options_haddock prune #-}

-- |Description: Streaming Implementation, Internal
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 forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< forall e (r :: EffectRow) a.
Member (Error e) r =>
Either e a -> Sem r a
fromEither forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< 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) =
      forall x. StreamEvent o c h x -> Sem r x
process (forall c h r. Response c -> h -> StreamEvent r c h r
StreamEvent.Result Response c
response h
handle)
    handleChunk !ByteString
chunk = do
      forall x. StreamEvent o c h x -> Sem r x
process (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 = do
  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 (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 c
response)
  where
    acquire :: Sem r h
acquire =
      forall x. StreamEvent o c h x -> Sem r x
process (forall c r h. Response c -> StreamEvent r c h h
StreamEvent.Acquire Response c
response)
    release :: h -> Sem r ()
release h
handle =
      forall x. StreamEvent o c h x -> Sem r x
process (forall h r c. h -> StreamEvent r c h ()
StreamEvent.Release h
handle)

-- |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") handle
-- 5.5
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 =
  forall e (r :: EffectRow) a.
Member (Error e) r =>
Either e a -> Sem r a
fromEither forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (m :: * -> *) a. Monad m => m (m a) -> m a
join forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< forall c (r :: EffectRow) a.
Member (Http c) r =>
Request -> (Response c -> Sem r a) -> Sem r (Either HttpError a)
Http.response Request
request (forall e (r :: EffectRow) a.
Sem (Error e : r) a -> Sem r (Either e a)
runError forall b c a. (b -> c) -> (a -> b) -> a -> c
. 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 (e :: (* -> *) -> * -> *) (r :: EffectRow) a.
Sem r a -> Sem (e : r) a
raise forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall x. StreamEvent o c h x -> Sem r x
process))