{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE QuasiQuotes #-}

-- |
-- Module      : Utils.Req
-- Description : Utilities to handle Network.Req HTTP exceptions
module Utils.Req
  ( showHTTPException,
    showRawResponse,
  )
where

import Data.ByteString.Char8 (ByteString)
import Data.Text (Text, pack)
import qualified Network.HTTP.Client as Client
import qualified Network.HTTP.Req as Req
import Network.HTTP.Types (Status (..))
import PyF (fmt)

showHTTPException ::
  -- | A function that accepts a StatusCodeException details and returns the appropriate text
  (Client.Response () -> ByteString -> Text) ->
  Req.HttpException ->
  Text
showHTTPException :: (Response () -> ByteString -> Text) -> HttpException -> Text
showHTTPException Response () -> ByteString -> Text
businessExcHandler (Req.VanillaHttpException HttpException
clientHttpException) = (Response () -> ByteString -> Text) -> HttpException -> Text
showClientHttpException Response () -> ByteString -> Text
businessExcHandler HttpException
clientHttpException
showHTTPException Response () -> ByteString -> Text
_ (Req.JsonHttpException String
exc) = String -> Text
pack String
exc

showClientHttpException ::
  -- | A function that accepts a StatusCodeException details and returns the appropriate text
  (Client.Response () -> ByteString -> Text) ->
  Client.HttpException ->
  Text
showClientHttpException :: (Response () -> ByteString -> Text) -> HttpException -> Text
showClientHttpException Response () -> ByteString -> Text
businessExcHandler (Client.HttpExceptionRequest Request
_ HttpExceptionContent
excContent) = (Response () -> ByteString -> Text) -> HttpExceptionContent -> Text
showExceptionContent Response () -> ByteString -> Text
businessExcHandler HttpExceptionContent
excContent
showClientHttpException Response () -> ByteString -> Text
_ (Client.InvalidUrlException String
_ String
reason) = String -> Text
pack String
reason

showExceptionContent ::
  -- | A function that accepts a StatusCodeException details and returns the appropriate text
  (Client.Response () -> ByteString -> Text) ->
  Client.HttpExceptionContent ->
  Text
showExceptionContent :: (Response () -> ByteString -> Text) -> HttpExceptionContent -> Text
showExceptionContent Response () -> ByteString -> Text
businessExcHandler (Client.StatusCodeException Response ()
resp ByteString
body) = Response () -> ByteString -> Text
businessExcHandler Response ()
resp ByteString
body
-- Catch all doing a simple and ugly show
showExceptionContent Response () -> ByteString -> Text
_ HttpExceptionContent
exc = String -> Text
pack forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Show a => a -> String
show forall a b. (a -> b) -> a -> b
$ HttpExceptionContent
exc

showRawResponse ::
  Client.Response () ->
  ByteString ->
  Text
showRawResponse :: Response () -> ByteString -> Text
showRawResponse Response ()
resp ByteString
body =
  [fmt|\
HTTP call failed: {show status} - {show statusMsg}
      {show body}\
|]
  where
    status :: Int
status = Status -> Int
statusCode forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall body. Response body -> Status
Client.responseStatus forall a b. (a -> b) -> a -> b
$ Response ()
resp
    statusMsg :: ByteString
statusMsg = Status -> ByteString
statusMessage forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall body. Response body -> Status
Client.responseStatus forall a b. (a -> b) -> a -> b
$ Response ()
resp