1- {-# LANGUAGE TupleSections, BangPatterns #-}
1+ {-# LANGUAGE TupleSections #-}
22
33-- TODO change the module name probably Distribution.Server.Features.PackageList.PackageRank
44
@@ -43,7 +43,7 @@ import qualified System.IO as SIO
4343
4444data Scorer = Scorer
4545 { maximumS :: ! Float
46- , score :: ! Float
46+ , score :: ! Float
4747 }
4848 deriving Show
4949
@@ -112,17 +112,18 @@ rankIO
112112 -> ServerEnv
113113 -> TarIndexCacheFeature
114114 -> [PkgInfo ]
115- -> PkgInfo
115+ -> Maybe PkgInfo
116116 -> IO Scorer
117117
118118rankIO _ _ _ _ _ _ _ Nothing = return (Scorer (118 + 16 + 4 + 1 ) 0 )
119- rankIO vers recentDownloads maintainers docs env tarCache pkgs pkg = do
119+ rankIO vers recentDownloads maintainers docs env tarCache pkgs ( Just pkgI) = do
120120 temp <- temporalScore pkg lastUploads versionList recentDownloads
121121 versS <- versionScore versionList vers lastUploads pkg
122122 codeS <- codeScore documentLines srcLines
123123 return (temp <> versS <> codeS <> authorScore maintainers pkg)
124124
125125 where
126+ pkg = packageDescription $ pkgDesc pkgI
126127 pkgId = package pkg
127128 lastUploads =
128129 sortBy (flip compare )
@@ -132,7 +133,7 @@ rankIO vers recentDownloads maintainers docs env tarCache pkgs pkg = do
132133 versionList = sortBy (flip compare )
133134 $ map (pkgVersion . package . packageDescription) (pkgDesc <$> pkgs)
134135 packageEntr = do
135- tarB <- packageTarball tarCache $ pkg
136+ tarB <- packageTarball tarCache pkgI
136137 return
137138 $ (\ (path, _, index) -> (path, ) <$> T. lookup index path)
138139 =<< rightToMaybe tarB
@@ -245,16 +246,16 @@ temporalScore p lastUploads versionList recentDownloads = do
245246 )
246247 5
247248 packageFreshness = case safeHead lastUploads of
248- Nothing -> return 0
249- (Just l) -> freshness versionList l isApp
249+ Nothing -> return 0
250+ (Just l) -> freshness versionList l isApp
250251 freshnessScore = fracScor 10 <$> packageFreshness
251252-- Missing dependencyFreshnessScore for reasonable effectivity needs caching
252253 tractionScore = do
253254 fresh <- packageFreshness
254255 return $ boolScor 1 (fresh * int2Float recentDownloads > 1000 )
255256
256257rankPackagePage :: Maybe PackageDescription -> Scorer
257- rankPackagePage Nothing = Scorer 233 0
258+ rankPackagePage Nothing = Scorer 233 0
258259rankPackagePage (Just p) = tests <> benchs <> desc <> homeP <> sourceRp <> cats
259260 where
260261 tests = boolScor 50 (hasTests p)
@@ -277,7 +278,12 @@ rankPackage
277278 -> [PkgInfo ]
278279 -> IO Float
279280rankPackage versions recentDownloads maintainers docs tarCache env pkgs =
280- total
281- . (<>) (rankPackagePage pkgD)
282- <$> rankIO versions recentDownloads maintainers docs env tarCache pkgs (safeLast pkgs)
281+ total . (<>) (rankPackagePage pkgD) <$> rankIO versions
282+ recentDownloads
283+ maintainers
284+ docs
285+ env
286+ tarCache
287+ pkgs
288+ (safeLast pkgs)
283289 where pkgD = packageDescription . pkgDesc <$> safeLast pkgs
0 commit comments