about summary refs log tree commit diff
path: root/users/Profpatsch/whatcd-resolver/src/Redacted.hs
diff options
context:
space:
mode:
Diffstat (limited to 'users/Profpatsch/whatcd-resolver/src/Redacted.hs')
-rw-r--r--users/Profpatsch/whatcd-resolver/src/Redacted.hs91
1 files changed, 63 insertions, 28 deletions
diff --git a/users/Profpatsch/whatcd-resolver/src/Redacted.hs b/users/Profpatsch/whatcd-resolver/src/Redacted.hs
index 4369c18408..c0ad9071af 100644
--- a/users/Profpatsch/whatcd-resolver/src/Redacted.hs
+++ b/users/Profpatsch/whatcd-resolver/src/Redacted.hs
@@ -3,6 +3,7 @@
 module Redacted where
 
 import AppT
+import Arg
 import Control.Monad.Logger.CallStack
 import Control.Monad.Reader
 import Data.Aeson qualified as Json
@@ -67,12 +68,8 @@ redactedGetTorrentFile dat = inSpan' "Redacted Get Torrent File" $ \span -> do
       )
   httpTorrent span req
 
--- fix
---   ( \io -> do
---       logInfo "delay"
---       liftIO $ threadDelay 10_000_000
---       io
---   )
+mkRedactedTorrentLink :: Arg "torrentGroupId" Int -> Text
+mkRedactedTorrentLink torrentId = [fmt|https://redacted.ch/torrents.php?id={torrentId.unArg}|]
 
 exampleSearch :: (MonadThrow m, MonadLogger m, MonadPostgres m, MonadOtel m) => m (Transaction m ())
 exampleSearch = do
@@ -360,11 +357,17 @@ data TorrentData transmissionInfo = TorrentData
   { groupId :: Int,
     torrentId :: Int,
     seedingWeight :: Int,
+    artists :: [T2 "artistId" Int "artistName" Text],
     torrentJson :: Json.Value,
-    torrentGroupJson :: T3 "artist" Text "groupName" Text "groupYear" Int,
+    torrentGroupJson :: TorrentGroupJson,
     torrentStatus :: TorrentStatus transmissionInfo
   }
 
+data TorrentGroupJson = TorrentGroupJson
+  { groupName :: Text,
+    groupYear :: Int
+  }
+
 data TorrentStatus transmissionInfo
   = NoTorrentFileYet
   | NotInTransmissionYet
@@ -381,38 +384,70 @@ getTorrentById dat = do
     (Dec.json Json.asValue)
     >>= ensureSingleRow
 
+data GetBestTorrentsFilter = GetBestTorrentsFilter
+  { onlyDownloaded :: Bool,
+    onlyArtist :: Maybe (Label "artistRedactedId" Natural)
+  }
+
 -- | Find the best torrent for each torrent group (based on the seeding_weight)
-getBestTorrents :: (MonadPostgres m) => Transaction m [TorrentData ()]
-getBestTorrents = do
+getBestTorrents ::
+  (MonadPostgres m) =>
+  GetBestTorrentsFilter ->
+  Transaction m [TorrentData ()]
+getBestTorrents opts = do
   queryWith
     [sql|
-      SELECT * FROM (
-        SELECT DISTINCT ON (group_id)
-          tg.group_id,
-          t.torrent_id,
-          seeding_weight,
-          t.full_json_result AS torrent_json,
-          tg.full_json_result AS torrent_group_json,
-          t.torrent_file IS NOT NULL,
-          t.transmission_torrent_hash
-        FROM redacted.torrents t
-        JOIN redacted.torrent_groups tg ON tg.id = t.torrent_group
-        ORDER BY group_id, seeding_weight DESC
-      ) as _
+      WITH filtered_torrents AS (
+        SELECT DISTINCT ON (torrent_group)
+          id
+        FROM
+          redacted.torrents
+        WHERE
+          -- onlyDownloaded
+          ((NOT ?::bool) OR torrent_file IS NOT NULL)
+          -- filter by artist id
+          AND
+          (?::bool OR (to_jsonb(?::int) <@ (jsonb_path_query_array(full_json_result, '$.artists[*].id'))))
+        ORDER BY torrent_group, seeding_weight DESC
+      )
+      SELECT
+        tg.group_id,
+        t.torrent_id,
+        t.seeding_weight,
+        t.full_json_result AS torrent_json,
+        tg.full_json_result AS torrent_group_json,
+        t.torrent_file IS NOT NULL AS has_torrent_file,
+        t.transmission_torrent_hash
+      FROM filtered_torrents f
+      JOIN redacted.torrents t ON t.id = f.id
+      JOIN redacted.torrent_groups tg ON tg.id = t.torrent_group
       ORDER BY seeding_weight DESC
     |]
-    ()
+    ( do
+        let (onlyArtistB, onlyArtistId) = case opts.onlyArtist of
+              Nothing -> (True, 0)
+              Just a -> (False, a.artistRedactedId)
+        ( opts.onlyDownloaded :: Bool,
+          onlyArtistB :: Bool,
+          onlyArtistId & fromIntegral @Natural @Int
+          )
+    )
     ( do
         groupId <- Dec.fromField @Int
         torrentId <- Dec.fromField @Int
         seedingWeight <- Dec.fromField @Int
-        torrentJson <- Dec.json Json.asValue
+        (torrentJson, artists) <- Dec.json $ do
+          val <- Json.asValue
+          artists <- Json.keyOrDefault "artists" [] $ Json.eachInArray $ do
+            id_ <- Json.keyLabel @"artistId" "id" (Json.asIntegral @_ @Int)
+            name <- Json.keyLabel @"artistName" "name" Json.asText
+            pure $ T2 id_ name
+          pure (val, artists)
         torrentGroupJson <-
           ( Dec.json $ do
-              artist <- Json.keyLabel @"artist" "artist" Json.asText
-              groupName <- Json.keyLabel @"groupName" "groupName" Json.asText
-              groupYear <- Json.keyLabel @"groupYear" "groupYear" (Json.asIntegral @_ @Int)
-              pure $ T3 artist groupName groupYear
+              groupName <- Json.key "groupName" Json.asText
+              groupYear <- Json.key "groupYear" (Json.asIntegral @_ @Int)
+              pure $ TorrentGroupJson {..}
             )
         hasTorrentFile <- Dec.fromField @Bool
         transmissionTorrentHash <-