2011-05-17 01:18:34 +00:00
|
|
|
{- git-annex command
|
|
|
|
-
|
2016-09-15 16:51:00 +00:00
|
|
|
- Copyright 2011-2016 Joey Hess <id@joeyh.name>
|
2011-05-17 01:18:34 +00:00
|
|
|
-
|
|
|
|
- Licensed under the GNU GPL version 3 or higher.
|
|
|
|
-}
|
|
|
|
|
Fix build with ghc 8.4+, which broke due to the Semigroup Monoid change
https://prime.haskell.org/wiki/Libraries/Proposals/SemigroupMonoid
I am not happy with the fragile pile of CPP boilerplate required to support
ghc back to 7.0, which git-annex still targets for both the android build
and the standalone build targeting old linux kernels. It makes me unlikely
to want to use Semigroup more in git-annex, because the benefit of the
abstraction is swamped by the ugliness. I actually considered ripping out
all the Semigroup instances, but some are needed to use
optparse-applicative.
The problem, I think, is they made this transaction on too fast a timeline.
(Although ironically, work on it started in 2015 or earlier!)
In particular, Debian oldstable is not out of security support, and it's
not possible to follow the simpler workarounds documented on the wiki and
have it build on oldstable (because the semigroups package in it is too
old).
I have only tested this build with ghc 8.2.2, not the newer and older
versions that branches of the CPP support. So there could be typoes, we'll
see.
This commit was sponsored by Brock Spratlen on Patreon.
2018-05-30 16:28:43 +00:00
|
|
|
{-# LANGUAGE BangPatterns, DeriveDataTypeable, CPP #-}
|
2012-03-11 21:15:58 +00:00
|
|
|
|
2013-11-07 16:45:59 +00:00
|
|
|
module Command.Info where
|
2011-05-17 01:18:34 +00:00
|
|
|
|
2012-10-24 18:43:32 +00:00
|
|
|
import "mtl" Control.Monad.State.Strict
|
2015-04-12 16:49:11 +00:00
|
|
|
import qualified Data.Map.Strict as M
|
Fix mangling of --json output of utf-8 characters when not running in a utf-8 locale
As long as all code imports Utility.Aeson rather than Data.Aeson,
and no Strings that may contain utf-8 characters are used for eg, object
keys via T.pack, this is guaranteed to fix the problem everywhere that
git-annex generates json.
It's kind of annoying to need to wrap ToJSON with a ToJSON', especially
since every data type that has a ToJSON instance has to be ported over.
However, that only took 50 lines of code, which is worth it to ensure full
coverage. I initially tried an alternative approach of a newtype FileEncoded,
which had to be used everywhere a String was fed into aeson, and chasing
down all the sites would have been far too hard. Did consider creating an
intentionally overlapping instance ToJSON String, and letting ghc fail
to build anything that passed in a String, but am not sure that wouldn't
pollute some library that git-annex depends on that happens to use ToJSON
String internally.
This commit was supported by the NSF-funded DataLad project.
2018-04-16 19:42:45 +00:00
|
|
|
import qualified Data.Vector as V
|
2013-09-15 23:10:38 +00:00
|
|
|
import Data.Ord
|
Fix build with ghc 8.4+, which broke due to the Semigroup Monoid change
https://prime.haskell.org/wiki/Libraries/Proposals/SemigroupMonoid
I am not happy with the fragile pile of CPP boilerplate required to support
ghc back to 7.0, which git-annex still targets for both the android build
and the standalone build targeting old linux kernels. It makes me unlikely
to want to use Semigroup more in git-annex, because the benefit of the
abstraction is swamped by the ugliness. I actually considered ripping out
all the Semigroup instances, but some are needed to use
optparse-applicative.
The problem, I think, is they made this transaction on too fast a timeline.
(Although ironically, work on it started in 2015 or earlier!)
In particular, Debian oldstable is not out of security support, and it's
not possible to follow the simpler workarounds documented on the wiki and
have it build on oldstable (because the semigroups package in it is too
old).
I have only tested this build with ghc 8.2.2, not the newer and older
versions that branches of the CPP support. So there could be typoes, we'll
see.
This commit was sponsored by Brock Spratlen on Patreon.
2018-05-30 16:28:43 +00:00
|
|
|
import qualified Data.Semigroup as Sem
|
|
|
|
import Prelude
|
2011-05-17 01:18:34 +00:00
|
|
|
|
2016-01-20 20:36:33 +00:00
|
|
|
import Command
|
2011-06-30 17:16:57 +00:00
|
|
|
import qualified Git
|
2011-11-14 23:27:00 +00:00
|
|
|
import qualified Annex
|
2014-10-21 17:44:17 +00:00
|
|
|
import qualified Remote
|
|
|
|
import qualified Types.Remote as Remote
|
2011-07-06 00:36:43 +00:00
|
|
|
import Utility.DataUnits
|
2012-03-22 21:09:54 +00:00
|
|
|
import Utility.DiskFree
|
2011-10-04 04:40:47 +00:00
|
|
|
import Annex.Content
|
2016-02-19 19:16:52 +00:00
|
|
|
import Annex.UUID
|
2016-09-15 16:51:00 +00:00
|
|
|
import Annex.CatFile
|
2011-10-15 20:21:08 +00:00
|
|
|
import Logs.UUID
|
2011-11-14 20:14:17 +00:00
|
|
|
import Logs.Trust
|
2015-01-13 22:11:03 +00:00
|
|
|
import Logs.Location
|
2015-04-30 18:02:56 +00:00
|
|
|
import Annex.NumCopies
|
2011-09-30 07:20:24 +00:00
|
|
|
import Remote
|
2012-03-22 01:55:02 +00:00
|
|
|
import Config
|
2016-07-30 16:29:59 +00:00
|
|
|
import Git.Config (boolConfig)
|
2016-09-15 16:51:00 +00:00
|
|
|
import qualified Git.LsTree as LsTree
|
2012-04-29 21:48:07 +00:00
|
|
|
import Utility.Percentage
|
Fix mangling of --json output of utf-8 characters when not running in a utf-8 locale
As long as all code imports Utility.Aeson rather than Data.Aeson,
and no Strings that may contain utf-8 characters are used for eg, object
keys via T.pack, this is guaranteed to fix the problem everywhere that
git-annex generates json.
It's kind of annoying to need to wrap ToJSON with a ToJSON', especially
since every data type that has a ToJSON instance has to be ported over.
However, that only took 50 lines of code, which is worth it to ensure full
coverage. I initially tried an alternative approach of a newtype FileEncoded,
which had to be used everywhere a String was fed into aeson, and chasing
down all the sites would have been far too hard. Did consider creating an
intentionally overlapping instance ToJSON String, and letting ghc fail
to build anything that passed in a String, but am not sure that wouldn't
pollute some library that git-annex depends on that happens to use ToJSON
String internally.
This commit was supported by the NSF-funded DataLad project.
2018-04-16 19:42:45 +00:00
|
|
|
import Utility.Aeson hiding (json)
|
2016-08-03 16:37:12 +00:00
|
|
|
import Types.Transfer
|
2012-07-01 20:59:54 +00:00
|
|
|
import Logs.Transfer
|
2017-02-24 19:16:56 +00:00
|
|
|
import Types.Key
|
2012-10-03 21:04:52 +00:00
|
|
|
import Types.TrustLevel
|
2013-05-25 03:07:26 +00:00
|
|
|
import Types.FileMatcher
|
2017-03-10 17:12:24 +00:00
|
|
|
import Types.ActionItem
|
2013-03-11 05:22:56 +00:00
|
|
|
import qualified Limit
|
2016-07-26 23:15:34 +00:00
|
|
|
import Messages.JSON (DualDisp(..), ObjectMap(..))
|
2015-06-16 21:58:15 +00:00
|
|
|
import Annex.BloomFilter
|
|
|
|
import qualified Command.Unused
|
2011-05-17 01:18:34 +00:00
|
|
|
|
|
|
|
-- a named computation that produces a statistic
|
2011-09-20 22:57:05 +00:00
|
|
|
type Stat = StatState (Maybe (String, StatState String))
|
2011-05-17 01:18:34 +00:00
|
|
|
|
2012-03-11 21:15:58 +00:00
|
|
|
-- data about a set of keys
|
|
|
|
data KeyData = KeyData
|
|
|
|
{ countKeys :: Integer
|
|
|
|
, sizeKeys :: Integer
|
|
|
|
, unknownSizeKeys :: Integer
|
2017-02-24 19:16:56 +00:00
|
|
|
, backendsKeys :: M.Map KeyVariety Integer
|
2012-03-11 21:15:58 +00:00
|
|
|
}
|
Fix build with ghc 8.4+, which broke due to the Semigroup Monoid change
https://prime.haskell.org/wiki/Libraries/Proposals/SemigroupMonoid
I am not happy with the fragile pile of CPP boilerplate required to support
ghc back to 7.0, which git-annex still targets for both the android build
and the standalone build targeting old linux kernels. It makes me unlikely
to want to use Semigroup more in git-annex, because the benefit of the
abstraction is swamped by the ugliness. I actually considered ripping out
all the Semigroup instances, but some are needed to use
optparse-applicative.
The problem, I think, is they made this transaction on too fast a timeline.
(Although ironically, work on it started in 2015 or earlier!)
In particular, Debian oldstable is not out of security support, and it's
not possible to follow the simpler workarounds documented on the wiki and
have it build on oldstable (because the semigroups package in it is too
old).
I have only tested this build with ghc 8.2.2, not the newer and older
versions that branches of the CPP support. So there could be typoes, we'll
see.
This commit was sponsored by Brock Spratlen on Patreon.
2018-05-30 16:28:43 +00:00
|
|
|
|
|
|
|
instance Sem.Semigroup KeyData where
|
2018-10-13 05:36:06 +00:00
|
|
|
a <> b = KeyData
|
|
|
|
{ countKeys = countKeys a + countKeys b
|
|
|
|
, sizeKeys = sizeKeys a + sizeKeys b
|
|
|
|
, unknownSizeKeys = unknownSizeKeys a + unknownSizeKeys b
|
|
|
|
, backendsKeys = backendsKeys a <> backendsKeys b
|
|
|
|
}
|
2012-03-11 21:15:58 +00:00
|
|
|
|
2018-04-05 18:44:58 +00:00
|
|
|
instance Monoid KeyData where
|
|
|
|
mempty = KeyData 0 0 0 M.empty
|
2018-10-13 05:36:06 +00:00
|
|
|
#if ! MIN_VERSION_base(4,11,0)
|
Fix build with ghc 8.4+, which broke due to the Semigroup Monoid change
https://prime.haskell.org/wiki/Libraries/Proposals/SemigroupMonoid
I am not happy with the fragile pile of CPP boilerplate required to support
ghc back to 7.0, which git-annex still targets for both the android build
and the standalone build targeting old linux kernels. It makes me unlikely
to want to use Semigroup more in git-annex, because the benefit of the
abstraction is swamped by the ugliness. I actually considered ripping out
all the Semigroup instances, but some are needed to use
optparse-applicative.
The problem, I think, is they made this transaction on too fast a timeline.
(Although ironically, work on it started in 2015 or earlier!)
In particular, Debian oldstable is not out of security support, and it's
not possible to follow the simpler workarounds documented on the wiki and
have it build on oldstable (because the semigroups package in it is too
old).
I have only tested this build with ghc 8.2.2, not the newer and older
versions that branches of the CPP support. So there could be typoes, we'll
see.
This commit was sponsored by Brock Spratlen on Patreon.
2018-05-30 16:28:43 +00:00
|
|
|
mappend = (Sem.<>)
|
|
|
|
#endif
|
2018-04-05 18:44:58 +00:00
|
|
|
|
2013-09-15 23:10:38 +00:00
|
|
|
data NumCopiesStats = NumCopiesStats
|
2013-10-07 08:06:10 +00:00
|
|
|
{ numCopiesVarianceMap :: M.Map Variance Integer
|
2013-09-15 23:10:38 +00:00
|
|
|
}
|
|
|
|
|
2013-10-07 08:06:10 +00:00
|
|
|
newtype Variance = Variance Int
|
|
|
|
deriving (Eq, Ord)
|
2013-09-15 23:10:38 +00:00
|
|
|
|
2013-10-07 08:06:10 +00:00
|
|
|
instance Show Variance where
|
|
|
|
show (Variance n)
|
2015-06-16 17:50:28 +00:00
|
|
|
| n >= 0 = "+" ++ show n
|
|
|
|
| otherwise = show n
|
2013-09-15 23:10:38 +00:00
|
|
|
|
2012-03-11 21:15:58 +00:00
|
|
|
-- cached info that multiple Stats use
|
2011-05-17 01:18:34 +00:00
|
|
|
data StatInfo = StatInfo
|
2012-03-11 21:15:58 +00:00
|
|
|
{ presentData :: Maybe KeyData
|
|
|
|
, referencedData :: Maybe KeyData
|
2015-04-12 16:49:11 +00:00
|
|
|
, repoData :: M.Map UUID KeyData
|
2013-09-15 23:10:38 +00:00
|
|
|
, numCopiesStats :: Maybe NumCopiesStats
|
2015-07-11 14:41:52 +00:00
|
|
|
, infoOptions :: InfoOptions
|
2011-05-17 01:18:34 +00:00
|
|
|
}
|
2015-01-13 22:11:03 +00:00
|
|
|
|
2015-07-11 14:41:52 +00:00
|
|
|
emptyStatInfo :: InfoOptions -> StatInfo
|
2015-01-13 22:11:03 +00:00
|
|
|
emptyStatInfo = StatInfo Nothing Nothing M.empty Nothing
|
2011-05-17 01:18:34 +00:00
|
|
|
|
|
|
|
-- a state monad for running Stats in
|
|
|
|
type StatState = StateT StatInfo Annex
|
|
|
|
|
2015-07-08 16:33:27 +00:00
|
|
|
cmd :: Command
|
2018-02-19 18:28:17 +00:00
|
|
|
cmd = noCommit $ withGlobalOptions [jsonOptions, annexedMatchingOptions] $
|
2015-07-08 19:08:02 +00:00
|
|
|
command "info" SectionQuery
|
|
|
|
"shows information about the specified item or the repository as a whole"
|
2015-07-11 14:41:52 +00:00
|
|
|
(paramRepeating paramItem) (seek <$$> optParser)
|
2011-05-17 01:18:34 +00:00
|
|
|
|
2015-07-11 14:41:52 +00:00
|
|
|
data InfoOptions = InfoOptions
|
|
|
|
{ infoFor :: CmdParams
|
|
|
|
, bytesOption :: Bool
|
2016-01-15 19:56:47 +00:00
|
|
|
, batchOption :: BatchMode
|
2015-07-11 14:41:52 +00:00
|
|
|
}
|
|
|
|
|
|
|
|
optParser :: CmdParamsDesc -> Parser InfoOptions
|
|
|
|
optParser desc = InfoOptions
|
|
|
|
<$> cmdParams desc
|
|
|
|
<*> switch
|
|
|
|
( long "bytes"
|
|
|
|
<> help "display file sizes in bytes"
|
|
|
|
)
|
2016-01-15 19:56:47 +00:00
|
|
|
<*> parseBatchOption
|
2015-07-11 14:41:52 +00:00
|
|
|
|
|
|
|
seek :: InfoOptions -> CommandSeek
|
2016-01-15 19:56:47 +00:00
|
|
|
seek o = case batchOption o of
|
2018-10-01 18:12:06 +00:00
|
|
|
NoBatch -> withWords (commandAction . start o) (infoFor o)
|
added -z
Added -z option to git-annex commands that use --batch, useful for
supporting filenames containing newlines.
It only controls input to --batch, the output will still be line delimited
unless --json or etc is used to get some other output. While git often
makes -z affect both input and output, I don't like trying them together,
and making it affect output would have been a significant complication,
and also git-annex output is generally not intended to be machine parsed,
unless using --json or a format option.
Commands that take pairs like "file key" still separate them with a space
in --batch mode. All such commands take care to support filenames with
spaces when parsing that, so there was no need to change it, and it would
have needed significant changes to the batch machinery to separate tose
with a null.
To make fromkey and registerurl support -z, I had to give them a --batch
option. The implicit batch mode they enter when not provided with input
parameters does not support -z as that would have complicated option
parsing. Seemed better to move these toward using the same --batch as
everything else, though the implicit batch mode can still be used.
This commit was sponsored by Ole-Morten Duesund on Patreon.
2018-09-20 20:09:21 +00:00
|
|
|
Batch fmt -> batchInput fmt Right (itemInfo o)
|
2013-03-11 05:22:56 +00:00
|
|
|
|
2015-07-11 14:41:52 +00:00
|
|
|
start :: InfoOptions -> [String] -> CommandStart
|
|
|
|
start o [] = do
|
|
|
|
globalInfo o
|
2013-03-11 05:22:56 +00:00
|
|
|
stop
|
2015-07-11 14:41:52 +00:00
|
|
|
start o ps = do
|
|
|
|
mapM_ (itemInfo o) ps
|
2013-03-11 05:22:56 +00:00
|
|
|
stop
|
|
|
|
|
2015-07-11 14:41:52 +00:00
|
|
|
globalInfo :: InfoOptions -> Annex ()
|
|
|
|
globalInfo o = do
|
2016-02-19 19:16:52 +00:00
|
|
|
u <- getUUID
|
|
|
|
whenM ((==) DeadTrusted <$> lookupTrust u) $
|
|
|
|
earlyWarning "Warning: This repository is currently marked as dead."
|
2013-09-15 23:17:56 +00:00
|
|
|
stats <- selStats global_fast_stats global_slow_stats
|
2013-11-07 16:45:59 +00:00
|
|
|
showCustom "info" $ do
|
2015-07-11 14:41:52 +00:00
|
|
|
evalStateT (mapM_ showStat stats) (emptyStatInfo o)
|
2013-03-11 05:22:56 +00:00
|
|
|
return True
|
|
|
|
|
2015-07-11 14:41:52 +00:00
|
|
|
itemInfo :: InfoOptions -> String -> Annex ()
|
|
|
|
itemInfo o p = ifM (isdir p)
|
|
|
|
( dirInfo o p
|
2014-10-21 17:44:17 +00:00
|
|
|
, do
|
|
|
|
v <- Remote.byName' p
|
|
|
|
case v of
|
2015-07-11 14:41:52 +00:00
|
|
|
Right r -> remoteInfo o r
|
2015-01-13 22:11:03 +00:00
|
|
|
Left _ -> do
|
|
|
|
v' <- Remote.nameToUUID' p
|
|
|
|
case v' of
|
2015-07-11 14:41:52 +00:00
|
|
|
Right u -> uuidInfo o u
|
2016-01-15 19:56:47 +00:00
|
|
|
Left _ -> ifAnnexed p
|
|
|
|
(fileInfo o p)
|
2016-09-15 16:51:00 +00:00
|
|
|
(treeishInfo o p)
|
2014-10-21 17:24:15 +00:00
|
|
|
)
|
|
|
|
where
|
|
|
|
isdir = liftIO . catchBoolIO . (isDirectory <$$> getFileStatus)
|
2016-01-15 19:56:47 +00:00
|
|
|
|
|
|
|
noInfo :: String -> Annex ()
|
|
|
|
noInfo s = do
|
|
|
|
showStart "info" s
|
2016-09-15 16:51:00 +00:00
|
|
|
showNote $ "not a directory or an annexed file or a treeish or a remote or a uuid"
|
2016-01-15 19:56:47 +00:00
|
|
|
showEndFail
|
2014-10-21 17:24:15 +00:00
|
|
|
|
2015-07-11 14:41:52 +00:00
|
|
|
dirInfo :: InfoOptions -> FilePath -> Annex ()
|
|
|
|
dirInfo o dir = showCustom (unwords ["info", dir]) $ do
|
2016-09-15 16:51:00 +00:00
|
|
|
stats <- selStats
|
|
|
|
(tostats (dir_name:tree_fast_stats True))
|
|
|
|
(tostats tree_slow_stats)
|
2015-07-11 14:41:52 +00:00
|
|
|
evalStateT (mapM_ showStat stats) =<< getDirStatInfo o dir
|
2013-03-11 05:22:56 +00:00
|
|
|
return True
|
2013-09-15 23:17:56 +00:00
|
|
|
where
|
2014-10-09 18:53:13 +00:00
|
|
|
tostats = map (\s -> s dir)
|
2013-09-15 23:17:56 +00:00
|
|
|
|
2016-09-15 16:51:00 +00:00
|
|
|
treeishInfo :: InfoOptions -> String -> Annex ()
|
|
|
|
treeishInfo o t = do
|
|
|
|
mi <- getTreeStatInfo o (Git.Ref t)
|
|
|
|
case mi of
|
|
|
|
Nothing -> noInfo t
|
|
|
|
Just i -> showCustom (unwords ["info", t]) $ do
|
|
|
|
stats <- selStats
|
|
|
|
(tostats (tree_name:tree_fast_stats False))
|
|
|
|
(tostats tree_slow_stats)
|
|
|
|
evalStateT (mapM_ showStat stats) i
|
|
|
|
return True
|
|
|
|
where
|
|
|
|
tostats = map (\s -> s t)
|
|
|
|
|
2015-07-11 14:41:52 +00:00
|
|
|
fileInfo :: InfoOptions -> FilePath -> Key -> Annex ()
|
|
|
|
fileInfo o file k = showCustom (unwords ["info", file]) $ do
|
|
|
|
evalStateT (mapM_ showStat (file_stats file k)) (emptyStatInfo o)
|
2014-10-21 17:24:15 +00:00
|
|
|
return True
|
|
|
|
|
2015-07-11 14:41:52 +00:00
|
|
|
remoteInfo :: InfoOptions -> Remote -> Annex ()
|
|
|
|
remoteInfo o r = showCustom (unwords ["info", Remote.name r]) $ do
|
2015-07-09 20:05:45 +00:00
|
|
|
i <- map (\(k, v) -> simpleStat k (pure v)) <$> Remote.getInfo r
|
2018-06-24 21:38:18 +00:00
|
|
|
let u = Remote.uuid r
|
|
|
|
l <- selStats
|
|
|
|
(uuid_fast_stats u ++ remote_fast_stats r ++ i)
|
|
|
|
(uuid_slow_stats u)
|
2015-07-11 14:41:52 +00:00
|
|
|
evalStateT (mapM_ showStat l) (emptyStatInfo o)
|
2015-01-13 22:11:03 +00:00
|
|
|
return True
|
|
|
|
|
2015-07-11 14:41:52 +00:00
|
|
|
uuidInfo :: InfoOptions -> UUID -> Annex ()
|
|
|
|
uuidInfo o u = showCustom (unwords ["info", fromUUID u]) $ do
|
2018-06-24 21:38:18 +00:00
|
|
|
l <- selStats (uuid_fast_stats u) (uuid_slow_stats u)
|
2015-07-11 14:41:52 +00:00
|
|
|
evalStateT (mapM_ showStat l) (emptyStatInfo o)
|
2014-10-21 17:44:17 +00:00
|
|
|
return True
|
|
|
|
|
2013-09-15 23:17:56 +00:00
|
|
|
selStats :: [Stat] -> [Stat] -> Annex [Stat]
|
|
|
|
selStats fast_stats slow_stats = do
|
|
|
|
fast <- Annex.getState Annex.fast
|
|
|
|
return $ if fast
|
|
|
|
then fast_stats
|
|
|
|
else fast_stats ++ slow_stats
|
2011-05-17 01:18:34 +00:00
|
|
|
|
|
|
|
{- Order is significant. Less expensive operations, and operations
|
|
|
|
- that share data go together.
|
|
|
|
-}
|
2013-03-11 05:22:56 +00:00
|
|
|
global_fast_stats :: [Stat]
|
|
|
|
global_fast_stats =
|
2013-10-02 00:50:46 +00:00
|
|
|
[ repository_mode
|
2015-04-12 16:49:11 +00:00
|
|
|
, repo_list Trusted
|
|
|
|
, repo_list SemiTrusted
|
|
|
|
, repo_list UnTrusted
|
2012-07-01 20:59:54 +00:00
|
|
|
, transfer_list
|
2012-04-23 14:37:05 +00:00
|
|
|
, disk_size
|
2011-11-14 23:27:00 +00:00
|
|
|
]
|
2016-09-15 16:51:00 +00:00
|
|
|
|
2013-03-11 05:22:56 +00:00
|
|
|
global_slow_stats :: [Stat]
|
|
|
|
global_slow_stats =
|
2011-11-14 23:27:00 +00:00
|
|
|
[ tmp_size
|
2011-05-17 02:01:50 +00:00
|
|
|
, bad_data_size
|
2011-09-20 22:13:08 +00:00
|
|
|
, local_annex_keys
|
2011-05-17 02:19:15 +00:00
|
|
|
, local_annex_size
|
2016-09-15 16:51:00 +00:00
|
|
|
, known_annex_files True
|
|
|
|
, known_annex_size True
|
2012-03-12 20:18:14 +00:00
|
|
|
, bloom_info
|
2011-05-17 01:18:34 +00:00
|
|
|
, backend_usage
|
|
|
|
]
|
2016-09-15 16:51:00 +00:00
|
|
|
|
|
|
|
tree_fast_stats :: Bool -> [FilePath -> Stat]
|
|
|
|
tree_fast_stats isworktree =
|
|
|
|
[ const local_annex_keys
|
2013-03-11 05:22:56 +00:00
|
|
|
, const local_annex_size
|
2016-09-15 16:51:00 +00:00
|
|
|
, const (known_annex_files isworktree)
|
|
|
|
, const (known_annex_size isworktree)
|
2013-09-15 23:17:56 +00:00
|
|
|
]
|
2016-09-15 16:51:00 +00:00
|
|
|
|
|
|
|
tree_slow_stats :: [FilePath -> Stat]
|
|
|
|
tree_slow_stats =
|
2013-09-15 23:17:56 +00:00
|
|
|
[ const numcopies_stats
|
2015-04-12 16:49:11 +00:00
|
|
|
, const reposizes_stats
|
2018-04-05 18:44:58 +00:00
|
|
|
, const reposizes_total
|
2013-03-11 05:22:56 +00:00
|
|
|
]
|
2011-05-17 01:18:34 +00:00
|
|
|
|
2014-10-21 17:24:15 +00:00
|
|
|
file_stats :: FilePath -> Key -> [Stat]
|
|
|
|
file_stats f k =
|
2014-10-21 17:44:17 +00:00
|
|
|
[ file_name f
|
2014-10-21 17:24:15 +00:00
|
|
|
, key_size k
|
|
|
|
, key_name k
|
2016-07-30 16:29:59 +00:00
|
|
|
, content_present k
|
2014-10-21 17:24:15 +00:00
|
|
|
]
|
|
|
|
|
2015-01-13 22:11:03 +00:00
|
|
|
remote_fast_stats :: Remote -> [Stat]
|
|
|
|
remote_fast_stats r = map (\s -> s r)
|
2014-10-21 18:36:09 +00:00
|
|
|
[ remote_name
|
2015-04-05 17:51:01 +00:00
|
|
|
, remote_trust
|
2014-10-21 18:36:09 +00:00
|
|
|
, remote_cost
|
|
|
|
, remote_type
|
2014-10-21 17:44:17 +00:00
|
|
|
]
|
|
|
|
|
2018-06-24 21:38:18 +00:00
|
|
|
uuid_fast_stats :: UUID -> [Stat]
|
|
|
|
uuid_fast_stats u = map (\s -> s u)
|
|
|
|
[ repo_uuid
|
|
|
|
, repo_description
|
|
|
|
]
|
|
|
|
|
2015-01-13 22:11:03 +00:00
|
|
|
uuid_slow_stats :: UUID -> [Stat]
|
|
|
|
uuid_slow_stats u = map (\s -> s u)
|
2018-06-24 21:38:18 +00:00
|
|
|
[ repo_annex_keys
|
|
|
|
, repo_annex_size
|
2015-01-13 22:11:03 +00:00
|
|
|
]
|
|
|
|
|
2011-11-20 18:12:48 +00:00
|
|
|
stat :: String -> (String -> StatState String) -> Stat
|
|
|
|
stat desc a = return $ Just (desc, a desc)
|
2011-05-17 01:18:34 +00:00
|
|
|
|
2014-10-21 18:36:09 +00:00
|
|
|
-- The json simply contains the same string that is displayed.
|
|
|
|
simpleStat :: String -> StatState String -> Stat
|
|
|
|
simpleStat desc getval = stat desc $ json id getval
|
|
|
|
|
2011-05-17 02:01:50 +00:00
|
|
|
nostat :: Stat
|
2011-07-15 16:47:14 +00:00
|
|
|
nostat = return Nothing
|
2011-05-17 01:18:34 +00:00
|
|
|
|
Fix mangling of --json output of utf-8 characters when not running in a utf-8 locale
As long as all code imports Utility.Aeson rather than Data.Aeson,
and no Strings that may contain utf-8 characters are used for eg, object
keys via T.pack, this is guaranteed to fix the problem everywhere that
git-annex generates json.
It's kind of annoying to need to wrap ToJSON with a ToJSON', especially
since every data type that has a ToJSON instance has to be ported over.
However, that only took 50 lines of code, which is worth it to ensure full
coverage. I initially tried an alternative approach of a newtype FileEncoded,
which had to be used everywhere a String was fed into aeson, and chasing
down all the sites would have been far too hard. Did consider creating an
intentionally overlapping instance ToJSON String, and letting ghc fail
to build anything that passed in a String, but am not sure that wouldn't
pollute some library that git-annex depends on that happens to use ToJSON
String internally.
This commit was supported by the NSF-funded DataLad project.
2018-04-16 19:42:45 +00:00
|
|
|
json :: ToJSON' j => (j -> String) -> StatState j -> String -> StatState String
|
2015-06-16 17:50:28 +00:00
|
|
|
json fmt a desc = do
|
2011-11-20 18:12:48 +00:00
|
|
|
j <- a
|
2016-07-26 23:15:34 +00:00
|
|
|
lift $ maybeShowJSON $ JSONChunk [(desc, j)]
|
2015-06-16 17:50:28 +00:00
|
|
|
return $ fmt j
|
2011-11-20 18:12:48 +00:00
|
|
|
|
|
|
|
nojson :: StatState String -> String -> StatState String
|
|
|
|
nojson a _ = a
|
|
|
|
|
2011-05-17 02:01:50 +00:00
|
|
|
showStat :: Stat -> StatState ()
|
2012-04-22 03:32:33 +00:00
|
|
|
showStat s = maybe noop calc =<< s
|
2012-11-12 05:05:04 +00:00
|
|
|
where
|
|
|
|
calc (desc, a) = do
|
|
|
|
(lift . showHeader) desc
|
|
|
|
lift . showRaw =<< a
|
2011-05-17 01:18:34 +00:00
|
|
|
|
2012-12-13 17:48:07 +00:00
|
|
|
repository_mode :: Stat
|
2014-10-21 18:36:09 +00:00
|
|
|
repository_mode = simpleStat "repository mode" $ lift $
|
2012-12-13 17:48:07 +00:00
|
|
|
ifM isDirect
|
2015-04-09 16:28:26 +00:00
|
|
|
( return "direct"
|
|
|
|
, ifM (fromRepo Git.repoIsLocalBare)
|
|
|
|
( return "bare"
|
|
|
|
, return "indirect"
|
|
|
|
)
|
|
|
|
)
|
2012-12-13 17:48:07 +00:00
|
|
|
|
2015-04-12 16:49:11 +00:00
|
|
|
repo_list :: TrustLevel -> Stat
|
|
|
|
repo_list level = stat n $ nojson $ lift $ do
|
2014-10-28 20:03:57 +00:00
|
|
|
us <- filter (/= NoUUID) . M.keys
|
|
|
|
<$> (M.union <$> uuidMap <*> remoteMap Remote.name)
|
2011-11-15 04:33:54 +00:00
|
|
|
rs <- fst <$> trustPartition level us
|
2015-06-16 17:50:28 +00:00
|
|
|
countRepoList (length rs)
|
|
|
|
-- This also handles json display.
|
|
|
|
<$> prettyPrintUUIDs n rs
|
2012-11-12 05:05:04 +00:00
|
|
|
where
|
|
|
|
n = showTrustLevel level ++ " repositories"
|
2015-06-16 17:50:28 +00:00
|
|
|
|
|
|
|
countRepoList :: Int -> String -> String
|
|
|
|
countRepoList _ [] = "0"
|
|
|
|
countRepoList n s = show n ++ "\n" ++ beginning s
|
|
|
|
|
2014-10-21 17:44:17 +00:00
|
|
|
dir_name :: FilePath -> Stat
|
2014-10-21 18:36:09 +00:00
|
|
|
dir_name dir = simpleStat "directory" $ pure dir
|
2014-10-21 17:44:17 +00:00
|
|
|
|
2016-09-15 16:51:00 +00:00
|
|
|
tree_name :: String -> Stat
|
|
|
|
tree_name t = simpleStat "tree" $ pure t
|
|
|
|
|
2014-10-21 17:44:17 +00:00
|
|
|
file_name :: FilePath -> Stat
|
2014-10-21 18:36:09 +00:00
|
|
|
file_name file = simpleStat "file" $ pure file
|
2014-10-21 17:44:17 +00:00
|
|
|
|
|
|
|
remote_name :: Remote -> Stat
|
2014-10-21 18:36:09 +00:00
|
|
|
remote_name r = simpleStat "remote" $ pure (Remote.name r)
|
2014-10-21 17:44:17 +00:00
|
|
|
|
2018-06-24 21:38:18 +00:00
|
|
|
repo_description :: UUID -> Stat
|
|
|
|
repo_description = simpleStat "description" . lift . Remote.prettyUUID
|
2014-10-21 17:44:17 +00:00
|
|
|
|
2018-06-24 21:38:18 +00:00
|
|
|
repo_uuid :: UUID -> Stat
|
|
|
|
repo_uuid = simpleStat "uuid" . pure . fromUUID
|
2013-03-11 05:22:56 +00:00
|
|
|
|
2015-04-05 17:51:01 +00:00
|
|
|
remote_trust :: Remote -> Stat
|
|
|
|
remote_trust r = simpleStat "trust" $ lift $
|
|
|
|
showTrustLevel <$> lookupTrust (Remote.uuid r)
|
|
|
|
|
2014-10-21 17:44:17 +00:00
|
|
|
remote_cost :: Remote -> Stat
|
2014-10-21 18:36:09 +00:00
|
|
|
remote_cost r = simpleStat "cost" $ pure $
|
2014-10-21 17:44:17 +00:00
|
|
|
show $ Remote.cost r
|
2014-10-21 17:24:15 +00:00
|
|
|
|
2014-10-21 18:36:09 +00:00
|
|
|
remote_type :: Remote -> Stat
|
|
|
|
remote_type r = simpleStat "type" $ pure $
|
|
|
|
Remote.typename $ Remote.remotetype r
|
|
|
|
|
2013-10-28 19:04:38 +00:00
|
|
|
local_annex_keys :: Stat
|
|
|
|
local_annex_keys = stat "local annex keys" $ json show $
|
|
|
|
countKeys <$> cachedPresentData
|
|
|
|
|
2011-05-17 01:18:34 +00:00
|
|
|
local_annex_size :: Stat
|
2014-10-21 18:36:09 +00:00
|
|
|
local_annex_size = simpleStat "local annex size" $
|
2015-07-11 14:41:52 +00:00
|
|
|
showSizeKeys =<< cachedPresentData
|
2011-05-17 01:18:34 +00:00
|
|
|
|
2018-06-24 21:38:18 +00:00
|
|
|
-- "remote" is in the name for JSON backwards-compatibility
|
|
|
|
repo_annex_keys :: UUID -> Stat
|
|
|
|
repo_annex_keys u = stat "remote annex keys" $ json show $
|
2015-01-13 22:11:03 +00:00
|
|
|
countKeys <$> cachedRemoteData u
|
|
|
|
|
2018-06-24 21:38:18 +00:00
|
|
|
-- "remote" is in the name for JSON backwards-compatibility
|
|
|
|
repo_annex_size :: UUID -> Stat
|
|
|
|
repo_annex_size u = simpleStat "remote annex size" $
|
2015-07-11 14:41:52 +00:00
|
|
|
showSizeKeys =<< cachedRemoteData u
|
2015-01-13 22:11:03 +00:00
|
|
|
|
2016-09-15 16:51:00 +00:00
|
|
|
known_annex_files :: Bool -> Stat
|
|
|
|
known_annex_files isworktree =
|
|
|
|
stat ("annexed files in " ++ treeDesc isworktree) $ json show $
|
|
|
|
countKeys <$> cachedReferencedData
|
2011-05-17 01:18:34 +00:00
|
|
|
|
2016-09-15 16:51:00 +00:00
|
|
|
known_annex_size :: Bool -> Stat
|
|
|
|
known_annex_size isworktree =
|
|
|
|
simpleStat ("size of annexed files in " ++ treeDesc isworktree) $
|
|
|
|
showSizeKeys =<< cachedReferencedData
|
|
|
|
|
|
|
|
treeDesc :: Bool -> String
|
|
|
|
treeDesc True = "working tree"
|
|
|
|
treeDesc False = "tree"
|
2012-03-22 03:23:23 +00:00
|
|
|
|
|
|
|
tmp_size :: Stat
|
2014-02-26 20:52:56 +00:00
|
|
|
tmp_size = staleSize "temporary object directory size" gitAnnexTmpObjectDir
|
2012-03-22 03:23:23 +00:00
|
|
|
|
|
|
|
bad_data_size :: Stat
|
|
|
|
bad_data_size = staleSize "bad keys size" gitAnnexBadDir
|
|
|
|
|
2014-10-21 17:24:15 +00:00
|
|
|
key_size :: Key -> Stat
|
2015-07-11 14:41:52 +00:00
|
|
|
key_size k = simpleStat "size" $ showSizeKeys $ foldKeys [k]
|
2014-10-21 17:24:15 +00:00
|
|
|
|
|
|
|
key_name :: Key -> Stat
|
2014-10-21 18:36:09 +00:00
|
|
|
key_name k = simpleStat "key" $ pure $ key2file k
|
2014-10-21 17:24:15 +00:00
|
|
|
|
2016-07-30 16:29:59 +00:00
|
|
|
content_present :: Key -> Stat
|
|
|
|
content_present k = stat "present" $ json boolConfig $ lift $ inAnnex k
|
|
|
|
|
2012-03-12 20:18:14 +00:00
|
|
|
bloom_info :: Stat
|
2014-10-21 18:36:09 +00:00
|
|
|
bloom_info = simpleStat "bloom filter size" $ do
|
2012-03-12 20:18:14 +00:00
|
|
|
localkeys <- countKeys <$> cachedPresentData
|
2015-06-16 21:58:15 +00:00
|
|
|
capacity <- fromIntegral <$> lift bloomCapacity
|
2012-03-12 20:18:14 +00:00
|
|
|
let note = aside $
|
|
|
|
if localkeys >= capacity
|
|
|
|
then "appears too small for this repository; adjust annex.bloomcapacity"
|
2012-04-29 21:48:07 +00:00
|
|
|
else showPercentage 1 (percentage capacity localkeys) ++ " full"
|
2012-03-12 20:18:14 +00:00
|
|
|
|
2015-06-16 21:58:15 +00:00
|
|
|
-- Two bloom filters are used at the same time when running
|
|
|
|
-- git-annex unused, so double the size of one.
|
2015-07-11 14:41:52 +00:00
|
|
|
sizer <- mkSizer
|
2015-04-12 18:08:40 +00:00
|
|
|
size <- sizer memoryUnits False . (* 2) . fromIntegral . fst <$>
|
2015-06-16 21:58:15 +00:00
|
|
|
lift bloomBitsHashes
|
2012-03-12 20:18:14 +00:00
|
|
|
|
|
|
|
return $ size ++ note
|
|
|
|
|
2012-07-01 20:59:54 +00:00
|
|
|
transfer_list :: Stat
|
2015-06-16 17:50:28 +00:00
|
|
|
transfer_list = stat desc $ nojson $ lift $ do
|
2012-07-01 20:59:54 +00:00
|
|
|
uuidmap <- Remote.remoteMap id
|
|
|
|
ts <- getTransfers
|
Fix mangling of --json output of utf-8 characters when not running in a utf-8 locale
As long as all code imports Utility.Aeson rather than Data.Aeson,
and no Strings that may contain utf-8 characters are used for eg, object
keys via T.pack, this is guaranteed to fix the problem everywhere that
git-annex generates json.
It's kind of annoying to need to wrap ToJSON with a ToJSON', especially
since every data type that has a ToJSON instance has to be ported over.
However, that only took 50 lines of code, which is worth it to ensure full
coverage. I initially tried an alternative approach of a newtype FileEncoded,
which had to be used everywhere a String was fed into aeson, and chasing
down all the sites would have been far too hard. Did consider creating an
intentionally overlapping instance ToJSON String, and letting ghc fail
to build anything that passed in a String, but am not sure that wouldn't
pollute some library that git-annex depends on that happens to use ToJSON
String internally.
This commit was supported by the NSF-funded DataLad project.
2018-04-16 19:42:45 +00:00
|
|
|
maybeShowJSON $ JSONChunk [(desc, V.fromList $ map (uncurry jsonify) ts)]
|
2013-09-25 07:09:06 +00:00
|
|
|
return $ if null ts
|
|
|
|
then "none"
|
|
|
|
else multiLine $
|
|
|
|
map (uncurry $ line uuidmap) $ sort ts
|
2012-11-12 05:05:04 +00:00
|
|
|
where
|
2015-06-16 17:50:28 +00:00
|
|
|
desc = "transfers in progress"
|
2012-11-12 05:05:04 +00:00
|
|
|
line uuidmap t i = unwords
|
2017-02-24 22:51:57 +00:00
|
|
|
[ formatDirection (transferDirection t) ++ "ing"
|
2017-03-10 17:12:24 +00:00
|
|
|
, actionItemDesc
|
|
|
|
(ActionItemAssociatedFile (associatedFile i))
|
|
|
|
(transferKey t)
|
2012-11-12 05:05:04 +00:00
|
|
|
, if transferDirection t == Upload then "to" else "from"
|
|
|
|
, maybe (fromUUID $ transferUUID t) Remote.name $
|
|
|
|
M.lookup (transferUUID t) uuidmap
|
|
|
|
]
|
Fix mangling of --json output of utf-8 characters when not running in a utf-8 locale
As long as all code imports Utility.Aeson rather than Data.Aeson,
and no Strings that may contain utf-8 characters are used for eg, object
keys via T.pack, this is guaranteed to fix the problem everywhere that
git-annex generates json.
It's kind of annoying to need to wrap ToJSON with a ToJSON', especially
since every data type that has a ToJSON instance has to be ported over.
However, that only took 50 lines of code, which is worth it to ensure full
coverage. I initially tried an alternative approach of a newtype FileEncoded,
which had to be used everywhere a String was fed into aeson, and chasing
down all the sites would have been far too hard. Did consider creating an
intentionally overlapping instance ToJSON String, and letting ghc fail
to build anything that passed in a String, but am not sure that wouldn't
pollute some library that git-annex depends on that happens to use ToJSON
String internally.
This commit was supported by the NSF-funded DataLad project.
2018-04-16 19:42:45 +00:00
|
|
|
jsonify t i = object $ map (\(k, v) -> (packString k, v)) $
|
|
|
|
[ ("transfer", toJSON' (formatDirection (transferDirection t)))
|
|
|
|
, ("key", toJSON' (transferKey t))
|
|
|
|
, ("file", toJSON' afile)
|
|
|
|
, ("remote", toJSON' (fromUUID (transferUUID t)))
|
2015-06-16 17:50:28 +00:00
|
|
|
]
|
2017-03-10 17:12:24 +00:00
|
|
|
where
|
|
|
|
AssociatedFile afile = associatedFile i
|
2012-07-01 20:59:54 +00:00
|
|
|
|
2012-03-22 01:55:02 +00:00
|
|
|
disk_size :: Stat
|
2015-07-11 14:41:52 +00:00
|
|
|
disk_size = simpleStat "available local disk space" $
|
2012-03-22 21:09:54 +00:00
|
|
|
calcfree
|
2015-07-11 14:41:52 +00:00
|
|
|
<$> (lift $ annexDiskReserve <$> Annex.getGitConfig)
|
|
|
|
<*> (lift $ inRepo $ getDiskFree . gitAnnexDir)
|
2015-04-12 18:08:40 +00:00
|
|
|
<*> mkSizer
|
2012-11-12 05:05:04 +00:00
|
|
|
where
|
2015-04-12 18:08:40 +00:00
|
|
|
calcfree reserve (Just have) sizer = unwords
|
|
|
|
[ sizer storageUnits False $ nonneg $ have - reserve
|
|
|
|
, "(+" ++ sizer storageUnits False reserve
|
2012-11-12 05:05:04 +00:00
|
|
|
, "reserved)"
|
|
|
|
]
|
2015-04-12 18:08:40 +00:00
|
|
|
calcfree _ _ _ = "unknown"
|
2012-11-12 05:05:04 +00:00
|
|
|
|
|
|
|
nonneg x
|
|
|
|
| x >= 0 = x
|
|
|
|
| otherwise = 0
|
2012-03-22 01:55:02 +00:00
|
|
|
|
2011-05-17 01:18:34 +00:00
|
|
|
backend_usage :: Stat
|
2015-06-16 17:50:28 +00:00
|
|
|
backend_usage = stat "backend usage" $ json fmt $
|
2017-02-24 19:16:56 +00:00
|
|
|
ObjectMap . (M.mapKeys formatKeyVariety) . backendsKeys
|
|
|
|
<$> cachedReferencedData
|
2012-11-12 05:05:04 +00:00
|
|
|
where
|
2016-07-26 23:15:34 +00:00
|
|
|
fmt = multiLine . map (\(b, n) -> b ++ ": " ++ show n) . sort . M.toList . fromObjectMap
|
2011-05-17 01:18:34 +00:00
|
|
|
|
2013-09-15 23:10:38 +00:00
|
|
|
numcopies_stats :: Stat
|
2015-06-16 17:50:28 +00:00
|
|
|
numcopies_stats = stat "numcopies stats" $ json fmt $
|
2013-10-07 08:06:10 +00:00
|
|
|
calc <$> (maybe M.empty numCopiesVarianceMap <$> cachedNumCopiesStats)
|
2013-09-15 23:10:38 +00:00
|
|
|
where
|
Fix mangling of --json output of utf-8 characters when not running in a utf-8 locale
As long as all code imports Utility.Aeson rather than Data.Aeson,
and no Strings that may contain utf-8 characters are used for eg, object
keys via T.pack, this is guaranteed to fix the problem everywhere that
git-annex generates json.
It's kind of annoying to need to wrap ToJSON with a ToJSON', especially
since every data type that has a ToJSON instance has to be ported over.
However, that only took 50 lines of code, which is worth it to ensure full
coverage. I initially tried an alternative approach of a newtype FileEncoded,
which had to be used everywhere a String was fed into aeson, and chasing
down all the sites would have been far too hard. Did consider creating an
intentionally overlapping instance ToJSON String, and letting ghc fail
to build anything that passed in a String, but am not sure that wouldn't
pollute some library that git-annex depends on that happens to use ToJSON
String internally.
This commit was supported by the NSF-funded DataLad project.
2018-04-16 19:42:45 +00:00
|
|
|
calc = V.fromList
|
|
|
|
. map (\(variance, count) -> (show variance, count))
|
2018-04-05 18:54:39 +00:00
|
|
|
. sortBy (flip (comparing fst))
|
2015-06-16 17:50:28 +00:00
|
|
|
. M.toList
|
Fix mangling of --json output of utf-8 characters when not running in a utf-8 locale
As long as all code imports Utility.Aeson rather than Data.Aeson,
and no Strings that may contain utf-8 characters are used for eg, object
keys via T.pack, this is guaranteed to fix the problem everywhere that
git-annex generates json.
It's kind of annoying to need to wrap ToJSON with a ToJSON', especially
since every data type that has a ToJSON instance has to be ported over.
However, that only took 50 lines of code, which is worth it to ensure full
coverage. I initially tried an alternative approach of a newtype FileEncoded,
which had to be used everywhere a String was fed into aeson, and chasing
down all the sites would have been far too hard. Did consider creating an
intentionally overlapping instance ToJSON String, and letting ghc fail
to build anything that passed in a String, but am not sure that wouldn't
pollute some library that git-annex depends on that happens to use ToJSON
String internally.
This commit was supported by the NSF-funded DataLad project.
2018-04-16 19:42:45 +00:00
|
|
|
fmt = multiLine
|
|
|
|
. map (\(variance, count) -> "numcopies " ++ variance ++ ": " ++ show count)
|
|
|
|
. V.toList
|
2013-09-15 23:10:38 +00:00
|
|
|
|
2015-04-12 16:49:11 +00:00
|
|
|
reposizes_stats :: Stat
|
2015-06-16 17:50:28 +00:00
|
|
|
reposizes_stats = stat desc $ nojson $ do
|
2015-07-11 14:41:52 +00:00
|
|
|
sizer <- mkSizer
|
2015-06-16 17:50:28 +00:00
|
|
|
l <- map (\(u, kd) -> (u, sizer storageUnits True (sizeKeys kd)))
|
|
|
|
. sortBy (flip (comparing (sizeKeys . snd)))
|
|
|
|
. M.toList
|
|
|
|
<$> cachedRepoData
|
|
|
|
let maxlen = maximum (map (length . snd) l)
|
2015-10-26 18:55:40 +00:00
|
|
|
descm <- lift uuidDescriptions
|
2015-06-16 17:50:28 +00:00
|
|
|
-- This also handles json display.
|
2016-01-15 18:16:48 +00:00
|
|
|
s <- lift $ prettyPrintUUIDsWith (Just "size") desc descm (Just . show) $
|
2015-06-16 17:50:28 +00:00
|
|
|
map (\(u, sz) -> (u, Just $ mkdisp sz maxlen)) l
|
|
|
|
return $ countRepoList (length l) s
|
2015-04-12 16:49:11 +00:00
|
|
|
where
|
2015-06-16 17:50:28 +00:00
|
|
|
desc = "repositories containing these files"
|
|
|
|
mkdisp sz maxlen = DualDisp
|
|
|
|
{ dispNormal = lpad maxlen sz
|
|
|
|
, dispJson = sz
|
|
|
|
}
|
2015-04-12 16:49:11 +00:00
|
|
|
lpad n s = (replicate (n - length s) ' ') ++ s
|
|
|
|
|
2018-04-05 18:44:58 +00:00
|
|
|
reposizes_total :: Stat
|
|
|
|
reposizes_total = simpleStat "combined size of repositories containing these files" $
|
|
|
|
showSizeKeys . mconcat . M.elems =<< cachedRepoData
|
|
|
|
|
2012-03-11 21:15:58 +00:00
|
|
|
cachedPresentData :: StatState KeyData
|
|
|
|
cachedPresentData = do
|
2011-05-17 01:18:34 +00:00
|
|
|
s <- get
|
2012-03-11 21:15:58 +00:00
|
|
|
case presentData s of
|
2011-05-17 01:18:34 +00:00
|
|
|
Just v -> return v
|
|
|
|
Nothing -> do
|
2014-03-07 16:43:56 +00:00
|
|
|
v <- foldKeys <$> lift (getKeysPresent InRepository)
|
2012-03-11 21:15:58 +00:00
|
|
|
put s { presentData = Just v }
|
|
|
|
return v
|
2011-05-17 01:18:34 +00:00
|
|
|
|
2015-01-13 22:11:03 +00:00
|
|
|
cachedRemoteData :: UUID -> StatState KeyData
|
|
|
|
cachedRemoteData u = do
|
|
|
|
s <- get
|
2015-04-12 16:49:11 +00:00
|
|
|
case M.lookup u (repoData s) of
|
2015-01-13 22:11:03 +00:00
|
|
|
Just v -> return v
|
|
|
|
Nothing -> do
|
2018-04-26 20:13:05 +00:00
|
|
|
let combinedata d uk = finishCheck uk >>= \case
|
|
|
|
Nothing -> return d
|
|
|
|
Just k -> return $ addKey k d
|
|
|
|
v <- lift $ foldM combinedata emptyKeyData
|
|
|
|
=<< loggedKeysFor' u
|
2015-04-12 16:49:11 +00:00
|
|
|
put s { repoData = M.insert u v (repoData s) }
|
2015-01-13 22:11:03 +00:00
|
|
|
return v
|
|
|
|
|
2012-03-11 21:15:58 +00:00
|
|
|
cachedReferencedData :: StatState KeyData
|
|
|
|
cachedReferencedData = do
|
2011-05-17 01:18:34 +00:00
|
|
|
s <- get
|
2012-03-11 21:15:58 +00:00
|
|
|
case referencedData s of
|
2011-05-17 01:18:34 +00:00
|
|
|
Just v -> return v
|
|
|
|
Nothing -> do
|
2012-03-11 21:15:58 +00:00
|
|
|
!v <- lift $ Command.Unused.withKeysReferenced
|
|
|
|
emptyKeyData addKey
|
|
|
|
put s { referencedData = Just v }
|
|
|
|
return v
|
|
|
|
|
2014-10-21 17:24:15 +00:00
|
|
|
-- currently only available for directory info
|
2013-09-15 23:10:38 +00:00
|
|
|
cachedNumCopiesStats :: StatState (Maybe NumCopiesStats)
|
|
|
|
cachedNumCopiesStats = numCopiesStats <$> get
|
|
|
|
|
2015-04-12 16:49:11 +00:00
|
|
|
-- currently only available for directory info
|
|
|
|
cachedRepoData :: StatState (M.Map UUID KeyData)
|
|
|
|
cachedRepoData = repoData <$> get
|
|
|
|
|
2015-07-11 14:41:52 +00:00
|
|
|
getDirStatInfo :: InfoOptions -> FilePath -> Annex StatInfo
|
|
|
|
getDirStatInfo o dir = do
|
2013-09-15 23:17:56 +00:00
|
|
|
fast <- Annex.getState Annex.fast
|
2013-03-11 05:22:56 +00:00
|
|
|
matcher <- Limit.getMatcher
|
2015-04-12 16:49:11 +00:00
|
|
|
(presentdata, referenceddata, numcopiesstats, repodata) <-
|
2013-03-11 05:22:56 +00:00
|
|
|
Command.Unused.withKeysFilesReferencedIn dir initial
|
2013-09-15 23:17:56 +00:00
|
|
|
(update matcher fast)
|
2015-07-11 14:41:52 +00:00
|
|
|
return $ StatInfo (Just presentdata) (Just referenceddata) repodata (Just numcopiesstats) o
|
2013-03-11 05:22:56 +00:00
|
|
|
where
|
2015-04-12 16:49:11 +00:00
|
|
|
initial = (emptyKeyData, emptyKeyData, emptyNumCopiesStats, M.empty)
|
|
|
|
update matcher fast key file vs@(presentdata, referenceddata, numcopiesstats, repodata) =
|
2014-01-18 18:51:55 +00:00
|
|
|
ifM (matcher $ MatchingFile $ FileInfo file file)
|
2013-10-07 06:48:39 +00:00
|
|
|
( do
|
|
|
|
!presentdata' <- ifM (inAnnex key)
|
2013-03-11 05:22:56 +00:00
|
|
|
( return $ addKey key presentdata
|
|
|
|
, return presentdata
|
|
|
|
)
|
2013-10-07 06:48:39 +00:00
|
|
|
let !referenceddata' = addKey key referenceddata
|
2015-04-12 16:49:11 +00:00
|
|
|
(!numcopiesstats', !repodata') <- if fast
|
|
|
|
then return (numcopiesstats, repodata)
|
|
|
|
else do
|
|
|
|
locs <- Remote.keyLocations key
|
|
|
|
nc <- updateNumCopiesStats file numcopiesstats locs
|
|
|
|
return (nc, updateRepoData key locs repodata)
|
|
|
|
return $! (presentdata', referenceddata', numcopiesstats', repodata')
|
2013-03-11 05:22:56 +00:00
|
|
|
, return vs
|
|
|
|
)
|
|
|
|
|
2016-09-15 16:51:00 +00:00
|
|
|
getTreeStatInfo :: InfoOptions -> Git.Ref -> Annex (Maybe StatInfo)
|
|
|
|
getTreeStatInfo o r = do
|
|
|
|
fast <- Annex.getState Annex.fast
|
|
|
|
(ls, cleanup) <- inRepo $ LsTree.lsTree r
|
|
|
|
(presentdata, referenceddata, repodata) <- go fast ls initial
|
|
|
|
ifM (liftIO cleanup)
|
|
|
|
( return $ Just $
|
|
|
|
StatInfo (Just presentdata) (Just referenceddata) repodata Nothing o
|
|
|
|
, return Nothing
|
|
|
|
)
|
|
|
|
where
|
|
|
|
initial = (emptyKeyData, emptyKeyData, M.empty)
|
|
|
|
go _ [] vs = return vs
|
|
|
|
go fast (l:ls) vs@(presentdata, referenceddata, repodata) = do
|
|
|
|
mk <- catKey (LsTree.sha l)
|
|
|
|
case mk of
|
|
|
|
Nothing -> go fast ls vs
|
|
|
|
Just key -> do
|
|
|
|
!presentdata' <- ifM (inAnnex key)
|
|
|
|
( return $ addKey key presentdata
|
|
|
|
, return presentdata
|
|
|
|
)
|
|
|
|
let !referenceddata' = addKey key referenceddata
|
|
|
|
!repodata' <- if fast
|
|
|
|
then return repodata
|
|
|
|
else do
|
|
|
|
locs <- Remote.keyLocations key
|
|
|
|
return (updateRepoData key locs repodata)
|
|
|
|
go fast ls $! (presentdata', referenceddata', repodata')
|
|
|
|
|
2012-03-11 21:15:58 +00:00
|
|
|
emptyKeyData :: KeyData
|
|
|
|
emptyKeyData = KeyData 0 0 0 M.empty
|
2011-09-20 22:57:05 +00:00
|
|
|
|
2013-09-15 23:10:38 +00:00
|
|
|
emptyNumCopiesStats :: NumCopiesStats
|
2013-10-07 08:06:10 +00:00
|
|
|
emptyNumCopiesStats = NumCopiesStats M.empty
|
2013-09-15 23:10:38 +00:00
|
|
|
|
2012-03-11 21:15:58 +00:00
|
|
|
foldKeys :: [Key] -> KeyData
|
|
|
|
foldKeys = foldl' (flip addKey) emptyKeyData
|
|
|
|
|
|
|
|
addKey :: Key -> KeyData -> KeyData
|
|
|
|
addKey key (KeyData count size unknownsize backends) =
|
|
|
|
KeyData count' size' unknownsize' backends'
|
2012-11-12 05:05:04 +00:00
|
|
|
where
|
|
|
|
{- All calculations strict to avoid thunks when repeatedly
|
|
|
|
- applied to many keys. -}
|
|
|
|
!count' = count + 1
|
2017-02-24 19:16:56 +00:00
|
|
|
!backends' = M.insertWith (+) (keyVariety key) 1 backends
|
2012-11-12 05:05:04 +00:00
|
|
|
!size' = maybe size (+ size) ks
|
|
|
|
!unknownsize' = maybe (unknownsize + 1) (const unknownsize) ks
|
|
|
|
ks = keySize key
|
2012-03-11 21:15:58 +00:00
|
|
|
|
2015-04-12 16:49:11 +00:00
|
|
|
updateRepoData :: Key -> [UUID] -> M.Map UUID KeyData -> M.Map UUID KeyData
|
|
|
|
updateRepoData key locs m = m'
|
|
|
|
where
|
|
|
|
!m' = M.unionWith (\_old new -> new) m $
|
|
|
|
M.fromList $ zip locs (map update locs)
|
|
|
|
update loc = addKey key (fromMaybe emptyKeyData $ M.lookup loc m)
|
|
|
|
|
|
|
|
updateNumCopiesStats :: FilePath -> NumCopiesStats -> [UUID] -> Annex NumCopiesStats
|
|
|
|
updateNumCopiesStats file (NumCopiesStats m) locs = do
|
|
|
|
have <- trustExclude UnTrusted locs
|
|
|
|
!variance <- Variance <$> numCopiesCheck' file (-) have
|
|
|
|
let !m' = M.insertWith (+) variance 1 m
|
2013-10-07 08:06:10 +00:00
|
|
|
let !ret = NumCopiesStats m'
|
2013-10-07 06:48:39 +00:00
|
|
|
return ret
|
2013-09-15 23:10:38 +00:00
|
|
|
|
2015-07-11 14:41:52 +00:00
|
|
|
showSizeKeys :: KeyData -> StatState String
|
2015-04-12 18:08:40 +00:00
|
|
|
showSizeKeys d = do
|
|
|
|
sizer <- mkSizer
|
|
|
|
return $ total sizer ++ missingnote
|
2012-11-12 05:05:04 +00:00
|
|
|
where
|
2015-04-12 18:08:40 +00:00
|
|
|
total sizer = sizer storageUnits False $ sizeKeys d
|
2012-11-12 05:05:04 +00:00
|
|
|
missingnote
|
|
|
|
| unknownSizeKeys d == 0 = ""
|
|
|
|
| otherwise = aside $
|
|
|
|
"+ " ++ show (unknownSizeKeys d) ++
|
2013-10-28 19:04:38 +00:00
|
|
|
" unknown size"
|
2011-05-17 02:01:50 +00:00
|
|
|
|
|
|
|
staleSize :: String -> (Git.Repo -> FilePath) -> Stat
|
2013-10-10 21:27:00 +00:00
|
|
|
staleSize label dirspec = go =<< lift (dirKeys dirspec)
|
2012-11-12 05:05:04 +00:00
|
|
|
where
|
|
|
|
go [] = nostat
|
|
|
|
go keys = onsize =<< sum <$> keysizes keys
|
|
|
|
onsize 0 = nostat
|
|
|
|
onsize size = stat label $
|
2015-04-12 18:08:40 +00:00
|
|
|
json (++ aside "clean up with git-annex unused") $ do
|
2015-07-11 14:41:52 +00:00
|
|
|
sizer <- mkSizer
|
2015-04-12 18:08:40 +00:00
|
|
|
return $ sizer storageUnits False size
|
2013-10-13 17:30:24 +00:00
|
|
|
keysizes keys = do
|
2012-11-12 05:05:04 +00:00
|
|
|
dir <- lift $ fromRepo dirspec
|
2013-10-13 17:30:24 +00:00
|
|
|
liftIO $ forM keys $ \k -> catchDefaultIO 0 $
|
2015-01-20 20:58:48 +00:00
|
|
|
getFileSize (dir </> keyFile k)
|
2011-05-17 02:49:41 +00:00
|
|
|
|
|
|
|
aside :: String -> String
|
2011-09-30 07:05:10 +00:00
|
|
|
aside s = " (" ++ s ++ ")"
|
2012-10-02 17:45:30 +00:00
|
|
|
|
|
|
|
multiLine :: [String] -> String
|
|
|
|
multiLine = concatMap (\l -> "\n\t" ++ l)
|
2015-04-12 18:08:40 +00:00
|
|
|
|
2015-07-11 14:41:52 +00:00
|
|
|
mkSizer :: StatState ([Unit] -> Bool -> ByteSize -> String)
|
|
|
|
mkSizer = ifM (bytesOption . infoOptions <$> get)
|
2015-04-12 18:08:40 +00:00
|
|
|
( return (const $ const show)
|
|
|
|
, return roughSize
|
|
|
|
)
|