feat(users/Profpatsch/whatcd-resolver): Show percent done

Change-Id: I6d7852570bdca807e4d4fff01d72de9f1084fd42
Reviewed-on: https://cl.tvl.fyi/c/depot/+/8910
Reviewed-by: Profpatsch <mail@profpatsch.de>
Tested-by: BuildkiteCI
This commit is contained in:
Profpatsch 2023-06-30 23:46:22 +02:00
parent 50c27b6ba1
commit 43feacb64b
2 changed files with 65 additions and 46 deletions

View file

@ -17,6 +17,7 @@ import Data.List.NonEmpty qualified as NonEmpty
import Data.Map.Strict qualified as Map import Data.Map.Strict qualified as Map
import Data.Pool (Pool) import Data.Pool (Pool)
import Data.Pool qualified as Pool import Data.Pool qualified as Pool
import Data.Scientific (Scientific)
import Data.Text qualified as Text import Data.Text qualified as Text
import Database.PostgreSQL.Simple (Binary (Binary), Only (..)) import Database.PostgreSQL.Simple (Binary (Binary), Only (..))
import Database.PostgreSQL.Simple qualified as Postgres import Database.PostgreSQL.Simple qualified as Postgres
@ -24,6 +25,7 @@ import Database.PostgreSQL.Simple.SqlQQ (sql)
import Database.PostgreSQL.Simple.Types (PGArray (PGArray)) import Database.PostgreSQL.Simple.Types (PGArray (PGArray))
import Database.PostgreSQL.Simple.Types qualified as Postgres import Database.PostgreSQL.Simple.Types qualified as Postgres
import Database.Postgres.Temp qualified as TmpPg import Database.Postgres.Temp qualified as TmpPg
import FieldParser (FieldParser' (..))
import FieldParser qualified as Field import FieldParser qualified as Field
import GHC.Records (HasField (..)) import GHC.Records (HasField (..))
import IHP.HSX.QQ (hsx) import IHP.HSX.QQ (hsx)
@ -156,32 +158,7 @@ htmlUi = do
everySecond call extraData innerHtml = [hsx|<div hx-trigger="every 1s" hx-swap="outerHTML" hx-post={call} hx-vals={Enc.encToBytesUtf8 extraData}>{innerHtml}</div>|] everySecond call extraData innerHtml = [hsx|<div hx-trigger="every 1s" hx-swap="outerHTML" hx-post={call} hx-vals={Enc.encToBytesUtf8 extraData}>{innerHtml}</div>|]
mainHtml = runTransaction $ do mainHtml = runTransaction $ do
bestStale :: [TorrentData] <- getBestTorrents bestTorrentsTable <- getBestTorrentsTable
actual <-
getAndUpdateTransmissionTorrentsStatus
( bestStale
& mapMaybe
( \td -> case td.torrentStatus of
InTransmission h -> Just h
_ -> Nothing
)
<&> (,())
& Map.fromList
)
let fresh =
bestStale
-- we have to update the status of every torrent thats not in tranmission anymore
-- TODO I feel like its easier (& more correct?) to just do the database request again …
<&> ( \td -> case td.torrentStatus of
InTransmission hash ->
case actual & Map.lookup hash of
-- TODO this is also pretty dumb, cause it assumes that we have the torrent file if it was in transmission before,
-- which is an internal factum that is established in getBestTorrents (and might change later)
Nothing -> td {torrentStatus = NotInTransmissionYet}
Just () -> td
_ -> td
)
bestTorrentsTable <- getBestTorrentsTable fresh
transmissionTorrentsTable <- lift @Transaction getTransmissionTorrentsTable transmissionTorrentsTable <- lift @Transaction getTransmissionTorrentsTable
pure $ pure $
Html.docTypeHtml Html.docTypeHtml
@ -218,7 +195,8 @@ snipsRedactedSearch ::
MonadIO m, MonadIO m,
MonadPostgres m, MonadPostgres m,
HasField "searchstr" r ByteString, HasField "searchstr" r ByteString,
MonadThrow m MonadThrow m,
MonadTransmission m
) => ) =>
r -> r ->
m Html m Html
@ -229,17 +207,42 @@ snipsRedactedSearch dat = do
] ]
runTransaction $ do runTransaction $ do
t t
best :: [TorrentData] <- getBestTorrents getBestTorrentsTable
getBestTorrentsTable best
getBestTorrentsTable :: (MonadPostgres m) => [TorrentData] -> Transaction m Html getBestTorrentsTable :: (MonadIO m, MonadTransmission m, MonadThrow m, MonadLogger m, MonadPostgres m) => Transaction m Html
getBestTorrentsTable best = do getBestTorrentsTable = do
bestStale :: [TorrentData ()] <- getBestTorrents
actual <-
getAndUpdateTransmissionTorrentsStatus
( bestStale
& mapMaybe
( \td -> case td.torrentStatus of
InTransmission h -> Just h
_ -> Nothing
)
<&> (\t -> (getLabel @"torrentHash" t, t.transmissionInfo))
& Map.fromList
)
let fresh =
bestStale
-- we have to update the status of every torrent thats not in tranmission anymore
-- TODO I feel like its easier (& more correct?) to just do the database request again …
<&> ( \td -> case td.torrentStatus of
InTransmission info ->
case actual & Map.lookup (getLabel @"torrentHash" info) of
-- TODO this is also pretty dumb, cause it assumes that we have the torrent file if it was in transmission before,
-- which is an internal factum that is established in getBestTorrents (and might change later)
Nothing -> td {torrentStatus = NotInTransmissionYet}
Just transmissionInfo -> td {torrentStatus = InTransmission (T2 (getLabel @"torrentHash" info) (label @"transmissionInfo" transmissionInfo))}
NotInTransmissionYet -> td {torrentStatus = NotInTransmissionYet}
NoTorrentFileYet -> td {torrentStatus = NotInTransmissionYet}
)
let localTorrent b = case b.torrentStatus of let localTorrent b = case b.torrentStatus of
NoTorrentFileYet -> [hsx|<button hx-post="snips/redacted/getTorrentFile" hx-swap="outerHTML" hx-vals={Enc.encToBytesUtf8 $ Enc.object [("torrent-id", Enc.int b.torrentId)]}>Get Torrent</button>|] NoTorrentFileYet -> [hsx|<button hx-post="snips/redacted/getTorrentFile" hx-swap="outerHTML" hx-vals={Enc.encToBytesUtf8 $ Enc.object [("torrent-id", Enc.int b.torrentId)]}>Upload Torrent</button>|]
InTransmission _hash -> [hsx|Started.|] InTransmission info -> [hsx|{info.transmissionInfo.percentDone.unPercentage}% done|]
NotInTransmissionYet -> [hsx|<button hx-post="snips/redacted/startTorrentFile" hx-swap="outerHTML" hx-vals={Enc.encToBytesUtf8 $ Enc.object [("torrent-id", Enc.int b.torrentId)]}>Start Torrent</button>|] NotInTransmissionYet -> [hsx|<button hx-post="snips/redacted/startTorrentFile" hx-swap="outerHTML" hx-vals={Enc.encToBytesUtf8 $ Enc.object [("torrent-id", Enc.int b.torrentId)]}>Start Torrent</button>|]
let bestRows = let bestRows =
best fresh
& foldMap & foldMap
( \b -> do ( \b -> do
[hsx| [hsx|
@ -273,15 +276,29 @@ getBestTorrentsTable best = do
</table> </table>
|] |]
-- | A value between (inclusive) 0% and (inclusive) 100%. Precise to 1% steps.
newtype Percentage = Percentage {unPercentage :: Int}
deriving stock (Show)
-- | Parse a scientific into a Percentage
scientificPercentage :: FieldParser' Error Scientific Percentage
scientificPercentage =
Field.boundedScientificRealFloat @Float
>>> ( FieldParser $ \f ->
if
| f < 0 -> Left "percentage cannot be negative"
| f > 1 -> Left "percentage cannot be over 100%"
| otherwise -> Right $ Percentage $ ceiling (f * 100)
)
-- | Fetch the current status from transmission, and remove the tranmission hash from our database -- | Fetch the current status from transmission, and remove the tranmission hash from our database
-- iff it does not exist in transmission anymore -- iff it does not exist in transmission anymore
getAndUpdateTransmissionTorrentsStatus :: getAndUpdateTransmissionTorrentsStatus ::
(MonadIO m, MonadTransmission m, MonadThrow m, MonadLogger m, MonadPostgres m) => (MonadIO m, MonadTransmission m, MonadThrow m, MonadLogger m, MonadPostgres m) =>
Map (Label "torrentHash" Text) () -> Map (Label "torrentHash" Text) () ->
Transaction m (Map (Label "torrentHash" Text) ()) (Transaction m (Map (Label "torrentHash" Text) (Label "percentDone" Percentage)))
getAndUpdateTransmissionTorrentsStatus knownTorrents = do getAndUpdateTransmissionTorrentsStatus knownTorrents = do
let fields = ["hashString"] let fields = ["hashString", "percentDone"]
logInfo [fmt|known: {showPretty knownTorrents}|]
actualTorrents <- actualTorrents <-
lift @Transaction $ lift @Transaction $
doTransmissionRequest' doTransmissionRequest'
@ -292,12 +309,11 @@ getAndUpdateTransmissionTorrentsStatus knownTorrents = do
) )
$ do $ do
torrentHash <- Json.keyLabel @"torrentHash" "hashString" Json.asText torrentHash <- Json.keyLabel @"torrentHash" "hashString" Json.asText
pure (torrentHash, ()) percentDone <- Json.keyLabel @"percentDone" "percentDone" (Field.jsonParser $ Field.jsonNumber >>> scientificPercentage)
pure (torrentHash, percentDone)
) )
<&> Map.fromList <&> Map.fromList
logInfo [fmt|actual: {showPretty actualTorrents}|]
let toDelete = Map.difference knownTorrents actualTorrents let toDelete = Map.difference knownTorrents actualTorrents
logInfo [fmt|toDelete: {showPretty toDelete}|]
execute execute
[fmt| [fmt|
UPDATE redacted.torrents_json UPDATE redacted.torrents_json
@ -821,19 +837,19 @@ migrate = do
CREATE INDEX IF NOT EXISTS torrents_json_snatches ON redacted.torrents_json(((full_json_result->'snatches')::integer)); CREATE INDEX IF NOT EXISTS torrents_json_snatches ON redacted.torrents_json(((full_json_result->'snatches')::integer));
|] |]
data TorrentData = TorrentData data TorrentData transmissionInfo = TorrentData
{ groupId :: Int, { groupId :: Int,
torrentId :: Int, torrentId :: Int,
seedingWeight :: Int, seedingWeight :: Int,
torrentJson :: Json.Value, torrentJson :: Json.Value,
torrentGroupJson :: T2 "artist" Text "groupName" Text, torrentGroupJson :: T2 "artist" Text "groupName" Text,
torrentStatus :: TorrentStatus torrentStatus :: TorrentStatus transmissionInfo
} }
data TorrentStatus data TorrentStatus transmissionInfo
= NoTorrentFileYet = NoTorrentFileYet
| NotInTransmissionYet | NotInTransmissionYet
| InTransmission (Label "torrentHash" Text) | InTransmission (T2 "torrentHash" Text "transmissionInfo" transmissionInfo)
getTorrentById :: (MonadPostgres m, HasField "torrentId" r Int, MonadThrow m) => r -> Transaction m Json.Value getTorrentById :: (MonadPostgres m, HasField "torrentId" r Int, MonadThrow m) => r -> Transaction m Json.Value
getTorrentById dat = do getTorrentById dat = do
@ -847,7 +863,7 @@ getTorrentById dat = do
>>= ensureSingleRow >>= ensureSingleRow
-- | 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 => Transaction m [TorrentData] getBestTorrents :: MonadPostgres m => Transaction m [TorrentData ()]
getBestTorrents = do getBestTorrents = do
queryWith queryWith
[sql| [sql|
@ -887,7 +903,9 @@ getBestTorrents = do
if if
| not hasTorrentFile -> NoTorrentFileYet | not hasTorrentFile -> NoTorrentFileYet
| Nothing <- transmissionTorrentHash -> NotInTransmissionYet | Nothing <- transmissionTorrentHash -> NotInTransmissionYet
| Just hash <- transmissionTorrentHash -> InTransmission (label @"torrentHash" hash), | Just hash <- transmissionTorrentHash ->
InTransmission $
T2 (label @"torrentHash" hash) (label @"transmissionInfo" ()),
.. ..
} }
) )

View file

@ -96,5 +96,6 @@ library
blaze-html, blaze-html,
bytestring, bytestring,
dlist, dlist,
scientific,
selective selective