snix/users/Profpatsch/whatcd-resolver/src/Http.hs
Profpatsch 3040fe2e90 feat(users/Profpatsch/whatcd-resolver): implement artist refresh v0
This is kind of a chonker because I went into so many rabbit holes.

Foremost this implements a simple “Refresh Artist” button that fetches
current artist torrent groups.

BUG: the `artist` endpoint torrent struct is shite, it’s missing most
info that we get in the `search` endpoint torrent struct, plus it’s
organized differently (e.g. the `artists` thingy is in the
torrent_group not the torrent).

I should switch everything over to fetching the `torrent_group.id`s
first and then going through and slowly fetching every torrent group
separately … however that might time out very quickly. ugh. There
doesn’t seem to be a way of fetching multiple torrent groups.

Random other shit & improvements:

* intersperse for builders
* fix json errors so that the structs don’t get too
  big (`restrictJson`)
* show error messages as json so jaeger displays it with nested UI
* color pretty-printed json outpt on command line
* add some important integral functions to MyPrelude
* add `sintersperse` and `mintersperse` to MyPrelude

Change-Id: If8bfcd68dc5c905e118ad86d50d7416962bf55d4
Reviewed-on: https://cl.tvl.fyi/c/depot/+/12960
Tested-by: BuildkiteCI
Reviewed-by: Profpatsch <mail@profpatsch.de>
2025-01-06 16:43:05 +00:00

227 lines
8.2 KiB
Haskell
Raw Blame History

This file contains ambiguous Unicode characters

This file contains Unicode characters that might be confused with other characters. If you think that this is intentional, you can safely ignore this warning. Use the Escape button to reveal them.

{-# LANGUAGE QuasiQuotes #-}
module Http
( doRequestJson,
RequestOptions (..),
mkRequestOptions,
httpJson,
Http.httpBS,
Http.Request,
Http.setRequestMethod,
Http.setQueryString,
Http.setRequestBodyLBS,
Http.setRequestHeader,
Http.getResponseStatus,
Http.getResponseHeader,
Http.getResponseHeaders,
Http.getResponseBody,
)
where
import AppT
import Data.Aeson qualified as Json
import Data.Aeson.BetterErrors qualified as Json
import Data.CaseInsensitive (CI (original))
import Data.Char qualified as Char
import Data.Error.Tree
import Data.List qualified as List
import Data.List.NonEmpty qualified as NonEmpty
import Data.Ord (clamp)
import Data.Text qualified as Text
import Data.Text.Punycode qualified as Punycode
import FieldParser qualified as Field
import Json qualified
import Json.Enc qualified as Enc
import Label
import MyPrelude
import Network.HTTP.Client
import Network.HTTP.Client qualified as Http
import Network.HTTP.Simple qualified as Http
import Network.HTTP.Types.Status (Status (..))
import Network.Wai.Parse qualified as Wai
import Optional
import Pretty
import UnliftIO.Concurrent (threadDelay)
import Prelude hiding (span)
data RequestOptions = RequestOptions
{ method :: ByteString,
host :: Text,
port :: Optional Int,
path :: Optional [Text],
headers :: Optional [Http.Header],
usePlainHttp :: Optional Bool
}
mkRequestOptions :: (HasField "method" r ByteString, HasField "host" r Text) => r -> RequestOptions
mkRequestOptions opts =
RequestOptions
{ method = opts.method,
port = defaults,
host = opts.host,
path = defaults,
headers = defaults,
usePlainHttp = defaults
}
httpJson ::
( MonadThrow m,
MonadOtel m
) =>
(Optional (Label "contentType" ByteString)) ->
Json.Parse ErrorTree b ->
Http.Request ->
m b
httpJson opts parser req = inSpan' "HTTP Request (JSON)" $ \span -> do
let opts' = opts.withDefault (label @"contentType" "application/json")
let go =
Http.httpBS req
>>= ( \resp -> do
let statusCode = resp & Http.responseStatus & (.statusCode)
contentType =
resp
& Http.responseHeaders
& List.lookup "content-type"
<&> Wai.parseContentType
<&> (\(ct, _mimeAttributes) -> ct)
if
| statusCode == 200,
Just ct <- contentType,
ct == opts'.contentType ->
pure $ Right $ (resp & Http.responseBody)
| statusCode == 200,
Just otherType <- contentType ->
pure $ Left [fmt|Server returned a non-json body, with content-type "{otherType}"|]
| statusCode == 200,
Nothing <- contentType ->
pure $ Left [fmt|Server returned a body with unspecified content type|]
| statusCode == 429 -> do
let retryAfter =
resp
& Http.getResponseHeader "Retry-After"
& nonEmpty
>>= ( NonEmpty.head
>>> Field.runFieldParser
( Field.utf8
>>> (Field.decimalNatural <&> toInteger)
>>> (Field.bounded @Int "Int" <&> clamp @Int (0, 10))
)
>>> hush
)
& fromMaybe 2
inSpan' "HTTP Request (JSON) - Rate Limited" $ \span' -> do
addAttribute span' "request.response.status" statusCode
addAttribute span' "request.response.retry-after" retryAfter
threadDelay (retryAfter * 1_000_000)
go
| code <- statusCode -> pure $ Left $ AppExceptionPretty [[fmt|Server returned an non-200 error code, code {code}:|], pretty resp]
)
go
>>= orAppThrow span
>>= \body -> do
val <-
Json.eitherDecodeStrict body
& first (\err -> AppExceptionTree $ nestedError "HTTP response was not valid JSON" (err & stringToText & newError & singleError))
& orAppThrow span
let res = Json.parseValue parser val
case res of
Left e -> do
let err = Json.parseErrorTreeValCtx val e
appThrow
span
( AppExceptionEnc $
Enc.tuple3
Enc.text
Enc.enc
(Enc.nullOr Enc.value)
("Could not parse HTTP response", err.errorMessage, err.valueAtErrorPath)
)
Right a -> pure a
hush :: Either e a -> Maybe a
hush (Right a) = Just a
hush _ = Nothing
doRequestJson ::
(MonadOtel m) =>
RequestOptions ->
Enc.Enc ->
m (Response ByteString)
doRequestJson opts val = inSpan' "HTTP Request (JSON)" $ \span -> do
addAttribute span "request.xh" (requestToXhCommandLine opts val)
resp <-
defaultRequest {secure = not (opts & optsUsePlainHttp)}
& Http.setRequestHost (opts & optsHost)
& Http.setRequestPort (opts & optsPort)
-- TODO: is this automatically escaped by the library?
& Http.setRequestPath (opts & optsPath)
& Http.setRequestHeaders (opts & optsHeaders)
& Http.setRequestMethod opts.method
& Http.setRequestBodyLBS (Enc.encToBytesUtf8Lazy val)
& Http.httpBS
let code = resp & Http.getResponseStatus & (.statusCode)
let msg = resp & Http.getResponseStatus & (.statusMessage) & bytesToTextUtf8Lenient
addAttribute
span
"request.response.status"
([fmt|{code} {msg}|] :: Text)
pure resp
optsHost :: RequestOptions -> ByteString
optsHost opts =
if opts.host & Text.isAscii
then opts.host & textToBytesUtf8
else opts.host & Punycode.encode
optsUsePlainHttp :: RequestOptions -> Bool
optsUsePlainHttp opts = opts.usePlainHttp.withDefault False
optsPort :: RequestOptions -> Int
optsPort opts = opts.port.withDefault (if opts & optsUsePlainHttp then 80 else 443)
optsPath :: RequestOptions -> ByteString
optsPath opts = opts.path.withDefault [] & Text.intercalate "/" & ("/" <>) & textToBytesUtf8
optsHeaders :: RequestOptions -> [Http.Header]
optsHeaders opts = opts.headers.withDefault []
-- | Create a string that can be pasted on the command line to invoke the same HTTP request via the `xh` tool (curl but nicer syntax)
requestToXhCommandLine :: RequestOptions -> Enc.Enc -> Text
requestToXhCommandLine opts val = do
let protocol = if opts & optsUsePlainHttp then "http" :: Text else "https"
let url = [fmt|{protocol}://{opts & optsHost}:{opts & optsPort}{opts & optsPath}|]
let headers = opts & optsHeaders <&> \(hdr, v) -> hdr.original <> ":" <> v
prettyArgsForBash $
mconcat
[ ["xh", url],
headers <&> bytesToTextUtf8Lenient,
["--raw"],
[val & Enc.encToBytesUtf8 & bytesToTextUtf8Lenient]
]
-- | Pretty print a command line in a way that can be copied to bash.
prettyArgsForBash :: [Text] -> Text
prettyArgsForBash = Text.intercalate " " . map simpleBashEscape
-- | Simple escaping for bash words. If they contain anything thats not ascii chars
-- and a bunch of often-used special characters, put the word in single quotes.
simpleBashEscape :: Text -> Text
simpleBashEscape t = do
case Text.find (not . isSimple) t of
Just _ -> escapeSingleQuote t
Nothing -> t
where
-- any word that is just ascii characters is simple (no spaces or control characters)
-- or contains a few often-used characters like - or .
isSimple c =
Char.isAsciiLower c
|| Char.isAsciiUpper c
|| Char.isDigit c
-- These are benign, bash will not interpret them as special characters.
|| List.elem c ['-', '.', ':', '/']
-- Put the word in single quotes
-- If there is a single quote in the word,
-- close the single quoted word, add a single quote, open the word again
escapeSingleQuote t' = "'" <> Text.replace "'" "'\\''" t' <> "'"