1
1
{-# LANGUAGE TupleSections #-}
2
2
3
+ -- TODO change the module name probably Distribution.Server.Features.PackageList.PackageRank
4
+
3
5
module Distribution.Server.Features.PackageRank
4
6
( rankPackage
5
7
) where
@@ -8,33 +10,29 @@ import Distribution.Package
8
10
import Distribution.PackageDescription
9
11
import Distribution.Server.Features.Documentation
10
12
( DocumentationFeature (.. ) )
11
- import Distribution.Server.Features.DownloadCount
12
13
import Distribution.Server.Features.PreferredVersions
13
14
import Distribution.Server.Features.PreferredVersions.State
14
15
import Distribution.Server.Features.TarIndexCache
15
- import Distribution.Server.Features.Upload
16
16
import qualified Distribution.Server.Framework.BlobStorage
17
17
as BlobStorage
18
18
import Distribution.Server.Framework.ServerEnv
19
19
( ServerEnv (.. ) )
20
20
import Distribution.Server.Packages.Types
21
- import Distribution.Server.Users.Group
22
- ( queryUserGroups
23
- , size )
24
- import Distribution.Server.Util.CountingMap
25
- ( cmFind )
26
21
import Distribution.Simple.Utils ( safeHead
27
- , safeLast )
22
+ , safeLast
23
+ )
28
24
import Distribution.Types.Version
29
25
import qualified Distribution.Utils.ShortText as S
30
26
31
27
import qualified Codec.Archive.Tar as Tar
32
28
import qualified Codec.Archive.Tar.Entry as Tar
33
29
import Control.Monad ( join
34
- , liftM2 )
30
+ , liftM2
31
+ )
35
32
import qualified Data.ByteString.Lazy as BSL
36
33
import Data.List ( maximumBy
37
- , sortBy )
34
+ , sortBy
35
+ )
38
36
import Data.Maybe ( isNothing )
39
37
import Data.Ord ( comparing )
40
38
import qualified Data.TarIndex as T
@@ -108,35 +106,31 @@ freshness (x : xs) lastUpd app =
108
106
-- TODO CoreFeature can be substituted by CoreResource
109
107
rankIO
110
108
:: VersionsFeature
111
- -> DownloadFeature
112
- -> UploadFeature
109
+ -> Int
110
+ -> Int
113
111
-> DocumentationFeature
114
112
-> ServerEnv
115
113
-> TarIndexCacheFeature
116
114
-> [PkgInfo ]
117
115
-> IO Scorer
118
116
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
121
119
versS <- versionScore versionList vers lastUploads pkg
122
- auth <- authorScore upl pkg
123
120
codeS <- codeScore documentLines srcLines
124
- return (temp <> versS <> auth <> codeS )
121
+ return (temp <> versS <> codeS <> authorScore maintainers pkg )
125
122
126
123
where
127
124
pkg = packageDescription <$> pkgDesc $ last pkgs
128
125
pkgId = package pkg
129
- pkgNm = pkgName pkgId
130
126
lastUploads =
131
127
sortBy (flip compare )
132
128
$ (fst . pkgOriginalUploadInfo <$> pkgs)
133
129
++ (fst . pkgLatestUploadInfo <$> pkgs)
134
130
versionList :: [Version ]
135
131
versionList = sortBy (flip compare )
136
132
$ 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
140
134
tarB <- packageTarball tarCache . head $ pkgs
141
135
return
142
136
$ (\ (path, _, index) -> (path, ) <$> T. lookup index path)
@@ -179,16 +173,12 @@ rankIO vers downs upl docs env tarCache pkgs = do
179
173
blob <- documentBlob
180
174
return $ BlobStorage. filepath (serverBlobStore env) <$> blob
181
175
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
185
179
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)
192
182
193
183
codeScore :: IO Double -> IO Double -> IO Scorer
194
184
codeScore documentL haskellL = do
@@ -241,15 +231,14 @@ versionScore versionList versions lastUploads desc = do
241
231
<> boolScor 5 (not $ null depre)
242
232
243
233
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
246
236
fresh <- freshnessScore
247
- downs <- downloadScore
248
237
tract <- tractionScore
249
- return $ tract <> fresh <> downs
238
+ return $ tract <> fresh <> downloadScore
250
239
where
251
240
isApp = (isNothing . library) p && (not . null . executables) p
252
- downloadScore = calcDownScore <$> downloadsPerMonth
241
+ downloadScore = calcDownScore recentDownloads
253
242
calcDownScore i = Scorer 5 $ min
254
243
( (logBase 2 (int2Double $ max 0 (i - 100 ) + 100 ) - 6.6 )
255
244
/ (if isApp then 5 else 6 )
@@ -261,9 +250,8 @@ temporalScore p lastUploads versionList downloadsPerMonth = do
261
250
freshnessScore = fracScor 10 <$> packageFreshness
262
251
-- Missing dependencyFreshnessScore for reasonable effectivity needs caching
263
252
tractionScore = do
264
- dows <- downloadsPerMonth
265
253
fresh <- packageFreshness
266
- return $ boolScor 1 (fresh * int2Double dows > 1000 )
254
+ return $ boolScor 1 (fresh * int2Double recentDownloads > 1000 )
267
255
268
256
rankPackagePage :: PackageDescription -> Scorer
269
257
rankPackagePage p = tests <> benchs <> desc <> homeP <> sourceRp <> cats
@@ -280,15 +268,15 @@ rankPackagePage p = tests <> benchs <> desc <> homeP <> sourceRp <> cats
280
268
281
269
rankPackage
282
270
:: VersionsFeature
283
- -> DownloadFeature
284
- -> UploadFeature
271
+ -> Int
272
+ -> Int
285
273
-> DocumentationFeature
286
- -> ServerEnv
287
274
-> TarIndexCacheFeature
275
+ -> ServerEnv
288
276
-> [PkgInfo ]
289
277
-> IO Double
290
- rankPackage versions download upload docs env tarCache pkgs =
278
+ rankPackage versions recentDownloads maintainers docs tarCache env pkgs =
291
279
total
292
280
. (<>) (rankPackagePage pkgD)
293
- <$> rankIO versions download upload docs env tarCache pkgs
281
+ <$> rankIO versions recentDownloads maintainers docs env tarCache pkgs
294
282
where pkgD = packageDescription $ pkgDesc $ last pkgs
0 commit comments