2016-07-26 17:30:07 +00:00
|
|
|
{- git-annex command-line JSON output and input
|
2011-09-01 19:16:31 +00:00
|
|
|
-
|
2018-02-19 18:59:30 +00:00
|
|
|
- Copyright 2011-2018 Joey Hess <id@joeyh.name>
|
2011-09-01 19:16:31 +00:00
|
|
|
-
|
2019-03-13 19:48:14 +00:00
|
|
|
- Licensed under the GNU AGPL version 3 or higher.
|
2011-09-01 19:16:31 +00:00
|
|
|
-}
|
|
|
|
|
2016-09-09 22:13:55 +00:00
|
|
|
{-# LANGUAGE OverloadedStrings, GADTs #-}
|
2016-07-26 18:10:29 +00:00
|
|
|
|
2011-09-01 19:16:31 +00:00
|
|
|
module Messages.JSON (
|
2016-09-09 22:13:55 +00:00
|
|
|
JSONBuilder,
|
|
|
|
JSONChunk(..),
|
2016-09-09 19:49:44 +00:00
|
|
|
emit,
|
|
|
|
none,
|
2011-09-01 19:16:31 +00:00
|
|
|
start,
|
|
|
|
end,
|
2018-02-19 18:59:30 +00:00
|
|
|
finalize,
|
2018-02-19 19:28:38 +00:00
|
|
|
addErrorMessage,
|
2011-09-02 20:44:04 +00:00
|
|
|
note,
|
2018-02-06 17:03:55 +00:00
|
|
|
info,
|
2011-12-23 02:03:18 +00:00
|
|
|
add,
|
2015-06-16 17:50:28 +00:00
|
|
|
complete,
|
2016-09-09 19:06:54 +00:00
|
|
|
progress,
|
2015-06-16 17:50:28 +00:00
|
|
|
DualDisp(..),
|
2016-07-26 23:15:34 +00:00
|
|
|
ObjectMap(..),
|
2016-07-26 23:50:02 +00:00
|
|
|
JSONActionItem(..),
|
2011-09-01 19:16:31 +00:00
|
|
|
) where
|
|
|
|
|
2016-07-26 18:10:29 +00:00
|
|
|
import Control.Applicative
|
2016-07-26 23:15:34 +00:00
|
|
|
import qualified Data.Map as M
|
2018-02-19 19:28:38 +00:00
|
|
|
import qualified Data.Vector as V
|
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.ByteString.Lazy as L
|
2016-09-09 22:13:55 +00:00
|
|
|
import qualified Data.HashMap.Strict as HM
|
2016-07-27 01:43:05 +00:00
|
|
|
import System.IO
|
2016-09-09 19:49:44 +00:00
|
|
|
import System.IO.Unsafe (unsafePerformIO)
|
|
|
|
import Control.Concurrent
|
2016-09-09 18:26:34 +00:00
|
|
|
import Data.Maybe
|
2016-08-08 14:49:49 +00:00
|
|
|
import Data.Monoid
|
|
|
|
import Prelude
|
2011-09-02 20:44:04 +00:00
|
|
|
|
2018-02-19 18:59:30 +00:00
|
|
|
import Types.Messages
|
2017-02-24 17:42:30 +00:00
|
|
|
import Key
|
2016-09-09 19:06:54 +00:00
|
|
|
import Utility.Metered
|
|
|
|
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
|
2016-03-06 16:56:39 +00:00
|
|
|
|
2016-09-09 19:49:44 +00:00
|
|
|
-- A global lock to avoid concurrent threads emitting json at the same time.
|
|
|
|
{-# NOINLINE emitLock #-}
|
|
|
|
emitLock :: MVar ()
|
|
|
|
emitLock = unsafePerformIO $ newMVar ()
|
|
|
|
|
2016-09-09 22:13:55 +00:00
|
|
|
emit :: Object -> IO ()
|
|
|
|
emit o = do
|
2016-09-09 19:49:44 +00:00
|
|
|
takeMVar emitLock
|
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
|
|
|
L.hPut stdout (encode o)
|
2016-09-09 22:13:55 +00:00
|
|
|
putStr "\n"
|
2016-09-09 19:49:44 +00:00
|
|
|
putMVar emitLock ()
|
|
|
|
|
2016-09-09 22:13:55 +00:00
|
|
|
-- Building up a JSON object can be done by first using start,
|
|
|
|
-- then add and note any number of times, and finally complete.
|
|
|
|
type JSONBuilder = Maybe (Object, Bool) -> Maybe (Object, Bool)
|
|
|
|
|
|
|
|
none :: JSONBuilder
|
|
|
|
none = id
|
2016-09-09 19:49:44 +00:00
|
|
|
|
2016-09-09 22:13:55 +00:00
|
|
|
start :: String -> Maybe FilePath -> Maybe Key -> JSONBuilder
|
|
|
|
start command file key _ = Just (o, False)
|
2012-11-11 04:51:07 +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
|
|
|
Object o = toJSON' $ JSONActionItem
|
2016-07-26 23:50:02 +00:00
|
|
|
{ itemCommand = Just command
|
|
|
|
, itemKey = key
|
|
|
|
, itemFile = file
|
|
|
|
, itemAdded = Nothing
|
|
|
|
}
|
2011-09-01 19:16:31 +00:00
|
|
|
|
2016-09-09 22:13:55 +00:00
|
|
|
end :: Bool -> JSONBuilder
|
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
|
|
|
end b (Just (o, _)) = Just (HM.insert "success" (toJSON' b) o, True)
|
2016-09-09 22:13:55 +00:00
|
|
|
end _ Nothing = Nothing
|
2011-09-01 19:16:31 +00:00
|
|
|
|
2018-02-19 18:59:30 +00:00
|
|
|
finalize :: JSONOptions -> Object -> Object
|
|
|
|
finalize jsonoptions o
|
|
|
|
-- Always include error-messages field, even if empty,
|
|
|
|
-- to make the json be self-documenting.
|
2018-02-19 19:28:38 +00:00
|
|
|
| jsonErrorMessages jsonoptions = addErrorMessage [] o
|
2018-02-19 18:59:30 +00:00
|
|
|
| otherwise = o
|
2018-02-19 19:28:38 +00:00
|
|
|
|
|
|
|
addErrorMessage :: [String] -> Object -> Object
|
|
|
|
addErrorMessage msg o =
|
2018-02-19 19:39:52 +00:00
|
|
|
HM.insertWith combinearray "error-messages" v o
|
2018-02-19 18:59:30 +00:00
|
|
|
where
|
|
|
|
combinearray (Array new) (Array old) = Array (old <> new)
|
|
|
|
combinearray new _old = new
|
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
|
|
|
v = Array $ V.fromList $ map (String . packString) msg
|
2018-02-19 18:59:30 +00:00
|
|
|
|
2016-09-09 22:13:55 +00:00
|
|
|
note :: String -> JSONBuilder
|
|
|
|
note _ Nothing = Nothing
|
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
|
|
|
note s (Just (o, e)) = Just (HM.insertWith combinelines "note" (toJSON' s) o, e)
|
2018-02-16 17:27:17 +00:00
|
|
|
where
|
|
|
|
combinelines (String new) (String old) =
|
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
|
|
|
String (old <> "\n" <> new)
|
2018-02-16 17:27:17 +00:00
|
|
|
combinelines new _old = new
|
2011-09-02 20:44:04 +00:00
|
|
|
|
2018-02-06 17:03:55 +00:00
|
|
|
info :: String -> JSONBuilder
|
|
|
|
info s _ = Just (o, True)
|
|
|
|
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
|
|
|
Object o = object ["info" .= toJSON' s]
|
2018-02-06 17:03:55 +00:00
|
|
|
|
2016-09-09 22:13:55 +00:00
|
|
|
data JSONChunk v where
|
|
|
|
AesonObject :: Object -> JSONChunk Object
|
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
|
|
|
JSONChunk :: ToJSON' v => [(String, v)] -> JSONChunk [(String, v)]
|
2011-12-23 02:03:18 +00:00
|
|
|
|
2016-09-09 22:13:55 +00:00
|
|
|
add :: JSONChunk v -> JSONBuilder
|
|
|
|
add v (Just (o, e)) = Just (HM.union o' o, e)
|
|
|
|
where
|
|
|
|
Object o' = case v of
|
|
|
|
AesonObject ao -> Object ao
|
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
|
|
|
JSONChunk l -> object $ map mkPair l
|
|
|
|
mkPair (s, d) = (packString s, toJSON' d)
|
2016-09-09 22:13:55 +00:00
|
|
|
add _ Nothing = Nothing
|
|
|
|
|
|
|
|
complete :: JSONChunk v -> JSONBuilder
|
|
|
|
complete v _ = add v (Just (HM.empty, True))
|
|
|
|
|
|
|
|
-- Show JSON formatted progress, including the current state of the JSON
|
|
|
|
-- object for the action being performed.
|
2016-09-29 20:59:48 +00:00
|
|
|
progress :: Maybe Object -> Maybe Integer -> BytesProcessed -> IO ()
|
|
|
|
progress maction msize bytesprocessed = emit $ case maction of
|
2016-09-09 22:13:55 +00:00
|
|
|
Just action -> HM.insert "action" (Object action) o
|
|
|
|
Nothing -> o
|
2016-09-09 19:06:54 +00:00
|
|
|
where
|
|
|
|
n = fromBytesProcessed bytesprocessed :: Integer
|
2016-09-29 20:59:48 +00:00
|
|
|
Object o = case msize of
|
|
|
|
Just size -> object
|
|
|
|
[ "byte-progress" .= n
|
|
|
|
, "percent-progress" .= showPercentage 2 (percentage size n)
|
|
|
|
, "total-size" .= size
|
|
|
|
]
|
|
|
|
Nothing -> object
|
|
|
|
[ "byte-progress" .= n ]
|
2016-09-09 19:06:54 +00:00
|
|
|
|
2015-06-16 17:50:28 +00:00
|
|
|
-- A value that can be displayed either normally, or as JSON.
|
|
|
|
data DualDisp = DualDisp
|
|
|
|
{ dispNormal :: String
|
|
|
|
, dispJson :: String
|
|
|
|
}
|
|
|
|
|
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
|
|
|
instance ToJSON' DualDisp where
|
|
|
|
toJSON' = toJSON' . dispJson
|
2015-06-16 17:50:28 +00:00
|
|
|
|
|
|
|
instance Show DualDisp where
|
|
|
|
show = dispNormal
|
2016-07-26 18:10:29 +00:00
|
|
|
|
2016-07-26 23:15:34 +00:00
|
|
|
-- 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 }
|
|
|
|
|
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
|
|
|
instance ToJSON' a => ToJSON' (ObjectMap a) where
|
|
|
|
toJSON' (ObjectMap m) = object $ map go $ M.toList m
|
2016-07-26 23:15:34 +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
|
|
|
go (k, v) = (packString k, toJSON' v)
|
2016-07-26 23:15:34 +00:00
|
|
|
|
2016-07-26 23:50:02 +00:00
|
|
|
-- An item that a git-annex command acts on, and displays a JSON object about.
|
|
|
|
data JSONActionItem a = JSONActionItem
|
|
|
|
{ itemCommand :: Maybe String
|
|
|
|
, itemKey :: Maybe Key
|
|
|
|
, itemFile :: Maybe FilePath
|
|
|
|
, itemAdded :: Maybe a -- for additional fields added by `add`
|
2016-07-26 18:10:29 +00:00
|
|
|
}
|
|
|
|
deriving (Show)
|
|
|
|
|
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
|
|
|
instance ToJSON' (JSONActionItem a) where
|
|
|
|
toJSON' i = object $ catMaybes
|
2016-09-09 18:26:34 +00:00
|
|
|
[ Just $ "command" .= itemCommand i
|
|
|
|
, case itemKey i of
|
|
|
|
Nothing -> Nothing
|
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
|
|
|
Just k -> Just $ "key" .= toJSON' k
|
|
|
|
, Just $ "file" .= toJSON' (itemFile i)
|
2016-07-26 23:50:02 +00:00
|
|
|
-- itemAdded is not included; must be added later by 'add'
|
|
|
|
]
|
|
|
|
|
|
|
|
instance FromJSON a => FromJSON (JSONActionItem a) where
|
|
|
|
parseJSON (Object v) = JSONActionItem
|
2016-07-26 18:10:29 +00:00
|
|
|
<$> (v .:? "command")
|
2016-07-26 23:50:02 +00:00
|
|
|
<*> (maybe (return Nothing) parseJSON =<< (v .:? "key"))
|
|
|
|
<*> (v .:? "file")
|
2016-07-26 18:10:29 +00:00
|
|
|
<*> parseadded
|
|
|
|
where
|
|
|
|
parseadded = (Just <$> parseJSON (Object v)) <|> return Nothing
|
|
|
|
parseJSON _ = mempty
|