waargonaut-0.8.0.0: JSON wrangling

Safe HaskellNone
LanguageHaskell2010

Waargonaut.Decode.Runners

Contents

Description

Functions to execution of Decoders

Synopsis

General over f

decodeWithInput :: (CharParsing f, Show e, Monad g, Monad f) => (forall a. f a -> i -> Either e a) -> (ByteString -> i) -> (i -> ByteString) -> Decoder g x -> i -> g (Either (DecodeError, CursorHistory) x) Source #

General decoding function that takes a given parsing function and some functions to handle the transition from the input of the JCurs to the desired input type. The indexer and cursor requires a ByteString to work efficiently, but this does not preclude the use of other text types, provided the right functions are present.

There are some specialised versions of this function provided for Text, String, and ByteString. They are implemented using this function, for example to work with Text input and the attoparsec package:

import qualified Data.Attoparsec.Text as AT
import qualified Data.Text as Text

textDecode :: Monad g => Decoder g x -> Text -> g (Either (DecodeError, CursorHistory) x)
textDecode = decodeWithInput AT.parseOnly Text.decodeUtf8 Text.encodeUtf8

decodeFromString :: (CharParsing f, Monad f, Monad g, Show e) => (forall a. f a -> String -> Either e a) -> Decoder g x -> String -> g (Either (DecodeError, CursorHistory) x) Source #

As per the decodeWithInput function, but with the input type specialised to String.

This function goes via Text to ensure the UTF-8 is handled as best as we can.

decodeFromText :: (CharParsing f, Monad f, Monad g, Show e) => (forall a. f a -> Text -> Either e a) -> Decoder g x -> Text -> g (Either (DecodeError, CursorHistory) x) Source #

As per decodeWithInput function but specialised to the Text input type.

An example:

textDecode :: Decoder f a -> f (Either (DecodeError, CursorHistory) a)
textDecode = decodeFromText AT.parseOnly

decodeFromByteString :: (CharParsing f, Monad f, Monad g, Show e) => (forall a. f a -> ByteString -> Either e a) -> Decoder g x -> ByteString -> g (Either (DecodeError, CursorHistory) x) Source #

As per decodeWithInput function but specialised to the ByteString input type.

Identity

pureDecodeWithInput :: (Monad f, CharParsing f, Show e) => (forall g. Monad g => (forall a. f a -> i -> Either e a) -> Decoder g x -> i -> g (Either (DecodeError, CursorHistory) x)) -> (forall a. f a -> i -> Either e a) -> Decoder Identity x -> i -> Either (DecodeError, CursorHistory) x Source #

This function works using one of the 'decodeFrom*' functions and provides a pure decoder that demands the Decoder but specialised to Identity. Decoders are often to be general in their g type so most are fine to use this function. It is offered as a convenience and can be used like so:

import qualified Data.Attoparsec.Text as AT
import qualified Data.Text as Text

pureTextDecode :: Decoder Identity x -> Text -> Either (DecodeError, CursorHistory) x
pureTextDecode = pureDecodeWithInput decodeWithText AT.parseOnly

pureDecodeFromText :: (Monad f, CharParsing f, Show e) => (forall a. f a -> Text -> Either e a) -> Decoder Identity x -> Text -> Either (DecodeError, CursorHistory) x Source #

As per pureDecodeWithInput but specialised to Text.

pureDecodeFromString :: (Monad f, CharParsing f, Show e) => (forall a. f a -> String -> Either e a) -> Decoder Identity x -> String -> Either (DecodeError, CursorHistory) x Source #

As per pureDecodeWithInput but specialised to String.

Helpers

overrideParser :: (CharParsing g, Monad g, Monad f, Show e) => (forall x. g x -> i -> Either e x) -> (ByteString -> i) -> g Json -> DecodeResult f a -> DecodeResult f a Source #

This function lets you override the parsing function that is being used in a decoder for a different one. This means that when building your Decoder you are not bound to only using a single parsing function. If you have specific needs for alternate parsers then you can use this function in your Decoder to make that change.

Similar to the other decoding functions, this operation allows you to specify your own parsing function and if necessary a 'ByteString -> i' conversion.

parseUsingByteString :: (Show e, CharParsing f, Monad f) => f a -> ByteString -> Either e a
parseUsingByteString = ...

myTricksyObj = withCursor $ curs -> do
  curs' <- down curs
  fA <- fromKey "normalFieldA" int curs'
  fB <- fromKey "normalFieldB" text curs'
  wB <- overrideParser parseUsingByteString id handTunedParser $ fromKey "weirdFieldC" fieldCDecoder curs'
  pure $ Foo fA fB wB

parseWith :: (CharParsing f, Show e) => (f a -> i -> Either e a) -> f a -> i -> Either DecodeError a Source #

Helper function to handle wrapping up a parse failure using the given parsing function. Intended to be used with the runDecode or simpleDecode functions.

import Data.Attoparsec.ByteString (parseOnly)

simpleDecode (list int) (parseWith (parseOnly parseWaargonaut)) "[1,1,2]"