Parsing an Options Object to a List of Options - json

I have been working on a small library against an JSON-based API. This library makes use of an "options" object, a series of key-value pairs that specify advanced behaviour:
{
"id": 1234
...
"options": {
"notify_no_data": True,
"no_data_timeframe": 20,
"notify_audit": False,
"silenced": {"*" :1428937807}
}
}
I've represented the options concept in Haskell using a list of options:
data Option = NotifyNoData NominalDiffTime -- notify after xyz
| NotifyAudit -- notify on changes
| Silenced (Maybe UTCTime) -- silence all notifications ("*") until xyz (or indefinitely)
newtype Options = Options [Option]
Implementing toJSON was simple enough; I instantiated toJSON for the Option type, and then used those as helpers for the Options type.
instance ToJSON Option where
toJSON (Silenced mtime) =
Object $ Data.HashMap.fromList [("silenced", mapping)]
where stamp = maybe Null (jsonTime . floor . utcTimeToPOSIXSeconds) mtime
mapping = Object $ Data.HashMap.singleton "*" stamp
toJSON (NotifyNoData difftime) =
Object $ Data.HashMap.fromList [("notify_no_data", Bool True)
,("no_data_timeframe", stamp)]
where stamp = jsonTime $ floor (difftime / 60)
toJSON NotifyAudit =
Object $ Data.HashMap.fromList [("notify_audit", Bool True)]
instance ToJSON Options where
toJSON (Options options) = Object $ Data.HashMap.unions $ reverse $ (opts:) $ map ((\(Object o) -> o) . toJSON) options
where opts = Data.HashMap.fromList [("silenced", Object Data.HashMap.empty)
,("notify_no_data", Bool False)
,("notify_audit", Bool False)]
The problem I am running into is in the fromJSON implementation for Options. All the use cases I've seen before supply a fairly simple json-object-representation to data-representation mapping. What I need to do is convert an object to an object of options to a list of data (Option) representations. For example, the sample JSON under "options" that I gave at the start would have to become:
Options [NotifyNoData 20, Silenced (Just (posixSecondsToUTCTime 1428937807))]
FromJSON requires an implementation of parseJSON :: FromJSON a => Value -> Parser a. I am having trouble understanding how to build a Parser using this optional object structure given by the API. Is there a standard approach to parsing a JSON object to a list like this? It may be that I am failing to fully understand the Parser typeclass.

You can maybe use the parser monad to extract all the information, something like:
parseJSON (Object v) = do
maybeNotify <- v .:? "notify_no_data"
maybeTimeFrame <- v .:? "no_data_timeframe"
let nots = case (maybeNotify,maybeTimeFrame) of
(Just True,Just stamp) -> [NotifyNoData $ fromJsontime stamp]
_ -> []
return $ Options nots
(fromJsontime is just a helper function to convert from the JSON value to your NominalDiffTime, I suppose you have something for that).
Do the same for the other types of options, concatenating the result.

Using the json-stream parser (which I am the author of), it would look like this (from my head, untested):
option = NotifyNoData <$> "no_data_timeframe" .: value
<* filterI id ("notify_no_data" .: bool)
<|> const NotifyAudit <$> filterI id ("notify_audit" .: bool)
<|> Silenced <$> "silenced" .: "*" .:? value
optionList = Options <$> toList option
The code expects you have FromJSON instance for UTCTime (or you could just use 'integer' and some kind of fromposixtime etc.).

Related

Parsing nested JSON into a list of Tuples with Aeson

Say I have the following structure:
data AddressDto = AddressDto
{ addressDtoId :: UUID
, addressDtoCode :: Text
, addressDtoCity :: Maybe Text
, addressDtoStreet :: Text
, addressDtoPostCode :: Text
} deriving (Eq, Show, Generic)
instance FromJSON AddressDto where
parseJSON = genericParseJSON $ apiOptions "addressDto"
instance ToJSON AddressDto where
toJSON = genericToJSON $ apiOptions "addressDto"
toEncoding = genericToEncoding $ apiOptions "addressDto"
This works as you would expect.
Now say I want to parse a JSON structure of the format:
{ UUID: AddressDto, UUID: AddressDto, UUID: AddressDto }
A reasonable Haskell representation would seem to be:
data AddressListDto = AddressListDto [(UUID, AddressDto)]
Creating a helper function like so:
keyAndValueToList :: Either ServiceError AddressListDto -> Text -> DiscountDto -> Either ServiceError AddressListDto
keyAndValueToList (Left err) _ _ = Left err
keyAndValueToList (Right (AddressListDto ald)) k v = do
let maybeUUID = fromString $ toS k
case maybeUUID of
Nothing -> Left $ ParseError $ InvalidDiscountId k
Just validUUID -> Right $ AddressListDto $ (validUUID, v) : ald
and finally an instance of FromJSON:
instance FromJSON AddressListDto where
parseJSON = withObject "tuple" $ \o -> do
let result = foldlWithKey' keyAndValueToList (Right $ AddressListDto []) o
case result of
Right res -> pure res
Left err -> throwError err
This fails to compile with:
Couldn't match type ‘aeson-1.4.5.0:Data.Aeson.Types.Internal.Value’
with ‘AddressDto’
Expected type: unordered-containers-0.2.10.0:Data.HashMap.Base.HashMap
Text AddressDto
Two questions:
1) How do I make sure the nested values in the hashmap get parsed correctly to an AddressDto.
2) How do I avoid forcing the initial value into an either? Is there a function I could use instead of foldlWithKey' that didn't make me wrap the initial value like this?
Funny answer. To implement parseJSON, you can use
parseJSON :: Value -> Parser (HashMap Text AddressDto)
...but even better, why not just use a type alias instead of a fresh data type, so:
type AddressListDto = HashMap UUID AddressDto
This already has a suitable FromJSON instance, so then you don't even need to write any code yourself.

Understanding the Data.Aeson FromJSON typeclass

I recently started using Data.Aeson for one of my projects. And I am recently new to Haskell as well. So I am trying to figure out how the implementation of parseJSON function in FromJSON typeclass works.
So I have a code from my codebase.
data MyProfile = MyProfile { name :: String, age :: Int } deriving Show
instance FromJSON MyProfile where
parseJSON (Object m) = MyProfile <$>
m .: "name" <*>
m .: "age"
parseJSON x = fail ("not an object: " ++ show x)
And the YAML file I am trying to read is pretty simple as well.
profile:
name: "Foo"
age: 16
I am trying to understand the working of that applicative functor. I browsed through the Data.Aeson module and found that (.:) returns a Parser (FromJSON a).
So the facts that I have understood is,
Object m holds the profile: section of the yaml
MyProfile corresponds to profile
name in ParseJSON is trying to get the value for the key in the JSON object m
Similar with age as well
And each <*> returns a Parser (FromJSON) which is then applied over to the next <*>
What I am not understanding is,
How does MyProfile gets mapped to the profile section? What if I have a huge yaml file and multiple data defined in my program?
In the code MyProfile <$> m .: "name", shouldn't the first argument of <$> be a function? I perceive that <$> is similar to fmap and hence the first argument must be a function (which is applied to the second argument). But MyProfile is a data! Confusing!
How is the yaml values, in this case, Foo and 16, added to the MyProfile data?
Please correct me if any of my understandings is wrong.

How can you have two records with the same field names?

I'm writing a JSON service for JIRA, and I've come across a requirement that conflicts with Haskell's namespace.
I have this record
data Assignee = Assignee {name :: Text} deriving Generic
instance ToJSON Assignee
This is dictated by what JIRA wants, unfortunately it wants the same field for a different object.
data Reporter = Reporter {name :: Text} deriving Generic
instance ToJSON Reporter
I see a few options:
Maybe I can circumvent the compiler's complaining with template Haskell, but how?
I could simply not have a Reporter record, and change the reporter field with a seperate service after the ticket has been created. That I know how to do, but is it the best way?
Create the JSON object by hand, but I form it from this record:
data Fields = Fields
{ project :: HashMap Key Project
, summary :: Text
, issuetype :: HashMap Name Task
, versions :: [HashMap Name Text]
, description :: Text
, assignee :: Assignee
} deriving (Generic)
The thought of making this by hand gives me the wiggins. If I must I will.
So, my question now is, if there is no other better way than the ones I've presented, which of these is the best course of action?
The most straightforward way is to enable the -XDisambiguateRecordFields extension.
If DisambiguateRecordFields and/or keeping the records in separate modules works for you, that's excellent.
If not, then a common way to work around this problem is to prefix record field labels in some way, to disambiguate:
data Assignee = Assignee {assigneeName :: Text} deriving Generic
data Reporter = Reporter {reporterName :: Text} deriving Generic
You can still use GHC Generics to derive the JSON translation functions, but you have to configure it so that the field labels are changed, for example like this:
stripPrefix :: Eq a => [a] -> [a] -> [a]
stripPrefix p x = case splitAt (length p) x of
(y, z)
| y == p -> z
| otherwise -> x
lower :: String -> String
lower [] = []
lower (x : xs) = toLower x : xs
stripPrefixOptions :: String -> Options
stripPrefixOptions p = defaultOptions {
fieldLabelModifier = lower . stripPrefix p
}
Then you can say:
data Assignee = Assignee {assigneeName :: Text} deriving Generic
instance ToJSON Assignee where
toJSON = genericToJSON (stripPrefixOptions "assignee")
data Reporter = Reporter {reporterName :: Text} deriving Generic
instance ToJSON Reporter where
toJSON = genericToJSON (stripPrefixOptions "reporter")
Testing in GHCi:
GHCi> > encode (Assignee { assigneeName = "foo" })
"{\"name\":\"foo\"}"

Haskell :: Aeson :: parse ADT based on field value

I'm using an external API which returns JSON responses. One of the responses is an array of objects and these objects are identified by the field value inside them. I'm having some trouble understanding how the parsing of such JSON response could be done with Aeson.
Here is a simplified version of my problem:
newtype Content = Content { content :: [Media] } deriving (Generic)
instance FromJSON Content
data Media =
Video { objectClass :: Text
, title :: Text } |
AudioBook { objectClass :: Text
, title :: Text }
In API documentation it is said that the object can be identified by the field objectClass which has value "video" for our Video object and "audiobook" for our AudioBook and so on. Example JSON:
[{objectClass: "video", title: "Some title"}
,{objectClass: "audiobook", title: "Other title"}]
The question is how can this type of JSON be approached using Aeson?
instance FromJSON Media where
parseJSON (Object x) = ???
You basically need a function Text -> Text -> Media:
toMedia :: Text -> Text -> Media
toMedia "video" = Video "video"
toMedia "audiobook" = AudioBook "audiobook"
The FromJSON instance is now really simple (using <$> and <*> from Control.Applicative):
instance FromJSON Media where
parseJSON (Object x) = toMedia <$> x .: "objectClass" <*> x .: "title"
However, at this point you're redundant: the objectClass field in Video or Audio doesn't give you more information than the actual type, so you might remove it:
data Media = Video { title :: Text }
| AudioBook { title :: Text }
toMedia :: Text -> Text -> Media
toMedia "video" = Video
toMedia "audiobook" = AudioBook
Also note that toMedia is partial. You probably want to catch invalid "objectClass" values:
instance FromJSON Media where
parseJSON (Object x) =
do oc <- x .: "objectClass"
case oc of
String "video" -> Video <$> x .: "title"
String "audiobook" -> AudioBook <$> x .: "title"
_ -> empty
{- an alternative using a proper toMedia
toMedia :: Alternative f => Text -> f (Text -> Media)
toMedia "video" = pure Video
toMedia "audiobook" = pure AudioBook
toMedia _ = empty
instance FromJSON Media where
parseJSON (Object x) = (x .: "objectClass" >>= toMedia) <*> x .: "title"
-}
And last, but not least, remember that valid JSON uses strings for the name.
The default translation for a data type like:
data Media = Video { title :: Text }
| AudioBook { title :: Text }
deriving Generic
is actually very close to what you want. (For the simplicity of my examples, I define ToJSON instances and encode the examples to see what kind of JSON we get.)
aeson, default
So, with the default instance we have (view the complete source file which produces this output):
[{"tag":"Video","title":"Some title"},{"tag":"AudioBook","title":"Other title"}]
Let's see whether we can get even closer with custom options...
aeson, custom tagFieldName
With custom options:
mediaJSONOptions :: Options
mediaJSONOptions =
defaultOptions{ sumEncoding =
TaggedObject{ tagFieldName = "objectClass"
-- , contentsFieldName = undefined
}
}
instance ToJSON Media
where toJSON = genericToJSON mediaJSONOptions
we get:
[{"objectClass":"Video","title":"Some title"},{"objectClass":"AudioBook","title":"Other title"}]
(Think yourself what you want to do with an undefined field in the real code.)
aeson, custom constructorTagModifier
Adding
, constructorTagModifier = fmap Char.toLower
to mediaJSONOptions gives:
[{"objectClass":"video","title":"Some title"},{"objectClass":"audiobook","title":"Other title"}]
Great! Exactly what you specified!
decoding
Simply add an instance with the same options to be able to decode from this format:
instance FromJSON Media
where parseJSON = genericParseJSON mediaJSONOptions
Example:
*Main> encode example
"[{\"objectClass\":\"video\",\"title\":\"Some title\"},{\"objectClass\":\"audiobook\",\"title\":\"Other title\"}]"
*Main> decode $ fromString "[{\"objectClass\":\"video\",\"title\":\"Some title\"},{\"objectClass\":\"audiobook\",\"title\":\"Other title\"}]" :: Maybe [Media]
Just [Video {title = "Some title"},AudioBook {title = "Other title"}]
*Main>
Complete source file.
generic-aeson, default
To get a more complete picture, let's also look at what generic-aeson package would give (at hackage). It has also nice default translations, different in some respects from those from aeson.
Doing
import Generics.Generic.Aeson -- from generic-aeson package
and defining:
instance ToJSON Media
where toJSON = gtoJson
gives the result:
[{"video":{"title":"Some title"}},{"audioBook":{"title":"Other title"}}]
So, it's different from all what we've seen when using aeson.
generic-aeson's options (Settings) are not interesting for us (they allow only to strip a prefix).
(The complete source file.)
aeson, ObjectWithSingleField
Apart from lower-casing the first letter of the constructor names, generic-aeson's translation seems similar to an option available in aeson:
Let's try this:
mediaJSONOptions =
defaultOptions{ sumEncoding = ObjectWithSingleField
, constructorTagModifier = fmap Char.toLower
}
and yes, the result is:
[{"video":{"title":"Some title"}},{"audiobook":{"title":"Other title"}}]
the rest of options: (aeson, TwoElemArray)
One available option for sumEncoding has been left out from consideration above, because it gives an array which is not quite similar to the JSON representation asked about. It's TwoElemArray. Example:
[["video",{"title":"Some title"}],["audiobook",{"title":"Other title"}]]
is given by:
mediaJSONOptions =
defaultOptions{ sumEncoding = TwoElemArray
, constructorTagModifier = fmap Char.toLower
}

JSON parsing befuddlement

I'm working on the I/O aspect of my json server, and there's a method I just can't get right.
First, I'll give the error, then the code and datatypes involved and some commentary about the problem afterwards.
("X-Response-Body-Start","<!DOCTYPE html>\n<html><head><title>Invalid Arguments</title></head><body><h1>Invalid Arguments</h1><ul><li>when expecting a unit constructor (U1), encountered String instead</li></ul></body></html>")
Expecting unit contructor?
Okay here's some relevant code. Let's see if we can see where I go wrong
from Datatypes.hs
data JobID = JobID Project Int deriving Generic
data Project = BNAP deriving (Show,Generic) -- one day to be an ADT
instance ToJSON Project where
toJSON = toJSON . show
instance FromJSON Project
instance FromJSON JobID
instance ToJSON JobID
The test code
testReadR :: IO Value
testReadR = do
req <- parseUrl readURI
manager <- newManager def
pBody <- runResourceT $ do
reqBody <- readObject
liftIO $ print reqBody
Response _ _ _ body <- http (buildReq req reqBody) manager
pBody <- body $$+- sinkParser json
return pBody -- (return wraps it up)
closeManager manager
return pBody
buildReq :: forall a (m :: * -> *) (t :: * -> *).
ToJSON a =>
Request t -> a -> Request m
buildReq req reqBody =
let reqBodyBS = Data.Aeson.encode reqBody
rHeaders = [(hContentType,pack "application/json")]
in req {method = fromString "POST"
, requestBody = RequestBodyLBS reqBodyBS
,requestHeaders=rHeaders
}
readObject :: ResourceT IO Value
readObject = do -- I took a bunch out because I thought simplifiying would help me
-- solve this
return $ Data.Aeson.toJSON $ JobID BNAP 306
The Handler
postReadR :: Handler RepJson
postReadR = do
conf <- parseJsonBody_ :: Handler JobID
liftIO $ print conf
testJ <- jsonToRepJson $ toJSON $ JobID BNAP 305
jValue <- jsonToRepJson conf -- to be replaced with
-- Either ErrorReport Response
-- (or something like that)
return jValue
when I change the line to
conf <- parseJsonBody_ :: Handler Value
print conf yields
Array (fromList [String "BNAP",Number 306])
So it seems the problem lies with String "BNAP" but I don't know why. Any ideas on how I can suss this out? Is there an obvious answer I'm not seeing?
Update : I have a new error. I'm sure I borked the FromJSON instance.
test: ResponseTimeout
instance FromJSON Project where
parseJSON (String p) = parseJSON $ toJSON p
parseJSON _ = mzero
The challenge here was that Project is a unary type. None of the examples I studied seemed to address that. But I know p is a Text, and toJSON can make a Value out of that, and parseJSON makes a Parser out of the Value. So it's all good right? Well, I still get the above error which is not informative at all. Any ideas?
instance ToJSON Project where
toJSON = toJSON . show
instance FromJSON Project
The instances don't work together. The generic FromJSON instance expects the generic unit constructor U1, but the ToJSON instance produces a String "BNAP".
If you have a hand-written ToJSON instance, you also need a hand-written FromJSON instance.
instance FromJSON Project where
parseJSON (String p) = parseJSON $ toJSON p
parseJSON _ = mzero
p is a Text, and we have
instance ToJSON Text where
toJSON = String
so the above instance for Project loops, since it expands parseJSON (String p) = parseJSON (String p).
For the type as it stands now,
instance FromJSON Project where
parseJSON (String "BNAP") = return BNAP
parseJSON _ = mzero
should work if you have OverloadedStrings enabled, if not,
instance FromJSON Project where
parseJSON (String p)
| p == pack "BNAP" = return BNAP
parseJSON _ = mzero