I'm trying to traverse some JSON response I'm getting from the OpenWeatherMap API but I'm getting some issues to retrieve some values. Here is my code:
{-# LANGUAGE OverloadedStrings #-}
import Control.Lens
import Data.Aeson.Lens (_String, key)
import Network.Wreq
myAPIKey :: String
myAPIKey = "my_api_key_here"
conditionsQuery :: String -> String -> String -> String
conditionsQuery city country key =
"https://api.openweathermap.org/data/2.5/forecast?q=" ++ city ++ "," ++ country ++ "&appid=" ++ key
main = do
print "What's the city?"
city <- getLine
print "And the country?"
country <- getLine
r <- get (conditionsQuery city country myAPIKey)
print $ r ^. responseBody . key "name" . _String
print $ r ^. responseBody . key "cod" . _String
print $ r ^. responseBody . key "id" . _String
The issue is that only the value of "cod" is returned ("200" in that case). The values for "name" and "id" appear as "", if we try with London,GB, Chicago, US (for instance). Yet the response body looks like:
{
...
"id": 2643743,
"name": "London",
"cod": 200
}
I first thought it was a type mismatch, but 200 is an Int there (unless I'm mistaken?) so I am not sure where the issue lies? "" seems to indicate that those 2 keys (id and name) do not exist, but they do.
Any ideas? Thanks in advance.
The response body does not look like that.
According to https://openweathermap.org/forecast5, the key "cod" appears at the outermost level of the JSON object, but "id" and "name" do not.
{
"city":{
"id":1851632,
"name":"Shuzenji",
...
}
"cod":"200",
...
}
Related
Let's say I want to use Aeson to parse the following JSON object:
{
"data": [
[
"data",
"more data"
],
[
"data",
"more data"
]
],
"error": {
"code": ""
}
}
I can create the records for the JSON objects, then create the instances to parse the pieces out like the documentation describes. But, I'm really only interested in the Vector Text that's inside data. Is there a more direct way to get at this than creating the records? It's not obvious how to create the Parser that gets me this directly.
It appears that there is an Aeson tutorial documenting exactly this problem: Parsing without creating extra types
In your case, data has arrays of arrays, so I'm not sure if you want a Vector (Vector Text) or flatten all of it into one array, but adapting from the documentation:
justData :: Value -> Parser (Vector (Vector Text))
justData = withObject "structure with data" $ \o -> o .: "data"
justDataFlat :: Value -> Parser (Vector Text)
justDataFlat value = fmap join (justData value)
Also note that if your structure is deeper, like this:
{
"data": {
"deep": [
"data",
"more data"
]
}
}
you can use .: more than once:
deeperData :: Value -> Parser (Vector Text)
deeperData = withObject "structure with deeper data" $ \o ->
step1 <- o .: "data"
step1 .: "deep"
I have a JSON data source which looks like this:
{ "fields": [
{ "type": "datetime",
"name": "Observation Valid",
"description": "Observation Valid Time"},
{ "type": "datetime",
"name": "Observation Valid UTC",
"description": "Observation Valid Time UTC"},
{ "type": "number",
"name": "Air Temperature[F]",
"description": "Air Temperature at 2m AGL"},
{ "type": "number",
"name": "Wind Speed[kt]",
"description": "Wind Speed"},
{ "type": "number",
"name": "Wind Gust[kt]",
"description": "Wind Gust"},
{ "type": "number", "name":
"Wind Direction[deg]",
"description": "Wind Direction"}
],
"rows": [
["2018-04-22T00:10:00", "2018-04-22T05:10:00Z", 50.0, 9.0, null, 50.0],
["2018-04-22T00:15:00", "2018-04-22T05:15:00Z", 50.0, 9.0, null, 60.0],
["2018-04-22T00:20:00", "2018-04-22T05:20:00Z", 50.0, 8.0, null, 60.0],
["2018-04-22T00:30:00", "2018-04-22T05:30:00Z", 50.0, 9.0, null, 60.0]
]
}
( https://mesonet.agron.iastate.edu/json/obhistory.py?station=TVK&network=AWOS&date=2018-04-22 )
And tried several data descriptions, lastly this:
data Entry = -- Data entries
Entry { time :: Text -- Observation Valid Time
, timeUTC :: Text -- Observation Valid Time UTC
, airTemp :: Float -- Air Temperature[F] at 2m AGL
, wind :: Float -- Wind Speed [kt]
, gust :: Float -- Wind Gust [kt]
, direction :: Int -- Wind Direction[deg]
} deriving (Show,Generic)
data Field = -- Schema Definition
Field { ftype :: String --
, name :: String --
, description :: String --
} deriving (Show,Generic)
data Record =
Record { fields :: [Field] --
, rows :: [Entry] -- data
} deriving (Show,Generic)
-- Instances to convert our type to/from JSON.
instance FromJSON Entry
instance FromJSON Field
instance FromJSON Record
-- Get JSON data and decode it
dat <- (eitherDecode <$> getJSON) :: IO (Either String Record)
which gives this error:
Error in $.fields[0]: key "ftype" not present
The (first) error comes from the field definitions (which I don’t use). In the JSON the Entry’s are arrays of mixed types, but in the Haskell it is just a data structure, not an array – not sure how to reconcile these.
No doubt a beginner error – but I haven’t found any examples which seem to have this structure. Do I need to write a custom parser for this?
Three things prevent this from working as intended:
The JSON data contains a field named "type" . A custom FromJson instance for the Field record type can handle this.
The data in the Entry type is unnamed so it is better represented as either a data record without field names or a tuple.
The Float representing wind gust is sometimes null so it should be a Maybe Float
The code below contains all of these modifications and parses your example JSON data :
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE OverloadedStrings #-}
import Data.ByteString.Lazy as BSL
import Data.Text (Text)
import Data.Aeson
import GHC.Generics
-- Either this tuple definition of Entry or the data definition without
-- names (commented out) will work.
type Entry = -- Data entries
( Text -- Observation Valid Time
, Text -- Observation Valid Time UTC
, Float -- Air Temperature[F] at 2m AGL
, Float -- Wind Speed [kt]
, Maybe Float -- Wind Gust [kt]
, Int -- Wind Direction[deg]
)
-- data Entry = -- Data entries
-- Entry Text -- Observation Valid Time
-- Text -- Observation Valid Time UTC
-- Float -- Air Temperature[F] at 2m AGL
-- Float -- Wind Speed [kt]
-- (Maybe Float) -- Wind Gust [kt]
-- Int -- Wind Direction[deg]
-- deriving (Show,Generic)
-- instance FromJSON Entry
data Field = -- Schema Definition
Field { ftype :: String --
, name :: String --
, description :: String --
} deriving (Show,Generic)
instance FromJSON Field where
parseJSON = withObject "Field" $ \v -> Field
<$> v .: "type"
<*> v .: "name"
<*> v .: "description"
data Record =
Record { fields :: [Field] --
, rows :: [Entry] -- data
} deriving (Show,Generic)
instance FromJSON Record
getJSON :: IO ByteString
getJSON = BSL.readFile "json.txt"
main :: IO()
main = do
-- Get JSON data and decode it
dat <- (eitherDecode <$> getJSON) :: IO (Either String Record)
case dat of
Right parsed -> print parsed
Left err -> print err
Field has an ftype field, so AESON is trying to find ftype in the JSON but can't (as it contains ftype). I understand you can't name a field type in Haskell so you need to find a way make AESON use a different name. You need to use template Haskell and set fieldLabelModifier accordingly. Alternatively, writing the insistence manually might be simpler.
I am trying to generate auto json paths from given json structure but stuck in the programatic part. Can someone please help out with the idea to take it further?
Below is the code so far i have achieved.
def iterate_dict(dict_data, key, tmp_key):
for k, v in dict_data.items():
key = key + tmp_key + '.' + k
key = key.replace('$$', '$')
if type(v) is dict:
tmp_key = key
key = '$'
iterate_dict(v, key, tmp_key)
elif type(v) is list:
str_encountered = False
for i in v:
if type(i) is str:
str_encountered = True
tmp_key = key
break
tmp_key = key
key = '$'
iterate_dict(i, key, tmp_key)
if str_encountered:
print(key, v)
if tmp_key is not None:
tmp_key = str(tmp_key)[:-str(k).__len__() - 1]
key = '$'
else:
print(key, v)
key = '$'
import json
iterate_dict_new(dict(json.loads(d_data)), '$', '')
consider the below json structure
{
"id": "1",
"categories": [
{
"name": "author",
"book": "fiction",
"leaders": [
{
"ref": ["wiki", "google"],
"athlete": {
"$ref": "some data"
},
"data": {
"$data": "some other data"
}
}
]
},
{
"name": "dummy name"
}
]
}
Expected output out of python script:
$id = 1
$categories[0].name = author
$categories[0].book = fiction
$categories[0].leaders[0].ref[0] = wiki
$categories[0].leaders[0].ref[1] = google
$categories[0].leaders[0].athlete.$ref = some data
$categories[0].leaders[0].data.$data = some other data
$categories[1].name = dummy name
Current output with above python script:
$.id 1
$$.categories.name author
$$.categories.book fiction
$$$.categories.leaders.ref ["wiki", "google"]
$$$$$.categories.leaders.athlete.$ref some data
$$$$$$.categories.leaders.athlete.data.$data some other data
$$.name dummy name
The following recursive function is similar to yours, but instead of just displaying a dictionary, it can also take a list. This means that if you passed in a dictionary where one of the values was a nested list, then the output would still be correct (printing things like dict.key[3][4] = element).
def disp_paths(it, p='$'):
for k, v in (it.items() if type(it) is dict else enumerate(it)):
if type(v) is dict:
disp_paths(v, '{}.{}'.format(p, k))
elif type(v) is list:
for i, e in enumerate(v):
if type(e) is dict or type(e) is list:
disp_paths(e, '{}.{}[{}]'.format(p, k, i))
else:
print('{}.{}[{}] = {}'.format(p, k, i, e))
else:
f = '{}.{} = {}' if type(it) is dict else '{}[{}] = {}'
print(f.format(p, k, v))
which, when ran with your dictionary (disp_paths(d)), gives the expected output of:
$.categories[0].leaders[0].athlete.$ref = some data
$.categories[0].leaders[0].data.$data = some other data
$.categories[0].leaders[0].ref[0] = wiki
$.categories[0].leaders[0].ref[1] = google
$.categories[0].book = fiction
$.categories[0].name = author
$.categories[1].name = dummy name
$.id = 1
Note that this is unfortunately not ordered, but that is unavoidable as dictionaries have no inherent order (they are just sets of key:value pairs)
If you need help understanding my modifications, just drop a comment!
I'm calling a Api Service that has the following json requirement:
{
"user": {
"userid": "123456"
},
"access_token": "ABCDEFGHIJKLMPNOPQRST"
}
I'm doing the following in my code:
MyUser = {<<"uid">>, <<"MyId-1">>},
Body = json_body_([{{<<"user">>, MyUser},{<<"access_token">>, <<?ORGANIZATION_ACCESS_TOKEN>>}}]),
Body1 = lists:map(fun erlang:tuple_to_list/1, Body),
io:format("Body in start : ~n~p~n", [Body1]).
json_body_(ParamList) ->
json_body__(ParamList, []).
json_body__([], Acc) ->
jsx:encode(lists:reverse(Acc));
json_body__([{K, V} | Rest], Acc) ->
Acc1 = [{sanitize_(K), sanitize_(V)} | Acc],
json_body__(Rest, Acc1).
sanitize_(Parm) ->
Parm.
When I apply jsx:enocode to "Body1" the result is:
[{\"user\":{\"uid\":\"My-id-1234\"},\"access_token\":\"12345678ff4089\"}]
How can I get rid of the escape "\"?
Your string doesn't contain any \. Since you printed using ~p, Erlang escaped every double quote in the string to make the final output valid Erlang code. You can verify this by printing using ~s instead.
1> S = "{\"foo\": \"bar\"}".
"{\"foo\": \"bar\"}"
2> io:format("~p~n", [S]).
"{\"foo\": \"bar\"}"
ok
3> io:format("~s~n", [S]).
{"foo": "bar"}
ok
Looking to extract records from a table in a very well formed HTMl table using HXT. I've reviewed a couple of examples on SO and the HXT documentation, such as:
Extracting Values from a Subtree
http://adit.io/posts/2012-04-14-working_with_HTML_in_haskell.html
https://www.schoolofhaskell.com/school/advanced-haskell/xml-parsing-with-validation
Running Haskell HXT outside of IO?
extract multiples html tables with hxt
Parsing html in haskell
http://neilbartlett.name/blog/2007/08/01/haskell-explaining-arrows-through-xml-transformationa/
https://wiki.haskell.org/HXT/Practical/Simple2
https://wiki.haskell.org/HXT/Practical/Simple1
Group html table rows with HXT in Haskell
Parsing multiple child nodes in Haskell with HXT
My problem is:
I want to identify a table uniquely by a known id, and then for each
tr within that table, create a record object and return this as a list
of records.
Here's my HTML
<!DOCTYPE html>
<head>
<title>FakeHTML</title>
</head>
<body>
<table id="fakeout-dont-get-me">
<thead><tr><td>Null</td></tr></thead>
<tbody><tr><td>Junk!</td></tr></tbody>
</table>
<table id="Greatest-Table">
<thead>
<tr><td>Name</td><td>Favorite Rock</td></tr>
</thead>
<tbody>
<tr id="rock1">
<td>Fred</td>
<td>Igneous</td>
</tr>
<tr id="rock2">
<td>Bill</td>
<td>Sedimentary</td>
</tr>
</tbody>
</table>
</body>
</html>
Here's the code I'm trying, along with 2 different approaches to parsing this. First, imports ...
{-# LANGUAGE Arrows, OverloadedStrings, DeriveDataTypeable, FlexibleContexts #-}
import Text.XML.HXT.Core
import Text.HandsomeSoup
import Text.XML.HXT.XPath.XPathEval
import Data.Tree.NTree.TypeDefs
import Text.XML.HXT.XPath.Arrows
What I want is a list of Rockrecs, eg from...
recs = [("rock1", "Name", "Fred", "Favorite Rock", "Igneous"),
("rock2", "Name", "Bill", "Favorite Rock", "Sedimentary")]
data Rockrec = Rockrec { rockID:: String,
rockName :: String,
rockFav :: String} deriving Show
rocks = [(\(a,_,b,_,c) -> Rockrec a b c ) r | r <- recs]
-- [Rockrec {rockID = "rock1", rockName = "Fred", rockFav = "Igneous"},
-- Rockrec {rockID = "rock2", rockName = "Bill", rockFav = "Sedimentary"}]
Here's my first way, which uses a bind on runLA after I return a bunch of [XMLTree]. That is, I do a first parse just to get the right table, then I process the tree rows after that first grab.
Attempt 1
getTab = do
dt <- Prelude.readFile "fake.html"
let html = parseHtml dt
tab <- runX $ html //> hasAttrValue "id" (== "Greatest-Table")
return tab
-- hmm, now this gets tricky...
-- table <- getTab
node tag = multi (hasName tag)
-- a la https://stackoverflow.com/questions/3901492/running-haskell-hxt-outside-of-io?rq=1
getIt :: ArrowXml cat => cat (Data.Tree.NTree.TypeDefs.NTree XNode) (String, String)
getIt = (node "tr" >>>
(getAttrValue "id" &&& (node "td" //> getText)))
This kinda works. I need to massage a bit, but can get it to run...
-- table >>= runLA getIt
-- [("","Name"),("","Favorite Rock"),("rock1","Fred"),("rock1","Igneous"),("rock2","Bill"),("rock2","Sedimentary")]
This is a second approach, inspired by https://wiki.haskell.org/HXT/Practical/Simple1. Here, I think I'm relying on something in {-# LANGUAGE Arrows -} (which coincidentally breaks my list comprehension for rec above), to use the proc function to do this in a more readable do block. That said, I can't even get a minimal version of this to compile:
Attempt 2
getR :: ArrowXml cat => cat XmlTree Rockrec
getR = (hasAttrValue "id" (== "Greatest-Table")) >>>
proc x -> do
rockId <- getText -< x
rockName <- getText -< x
rockFav <- getText -< x
returnA -< Rockrec rockId rockName rockFav
EDIT
Trouble with the types, in response to the comment below from Alec
λ> getR [table]
<interactive>:56:1-12: error:
• Couldn't match type ‘NTree XNode’ with ‘[[XmlTree]]’
Expected type: [[XmlTree]] -> Rockrec
Actual type: XmlTree -> Rockrec
• The function ‘getR’ is applied to one argument,
its type is ‘cat0 XmlTree Rockrec’,
it is specialized to ‘XmlTree -> Rockrec’
In the expression: getR [table]
In an equation for ‘it’: it = getR [table]
λ> getR table
<interactive>:57:1-10: error:
• Couldn't match type ‘NTree XNode’ with ‘[XmlTree]’
Expected type: [XmlTree] -> Rockrec
Actual type: XmlTree -> Rockrec
• The function ‘getR’ is applied to one argument,
its type is ‘cat0 XmlTree Rockrec’,
it is specialized to ‘XmlTree -> Rockrec’
In the expression: getR table
In an equation for ‘it’: it = getR table
END EDIT
Even if I'm not selecting elements, I can't get the above to run. I'm also a little puzzled at how I should do something like put the first td in rockName and the second td in rockFav, how to include an iterator on these (supposing I have a lot of td fields, instead of just 2.)
Any further general tips on how to do this more painlessly appreciated.
From HXT/Practical/Google1 I think I am able to piece together a solution.
{-# LANGUAGE Arrows #-}
{-# LANGUAGE ScopedTypeVariables #-}
module Hanzo where
import Text.HandsomeSoup
import Text.XML.HXT.Cor
atTag tag =
deep (isElem >>> hasName tag)
text =
deep isText >>> getText
data Rock = Rock String String String deriving Show
rocks =
atTag "tbody" //> atTag "tr"
>>> proc x -> do
rowID <- x >- getAttrValue "id"
name <- x >- atTag "td" >. (!! 0) >>> text
kind <- x >- atTag "td" >. (!! 1) >>> text
returnA -< Rock rowID name kind
main = do
dt <- readFile "html.html"
result <- runX $ parseHtml dt
//> hasAttrValue "id" (== "Greatest-Table")
>>> rocks
print result
The key takeways are these:
Your arrows work on streams of elements, but not individual elements. This is the ArrowList constraint. Thus, calling getText three times will produce surprising behavior because getText represents all the different possible text values you could get in the course of streaming <table> elements through your proc x -> do {...}.
What we can do instead is focus on the stream we want: a stream of <tr>s inside the <tbody>. For each table row, we grab the ID attribute value and the text of the first two <td>s.
This does not seem the most elegant solution, but one way we can index into a stream is to filter it down with the (>.) :: ArrowList cat => cat a b -> ([b] -> c) -> cat a c combinator.
One last trick, one that I noticed in the practical wiki examples: we can use deep and isElem/isText to focus on just the nodes we want. XML trees are noisy!