summaryrefslogtreecommitdiff
diff options
context:
space:
mode:
-rw-r--r--Biz/Devalloc.hs19
1 files changed, 17 insertions, 2 deletions
diff --git a/Biz/Devalloc.hs b/Biz/Devalloc.hs
index cafe9fa..2131983 100644
--- a/Biz/Devalloc.hs
+++ b/Biz/Devalloc.hs
@@ -13,6 +13,7 @@
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE Strict #-}
{-# LANGUAGE TemplateHaskell #-}
+{-# LANGUAGE TupleSections #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeOperators #-}
@@ -83,6 +84,7 @@ import Data.Data (Data, Typeable)
import Data.IxSet (Indexable (..), IxSet, ixFun, ixSet, (&&&), (@=))
import qualified Data.IxSet as IxSet
import qualified Data.List as List
+import qualified Data.Map as Map
import Data.SafeCopy (base, deriveSafeCopy, extension)
import qualified Data.SafeCopy as SafeCopy
import qualified Data.Set as Set
@@ -271,6 +273,7 @@ data Analysis0 = Analysis0
{ analysisId :: Id.Id Analysis0,
url :: URL,
bareRepo :: FilePath,
+ repoVisibility :: Visibility,
blackholes :: [Text],
liabilities :: [Text],
stale :: [(FilePath, Int)],
@@ -299,6 +302,9 @@ data Analysis = Analysis
blackholes :: [Text],
-- | A path with < 3 active contributors
liabilities :: [Text],
+ -- | Map of path to number of commits, for detecting paths that continually
+ -- get rewritten.
+ hotspotMap :: Map FilePath Int,
-- | Files that have not been touched in 6 months
stale :: [(FilePath, Int)],
-- | Total score for the repo
@@ -319,7 +325,7 @@ instance SafeCopy.Migrate Analysis where
migrate Analysis0 {..} =
Analysis
{ analysisId = Id.mk (Proxy :: Proxy Analysis) <| Id.untag analysisId,
- repoVisibility = Public,
+ hotspotMap = mempty,
..
}
@@ -1461,6 +1467,8 @@ analyze keep askedBy activeAuthors url bareRepo repoPrivate = do
let numBlackholes = realToFrac <| length blackholes
let numLiabilities = realToFrac <| length liabilities
let numTotal = realToFrac <| length tree
+ hotspotMap <-
+ Map.fromList </ Async.mapConcurrently getChangeCount tree
Analysis
{ analysisId = mempty,
stale =
@@ -1479,6 +1487,13 @@ analyze keep askedBy activeAuthors url bareRepo repoPrivate = do
third :: (a, b, c) -> c
third (_, _, a) = a
git args = Process.readProcess "git" (["--git-dir", bareRepo] ++ args) ""
+ getChangeCount :: FilePath -> IO (FilePath, Int)
+ getChangeCount path =
+ git ["rev-list", "--count", "HEAD", "--", path]
+ /> filter (/= '\n')
+ /> readMaybe
+ /> fromMaybe 0
+ /> (path,)
-- | Does the aggregate score calculation given number of files found to be
-- blackholes, liabilities, etc.
@@ -1529,7 +1544,7 @@ lastTouched bareRepo path = do
where
calculateAge now n = round <| Time.diffUTCTime now n / Time.nominalDay
--- | Given a git dir and a path inside the git repo, pure a list of tuples
+-- | Given a git dir and a path inside the git repo, return a list of tuples
-- with number of commits and author.
authorsFor ::
FilePath ->