Skip to content

Commit de621f7

Browse files
committed
integrated PackageRank into ListFeature
1 parent 500571b commit de621f7

File tree

1 file changed

+29
-41
lines changed

1 file changed

+29
-41
lines changed

src/Distribution/Server/Features/PackageRank.hs

Lines changed: 29 additions & 41 deletions
Original file line numberDiff line numberDiff line change
@@ -1,5 +1,7 @@
11
{-# LANGUAGE TupleSections #-}
22

3+
-- TODO change the module name probably Distribution.Server.Features.PackageList.PackageRank
4+
35
module Distribution.Server.Features.PackageRank
46
( rankPackage
57
) where
@@ -8,33 +10,29 @@ import Distribution.Package
810
import Distribution.PackageDescription
911
import Distribution.Server.Features.Documentation
1012
( DocumentationFeature(..) )
11-
import Distribution.Server.Features.DownloadCount
1213
import Distribution.Server.Features.PreferredVersions
1314
import Distribution.Server.Features.PreferredVersions.State
1415
import Distribution.Server.Features.TarIndexCache
15-
import Distribution.Server.Features.Upload
1616
import qualified Distribution.Server.Framework.BlobStorage
1717
as BlobStorage
1818
import Distribution.Server.Framework.ServerEnv
1919
( ServerEnv(..) )
2020
import Distribution.Server.Packages.Types
21-
import Distribution.Server.Users.Group
22-
( queryUserGroups
23-
, size)
24-
import Distribution.Server.Util.CountingMap
25-
( cmFind )
2621
import Distribution.Simple.Utils ( safeHead
27-
, safeLast)
22+
, safeLast
23+
)
2824
import Distribution.Types.Version
2925
import qualified Distribution.Utils.ShortText as S
3026

3127
import qualified Codec.Archive.Tar as Tar
3228
import qualified Codec.Archive.Tar.Entry as Tar
3329
import Control.Monad ( join
34-
, liftM2)
30+
, liftM2
31+
)
3532
import qualified Data.ByteString.Lazy as BSL
3633
import Data.List ( maximumBy
37-
, sortBy)
34+
, sortBy
35+
)
3836
import Data.Maybe ( isNothing )
3937
import Data.Ord ( comparing )
4038
import qualified Data.TarIndex as T
@@ -108,35 +106,31 @@ freshness (x : xs) lastUpd app =
108106
-- TODO CoreFeature can be substituted by CoreResource
109107
rankIO
110108
:: VersionsFeature
111-
-> DownloadFeature
112-
-> UploadFeature
109+
-> Int
110+
-> Int
113111
-> DocumentationFeature
114112
-> ServerEnv
115113
-> TarIndexCacheFeature
116114
-> [PkgInfo]
117115
-> IO Scorer
118116

119-
rankIO vers downs upl docs env tarCache pkgs = do
120-
temp <- temporalScore pkg lastUploads versionList downloadsPerMonth
117+
rankIO vers recentDownloads maintainers docs env tarCache pkgs = do
118+
temp <- temporalScore pkg lastUploads versionList recentDownloads
121119
versS <- versionScore versionList vers lastUploads pkg
122-
auth <- authorScore upl pkg
123120
codeS <- codeScore documentLines srcLines
124-
return (temp <> versS <> auth <> codeS)
121+
return (temp <> versS <> codeS <> authorScore maintainers pkg)
125122

126123
where
127124
pkg = packageDescription <$> pkgDesc $ last pkgs
128125
pkgId = package pkg
129-
pkgNm = pkgName pkgId
130126
lastUploads =
131127
sortBy (flip compare)
132128
$ (fst . pkgOriginalUploadInfo <$> pkgs)
133129
++ (fst . pkgLatestUploadInfo <$> pkgs)
134130
versionList :: [Version]
135131
versionList = sortBy (flip compare)
136132
$ map (pkgVersion . package . packageDescription) (pkgDesc <$> pkgs)
137-
downloadsPerMonth = cmFind pkgNm <$> recentPackageDownloads downs
138-
-- TODO get appropriate pkgInfo (head might fail)
139-
packageEntr = do
133+
packageEntr = do
140134
tarB <- packageTarball tarCache . head $ pkgs
141135
return
142136
$ (\(path, _, index) -> (path, ) <$> T.lookup index path)
@@ -179,16 +173,12 @@ rankIO vers downs upl docs env tarCache pkgs = do
179173
blob <- documentBlob
180174
return $ BlobStorage.filepath (serverBlobStore env) <$> blob
181175

182-
authorScore :: UploadFeature -> PackageDescription -> IO Scorer
183-
authorScore upload desc =
184-
maintScore >>= (\x -> return $ boolScor 1 (not $ S.null $ author desc) <> x)
176+
authorScore :: Int -> PackageDescription -> Scorer
177+
authorScore maintainers desc =
178+
boolScor 1 (not $ S.null $ author desc) <> maintScore
185179
where
186-
pkgNm = pkgName $ package desc
187-
maintScore :: IO Scorer
188-
maintScore = do
189-
maint <- queryUserGroups [maintainersGroup upload pkgNm]
190-
191-
return $ boolScor 3 (size maint > 1) <> scorer 5 (int2Double $ size maint)
180+
maintScore =
181+
boolScor 3 (maintainers > 1) <> scorer 5 (int2Double maintainers)
192182

193183
codeScore :: IO Double -> IO Double -> IO Scorer
194184
codeScore documentL haskellL = do
@@ -241,15 +231,14 @@ versionScore versionList versions lastUploads desc = do
241231
<> boolScor 5 (not $ null depre)
242232

243233
temporalScore
244-
:: PackageDescription -> [CL.UTCTime] -> [Version] -> IO Int -> IO Scorer
245-
temporalScore p lastUploads versionList downloadsPerMonth = do
234+
:: PackageDescription -> [CL.UTCTime] -> [Version] -> Int -> IO Scorer
235+
temporalScore p lastUploads versionList recentDownloads = do
246236
fresh <- freshnessScore
247-
downs <- downloadScore
248237
tract <- tractionScore
249-
return $ tract <> fresh <> downs
238+
return $ tract <> fresh <> downloadScore
250239
where
251240
isApp = (isNothing . library) p && (not . null . executables) p
252-
downloadScore = calcDownScore <$> downloadsPerMonth
241+
downloadScore = calcDownScore recentDownloads
253242
calcDownScore i = Scorer 5 $ min
254243
( (logBase 2 (int2Double $ max 0 (i - 100) + 100) - 6.6)
255244
/ (if isApp then 5 else 6)
@@ -261,9 +250,8 @@ temporalScore p lastUploads versionList downloadsPerMonth = do
261250
freshnessScore = fracScor 10 <$> packageFreshness
262251
-- Missing dependencyFreshnessScore for reasonable effectivity needs caching
263252
tractionScore = do
264-
dows <- downloadsPerMonth
265253
fresh <- packageFreshness
266-
return $ boolScor 1 (fresh * int2Double dows > 1000)
254+
return $ boolScor 1 (fresh * int2Double recentDownloads > 1000)
267255

268256
rankPackagePage :: PackageDescription -> Scorer
269257
rankPackagePage p = tests <> benchs <> desc <> homeP <> sourceRp <> cats
@@ -280,15 +268,15 @@ rankPackagePage p = tests <> benchs <> desc <> homeP <> sourceRp <> cats
280268

281269
rankPackage
282270
:: VersionsFeature
283-
-> DownloadFeature
284-
-> UploadFeature
271+
-> Int
272+
-> Int
285273
-> DocumentationFeature
286-
-> ServerEnv
287274
-> TarIndexCacheFeature
275+
-> ServerEnv
288276
-> [PkgInfo]
289277
-> IO Double
290-
rankPackage versions download upload docs env tarCache pkgs =
278+
rankPackage versions recentDownloads maintainers docs tarCache env pkgs =
291279
total
292280
. (<>) (rankPackagePage pkgD)
293-
<$> rankIO versions download upload docs env tarCache pkgs
281+
<$> rankIO versions recentDownloads maintainers docs env tarCache pkgs
294282
where pkgD = packageDescription $ pkgDesc $ last pkgs

0 commit comments

Comments
 (0)