improved use of Aeson for JSONActionItem
This commit is contained in:
parent
870873bdaa
commit
928fbb162d
3 changed files with 45 additions and 36 deletions
|
@ -10,7 +10,7 @@ module Command.MetaData where
|
||||||
import Command
|
import Command
|
||||||
import Annex.MetaData
|
import Annex.MetaData
|
||||||
import Logs.MetaData
|
import Logs.MetaData
|
||||||
import Messages.JSON (ParsedJSON(..))
|
import Messages.JSON (JSONActionItem(..))
|
||||||
|
|
||||||
import qualified Data.Set as S
|
import qualified Data.Set as S
|
||||||
import qualified Data.Text as T
|
import qualified Data.Text as T
|
||||||
|
@ -131,6 +131,11 @@ fieldsField = T.pack "fields"
|
||||||
parseJSONInput :: String -> Maybe (Either FilePath Key, MetaData)
|
parseJSONInput :: String -> Maybe (Either FilePath Key, MetaData)
|
||||||
parseJSONInput i = do
|
parseJSONInput i = do
|
||||||
v <- decode (BU.fromString i)
|
v <- decode (BU.fromString i)
|
||||||
case parsedAdded v of
|
let m = case itemAdded v of
|
||||||
Nothing -> return (parsedKeyfile v, emptyMetaData)
|
Nothing -> emptyMetaData
|
||||||
Just (MetaDataFields m) -> return (parsedKeyfile v, m)
|
Just (MetaDataFields m') -> m'
|
||||||
|
let keyfile = case (itemKey v, itemFile v) of
|
||||||
|
(Just k, _) -> Right k
|
||||||
|
(Nothing, Just f) -> Left f
|
||||||
|
(Nothing, Nothing) -> error "JSON input is missing either file or key"
|
||||||
|
return (keyfile, m)
|
||||||
|
|
|
@ -15,7 +15,7 @@ module Messages.JSON (
|
||||||
complete,
|
complete,
|
||||||
DualDisp(..),
|
DualDisp(..),
|
||||||
ObjectMap(..),
|
ObjectMap(..),
|
||||||
ParsedJSON(..),
|
JSONActionItem(..),
|
||||||
) where
|
) where
|
||||||
|
|
||||||
import Data.Aeson
|
import Data.Aeson
|
||||||
|
@ -25,17 +25,16 @@ 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
|
|
||||||
|
|
||||||
start :: String -> Maybe FilePath -> Maybe Key -> IO ()
|
start :: String -> Maybe FilePath -> Maybe Key -> IO ()
|
||||||
start command file key = putStr $ Stream.start $ Stream.JSONChunk $ catMaybes
|
start command file key = putStr $ Stream.start $ Stream.AesonObject o
|
||||||
[ part "command" (Just command)
|
|
||||||
, part "file" file
|
|
||||||
, part "key" (fmap key2file key)
|
|
||||||
]
|
|
||||||
where
|
where
|
||||||
part _ Nothing = Nothing
|
Object o = toJSON $ JSONActionItem
|
||||||
part l (Just v) = Just (l, v)
|
{ itemCommand = Just command
|
||||||
|
, itemKey = key
|
||||||
|
, itemFile = file
|
||||||
|
, itemAdded = Nothing
|
||||||
|
}
|
||||||
|
|
||||||
end :: Bool -> IO ()
|
end :: Bool -> IO ()
|
||||||
end b = putStr $ Stream.add (Stream.JSONChunk [("success", b)]) ++ Stream.end
|
end b = putStr $ Stream.add (Stream.JSONChunk [("success", b)]) ++ Stream.end
|
||||||
|
@ -71,33 +70,29 @@ instance ToJSON a => ToJSON (ObjectMap a) where
|
||||||
where
|
where
|
||||||
go (k, v) = (T.pack k, toJSON v)
|
go (k, v) = (T.pack k, toJSON v)
|
||||||
|
|
||||||
-- An Aeson parser for the JSON output by this module, and
|
-- An item that a git-annex command acts on, and displays a JSON object about.
|
||||||
-- similar JSON input from users.
|
data JSONActionItem a = JSONActionItem
|
||||||
data ParsedJSON a = ParsedJSON
|
{ itemCommand :: Maybe String
|
||||||
{ parsedCommand :: Maybe String -- optional
|
, itemKey :: Maybe Key
|
||||||
, parsedKeyfile :: Either FilePath Key -- key is preferred
|
, itemFile :: Maybe FilePath
|
||||||
, parsedNote :: Maybe String -- optional
|
, itemAdded :: Maybe a -- for additional fields added by `add`
|
||||||
, parsedSuccess :: Bool -- optional, defaults to True
|
|
||||||
, parsedAdded :: Maybe a -- to parse additional fields added by `add`
|
|
||||||
}
|
}
|
||||||
deriving (Show)
|
deriving (Show)
|
||||||
|
|
||||||
instance FromJSON a => FromJSON (ParsedJSON a) where
|
instance ToJSON (JSONActionItem a) where
|
||||||
parseJSON (Object v) = ParsedJSON
|
toJSON i = object
|
||||||
|
[ "command" .= itemCommand i
|
||||||
|
, "key" .= (toJSON (itemKey i))
|
||||||
|
, "file" .= itemFile i
|
||||||
|
-- itemAdded is not included; must be added later by 'add'
|
||||||
|
]
|
||||||
|
|
||||||
|
instance FromJSON a => FromJSON (JSONActionItem a) where
|
||||||
|
parseJSON (Object v) = JSONActionItem
|
||||||
<$> (v .:? "command")
|
<$> (v .:? "command")
|
||||||
<*> parsekeyfile
|
<*> (maybe (return Nothing) parseJSON =<< (v .:? "key"))
|
||||||
<*> (v .:? "note")
|
<*> (v .:? "file")
|
||||||
<*> (v .:? "success" .!= True)
|
|
||||||
<*> parseadded
|
<*> parseadded
|
||||||
where
|
where
|
||||||
parsekeyfile = do
|
|
||||||
mks <- v .:? "key"
|
|
||||||
case file2key =<< mks of
|
|
||||||
Just k -> return (Right k)
|
|
||||||
Nothing -> do
|
|
||||||
mf <- v .:? "file"
|
|
||||||
case mf of
|
|
||||||
Just f -> return (Left f)
|
|
||||||
Nothing -> fail "missing key or file"
|
|
||||||
parseadded = (Just <$> parseJSON (Object v)) <|> return Nothing
|
parseadded = (Just <$> parseJSON (Object v)) <|> return Nothing
|
||||||
parseJSON _ = mempty
|
parseJSON _ = mempty
|
||||||
|
|
11
Types/Key.hs
11
Types/Key.hs
|
@ -1,6 +1,6 @@
|
||||||
{- git-annex Key data type
|
{- git-annex Key data type
|
||||||
-
|
-
|
||||||
- Copyright 2011-2014 Joey Hess <id@joeyh.name>
|
- Copyright 2011-2016 Joey Hess <id@joeyh.name>
|
||||||
-
|
-
|
||||||
- Licensed under the GNU GPL version 3 or higher.
|
- Licensed under the GNU GPL version 3 or higher.
|
||||||
-}
|
-}
|
||||||
|
@ -21,6 +21,8 @@ module Types.Key (
|
||||||
) where
|
) where
|
||||||
|
|
||||||
import System.Posix.Types
|
import System.Posix.Types
|
||||||
|
import Data.Aeson
|
||||||
|
import qualified Data.Text as T
|
||||||
|
|
||||||
import Common
|
import Common
|
||||||
import Utility.QuickCheck
|
import Utility.QuickCheck
|
||||||
|
@ -120,6 +122,13 @@ file2key s
|
||||||
_ -> return k
|
_ -> return k
|
||||||
addfield _ _ _ = Nothing
|
addfield _ _ _ = Nothing
|
||||||
|
|
||||||
|
instance ToJSON Key where
|
||||||
|
toJSON = toJSON . key2file
|
||||||
|
|
||||||
|
instance FromJSON Key where
|
||||||
|
parseJSON (String t) = maybe mempty pure $ file2key $ T.unpack t
|
||||||
|
parseJSON _ = mempty
|
||||||
|
|
||||||
instance Arbitrary Key where
|
instance Arbitrary Key where
|
||||||
arbitrary = Key
|
arbitrary = Key
|
||||||
<$> (listOf1 $ elements $ ['A'..'Z'] ++ ['a'..'z'] ++ ['0'..'9'] ++ "-_\r\n \t")
|
<$> (listOf1 $ elements $ ['A'..'Z'] ++ ['a'..'z'] ++ ['0'..'9'] ++ "-_\r\n \t")
|
||||||
|
|
Loading…
Add table
Add a link
Reference in a new issue