[Haskell-beginners] Is it possible to "run" JSON Parser?

David McBride toad3k at gmail.com
Tue Aug 29 16:27:34 UTC 2017


There are three ways to go about this.

Method one, we could turn all the Values into Maybe MyTypes.
Method two, we could filter out any Value which cannot be turned into an MyType.
Method three, we could fail to parse entirely if any Value cannot be
turned into a MyType succesfully.

Here is some code that demonstrates all three approaches.

import Data.Aeson
import Data.Aeson.Types (Parser)
import Control.Monad
import qualified Data.Text as T
import Data.Maybe (catMaybes)

data Resp = Resp {
  rHeadings :: [T.Text],
  rows1 :: [Maybe MyType],
  rows2 :: [MyType],
  rows3 :: [MyType]
}

data MyType = MyType

instance FromJSON Resp where
  parseJSON = withObject "Resp" $ \v -> do
    hds <- v .: "headings"


    -- we could catch all of mytypes as maybes
    r1 <- fmap f <$> v .: "rows" :: Parser [Maybe MyType]

    -- we could throw away values which can't be turned into MyType
    r2 <- catMaybes . fmap f <$> v .: "rows" :: Parser [MyType]

    -- we could fail the parse entirely if any value fails.
    r3 <- v .: "rows" >>= traverse f'
    pure $ Resp hds r1 r2 r3

f :: Value -> Maybe MyType
f v = undefined

f' :: Value -> Parser MyType
f' (String t) = pure MyType
f' (Bool t) = pure MyType
f' (Number t) = pure MyType
f' (Null) = pure MyType
 -- Anything that is not one of the above will cause a failure of the
entire parse.
f' _ = mzero

On Tue, Aug 29, 2017 at 11:58 AM, Baa <aquagnu at gmail.com> wrote:
> Hello List again! :)
>
> If I have a `FromJSON` instance, with `parseJSON` which translates
> `Value` to MyType, how can I run this parser like I "run"
> state/writer/reader monads? I mean not decoding of a bytestring
> representation:
>
>   decode::ByteString -> Maybe MyType
>
> but
>
>   run::Value -> Maybe MyType
>
> The reason is that I have already collected Value's , and I have
> parsers, so what is the problem, it would seem, to run parser on the
> Value - to convert `Value` into `Maybe MyType`... Is it possible?
>
> ===
> Best regards, Paul
> _______________________________________________
> Beginners mailing list
> Beginners at haskell.org
> http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners


More information about the Beginners mailing list