summaryrefslogtreecommitdiff
path: root/Command/Status.hs
diff options
context:
space:
mode:
authorGravatar Joey Hess <joey@kitenet.net>2013-10-07 04:06:10 -0400
committerGravatar Joey Hess <joey@kitenet.net>2013-10-07 04:06:10 -0400
commit11c249244a9ec185225baecb79ec9505cb79d94e (patch)
tree2d2a61019defd49d35c5868beaab56984ecd9bd4 /Command/Status.hs
parentc0caa37187e9c062825dd6d5cb6be2dfa63bc7dd (diff)
Revert "use vector in local status", which was not an improvement
Diffstat (limited to 'Command/Status.hs')
-rw-r--r--Command/Status.hs53
1 files changed, 17 insertions, 36 deletions
diff --git a/Command/Status.hs b/Command/Status.hs
index d1f51c067..e9df79eb3 100644
--- a/Command/Status.hs
+++ b/Command/Status.hs
@@ -11,8 +11,6 @@ module Command.Status where
import "mtl" Control.Monad.State.Strict
import qualified Data.Map as M
-import qualified Data.Vector as V
-import qualified Data.Vector.Mutable as MV
import Text.JSON
import Data.Tuple
import Data.Ord
@@ -50,23 +48,16 @@ data KeyData = KeyData
}
data NumCopiesStats = NumCopiesStats
- { numCopiesVariances :: V.Vector Int
+ { numCopiesVarianceMap :: M.Map Variance Integer
}
-{- Since variances can be negative, maxVariance will be
- - added to a variance to get its position within the vector. -}
-maxVariance :: Int
-maxVariance = 1000
+newtype Variance = Variance Int
+ deriving (Eq, Ord)
-toVariance :: Int -> Int
-toVariance n = n + maxVariance
-
-showVariance :: Int -> String
-showVariance v
- | n >= 0 = "numcopies +" ++ show n
- | otherwise = "numcopies -" ++ show n
- where
- n = v - maxVariance
+instance Show Variance where
+ show (Variance n)
+ | n >= 0 = "numcopies +" ++ show n
+ | otherwise = "numcopies " ++ show n
-- cached info that multiple Stats use
data StatInfo = StatInfo
@@ -276,14 +267,12 @@ backend_usage = stat "backend usage" $ nojson $
M.unionWith (+) x y
numcopies_stats :: Stat
-numcopies_stats = stat "numcopies stats" $ nojson $ do
- gen . calc . maybe [] (V.toList . numCopiesVariances)
- <$> cachedNumCopiesStats
+numcopies_stats = stat "numcopies stats" $ nojson $
+ calc <$> (maybe M.empty numCopiesVarianceMap <$> cachedNumCopiesStats)
where
- gen = multiLine
- . map (\(variance, count) -> showVariance variance ++ ": " ++ show count)
- . reverse . sortBy (comparing snd)
- calc = filter (\(_variance, count) -> count > 0) . zip [0..]
+ calc = multiLine
+ . map (\(variance, count) -> show variance ++ ": " ++ show count)
+ . reverse . sortBy (comparing snd) . M.toList
cachedPresentData :: StatState KeyData
cachedPresentData = do
@@ -339,7 +328,7 @@ emptyKeyData :: KeyData
emptyKeyData = KeyData 0 0 0 M.empty
emptyNumCopiesStats :: NumCopiesStats
-emptyNumCopiesStats = NumCopiesStats $ V.replicate (maxVariance * 2) 0
+emptyNumCopiesStats = NumCopiesStats M.empty
foldKeys :: [Key] -> KeyData
foldKeys = foldl' (flip addKey) emptyKeyData
@@ -357,19 +346,11 @@ addKey key (KeyData count size unknownsize backends) =
ks = keySize key
updateNumCopiesStats :: Key -> FilePath -> NumCopiesStats -> Annex NumCopiesStats
-updateNumCopiesStats key file (NumCopiesStats v) = do
- !variance <- toVariance <$> numCopiesCheck file key (-)
- let !v' = V.modify (update variance) v
- let !ret = NumCopiesStats v'
+updateNumCopiesStats key file (NumCopiesStats m) = do
+ !variance <- Variance <$> numCopiesCheck file key (-)
+ let !m' = M.insertWith' (+) variance 1 m
+ let !ret = NumCopiesStats m'
return ret
- where
- update variance mv
- -- ignore really large variances (extremely unlikely)
- | variance < 0 || variance >= maxVariance * 2 = noop
- | otherwise = do
- n <- MV.read mv variance
- let !n' = n+1
- MV.write mv variance n'
showSizeKeys :: KeyData -> String
showSizeKeys d = total ++ missingnote