Removed dependency on json library; all JSON is now handled by aeson.

I've eyeballed all --json commands, and the only difference should be
that some fields are re-ordered.
This commit is contained in:
Joey Hess 2016-07-26 19:15:34 -04:00
parent eabef6efce
commit 870873bdaa
Failed to extract signature
12 changed files with 68 additions and 56 deletions

View file

@ -11,8 +11,9 @@ module Command.Info where
import "mtl" Control.Monad.State.Strict
import qualified Data.Map.Strict as M
import Text.JSON
import qualified Data.Text as T
import Data.Ord
import Data.Aeson hiding (json)
import Command
import qualified Git
@ -34,7 +35,7 @@ import Logs.Transfer
import Types.TrustLevel
import Types.FileMatcher
import qualified Limit
import Messages.JSON (DualDisp(..))
import Messages.JSON (DualDisp(..), ObjectMap(..))
import Annex.BloomFilter
import qualified Command.Unused
@ -247,10 +248,10 @@ simpleStat desc getval = stat desc $ json id getval
nostat :: Stat
nostat = return Nothing
json :: JSON j => (j -> String) -> StatState j -> String -> StatState String
json :: ToJSON j => (j -> String) -> StatState j -> String -> StatState String
json fmt a desc = do
j <- a
lift $ maybeShowJSON $ JSONObject [(desc, j)]
lift $ maybeShowJSON $ JSONChunk [(desc, j)]
return $ fmt j
nojson :: StatState String -> String -> StatState String
@ -374,7 +375,7 @@ transfer_list :: Stat
transfer_list = stat desc $ nojson $ lift $ do
uuidmap <- Remote.remoteMap id
ts <- getTransfers
maybeShowJSON $ JSONObject [(desc, map (uncurry jsonify) ts)]
maybeShowJSON $ JSONChunk [(desc, map (uncurry jsonify) ts)]
return $ if null ts
then "none"
else multiLine $
@ -388,11 +389,11 @@ transfer_list = stat desc $ nojson $ lift $ do
, maybe (fromUUID $ transferUUID t) Remote.name $
M.lookup (transferUUID t) uuidmap
]
jsonify t i = toJSObject
[ ("transfer", showLcDirection (transferDirection t))
, ("key", key2file (transferKey t))
, ("file", fromMaybe "" (associatedFile i))
, ("remote", fromUUID (transferUUID t))
jsonify t i = object $ map (\(k, v) -> (T.pack k, v)) $
[ ("transfer", toJSON (showLcDirection (transferDirection t)))
, ("key", toJSON (key2file (transferKey t)))
, ("file", toJSON (associatedFile i))
, ("remote", toJSON (fromUUID (transferUUID t)))
]
disk_size :: Stat
@ -415,9 +416,9 @@ disk_size = simpleStat "available local disk space" $
backend_usage :: Stat
backend_usage = stat "backend usage" $ json fmt $
toJSObject . sort . M.toList . backendsKeys <$> cachedReferencedData
ObjectMap . backendsKeys <$> cachedReferencedData
where
fmt = multiLine . map (\(b, n) -> b ++ ": " ++ show n) . fromJSObject
fmt = multiLine . map (\(b, n) -> b ++ ": " ++ show n) . sort . M.toList . fromObjectMap
numcopies_stats :: Stat
numcopies_stats = stat "numcopies stats" $ json fmt $