2024-03-17 12:43:05 +01:00
{- # LANGUAGE QuasiQuotes # -}
module Redacted where
import AppT
2024-05-17 00:05:37 +02:00
import Arg
2024-03-17 12:43:05 +01:00
import Control.Monad.Logger.CallStack
import Control.Monad.Reader
import Data.Aeson qualified as Json
import Data.Aeson.BetterErrors qualified as Json
import Data.Aeson.KeyMap qualified as KeyMap
import Data.Error.Tree
import Data.List qualified as List
import Database.PostgreSQL.Simple ( Binary ( Binary ) , Only ( .. ) )
import Database.PostgreSQL.Simple.Types ( PGArray ( PGArray ) )
import FieldParser qualified as Field
2024-08-04 11:09:26 +02:00
import Http qualified
2024-03-17 12:43:05 +01:00
import Json qualified
import Label
import MyPrelude
import Network.HTTP.Types
import Network.Wai.Parse qualified as Wai
import OpenTelemetry.Trace qualified as Otel hiding ( getTracer , inSpan , inSpan' )
2024-03-23 05:36:47 +01:00
import Optional
2024-03-17 12:43:05 +01:00
import Postgres.Decoder qualified as Dec
import Postgres.MonadPostgres
import Pretty
import Prelude hiding ( span )
2024-07-29 11:47:20 +02:00
class MonadRedacted m where
getRedactedApiKey :: m ByteString
instance ( MonadIO m ) => MonadRedacted ( AppT m ) where
getRedactedApiKey = AppT ( asks ( . redactedApiKey ) )
2024-03-17 12:43:05 +01:00
redactedSearch ::
2024-07-29 11:47:20 +02:00
( MonadThrow m , MonadOtel m , MonadRedacted m ) =>
2024-03-17 12:43:05 +01:00
[ ( ByteString , ByteString ) ] ->
Json . Parse ErrorTree a ->
m a
redactedSearch advanced parser =
inSpan " Redacted API Search " $
redactedApiRequestJson
( T2
( label @ " action " " browse " )
( label @ " actionArgs " ( ( advanced <&> second Just ) ) )
)
parser
redactedGetTorrentFile ::
( MonadLogger m ,
MonadThrow m ,
HasField " torrentId " dat Int ,
2024-07-29 11:47:20 +02:00
MonadOtel m ,
MonadRedacted m
2024-03-17 12:43:05 +01:00
) =>
dat ->
m ByteString
redactedGetTorrentFile dat = inSpan' " Redacted Get Torrent File " $ \ span -> do
req <-
mkRedactedApiRequest
( T2
( label @ " action " " download " )
( label @ " actionArgs "
[ ( " id " , Just ( dat . torrentId & showToText @ Int & textToBytesUtf8 ) )
-- try using tokens as long as we have them (TODO: what if there’ s no tokens left?
-- ANSWER: it breaks:
-- responseBody = "{\"status\":\"failure\",\"error\":\"You do not have any freeleech tokens left. Please use the regular DL link.\"}",
-- ("usetoken", Just "1")
]
)
)
httpTorrent span req
2024-06-03 00:17:40 +02:00
mkRedactedTorrentLink :: Arg " torrentGroupId " Int -> Text
2024-05-17 00:05:37 +02:00
mkRedactedTorrentLink torrentId = [ fmt | https :// redacted . ch / torrents . php ? id = { torrentId . unArg } | ]
2024-03-17 12:43:05 +01:00
2024-07-29 11:47:20 +02:00
exampleSearch :: ( MonadThrow m , MonadLogger m , MonadPostgres m , MonadOtel m , MonadRedacted m ) => m ( Transaction m () )
2024-03-17 12:43:05 +01:00
exampleSearch = do
t1 <-
redactedSearchAndInsert
[ ( " searchstr " , " cherish " ) ,
( " artistname " , " kirinji " ) ,
-- ("year", "1982"),
-- ("format", "MP3"),
-- ("releasetype", "album"),
( " order_by " , " year " )
]
t3 <-
redactedSearchAndInsert
[ ( " searchstr " , " mouss et hakim " ) ,
( " artistname " , " mouss et hakim " ) ,
-- ("year", "1982"),
-- ("format", "MP3"),
-- ("releasetype", "album"),
( " order_by " , " year " )
]
t2 <-
redactedSearchAndInsert
[ ( " searchstr " , " thriller " ) ,
( " artistname " , " michael jackson " ) ,
-- ("year", "1982"),
-- ("format", "MP3"),
-- ("releasetype", "album"),
( " order_by " , " year " )
]
pure ( t1 >> t2 >> t3 )
-- | Do the search, return a transaction that inserts all results from all pages of the search.
redactedSearchAndInsert ::
forall m .
( MonadLogger m ,
MonadPostgres m ,
MonadThrow m ,
2024-07-29 11:47:20 +02:00
MonadOtel m ,
MonadRedacted m
2024-03-17 12:43:05 +01:00
) =>
[ ( ByteString , ByteString ) ] ->
m ( Transaction m () )
redactedSearchAndInsert extraArguments = do
logInfo [ fmt | Doing redacted search with arguments : { showPretty extraArguments } | ]
-- The first search returns the amount of pages, so we use that to query all results piece by piece.
firstPage <- go Nothing
let remainingPages = firstPage . pages - 1
logInfo [ fmt | Got the first page , found { remainingPages } more pages | ]
let otherPagesNum = [ ( 2 :: Natural ) .. remainingPages ]
otherPages <- traverse go ( Just <$> otherPagesNum )
pure $
( firstPage : otherPages )
& concatMap ( . tourGroups )
& \ case
IsNonEmpty tgs -> tgs & insertTourGroupsAndTorrents
IsEmpty -> pure ()
where
go mpage =
redactedSearch
( extraArguments
-- pass the page (for every search but the first one)
2024-03-23 05:36:47 +01:00
<> ( mpage & ifExists ( \ page -> ( " page " , ( page :: Natural ) & showToText & textToBytesUtf8 ) ) )
2024-03-17 12:43:05 +01:00
)
( do
status <- Json . key " status " Json . asText
when ( status /= " success " ) $ do
Json . throwCustomError [ fmt | Status was not " success " , but { status } | ]
Json . key " response " $ do
pages <-
Json . keyMay " pages " ( Field . toJsonParser ( Field . mapError singleError $ Field . jsonNumber >>> Field . boundedScientificIntegral @ Int " not an Integer " >>> Field . integralToNatural ) )
-- in case the field is missing, let’ s assume there is only one page
<&> fromMaybe 1
Json . key " results " $ do
tourGroups <-
label @ " tourGroups "
<$> ( Json . eachInArray $ do
groupId <- Json . keyLabel @ " groupId " " groupId " ( Json . asIntegral @ _ @ Int )
groupName <- Json . keyLabel @ " groupName " " groupName " Json . asText
fullJsonResult <-
label @ " fullJsonResult "
<$> ( Json . asObject
-- remove torrents cause they are inserted separately below
<&> KeyMap . filterWithKey ( \ k _ -> k /= " torrents " )
<&> Json . Object
)
let tourGroup = T3 groupId groupName fullJsonResult
torrents <- Json . keyLabel @ " torrents " " torrents " $
Json . eachInArray $ do
torrentId <- Json . keyLabel @ " torrentId " " torrentId " ( Json . asIntegral @ _ @ Int )
fullJsonResultT <- label @ " fullJsonResult " <$> Json . asValue
pure $ T2 torrentId fullJsonResultT
pure ( T2 ( label @ " tourGroup " tourGroup ) torrents )
)
pure
( T2
( label @ " pages " pages )
tourGroups
)
)
insertTourGroupsAndTorrents ::
NonEmpty
( T2
" tourGroup "
( T3 " groupId " Int " groupName " Text " fullJsonResult " Json . Value )
" torrents "
[ T2 " torrentId " Int " fullJsonResult " Json . Value ]
) ->
Transaction m ()
insertTourGroupsAndTorrents dat = do
let tourGroups = dat <&> ( . tourGroup )
let torrents = dat <&> ( . torrents )
insertTourGroups tourGroups
>>= ( \ res ->
insertTorrents $
zipT2 $
T2
( label @ " torrentGroupIdPg " $ res <&> ( . tourGroupIdPg ) )
( label @ " torrents " ( torrents & toList ) )
)
insertTourGroups ::
NonEmpty
( T3
" groupId "
Int
" groupName "
Text
" fullJsonResult "
Json . Value
) ->
Transaction m [ Label " tourGroupIdPg " Int ]
insertTourGroups dats = do
let groupNames =
dats <&> \ dat -> [ fmt | { dat . groupId } : { dat . groupName } | ]
logInfo [ fmt | Inserting tour groups for { showPretty groupNames } | ]
_ <-
execute
[ fmt |
DELETE FROM redacted . torrent_groups
WHERE group_id = ANY ( ?:: integer [] )
| ]
( Only $ ( dats <&> ( . groupId ) & toList & PGArray :: PGArray Int ) )
executeManyReturningWith
[ fmt |
INSERT INTO redacted . torrent_groups (
group_id , group_name , full_json_result
) VALUES
( ? , ? , ? )
ON CONFLICT ( group_id ) DO UPDATE SET
group_id = excluded . group_id ,
group_name = excluded . group_name ,
full_json_result = excluded . full_json_result
RETURNING ( id )
| ]
( dats <&> \ dat ->
( dat . groupId ,
dat . groupName ,
dat . fullJsonResult
)
)
( label @ " tourGroupIdPg " <$> Dec . fromField @ Int )
insertTorrents ::
[ T2
" torrentGroupIdPg "
Int
" torrents "
[ T2 " torrentId " Int " fullJsonResult " Json . Value ]
] ->
Transaction m ()
insertTorrents dats = do
_ <-
execute
[ sql |
DELETE FROM redacted . torrents_json
WHERE torrent_id = ANY ( ?:: integer [] )
| ]
( Only $
PGArray
[ torrent . torrentId
| dat <- dats ,
torrent <- dat . torrents
]
)
execute
[ sql |
INSERT INTO redacted . torrents_json
( torrent_group
, torrent_id
, full_json_result )
SELECT *
FROM UNNEST (
?:: integer []
, ?:: integer []
, ?:: jsonb []
) AS inputs (
torrent_group
, torrent_id
, full_json_result )
| ]
( [ ( dat . torrentGroupIdPg :: Int ,
group . torrentId :: Int ,
group . fullJsonResult :: Json . Value
)
| dat <- dats ,
group <- dat . torrents
]
& unzip3PGArray
)
pure ()
unzip3PGArray :: [ ( a1 , a2 , a3 ) ] -> ( PGArray a1 , PGArray a2 , PGArray a3 )
unzip3PGArray xs = xs & unzip3 & \ ( a , b , c ) -> ( PGArray a , PGArray b , PGArray c )
redactedGetTorrentFileAndInsert ::
( HasField " torrentId " r Int ,
MonadPostgres m ,
MonadThrow m ,
MonadLogger m ,
2024-07-29 11:47:20 +02:00
MonadOtel m ,
MonadRedacted m
2024-03-17 12:43:05 +01:00
) =>
r ->
Transaction m ( Label " torrentFile " ByteString )
redactedGetTorrentFileAndInsert dat = inSpan' " Redacted Get Torrent File and Insert " $ \ span -> do
2024-07-29 11:47:20 +02:00
bytes <- lift $ redactedGetTorrentFile dat
2024-03-17 12:43:05 +01:00
execute
[ sql |
UPDATE redacted . torrents_json
SET torrent_file = ?:: bytea
WHERE torrent_id = ?:: integer
| ]
( ( Binary bytes :: Binary ByteString ) ,
dat . torrentId
)
>>= assertOneUpdated span " redactedGetTorrentFileAndInsert "
>>= \ () -> pure ( label @ " torrentFile " bytes )
getTorrentFileById ::
( MonadPostgres m ,
HasField " torrentId " r Int ,
MonadThrow m
) =>
r ->
Transaction m ( Maybe ( Label " torrentFile " ByteString ) )
getTorrentFileById dat = do
queryWith
[ sql |
SELECT torrent_file
FROM redacted . torrents
WHERE torrent_id = ?:: integer
| ]
( Only $ ( dat . torrentId :: Int ) )
( fmap @ Maybe ( label @ " torrentFile " ) <$> Dec . byteaMay )
>>= ensureSingleRow
updateTransmissionTorrentHashById ::
( MonadPostgres m ,
HasField " torrentId " r Int ,
HasField " torrentHash " r Text
) =>
r ->
Transaction m ( Label " numberOfRowsAffected " Natural )
updateTransmissionTorrentHashById dat = do
execute
[ sql |
UPDATE redacted . torrents_json
SET transmission_torrent_hash = ?:: text
WHERE torrent_id = ?:: integer
| ]
( dat . torrentHash :: Text ,
dat . torrentId :: Int
)
assertOneUpdated ::
( HasField " numberOfRowsAffected " r Natural , MonadThrow m , MonadIO m ) =>
Otel . Span ->
Text ->
r ->
m ()
assertOneUpdated span name x = case x . numberOfRowsAffected of
1 -> pure ()
2024-08-18 17:30:29 +02:00
n -> appThrow span ( [ fmt | { name :: Text } : Expected to update exactly one row , but updated { n :: Natural } row ( s ) | ] )
2024-03-17 12:43:05 +01:00
data TorrentData transmissionInfo = TorrentData
{ groupId :: Int ,
torrentId :: Int ,
seedingWeight :: Int ,
2024-05-14 20:42:13 +02:00
artists :: [ T2 " artistId " Int " artistName " Text ] ,
2024-05-15 14:09:11 +02:00
torrentGroupJson :: TorrentGroupJson ,
2024-03-17 12:43:05 +01:00
torrentStatus :: TorrentStatus transmissionInfo
}
2024-05-15 14:09:11 +02:00
data TorrentGroupJson = TorrentGroupJson
{ groupName :: Text ,
2024-08-06 11:46:33 +02:00
groupYear :: Natural
2024-05-15 14:09:11 +02:00
}
2024-03-17 12:43:05 +01:00
data TorrentStatus transmissionInfo
= NoTorrentFileYet
| NotInTransmissionYet
| InTransmission ( T2 " torrentHash " Text " transmissionInfo " transmissionInfo )
getTorrentById :: ( MonadPostgres m , HasField " torrentId " r Int , MonadThrow m ) => r -> Transaction m Json . Value
getTorrentById dat = do
queryWith
[ sql |
SELECT full_json_result FROM redacted . torrents
WHERE torrent_id = ?:: integer
| ]
( getLabel @ " torrentId " dat )
( Dec . json Json . asValue )
>>= ensureSingleRow
2024-05-15 14:09:11 +02:00
data GetBestTorrentsFilter = GetBestTorrentsFilter
{ onlyDownloaded :: Bool ,
2024-06-07 11:46:14 +02:00
onlyArtist :: Maybe ( Label " artistRedactedId " Natural )
2024-05-15 14:09:11 +02:00
}
2024-03-17 12:43:05 +01:00
-- | Find the best torrent for each torrent group (based on the seeding_weight)
2024-05-15 14:09:11 +02:00
getBestTorrents ::
( MonadPostgres m ) =>
GetBestTorrentsFilter ->
Transaction m [ TorrentData () ]
2024-05-11 22:35:25 +02:00
getBestTorrents opts = do
2024-03-17 12:43:05 +01:00
queryWith
[ sql |
2024-05-16 21:48:18 +02:00
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
)
2024-05-15 14:09:11 +02:00
SELECT
2024-05-16 21:48:18 +02:00
tg . group_id ,
t . torrent_id ,
t . seeding_weight ,
2024-08-06 11:46:33 +02:00
t . full_json_result -> 'artists' AS artists ,
tg . full_json_result ->> 'groupName' AS group_name ,
tg . full_json_result ->> 'groupYear' AS group_year ,
2024-05-16 21:48:18 +02:00
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
2024-03-17 12:43:05 +01:00
ORDER BY seeding_weight DESC
| ]
2024-05-15 14:09:11 +02:00
( do
let ( onlyArtistB , onlyArtistId ) = case opts . onlyArtist of
Nothing -> ( True , 0 )
2024-06-07 11:46:14 +02:00
Just a -> ( False , a . artistRedactedId )
2024-05-15 14:09:11 +02:00
( opts . onlyDownloaded :: Bool ,
onlyArtistB :: Bool ,
onlyArtistId & fromIntegral @ Natural @ Int
)
)
2024-03-17 12:43:05 +01:00
( do
groupId <- Dec . fromField @ Int
torrentId <- Dec . fromField @ Int
seedingWeight <- Dec . fromField @ Int
2024-08-06 11:46:33 +02:00
artists <- Dec . json $
Json . eachInArray $ do
2024-05-14 20:42:13 +02:00
id_ <- Json . keyLabel @ " artistId " " id " ( Json . asIntegral @ _ @ Int )
name <- Json . keyLabel @ " artistName " " name " Json . asText
pure $ T2 id_ name
2024-08-06 11:46:33 +02:00
torrentGroupJson <- do
groupName <- Dec . text
groupYear <- Dec . textParse Field . decimalNatural
pure $ TorrentGroupJson { .. }
2024-03-17 12:43:05 +01:00
hasTorrentFile <- Dec . fromField @ Bool
transmissionTorrentHash <-
Dec . fromField @ ( Maybe Text )
pure $
TorrentData
{ torrentStatus =
if
| not hasTorrentFile -> NoTorrentFileYet
| Nothing <- transmissionTorrentHash -> NotInTransmissionYet
| Just hash <- transmissionTorrentHash ->
InTransmission $
T2 ( label @ " torrentHash " hash ) ( label @ " transmissionInfo " () ) ,
..
}
)
-- | Do a request to the redacted API. If you know what that is, you know how to find the API docs.
mkRedactedApiRequest ::
( MonadThrow m ,
HasField " action " p ByteString ,
2024-07-29 11:47:20 +02:00
HasField " actionArgs " p [ ( ByteString , Maybe ByteString ) ] ,
MonadRedacted m
2024-03-17 12:43:05 +01:00
) =>
p ->
m Http . Request
mkRedactedApiRequest dat = do
2024-07-29 11:47:20 +02:00
authKey <- getRedactedApiKey
2024-03-17 12:43:05 +01:00
pure $
[ fmt | https :// redacted . ch / ajax . php | ]
& Http . setRequestMethod " GET "
& Http . setQueryString ( ( " action " , Just dat . action ) : dat . actionArgs )
& Http . setRequestHeader " Authorization " [ authKey ]
httpTorrent ::
( MonadIO m ,
MonadThrow m
) =>
Otel . Span ->
Http . Request ->
m ByteString
httpTorrent span req =
Http . httpBS req
>>= assertM
span
( \ resp -> do
2024-08-04 11:14:06 +02:00
let statusCode = resp & Http . getResponseStatus & ( . statusCode )
2024-03-17 12:43:05 +01:00
contentType =
resp
2024-08-04 11:14:06 +02:00
& Http . getResponseHeaders
2024-03-17 12:43:05 +01:00
& List . lookup " content-type "
<&> Wai . parseContentType
<&> ( \ ( ct , _mimeAttributes ) -> ct )
if
| statusCode == 200 ,
Just " application/x-bittorrent " <- contentType ->
2024-08-04 11:14:06 +02:00
Right $ ( resp & Http . getResponseBody )
2024-03-17 12:43:05 +01:00
| statusCode == 200 ,
Just otherType <- contentType ->
Left [ fmt | Redacted returned a non - torrent body , with content - type " {otherType} " | ]
| statusCode == 200 ,
Nothing <- contentType ->
Left [ fmt | Redacted returned a body with unspecified content type | ]
2024-08-18 17:30:29 +02:00
| code <- statusCode -> Left $ AppExceptionPretty [ [ fmt | Redacted returned an non - 200 error code , code { code } | ] , pretty resp ]
2024-03-17 12:43:05 +01:00
)
redactedApiRequestJson ::
( MonadThrow m ,
HasField " action " p ByteString ,
HasField " actionArgs " p [ ( ByteString , Maybe ByteString ) ] ,
2024-07-29 11:47:20 +02:00
MonadOtel m ,
MonadRedacted m
2024-03-17 12:43:05 +01:00
) =>
p ->
Json . Parse ErrorTree a ->
m a
redactedApiRequestJson dat parser =
do
mkRedactedApiRequest dat
2024-08-04 11:09:26 +02:00
>>= Http . httpJson defaults parser