urbit/pkg/hs-urbit/lib/Vere/Http/Client.hs

113 lines
3.4 KiB
Haskell
Raw Normal View History

2019-05-17 04:25:58 +03:00
{-
- TODO When making a request, handle the case where the request id is
already in use.
-}
2019-05-16 03:00:10 +03:00
module Vere.Http.Client where
import ClassyPrelude
2019-07-12 22:18:14 +03:00
import Noun
2019-07-12 22:18:14 +03:00
import Vere.Http
2019-05-17 03:05:34 +03:00
2019-05-18 00:52:12 +03:00
import qualified Data.CaseInsensitive as CI
2019-07-12 22:18:14 +03:00
import qualified Network.HTTP.Client as H
import qualified Network.HTTP.Types as HT
2019-05-17 04:25:58 +03:00
2019-06-28 00:28:58 +03:00
-- Types -----------------------------------------------------------------------
2019-05-17 04:25:58 +03:00
type ReqId = Word
data Ev = Receive ReqId Event -- [%receive @ todo]
2019-05-16 03:00:10 +03:00
data Eff
= NewReq ReqId Request -- [%request @ todo]
| CancelReq ReqId -- [%cancel-request @]
2019-06-28 00:28:58 +03:00
deriving (Eq, Ord, Show)
2019-05-17 04:25:58 +03:00
data State = State
{ sManager :: H.Manager
, sLive :: TVar (Map ReqId (Async ()))
2019-05-17 04:25:58 +03:00
, sChan :: MVar Ev
}
2019-06-28 00:28:58 +03:00
2019-05-17 04:25:58 +03:00
--------------------------------------------------------------------------------
2019-05-18 00:52:12 +03:00
cvtReq :: Request -> Maybe H.Request
cvtReq r =
2019-07-22 21:10:27 +03:00
H.parseRequest (unpack (unCord $ url r)) <&> \init -> init
2019-05-18 00:52:12 +03:00
{ H.method = encodeUtf8 $ tshow (method r),
H.requestHeaders =
2019-07-22 21:10:27 +03:00
headerList r <&> \(Header k v) -> (CI.mk (encodeUtf8 $ unCord k),
2019-07-23 03:46:06 +03:00
unBytes v),
2019-05-18 00:52:12 +03:00
H.requestBody =
H.RequestBodyBS $ case body r of
2019-07-22 21:10:27 +03:00
Nothing -> ""
Just (Octs bs) -> bs
2019-05-18 00:52:12 +03:00
}
2019-05-17 04:25:58 +03:00
cvtRespHeaders :: H.Response a -> ResponseHeader
2019-05-18 00:52:12 +03:00
cvtRespHeaders resp =
ResponseHeader (fromIntegral $ HT.statusCode (H.responseStatus resp)) heads
2019-05-18 00:52:12 +03:00
where
2019-05-24 02:58:18 +03:00
heads = convertHeaders (H.responseHeaders resp)
2019-05-18 00:52:12 +03:00
2019-05-17 03:05:34 +03:00
2019-05-17 04:25:58 +03:00
--------------------------------------------------------------------------------
2019-05-17 03:05:34 +03:00
initState :: IO State
2019-05-17 04:25:58 +03:00
initState = State <$> H.newManager H.defaultManagerSettings
<*> newTVarIO mempty
<*> newEmptyMVar
2019-05-17 03:05:34 +03:00
2019-05-17 04:25:58 +03:00
emit :: State -> Ev -> IO ()
emit st event = putMVar (sChan st) event
2019-05-17 03:05:34 +03:00
2019-05-17 04:25:58 +03:00
runEff :: State -> Eff -> IO ()
2019-05-18 00:52:12 +03:00
runEff st = \case NewReq id req -> newReq st id req
CancelReq id -> cancelReq st id
2019-05-17 03:05:34 +03:00
2019-05-17 04:25:58 +03:00
newReq :: State -> ReqId -> Request -> IO ()
newReq st id req = do async <- runReq st id req
atomically $ modifyTVar (sLive st) (insertMap id async)
waitCancel :: Async a -> IO (Either SomeException a)
waitCancel async = cancel async >> waitCatch async
cancelThread :: State -> ReqId -> Async a -> IO ()
cancelThread st id =
waitCancel >=> \case Left _ -> emit st (Receive id Canceled)
Right _ -> pure ()
2019-05-17 03:05:34 +03:00
2019-05-17 04:25:58 +03:00
cancelReq :: State -> ReqId -> IO ()
cancelReq st id =
2019-05-17 03:05:34 +03:00
join $ atomically $ do
2019-05-17 04:25:58 +03:00
tbl <- readTVar (sLive st)
case lookup id tbl of
Nothing -> pure (pure ())
Just async -> do writeTVar (sLive st) (deleteMap id tbl)
pure (cancelThread st id async)
runReq :: State -> ReqId -> Request -> IO (Async ())
2019-05-18 00:52:12 +03:00
runReq st id req = async $
case cvtReq req of
Nothing -> emit st (Receive id (Failed "bad-request-e"))
Just r -> H.withResponse r (sManager st) exec
2019-05-17 03:05:34 +03:00
where
2019-05-17 04:25:58 +03:00
recv :: H.BodyReader -> IO (Maybe ByteString)
recv read = read <&> \case chunk | null chunk -> Nothing
| otherwise -> Just chunk
exec :: H.Response H.BodyReader -> IO ()
exec resp = do
let headers = cvtRespHeaders resp
getChunk = recv (H.responseBody resp)
loop = getChunk >>= \case
Nothing -> emit st (Receive id Done)
2019-07-22 21:10:27 +03:00
Just bs -> do emit st (Receive id $ Received $ Octs bs)
loop
emit st (Receive id $ Started headers)
loop