Aeson: parsing json with 'data' field

Hi, please can you help me with this.......I have a json file which contains a field with name "data". Problem is that I can not create a data type with "data", (or can I)? How else can I handle this? I know I can convert all json to Object and then search for the field....but I was hoping for some friendly/easier option. json example: { "data" : { "foo" : "bar" } } below definition returns: parse error on input ‘data’ data Foo = Foo { data :: String } Cheers, Miro

{-# LANGUAGE OverloadedStrings #-}
import Data.Aeson ((.:), (.:?), decode, FromJSON(..), Value(..))
import Control.Applicative ((<$>), (<*>))
import qualified Data.ByteString.Lazy.Char8 as BS
data Foo = Foo {
_data :: String -- call it anything you like
}
deriving (Show)
instance FromJSON Foo where
parseJSON (Object v) =
Foo <$>
(v .: "data")
Testing:
ghci> let json = BS.pack "{\"data\":\"hello\"}"
ghci> let (Just x) = decode json :: Maybe Foo|
ghci> x
Foo {_data = "hello"}
On 4 October 2014 08:07, Miro Karpis
Hi, please can you help me with this.......I have a json file which contains a field with name "data". Problem is that I can not create a data type with "data", (or can I)? How else can I handle this? I know I can convert all json to Object and then search for the field....but I was hoping for some friendly/easier option.
json example:
{ "data" : { "foo" : "bar" } }
below definition returns: parse error on input ‘data’ data Foo = Foo { data :: String }
Cheers, Miro
_______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners

thank you, that helped ;-)
On Sat, Oct 4, 2014 at 6:40 PM, Derek McLoughlin wrote: {-# LANGUAGE OverloadedStrings #-} import Data.Aeson ((.:), (.:?), decode, FromJSON(..), Value(..))
import Control.Applicative ((<$>), (<*>))
import qualified Data.ByteString.Lazy.Char8 as BS data Foo = Foo {
_data :: String -- call it anything you like
}
deriving (Show) instance FromJSON Foo where
parseJSON (Object v) =
Foo <$>
(v .: "data") Testing: ghci> let json = BS.pack "{\"data\":\"hello\"}"
ghci> let (Just x) = decode json :: Maybe Foo|
ghci> x
Foo {_data = "hello"} On 4 October 2014 08:07, Miro Karpis Hi,
please can you help me with this.......I have a json file which contains
a
field with name "data". Problem is that I can not create a data type with
"data", (or can I)? How else can I handle this? I know I can convert all
json to Object and then search for the field....but I was hoping for some
friendly/easier option. json example: {
"data" : {
"foo" : "bar"
}
} below definition returns: parse error on input ‘data’
data Foo = Foo {
data :: String
} Cheers,
Miro _______________________________________________
Beginners mailing list
Beginners@haskell.org
http://www.haskell.org/mailman/listinfo/beginners
participants (2)
-
Derek McLoughlin
-
Miro Karpis