feat(users/Profpatsch/whatcd-resolver): add artist albums

Simple artist album page that only shows albums the artist was
involved with.

Change-Id: Icff34afc6d1b39b6fb17765c1b3ea500dd4b4d95
Reviewed-on: https://cl.tvl.fyi/c/depot/+/11675
Tested-by: BuildkiteCI
Autosubmit: Profpatsch <mail@profpatsch.de>
Reviewed-by: Profpatsch <mail@profpatsch.de>
This commit is contained in:
Profpatsch 2024-05-15 14:09:11 +02:00 committed by clbot
parent a3a03a5a80
commit b54ad3e580
3 changed files with 67 additions and 18 deletions

View file

@ -3,7 +3,6 @@
module JsonLd where module JsonLd where
import AppT import AppT
import Control.Monad.Reader
import Data.Aeson qualified as Json import Data.Aeson qualified as Json
import Data.Aeson.BetterErrors qualified as Json import Data.Aeson.BetterErrors qualified as Json
import Data.ByteString.Builder qualified as Builder import Data.ByteString.Builder qualified as Builder

View file

@ -362,10 +362,15 @@ data TorrentData transmissionInfo = TorrentData
seedingWeight :: Int, seedingWeight :: Int,
artists :: [T2 "artistId" Int "artistName" Text], artists :: [T2 "artistId" Int "artistName" Text],
torrentJson :: Json.Value, torrentJson :: Json.Value,
torrentGroupJson :: T2 "groupName" Text "groupYear" Int, torrentGroupJson :: TorrentGroupJson,
torrentStatus :: TorrentStatus transmissionInfo torrentStatus :: TorrentStatus transmissionInfo
} }
data TorrentGroupJson = TorrentGroupJson
{ groupName :: Text,
groupYear :: Int
}
data TorrentStatus transmissionInfo data TorrentStatus transmissionInfo
= NoTorrentFileYet = NoTorrentFileYet
| NotInTransmissionYet | NotInTransmissionYet
@ -382,30 +387,58 @@ getTorrentById dat = do
(Dec.json Json.asValue) (Dec.json Json.asValue)
>>= ensureSingleRow >>= ensureSingleRow
data GetBestTorrentsFilter = GetBestTorrentsFilter
{ onlyDownloaded :: Bool,
onlyArtist :: Maybe (Label "artistId" Natural)
}
-- | Find the best torrent for each torrent group (based on the seeding_weight) -- | Find the best torrent for each torrent group (based on the seeding_weight)
getBestTorrents :: (MonadPostgres m, HasField "onlyDownloaded" opts Bool) => opts -> Transaction m [TorrentData ()] getBestTorrents ::
(MonadPostgres m) =>
GetBestTorrentsFilter ->
Transaction m [TorrentData ()]
getBestTorrents opts = do getBestTorrents opts = do
queryWith queryWith
[sql| [sql|
SELECT * FROM ( SELECT
SELECT DISTINCT ON (group_id) group_id,
torrent_id,
seeding_weight,
torrent_json,
torrent_group_json,
has_torrent_file,
transmission_torrent_hash
FROM (
SELECT DISTINCT ON (tg.group_id)
tg.group_id, tg.group_id,
t.torrent_id, t.torrent_id,
seeding_weight, seeding_weight,
t.full_json_result AS torrent_json, t.full_json_result AS torrent_json,
tg.full_json_result AS torrent_group_json, tg.full_json_result AS torrent_group_json,
t.torrent_file IS NOT NULL as has_torrent_file, t.torrent_file IS NOT NULL as has_torrent_file,
t.transmission_torrent_hash t.transmission_torrent_hash,
(jsonb_path_query_array(t.full_json_result, '$.artists[*].id')) as torrent_artists
FROM redacted.torrents t FROM redacted.torrents t
JOIN redacted.torrent_groups tg ON tg.id = t.torrent_group JOIN redacted.torrent_groups tg ON tg.id = t.torrent_group
ORDER BY group_id, seeding_weight DESC ORDER BY tg.group_id, seeding_weight DESC
) as _ ) as _
WHERE WHERE
-- onlyDownloaded -- onlyDownloaded
((NOT ?::bool) OR has_torrent_file) ((NOT ?::bool) OR has_torrent_file)
-- filter by artist id
AND
(?::bool OR (to_jsonb(?::int) <@ torrent_artists))
ORDER BY seeding_weight DESC ORDER BY seeding_weight DESC
|] |]
(Only opts.onlyDownloaded :: Only Bool) ( do
let (onlyArtistB, onlyArtistId) = case opts.onlyArtist of
Nothing -> (True, 0)
Just a -> (False, a.artistId)
( opts.onlyDownloaded :: Bool,
onlyArtistB :: Bool,
onlyArtistId & fromIntegral @Natural @Int
)
)
( do ( do
groupId <- Dec.fromField @Int groupId <- Dec.fromField @Int
torrentId <- Dec.fromField @Int torrentId <- Dec.fromField @Int
@ -419,9 +452,9 @@ getBestTorrents opts = do
pure (val, artists) pure (val, artists)
torrentGroupJson <- torrentGroupJson <-
( Dec.json $ do ( Dec.json $ do
groupName <- Json.keyLabel @"groupName" "groupName" Json.asText groupName <- Json.key "groupName" Json.asText
groupYear <- Json.keyLabel @"groupYear" "groupYear" (Json.asIntegral @_ @Int) groupYear <- Json.key "groupYear" (Json.asIntegral @_ @Int)
pure $ T2 groupName groupYear pure $ TorrentGroupJson {..}
) )
hasTorrentFile <- Dec.fromField @Bool hasTorrentFile <- Dec.fromField @Bool
transmissionTorrentHash <- transmissionTorrentHash <-

View file

@ -213,7 +213,7 @@ htmlUi = do
htmlWithQueryArgs htmlWithQueryArgs
( label @"dbId" ( label @"dbId"
<$> (singleQueryArgument "db_id" Field.utf8) <$> (singleQueryArgument "db_id" (Field.utf8 >>> Field.decimalNatural))
) )
$ \qry _span -> do $ \qry _span -> do
artistPage qry artistPage qry
@ -256,7 +256,7 @@ htmlUi = do
-- "https://musicbrainz.org/work/92000fd4-d304-406d-aeb4-6bdbeed318ec" -- "https://musicbrainz.org/work/92000fd4-d304-406d-aeb4-6bdbeed318ec"
-- ) -- )
-- <&> renderJsonld -- <&> renderJsonld
bestTorrentsTable <- getBestTorrentsTable bestTorrentsTable <- getBestTorrentsTable Nothing
-- transmissionTorrentsTable <- lift @Transaction getTransmissionTorrentsTable -- transmissionTorrentsTable <- lift @Transaction getTransmissionTorrentsTable
pure $ pure $
Html.docTypeHtml Html.docTypeHtml
@ -305,11 +305,23 @@ htmlUi = do
</body> </body>
|] |]
artistPage :: (HasField "dbId" dat Text, Applicative m) => dat -> m Html artistPage ::
artistPage dat = do ( HasField "dbId" dat Natural,
MonadPostgres m,
MonadOtel m,
MonadLogger m,
MonadThrow m,
MonadTransmission m
) =>
dat ->
m Html
artistPage dat = runTransaction $ do
torrents <- getBestTorrentsTable (Just $ label @"artistId" dat.dbId)
pure pure
[hsx| [hsx|
Artist ID: {dat.dbId} Artist ID: {dat.dbId}
{torrents}
|] |]
type Handlers m = HandlerResponses m -> Map Text (m ResponseReceived) type Handlers m = HandlerResponses m -> Map Text (m ResponseReceived)
@ -451,7 +463,11 @@ snipsRedactedSearch dat = do
] ]
runTransaction $ do runTransaction $ do
t t
getBestTorrentsTable getBestTorrentsTable (Nothing :: Maybe (Label "artistId" Natural))
data ArtistFilter = ArtistFilter
{ onlyArtist :: Maybe (Label "artistId" Text)
}
getBestTorrentsTable :: getBestTorrentsTable ::
( MonadTransmission m, ( MonadTransmission m,
@ -460,9 +476,10 @@ getBestTorrentsTable ::
MonadPostgres m, MonadPostgres m,
MonadOtel m MonadOtel m
) => ) =>
Maybe (Label "artistId" Natural) ->
Transaction m Html Transaction m Html
getBestTorrentsTable = do getBestTorrentsTable artistFilter = do
bestStale :: [TorrentData ()] <- getBestTorrents (label @"onlyDownloaded" False) bestStale :: [TorrentData ()] <- getBestTorrents GetBestTorrentsFilter {onlyArtist = artistFilter, onlyDownloaded = False}
actual <- actual <-
getAndUpdateTransmissionTorrentsStatus getAndUpdateTransmissionTorrentsStatus
( bestStale ( bestStale