3

I have the following function:

parseUserBasic :: ByteString -> Either String [Either String UserBasic]
parseUserBasic x = do 
  xx <- parseItems x
  pure $ fmap (eitherDecode . encode) (items xx)

However it's not very efficient because of pure $ fmap (eitherDecode . encode) (items xx) - we are JSON encoding a Object into a ByteString, which we then decode into a UserBasic. Is there a way to do this directly? I assume this function would have the type FromJSON a => Value -> Maybe a.

The complete code:

{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE OverloadedStrings #-}

module UserBasic where

import GHC.Generics
import Data.Aeson
import Data.String.Conversions
import Data.ByteString.Lazy

data UserBasic = UserBasic
  { email :: String
  , name :: String
  , address_1 :: Maybe String
  , address_2 :: Maybe String
  , address_3 :: Maybe String
  , address_4 :: Maybe String
  } deriving (Generic, Show)

data Items = Items
  { items :: [Object]
  } deriving (Generic, Show)

instance FromJSON Items where
instance ToJSON Items where
  toEncoding = genericToEncoding defaultOptions

instance FromJSON UserBasic where
     parseJSON = withObject "Person" $ \v -> UserBasic
         <$> v .: "email"
         <*> ((++) . (++ " ") <$> v .: "first_name" <*> v .: "last_name")
         <*> v .: "first_name"
         <*> v .: "first_name"
         <*> v .: "first_name"
         <*> v .: "first_name"

parseItems :: ByteString -> Either String Items
parseItems = eitherDecode

parseUserBasic :: ByteString -> Either String [Either String UserBasic]
parseUserBasic x = do 
  xx <- parseItems x
  pure $ fmap (eitherDecode . encode) (items xx)
Chris Stryczynski
  • 30,145
  • 48
  • 175
  • 286
  • 2
    Would it be [fromJSON](http://hackage.haskell.org/package/aeson-1.5.2.0/docs/Data-Aeson-Types.html#v:fromJSON)? But I guess it's simpler to define a list of `UserBasic` and decode the JSON directly into it. – snak Jul 24 '20 at 14:20
  • Just to double-check: the idiomatic thing is to just use `eitherDecode :: ByteString -> Either String [UserBasic]` (or a minor variant if the existence of the top-level "items" key is a requirement handed down from heaven). Are you sure you don't want that? – Daniel Wagner Jul 24 '20 at 20:23
  • To be clear: when I said "just use", I meant "just use `eitherDecode` instead of `parseUserBasic`". – Daniel Wagner Jul 24 '20 at 20:34
  • Not sure I fully understand. But the JSON value I get (from an API) indeed has the users under the `items` key. So I don't see how just using `eitherDecode :: ByteString -> Either String [UserBasic]` would work. In terms of the 'variant' - I assume that would what `parseUserBasic` is - unless there is another alternative? – Chris Stryczynski Jul 24 '20 at 22:22

2 Answers2

2

Thanks to @snak pointing out fromJSON which is defined as:

-- | Convert a value from JSON, failing if the types do not match.
fromJSON :: (FromJSON a) => Value -> Result a
fromJSON = parse parseJSON

Which lead me to the solution:

fff :: Value -> Either String UserBasic
fff x = parseEither parseJSON $ x

parseUserBasic :: ByteString -> Either String [Either String UserBasic]
parseUserBasic x = do 
  xx <- parseItems x
  pure $ fmap (fff) (fmap Object $ items xx)
Chris Stryczynski
  • 30,145
  • 48
  • 175
  • 286
2

I recommend the following abbreviated code:

newtype Items = Items
  { items :: [UserBasic]
  } deriving (Generic, Show)

instance FromJSON Items
instance ToJSON Items where
  toEncoding = genericToEncoding defaultOptions

parseUserBasic :: ByteString -> Either String [UserBasic]
parseUserBasic bs = items <$> eitherDecode bs

-- OR, even better in many cases, don't bother unwrapping Items:

parseItems :: ByteString -> Either String Items
parseItems = eitherDecode -- why even bother naming parseItems lmao

Don't first decode to Object, then do further decoding; just decode directly to the type you care about.

Daniel Wagner
  • 145,880
  • 9
  • 220
  • 380