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

@ -12,6 +12,7 @@ git-annex (6.20160726) UNRELEASED; urgency=medium
since aws 0.14.0 is not compatible with the newer version. since aws 0.14.0 is not compatible with the newer version.
* git-annex.cabal: Temporarily limit to persistent <2.5 * git-annex.cabal: Temporarily limit to persistent <2.5
since esqueleto 2.4.3 is not compatible with the newer version. since esqueleto 2.4.3 is not compatible with the newer version.
* Removed dependency on json library; all JSON is now handled by aeson.
-- Joey Hess <id@joeyh.name> Wed, 20 Jul 2016 12:03:15 -0400 -- Joey Hess <id@joeyh.name> Wed, 20 Jul 2016 12:03:15 -0400

View file

@ -146,7 +146,7 @@ perform file = do
cleanup :: Key -> Bool -> CommandCleanup cleanup :: Key -> Bool -> CommandCleanup
cleanup key hascontent = do cleanup key hascontent = do
maybeShowJSON $ JSONObject [("key", key2file key)] maybeShowJSON $ JSONChunk [("key", key2file key)]
when hascontent $ when hascontent $
logStatus key InfoPresent logStatus key InfoPresent
return True return True

View file

@ -356,7 +356,7 @@ cleanup u url file key mtmp = case mtmp of
) )
where where
go = do go = do
maybeShowJSON $ JSONObject [("key", key2file key)] maybeShowJSON $ JSONChunk [("key", key2file key)]
when (isJust mtmp) $ when (isJust mtmp) $
logStatus key InfoPresent logStatus key InfoPresent
setUrlPresent u key url setUrlPresent u key url

View file

@ -66,7 +66,7 @@ start o file key = ifM (limited <||> inAnnex key)
showFormatted :: Maybe Utility.Format.Format -> String -> [(String, String)] -> Annex () showFormatted :: Maybe Utility.Format.Format -> String -> [(String, String)] -> Annex ()
showFormatted format unformatted vars = showFormatted format unformatted vars =
unlessM (showFullJSON $ JSONObject vars) $ unlessM (showFullJSON $ JSONChunk vars) $
case format of case format of
Nothing -> liftIO $ putStrLn unformatted Nothing -> liftIO $ putStrLn unformatted
Just formatter -> liftIO $ putStr $ Just formatter -> liftIO $ putStr $

View file

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

View file

@ -43,7 +43,7 @@ displayStatus s = do
let c = statusChar s let c = statusChar s
absf <- fromRepo $ fromTopFilePath (statusFile s) absf <- fromRepo $ fromTopFilePath (statusFile s)
f <- liftIO $ relPathCwdToFile absf f <- liftIO $ relPathCwdToFile absf
unlessM (showFullJSON $ JSONObject [("status", [c]), ("file", f)]) $ unlessM (showFullJSON $ JSONChunk [("status", [c]), ("file", f)]) $
liftIO $ putStrLn $ [c] ++ " " ++ f liftIO $ putStrLn $ [c] ++ " " ++ f
-- Git thinks that present direct mode files are typechanged. -- Git thinks that present direct mode files are typechanged.

View file

@ -14,19 +14,21 @@ module Messages.JSON (
add, add,
complete, complete,
DualDisp(..), DualDisp(..),
ObjectMap(..),
ParsedJSON(..), ParsedJSON(..),
) where ) where
import qualified Text.JSON as JSON
import Data.Aeson import Data.Aeson
import Control.Applicative import Control.Applicative
import qualified Data.Map as M
import qualified Data.Text as T
import qualified Utility.JSONStream as Stream import qualified Utility.JSONStream as Stream
import Types.Key import Types.Key
import Data.Maybe import Data.Maybe
start :: String -> Maybe FilePath -> Maybe Key -> IO () start :: String -> Maybe FilePath -> Maybe Key -> IO ()
start command file key = putStr $ Stream.start $ Stream.JSONObject $ catMaybes start command file key = putStr $ Stream.start $ Stream.JSONChunk $ catMaybes
[ part "command" (Just command) [ part "command" (Just command)
, part "file" file , part "file" file
, part "key" (fmap key2file key) , part "key" (fmap key2file key)
@ -36,10 +38,10 @@ start command file key = putStr $ Stream.start $ Stream.JSONObject $ catMaybes
part l (Just v) = Just (l, v) part l (Just v) = Just (l, v)
end :: Bool -> IO () end :: Bool -> IO ()
end b = putStr $ Stream.add (Stream.JSONObject [("success", b)]) ++ Stream.end end b = putStr $ Stream.add (Stream.JSONChunk [("success", b)]) ++ Stream.end
note :: String -> IO () note :: String -> IO ()
note s = add (Stream.JSONObject [("note", s)]) note s = add (Stream.JSONChunk [("note", s)])
add :: Stream.JSONChunk a -> IO () add :: Stream.JSONChunk a -> IO ()
add = putStr . Stream.add add = putStr . Stream.add
@ -53,13 +55,22 @@ data DualDisp = DualDisp
, dispJson :: String , dispJson :: String
} }
instance JSON.JSON DualDisp where instance ToJSON DualDisp where
showJSON = JSON.JSString . JSON.toJSString . dispJson toJSON = toJSON . dispJson
readJSON _ = JSON.Error "stub"
instance Show DualDisp where instance Show DualDisp where
show = dispNormal show = dispNormal
-- A Map that is serialized to JSON as an object, with each key being a
-- field of the object. This is different from Aeson's normal
-- serialization of Map, which uses "[key, value]".
data ObjectMap a = ObjectMap { fromObjectMap :: M.Map String a }
instance ToJSON a => ToJSON (ObjectMap a) where
toJSON (ObjectMap m) = object $ map go $ M.toList m
where
go (k, v) = (T.pack k, toJSON v)
-- An Aeson parser for the JSON output by this module, and -- An Aeson parser for the JSON output by this module, and
-- similar JSON input from users. -- similar JSON input from users.
data ParsedJSON a = ParsedJSON data ParsedJSON a = ParsedJSON

View file

@ -55,10 +55,10 @@ module Remote (
claimingUrl, claimingUrl,
) where ) where
import qualified Data.Map as M
import Text.JSON
import Text.JSON.Generic
import Data.Ord import Data.Ord
import Data.Aeson
import qualified Data.Map as M
import qualified Data.Text as T
import Annex.Common import Annex.Common
import Types.Remote import Types.Remote
@ -194,7 +194,7 @@ prettyPrintUUIDsDescs header descm uuids =
{- An optional field can be included in the list of UUIDs. -} {- An optional field can be included in the list of UUIDs. -}
prettyPrintUUIDsWith prettyPrintUUIDsWith
:: JSON v :: ToJSON v
=> Maybe String => Maybe String
-> String -> String
-> M.Map UUID RemoteName -> M.Map UUID RemoteName
@ -203,7 +203,7 @@ prettyPrintUUIDsWith
-> Annex String -> Annex String
prettyPrintUUIDsWith optfield header descm showval uuidvals = do prettyPrintUUIDsWith optfield header descm showval uuidvals = do
hereu <- getUUID hereu <- getUUID
maybeShowJSON $ JSONObject [(header, map (jsonify hereu) uuidvals)] maybeShowJSON $ JSONChunk [(header, map (jsonify hereu) uuidvals)]
return $ unwords $ map (\u -> "\t" ++ prettify hereu u ++ "\n") uuidvals return $ unwords $ map (\u -> "\t" ++ prettify hereu u ++ "\n") uuidvals
where where
finddescription u = M.findWithDefault "" u descm finddescription u = M.findWithDefault "" u descm
@ -220,12 +220,12 @@ prettyPrintUUIDsWith optfield header descm showval uuidvals = do
addoptval s = case showval =<< optval of addoptval s = case showval =<< optval of
Nothing -> s Nothing -> s
Just val -> val ++ ": " ++ s Just val -> val ++ ": " ++ s
jsonify hereu (u, optval) = toJSObject $ catMaybes jsonify hereu (u, optval) = object $ catMaybes
[ Just ("uuid", toJSON $ fromUUID u) [ Just (T.pack "uuid", toJSON $ fromUUID u)
, Just ("description", toJSON $ finddescription u) , Just (T.pack "description", toJSON $ finddescription u)
, Just ("here", toJSON $ hereu == u) , Just (T.pack "here", toJSON $ hereu == u)
, case (optfield, optval) of , case (optfield, optval) of
(Just field, Just val) -> Just (field, showJSON val) (Just field, Just val) -> Just (T.pack field, toJSON val)
_ -> Nothing _ -> Nothing
] ]

11
Test.hs
View file

@ -32,7 +32,8 @@ import Test.Tasty.Ingredients.Rerun
import Options.Applicative (switch, long, help) import Options.Applicative (switch, long, help)
import qualified Data.Map as M import qualified Data.Map as M
import qualified Text.JSON import qualified Data.Aeson
import qualified Data.ByteString.Lazy.UTF8 as BU8
import Common import Common
@ -924,10 +925,10 @@ test_merge = intmpclonerepo $
test_info :: Assertion test_info :: Assertion
test_info = intmpclonerepo $ do test_info = intmpclonerepo $ do
json <- git_annex_output "info" ["--json"] json <- BU8.fromString <$> git_annex_output "info" ["--json"]
case Text.JSON.decodeStrict json :: Text.JSON.Result (Text.JSON.JSObject Text.JSON.JSValue) of case Data.Aeson.eitherDecode json :: Either String Data.Aeson.Value of
Text.JSON.Ok _ -> return () Right _ -> return ()
Text.JSON.Error e -> assertFailure e Left e -> assertFailure e
test_version :: Assertion test_version :: Assertion
test_version = intmpclonerepo $ test_version = intmpclonerepo $

View file

@ -14,31 +14,30 @@ module Utility.JSONStream (
end end
) where ) where
import qualified Text.JSON as JSON import Data.Aeson
import qualified Data.Aeson as Aeson import qualified Data.Text as T
import qualified Data.ByteString.Lazy.UTF8 as B import qualified Data.ByteString.Lazy.UTF8 as B
{- Only JSON objects can be used as chunks in the stream, not data JSONChunk v where
- other values. JSONChunk :: ToJSON v => [(String, v)] -> JSONChunk [(String, v)]
- AesonObject :: Object -> JSONChunk Object
- Both Aeson and Text.Json objects are supported. -}
data JSONChunk a where
JSONObject :: JSON.JSON a => [(String, a)] -> JSONChunk [(String, a)]
AesonObject :: Aeson.Object -> JSONChunk Aeson.Object
encodeJSONChunk :: JSONChunk a -> String encodeJSONChunk :: JSONChunk v -> B.ByteString
encodeJSONChunk (JSONObject l) = JSON.encodeStrict $ JSON.toJSObject l encodeJSONChunk (JSONChunk l) = encode $ object $ map mkPair l
encodeJSONChunk (AesonObject o) = B.toString (Aeson.encode o) where
mkPair (s, v) = (T.pack s, toJSON v)
encodeJSONChunk (AesonObject o) = encode o
{- Text.JSON and Aeson do not support building up a larger JSON document {- Aeson does not support building up a larger JSON object piece by piece
- piece by piece as a stream. To support streaming, a hack. The final "}" - with streaming output. To support streaming, a hack:
- is left off the object, allowing it to be added to later. -} - The final "}" is left off the JSON, allowing more chunks to be added
- to later. -}
start :: JSONChunk a -> String start :: JSONChunk a -> String
start a start a
| last s == endchar = init s | last s == endchar = init s
| otherwise = bad s | otherwise = bad s
where where
s = encodeJSONChunk a s = B.toString $ encodeJSONChunk a
add :: JSONChunk a -> String add :: JSONChunk a -> String
add a add a

1
debian/control vendored
View file

@ -23,7 +23,6 @@ Build-Depends:
libghc-unix-compat-dev, libghc-unix-compat-dev,
libghc-dlist-dev, libghc-dlist-dev,
libghc-uuid-dev, libghc-uuid-dev,
libghc-json-dev,
libghc-aeson-dev, libghc-aeson-dev,
libghc-unordered-containers-dev, libghc-unordered-containers-dev,
libghc-ifelse-dev, libghc-ifelse-dev,

View file

@ -331,7 +331,7 @@ Executable git-annex
process, data-default, case-insensitive, uuid, random, dlist, process, data-default, case-insensitive, uuid, random, dlist,
unix-compat, SafeSemaphore, async, directory, filepath, IfElse, unix-compat, SafeSemaphore, async, directory, filepath, IfElse,
MissingH, hslogger, monad-logger, MissingH, hslogger, monad-logger,
utf8-string, bytestring, text, sandi, json, utf8-string, bytestring, text, sandi,
monad-control, transformers, monad-control, transformers,
bloomfilter, edit-distance, bloomfilter, edit-distance,
resourcet, http-conduit (<2.2.0), http-client, http-types, resourcet, http-conduit (<2.2.0), http-client, http-types,