2016-07-26 17:30:07 +00:00
|
|
|
{- git-annex command-line JSON output and input
|
2011-09-01 19:16:31 +00:00
|
|
|
-
|
expire, trust et al, dead, describe: Support --json and --json-error-messages
For expire, the normal output is unchanged, but the --json output includes the uuid
in machine parseable form. Which could be very useful for this somewhat obscure
command. That needed ActionItemUUID to be implemented, which seemed like a lot
of work, but then ---
I had been going to skip implementing them for trust, untrust, dead, semitrust,
and describe, but putting the uuid in the json is useful information, it tells
what uuid git-annex picked given the input. It was not hard to support
these once ActionItemUUID was implemented.
Sponsored-By: the NIH-funded NICEMAN (ReproNim TR&D3) project
2023-05-05 19:29:49 +00:00
|
|
|
- Copyright 2011-2023 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
|
|
|
-}
|
|
|
|
|
2022-03-02 20:16:10 +00:00
|
|
|
{-# LANGUAGE OverloadedStrings, GADTs, CPP #-}
|
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,
|
new protocol for transferkeys, with message serialization
Necessarily threw out the old protocol, so if an old git-annex assistant
is running, and starts a transferkeys from the new git-annex, it would
fail. But, that seems unlikely; the assistant starts up transferkeys
processes and then keeps them running. Still, may need to test that
scenario.
The new protocol is simple read/show and looks like this:
TransferRequest Download (Right "origin") (Key {keyName = "f8f8766a836fb6120abf4d5328ce8761404e437529e997aaa0363bdd4fecd7bb", keyVariety = SHA2Key (HashSize 256) (HasExt True), keySize = Just 30, keyMtime = Nothing, keyChunkSize = Nothing, keyChunkNum = Nothing}) (AssociatedFile (Just "foo"))
TransferOutput (ProgressMeter (Just 30) (MeterState {meterBytesProcessed = BytesProcessed 0, meterTimeStamp = 1.6070268727892535e9}) (MeterState {meterBytesProcessed = BytesProcessed 30, meterTimeStamp = 1.6070268728043e9}))
TransferOutput (OutputMessage "(checksum...) ")
TransferResult True
Granted, this is not optimally fast, but it seems good enough, and is
probably nearly as fast as the old protocol anyhow.
emitSerializedOutput for ProgressMeter is not yet implemented. It needs
to somehow start or update a progress meter. There may need to be a new
message that allocates a progress meter, and then have ProgressMeter
update it.
This commit was sponsored by Ethan Aubin
2020-12-03 20:21:20 +00:00
|
|
|
emit',
|
2016-09-09 19:49:44 +00:00
|
|
|
none,
|
2011-09-01 19:16:31 +00:00
|
|
|
start,
|
expire, trust et al, dead, describe: Support --json and --json-error-messages
For expire, the normal output is unchanged, but the --json output includes the uuid
in machine parseable form. Which could be very useful for this somewhat obscure
command. That needed ActionItemUUID to be implemented, which seemed like a lot
of work, but then ---
I had been going to skip implementing them for trust, untrust, dead, semitrust,
and describe, but putting the uuid in the json is useful information, it tells
what uuid git-annex picked given the input. It was not hard to support
these once ActionItemUUID was implemented.
Sponsored-By: the NIH-funded NICEMAN (ReproNim TR&D3) project
2023-05-05 19:29:49 +00:00
|
|
|
startActionItem,
|
2011-09-01 19:16:31 +00:00
|
|
|
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,
|
2023-04-26 16:53:30 +00:00
|
|
|
messageid,
|
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(..),
|
2023-05-08 18:39:12 +00:00
|
|
|
AddJSONActionItemField(..),
|
2023-05-08 20:03:34 +00:00
|
|
|
module Utility.Aeson,
|
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
|
2022-03-02 20:16:10 +00:00
|
|
|
#if MIN_VERSION_aeson(2,0,0)
|
|
|
|
import qualified Data.Aeson.KeyMap as HM
|
|
|
|
#else
|
2016-09-09 22:13:55 +00:00
|
|
|
import qualified Data.HashMap.Strict as HM
|
2022-03-02 20:16:10 +00:00
|
|
|
#endif
|
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
|
|
|
|
2020-09-15 20:22:44 +00:00
|
|
|
import Types.Command (SeekInput(..))
|
expire, trust et al, dead, describe: Support --json and --json-error-messages
For expire, the normal output is unchanged, but the --json output includes the uuid
in machine parseable form. Which could be very useful for this somewhat obscure
command. That needed ActionItemUUID to be implemented, which seemed like a lot
of work, but then ---
I had been going to skip implementing them for trust, untrust, dead, semitrust,
and describe, but putting the uuid in the json is useful information, it tells
what uuid git-annex picked given the input. It was not hard to support
these once ActionItemUUID was implemented.
Sponsored-By: the NIH-funded NICEMAN (ReproNim TR&D3) project
2023-05-05 19:29:49 +00:00
|
|
|
import Types.ActionItem
|
|
|
|
import Types.UUID
|
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
|
2019-11-26 19:27:22 +00:00
|
|
|
import Utility.FileSystemEncoding
|
2023-04-25 23:26:20 +00:00
|
|
|
import Types.Messages
|
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 ()
|
new protocol for transferkeys, with message serialization
Necessarily threw out the old protocol, so if an old git-annex assistant
is running, and starts a transferkeys from the new git-annex, it would
fail. But, that seems unlikely; the assistant starts up transferkeys
processes and then keeps them running. Still, may need to test that
scenario.
The new protocol is simple read/show and looks like this:
TransferRequest Download (Right "origin") (Key {keyName = "f8f8766a836fb6120abf4d5328ce8761404e437529e997aaa0363bdd4fecd7bb", keyVariety = SHA2Key (HashSize 256) (HasExt True), keySize = Just 30, keyMtime = Nothing, keyChunkSize = Nothing, keyChunkNum = Nothing}) (AssociatedFile (Just "foo"))
TransferOutput (ProgressMeter (Just 30) (MeterState {meterBytesProcessed = BytesProcessed 0, meterTimeStamp = 1.6070268727892535e9}) (MeterState {meterBytesProcessed = BytesProcessed 30, meterTimeStamp = 1.6070268728043e9}))
TransferOutput (OutputMessage "(checksum...) ")
TransferResult True
Granted, this is not optimally fast, but it seems good enough, and is
probably nearly as fast as the old protocol anyhow.
emitSerializedOutput for ProgressMeter is not yet implemented. It needs
to somehow start or update a progress meter. There may need to be a new
message that allocates a progress meter, and then have ProgressMeter
update it.
This commit was sponsored by Ethan Aubin
2020-12-03 20:21:20 +00:00
|
|
|
emit = emit' . encode
|
|
|
|
|
|
|
|
emit' :: L.ByteString -> IO ()
|
|
|
|
emit' b = do
|
2016-09-09 19:49:44 +00:00
|
|
|
takeMVar emitLock
|
new protocol for transferkeys, with message serialization
Necessarily threw out the old protocol, so if an old git-annex assistant
is running, and starts a transferkeys from the new git-annex, it would
fail. But, that seems unlikely; the assistant starts up transferkeys
processes and then keeps them running. Still, may need to test that
scenario.
The new protocol is simple read/show and looks like this:
TransferRequest Download (Right "origin") (Key {keyName = "f8f8766a836fb6120abf4d5328ce8761404e437529e997aaa0363bdd4fecd7bb", keyVariety = SHA2Key (HashSize 256) (HasExt True), keySize = Just 30, keyMtime = Nothing, keyChunkSize = Nothing, keyChunkNum = Nothing}) (AssociatedFile (Just "foo"))
TransferOutput (ProgressMeter (Just 30) (MeterState {meterBytesProcessed = BytesProcessed 0, meterTimeStamp = 1.6070268727892535e9}) (MeterState {meterBytesProcessed = BytesProcessed 30, meterTimeStamp = 1.6070268728043e9}))
TransferOutput (OutputMessage "(checksum...) ")
TransferResult True
Granted, this is not optimally fast, but it seems good enough, and is
probably nearly as fast as the old protocol anyhow.
emitSerializedOutput for ProgressMeter is not yet implemented. It needs
to somehow start or update a progress meter. There may need to be a new
message that allocates a progress meter, and then have ProgressMeter
update it.
This commit was sponsored by Ethan Aubin
2020-12-03 20:21:20 +00:00
|
|
|
L.hPut stdout b
|
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,
|
2023-04-26 16:53:30 +00:00
|
|
|
-- then add and note and messageid any number of times, and finally
|
2023-04-25 23:26:20 +00:00
|
|
|
-- complete.
|
2016-09-09 22:13:55 +00:00
|
|
|
type JSONBuilder = Maybe (Object, Bool) -> Maybe (Object, Bool)
|
|
|
|
|
|
|
|
none :: JSONBuilder
|
|
|
|
none = id
|
2016-09-09 19:49:44 +00:00
|
|
|
|
2020-09-15 20:22:44 +00:00
|
|
|
start :: String -> Maybe RawFilePath -> Maybe Key -> SeekInput -> JSONBuilder
|
|
|
|
start command file key si _ = case j of
|
2020-04-15 17:55:08 +00:00
|
|
|
Object o -> Just (o, False)
|
|
|
|
_ -> Nothing
|
2012-11-11 04:51:07 +00:00
|
|
|
where
|
2020-04-15 17:55:08 +00:00
|
|
|
j = toJSON' $ JSONActionItem
|
2016-07-26 23:50:02 +00:00
|
|
|
{ itemCommand = Just command
|
|
|
|
, itemKey = key
|
2019-11-26 19:27:22 +00:00
|
|
|
, itemFile = fromRawFilePath <$> file
|
expire, trust et al, dead, describe: Support --json and --json-error-messages
For expire, the normal output is unchanged, but the --json output includes the uuid
in machine parseable form. Which could be very useful for this somewhat obscure
command. That needed ActionItemUUID to be implemented, which seemed like a lot
of work, but then ---
I had been going to skip implementing them for trust, untrust, dead, semitrust,
and describe, but putting the uuid in the json is useful information, it tells
what uuid git-annex picked given the input. It was not hard to support
these once ActionItemUUID was implemented.
Sponsored-By: the NIH-funded NICEMAN (ReproNim TR&D3) project
2023-05-05 19:29:49 +00:00
|
|
|
, itemUUID = Nothing
|
|
|
|
, itemFields = Nothing :: Maybe Bool
|
|
|
|
, itemSeekInput = si
|
|
|
|
}
|
|
|
|
|
|
|
|
startActionItem :: String -> ActionItem -> SeekInput -> JSONBuilder
|
|
|
|
startActionItem command ai si _ = case j of
|
|
|
|
Object o -> Just (o, False)
|
|
|
|
_ -> Nothing
|
|
|
|
where
|
|
|
|
j = toJSON' $ JSONActionItem
|
|
|
|
{ itemCommand = Just command
|
|
|
|
, itemKey = actionItemKey ai
|
|
|
|
, itemFile = fromRawFilePath <$> actionItemFile ai
|
|
|
|
, itemUUID = actionItemUUID ai
|
2021-11-01 18:40:33 +00:00
|
|
|
, itemFields = Nothing :: Maybe Bool
|
2020-09-15 20:22:44 +00:00
|
|
|
, itemSeekInput = si
|
2016-07-26 23:50:02 +00:00
|
|
|
}
|
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
|
|
|
|
2020-12-03 18:47:04 +00:00
|
|
|
-- Always include error-messages field, even if empty,
|
|
|
|
-- to make the json be self-documenting.
|
|
|
|
finalize :: Object -> Object
|
|
|
|
finalize o = addErrorMessage [] o
|
2018-02-19 19:28:38 +00:00
|
|
|
|
|
|
|
addErrorMessage :: [String] -> Object -> Object
|
|
|
|
addErrorMessage msg o =
|
2022-03-02 20:16:10 +00:00
|
|
|
HM.unionWith combinearray (HM.singleton "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
|
2022-03-02 20:16:10 +00:00
|
|
|
note s (Just (o, e)) = Just (HM.unionWith combinelines (HM.singleton "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
|
|
|
|
2023-04-26 16:53:30 +00:00
|
|
|
messageid :: MessageId -> JSONBuilder
|
|
|
|
messageid _ Nothing = Nothing
|
|
|
|
messageid mid (Just (o, e)) = Just (HM.unionWith replaceold (HM.singleton "message-id" (toJSON' (show mid))) o, e)
|
2023-04-25 23:26:20 +00:00
|
|
|
where
|
|
|
|
replaceold new _old = new
|
|
|
|
|
2018-02-06 17:03:55 +00:00
|
|
|
info :: String -> JSONBuilder
|
2020-04-15 17:55:08 +00:00
|
|
|
info s _ = case j of
|
|
|
|
Object o -> Just (o, True)
|
|
|
|
_ -> Nothing
|
2018-02-06 17:03:55 +00:00
|
|
|
where
|
2020-04-15 17:55:08 +00:00
|
|
|
j = 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
|
2020-04-15 17:55:08 +00:00
|
|
|
add v (Just (o, e)) = case j of
|
|
|
|
Object o' -> Just (HM.union o' o, e)
|
|
|
|
_ -> Nothing
|
2016-09-09 22:13:55 +00:00
|
|
|
where
|
2020-04-15 17:55:08 +00:00
|
|
|
j = case v of
|
2016-09-09 22:13:55 +00:00
|
|
|
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
|
2022-03-02 22:24:06 +00:00
|
|
|
mkPair (s, d) = (textKey (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.
|
2020-12-11 16:03:40 +00:00
|
|
|
progress :: Maybe Object -> Maybe TotalSize -> BytesProcessed -> IO ()
|
2020-04-15 17:55:08 +00:00
|
|
|
progress maction msize bytesprocessed =
|
|
|
|
case j of
|
|
|
|
Object o -> emit $ case maction of
|
|
|
|
Just action -> HM.insert "action" (Object action) o
|
|
|
|
Nothing -> o
|
|
|
|
_ -> return ()
|
2016-09-09 19:06:54 +00:00
|
|
|
where
|
|
|
|
n = fromBytesProcessed bytesprocessed :: Integer
|
2020-04-15 17:55:08 +00:00
|
|
|
j = case msize of
|
2020-12-11 16:03:40 +00:00
|
|
|
Just (TotalSize size) -> object
|
2016-09-29 20:59:48 +00:00
|
|
|
[ "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
|
2022-03-02 22:24:06 +00:00
|
|
|
go (k, v) = (textKey (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
|
expire, trust et al, dead, describe: Support --json and --json-error-messages
For expire, the normal output is unchanged, but the --json output includes the uuid
in machine parseable form. Which could be very useful for this somewhat obscure
command. That needed ActionItemUUID to be implemented, which seemed like a lot
of work, but then ---
I had been going to skip implementing them for trust, untrust, dead, semitrust,
and describe, but putting the uuid in the json is useful information, it tells
what uuid git-annex picked given the input. It was not hard to support
these once ActionItemUUID was implemented.
Sponsored-By: the NIH-funded NICEMAN (ReproNim TR&D3) project
2023-05-05 19:29:49 +00:00
|
|
|
, itemUUID :: Maybe UUID
|
2021-11-01 18:40:33 +00:00
|
|
|
, itemFields :: Maybe a
|
2020-09-15 20:22:44 +00:00
|
|
|
, itemSeekInput :: SeekInput
|
2016-07-26 18:10:29 +00:00
|
|
|
}
|
|
|
|
deriving (Show)
|
|
|
|
|
2021-11-01 18:40:33 +00:00
|
|
|
instance ToJSON' a => ToJSON' (JSONActionItem a) 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
|
|
|
toJSON' i = object $ catMaybes
|
2016-09-09 18:26:34 +00:00
|
|
|
[ Just $ "command" .= itemCommand i
|
|
|
|
, case itemKey i of
|
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
|
2020-09-15 20:22:44 +00:00
|
|
|
Nothing -> Nothing
|
2023-05-08 18:39:12 +00:00
|
|
|
, case itemFile i of
|
|
|
|
Just f -> Just $ "file" .= toJSON' f
|
|
|
|
Nothing -> Nothing
|
2021-11-01 18:40:33 +00:00
|
|
|
, case itemFields i of
|
|
|
|
Just f -> Just $ "fields" .= toJSON' f
|
|
|
|
Nothing -> Nothing
|
expire, trust et al, dead, describe: Support --json and --json-error-messages
For expire, the normal output is unchanged, but the --json output includes the uuid
in machine parseable form. Which could be very useful for this somewhat obscure
command. That needed ActionItemUUID to be implemented, which seemed like a lot
of work, but then ---
I had been going to skip implementing them for trust, untrust, dead, semitrust,
and describe, but putting the uuid in the json is useful information, it tells
what uuid git-annex picked given the input. It was not hard to support
these once ActionItemUUID was implemented.
Sponsored-By: the NIH-funded NICEMAN (ReproNim TR&D3) project
2023-05-05 19:29:49 +00:00
|
|
|
, case itemUUID i of
|
|
|
|
Just u -> Just $ "uuid" .= toJSON' u
|
|
|
|
Nothing -> Nothing
|
2020-09-15 20:22:44 +00:00
|
|
|
, Just $ "input" .= fromSeekInput (itemSeekInput i)
|
2016-07-26 23:50:02 +00:00
|
|
|
]
|
|
|
|
|
|
|
|
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")
|
expire, trust et al, dead, describe: Support --json and --json-error-messages
For expire, the normal output is unchanged, but the --json output includes the uuid
in machine parseable form. Which could be very useful for this somewhat obscure
command. That needed ActionItemUUID to be implemented, which seemed like a lot
of work, but then ---
I had been going to skip implementing them for trust, untrust, dead, semitrust,
and describe, but putting the uuid in the json is useful information, it tells
what uuid git-annex picked given the input. It was not hard to support
these once ActionItemUUID was implemented.
Sponsored-By: the NIH-funded NICEMAN (ReproNim TR&D3) project
2023-05-05 19:29:49 +00:00
|
|
|
<*> (v .:? "uuid")
|
2021-11-01 18:40:33 +00:00
|
|
|
<*> (v .:? "fields")
|
2023-05-08 18:39:12 +00:00
|
|
|
-- ^ fields is used for metadata, which is currently the
|
|
|
|
-- only json that gets parsed
|
2020-09-15 20:22:44 +00:00
|
|
|
<*> pure (SeekInput [])
|
2016-07-26 18:10:29 +00:00
|
|
|
parseJSON _ = mempty
|
2021-11-01 18:40:33 +00:00
|
|
|
|
2023-05-08 18:39:12 +00:00
|
|
|
-- This can be used to populate a field after a JSONActionItem
|
2021-11-01 18:40:33 +00:00
|
|
|
-- has already been started.
|
2023-05-08 18:39:12 +00:00
|
|
|
data AddJSONActionItemField a = AddJSONActionItemField String a
|
2021-11-01 18:40:33 +00:00
|
|
|
deriving (Show)
|
|
|
|
|
2023-05-08 18:39:12 +00:00
|
|
|
instance ToJSON' a => ToJSON' (AddJSONActionItemField a) where
|
|
|
|
toJSON' (AddJSONActionItemField f a) = object [ (textKey (packString f), toJSON' a) ]
|