summaryrefslogtreecommitdiff
diff options
context:
space:
mode:
-rw-r--r--Command/Status.hs53
-rw-r--r--debian/control1
-rw-r--r--doc/install/fromscratch.mdwn1
-rw-r--r--git-annex.cabal2
4 files changed, 18 insertions, 39 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
diff --git a/debian/control b/debian/control
index f89b6ff58..911974604 100644
--- a/debian/control
+++ b/debian/control
@@ -8,7 +8,6 @@ Build-Depends:
libghc-missingh-dev,
libghc-hslogger-dev,
libghc-pcre-light-dev,
- libghc-vector-dev,
libghc-sha-dev,
libghc-cryptohash-dev,
libghc-regex-tdfa-dev [!mips !mipsel !s390],
diff --git a/doc/install/fromscratch.mdwn b/doc/install/fromscratch.mdwn
index 62fb75403..c85de7ef0 100644
--- a/doc/install/fromscratch.mdwn
+++ b/doc/install/fromscratch.mdwn
@@ -6,7 +6,6 @@ quite a lot.
* [mtl](http://hackage.haskell.org.package/mtl) (2.1.1 or newer)
* [MissingH](http://github.com/jgoerzen/missingh/wiki)
* [utf8-string](http://hackage.haskell.org/package/utf8-string)
- * [vector](http://hackage.haskell.org/package/vector)
* [SHA](http://hackage.haskell.org/package/SHA)
* [cryptohash](http://hackage.haskell.org/package/cryptohash) (optional but recommended)
* [dataenc](http://hackage.haskell.org/package/dataenc)
diff --git a/git-annex.cabal b/git-annex.cabal
index c8dc4bb9b..20ac48511 100644
--- a/git-annex.cabal
+++ b/git-annex.cabal
@@ -78,7 +78,7 @@ Executable git-annex
Main-Is: git-annex.hs
Build-Depends: MissingH, hslogger, directory, filepath,
containers, utf8-string, network (>= 2.0), mtl (>= 2),
- bytestring, old-locale, time, HTTP, vector,
+ bytestring, old-locale, time, HTTP,
extensible-exceptions, dataenc, SHA, process, json,
base (>= 4.5 && < 4.9), monad-control, MonadCatchIO-transformers,
IfElse, text, QuickCheck >= 2.1, bloomfilter, edit-distance, process,