3

I have a json source that is not well behaved. It too often provides unexpected JSON that contains array elements that are malformed. I would like to parse this JSON and ignore any malformed array elements.

Here is my attempt:

{-# LANGUAGE OverloadedStrings #-}
module Main where

import Control.Applicative        ((<$>), (<*>))
import Control.Monad              (mzero)
import Data.Aeson
import Data.ByteString.Lazy.Char8 (ByteString, pack)

data Foo = Foo Integer [Maybe Bar] deriving (Show)
data Bar = Bar Integer Integer deriving (Show)

instance FromJSON Foo where
    parseJSON (Object v) = Foo <$> (v .: "a") <*> (v .: "b") 
    parseJSON _          = mzero

instance FromJSON Bar where
    parseJSON (Object v) = Bar <$> (v .: "c") <*> (v .: "d")
    parseJSON _          = mzero

-- this string is malformed - second array element has an unexpected key
testString = pack "{\"a\":1, \"b\":[{\"c\":11, \"d\":12}, {\"C\":21, \"d\":22}, {\"c\":31, \"d\":32}]}"

-- want this to be: 
--
-- Just (Foo 1 [Just (Bar 11 12),Nothing,Just (Bar 31 32)])
--
-- or
--
-- Just (Foo 1 [Just (Bar 11 12),Just (Bar 31 32)])
main = print $ (decode testString :: Maybe Foo)

When teststring is malformed, the whole decoding of Foo returns Nothing. I would like Foo to parse, but any malformed array elements of b to be Nothing.

Bakuriu
  • 98,325
  • 22
  • 197
  • 231
helpwithhaskell
  • 558
  • 4
  • 13

1 Answers1

5

You can't rely on the default implementation of FromJSON for lists, you'll have to do a bit more work yourself:

instance FromJSON Foo where
    parseJSON (Object v) = do
        a <- v .: "a"
        bList <- v .: "b"
        return $ Foo a $ map (parseMaybe parseJSON) bList

The parseMaybe parseJSON function has the type FromJSON a => Value -> Maybe a, so bList :: [Value] meaning map (parseMaybe parseJSON) bList :: [Maybe Bar]. This is probably the best way to go about it considering the documentation (see "Decoding a mixed-type object") uses a similar approach for parsing JSON that isn't well behaved.

bheklilr
  • 53,530
  • 6
  • 107
  • 163