waargonaut-0.3.0.0: JSON wrangling

Safe HaskellNone
LanguageHaskell2010

Waargonaut.Decode.Internal

Contents

Description

Internal types and functions for building Decoder infrastructure.

Synopsis

Documentation

newtype CursorHistory' i Source #

Track the history of the cursor as we move around the zipper.

It is indexed over the type of the index used to navigate the zipper.

Constructors

CursorHistory' 
Instances
Monad f => MonadState CursorHistory (DecodeResult f) # 
Instance details

Defined in Waargonaut.Decode.Types

Eq i => Eq (CursorHistory' i) Source # 
Instance details

Defined in Waargonaut.Decode.Internal

Show i => Show (CursorHistory' i) Source # 
Instance details

Defined in Waargonaut.Decode.Internal

Wrapped (CursorHistory' i) Source # 
Instance details

Defined in Waargonaut.Decode.Internal

Associated Types

type Unwrapped (CursorHistory' i) :: * #

CursorHistory' i ~ t => Rewrapped (CursorHistory' i) t Source # 
Instance details

Defined in Waargonaut.Decode.Internal

Monad f => MonadState (CursorHistory' Int) (DecodeResult f) # 
Instance details

Defined in Waargonaut.Decode.Traversal

Monad f => MonadState (CursorHistory' i) (DecodeResultT i e f) Source # 
Instance details

Defined in Waargonaut.Decode.Internal

Methods

get :: DecodeResultT i e f (CursorHistory' i) #

put :: CursorHistory' i -> DecodeResultT i e f () #

state :: (CursorHistory' i -> (a, CursorHistory' i)) -> DecodeResultT i e f a #

type Unwrapped (CursorHistory' i) Source # 
Instance details

Defined in Waargonaut.Decode.Internal

ppCursorHistory :: CursorHistory' i -> Doc a Source #

Pretty print the given CursorHistory' to a more useful format compared to a Seq of i.

newtype DecodeResultT i e f a Source #

The general structure used to maintain the history of the moves around the zipper, as well as handle the decoding or movement errors that may occur. This structure is generalised of the inner f to allow you to interleave the decoding with your own actions. As well as the error type e so that you may provide your own error type.

If you use the provided Decode module then you probably won't need to care about this type. It is provided so that you're not limited to how we decide you should be running your decoder.

Constructors

DecodeResultT 
Instances
Monad f => MonadError e (DecodeResultT i e f) Source # 
Instance details

Defined in Waargonaut.Decode.Internal

Methods

throwError :: e -> DecodeResultT i e f a #

catchError :: DecodeResultT i e f a -> (e -> DecodeResultT i e f a) -> DecodeResultT i e f a #

MFunctor (DecodeResultT i e :: (* -> *) -> * -> *) Source # 
Instance details

Defined in Waargonaut.Decode.Internal

Methods

hoist :: Monad m => (forall a. m a -> n a) -> DecodeResultT i e m b -> DecodeResultT i e n b #

Monad f => MonadState (CursorHistory' i) (DecodeResultT i e f) Source # 
Instance details

Defined in Waargonaut.Decode.Internal

Methods

get :: DecodeResultT i e f (CursorHistory' i) #

put :: CursorHistory' i -> DecodeResultT i e f () #

state :: (CursorHistory' i -> (a, CursorHistory' i)) -> DecodeResultT i e f a #

MMonad (DecodeResultT i e) Source # 
Instance details

Defined in Waargonaut.Decode.Internal

Methods

embed :: Monad n => (forall a. m a -> DecodeResultT i e n a) -> DecodeResultT i e m b -> DecodeResultT i e n b #

MonadTrans (DecodeResultT i e) Source # 
Instance details

Defined in Waargonaut.Decode.Internal

Methods

lift :: Monad m => m a -> DecodeResultT i e m a #

Monad f => Monad (DecodeResultT i e f) Source # 
Instance details

Defined in Waargonaut.Decode.Internal

Methods

(>>=) :: DecodeResultT i e f a -> (a -> DecodeResultT i e f b) -> DecodeResultT i e f b #

(>>) :: DecodeResultT i e f a -> DecodeResultT i e f b -> DecodeResultT i e f b #

return :: a -> DecodeResultT i e f a #

fail :: String -> DecodeResultT i e f a #

Functor f => Functor (DecodeResultT i e f) Source # 
Instance details

Defined in Waargonaut.Decode.Internal

Methods

fmap :: (a -> b) -> DecodeResultT i e f a -> DecodeResultT i e f b #

(<$) :: a -> DecodeResultT i e f b -> DecodeResultT i e f a #

Monad f => Applicative (DecodeResultT i e f) Source # 
Instance details

Defined in Waargonaut.Decode.Internal

Methods

pure :: a -> DecodeResultT i e f a #

(<*>) :: DecodeResultT i e f (a -> b) -> DecodeResultT i e f a -> DecodeResultT i e f b #

liftA2 :: (a -> b -> c) -> DecodeResultT i e f a -> DecodeResultT i e f b -> DecodeResultT i e f c #

(*>) :: DecodeResultT i e f a -> DecodeResultT i e f b -> DecodeResultT i e f b #

(<*) :: DecodeResultT i e f a -> DecodeResultT i e f b -> DecodeResultT i e f a #

newtype Decoder' c i e f a Source #

Wrapper type to describe a Decoder from something that has a Jsonish value c, to some representation of a.

Constructors

Decoder' 

Fields

Instances
MFunctor (Decoder' c i e :: (* -> *) -> * -> *) Source # 
Instance details

Defined in Waargonaut.Decode.Internal

Methods

hoist :: Monad m => (forall a. m a -> n a) -> Decoder' c i e m b -> Decoder' c i e n b #

MonadTrans (Decoder' c i e) Source # 
Instance details

Defined in Waargonaut.Decode.Internal

Methods

lift :: Monad m => m a -> Decoder' c i e m a #

Monad f => Monad (Decoder' c i e f) Source # 
Instance details

Defined in Waargonaut.Decode.Internal

Methods

(>>=) :: Decoder' c i e f a -> (a -> Decoder' c i e f b) -> Decoder' c i e f b #

(>>) :: Decoder' c i e f a -> Decoder' c i e f b -> Decoder' c i e f b #

return :: a -> Decoder' c i e f a #

fail :: String -> Decoder' c i e f a #

Functor f => Functor (Decoder' c i e f) Source # 
Instance details

Defined in Waargonaut.Decode.Internal

Methods

fmap :: (a -> b) -> Decoder' c i e f a -> Decoder' c i e f b #

(<$) :: a -> Decoder' c i e f b -> Decoder' c i e f a #

Monad f => Applicative (Decoder' c i e f) Source # 
Instance details

Defined in Waargonaut.Decode.Internal

Methods

pure :: a -> Decoder' c i e f a #

(<*>) :: Decoder' c i e f (a -> b) -> Decoder' c i e f a -> Decoder' c i e f b #

liftA2 :: (a -> b -> c0) -> Decoder' c i e f a -> Decoder' c i e f b -> Decoder' c i e f c0 #

(*>) :: Decoder' c i e f a -> Decoder' c i e f b -> Decoder' c i e f b #

(<*) :: Decoder' c i e f a -> Decoder' c i e f b -> Decoder' c i e f a #

withCursor' :: (c -> DecodeResultT i e f a) -> Decoder' c i e f a Source #

Helper function for constructing a Decoder'.

This function is used by the implemented decoders to simplify constructing a more specific Decoder type.

withCursor' $ curs ->
  ...
  ...

runDecoderResultT :: Monad f => DecodeResultT i DecodeError f a -> f (Either (DecodeError, CursorHistory' i) a) Source #

Execute a given DecoderResultT.

If you're building your own decoder structure, this function will take care of the CursorHistory' and error handling (via ExceptT).

try :: MonadError e m => m a -> m (Maybe a) Source #

Attempt a Decoder action that might fail and return a Maybe value instead.

recordZipperMove :: MonadState (CursorHistory' i) m => ZipperMove -> i -> m () Source #

Record a move on the zipper and the index of the position where the move occured.

Generalised Decoder Functions

null' :: AsJType a ws a => a -> Maybe () Source #

Try to decode a null value from some Json value

int' :: AsJType a ws a => a -> Maybe Int Source #

Try to decode an Int from some Json value

text' :: AsJType a ws a => a -> Maybe Text Source #

Try to decode a Text value from some Json or value.

string' :: AsJType a ws a => a -> Maybe String Source #

Try to decode a String value from some Json or value.

unboundedChar' :: AsJType a ws a => a -> Maybe Char Source #

Decoder for a Haskell Char value whose values represent Unicode (or equivalently ISO/IEC 10646) characters

boundedChar' :: AsJType a ws a => a -> Maybe Char Source #

Decoder for a Char value that cannot contain values in the range U+D800 to U+DFFF. This decoder will fail if the Char is outside of this range.

bool' :: AsJType a ws a => a -> Maybe Bool Source #

Try to decode a Bool from some Json value

array' :: AsJType a ws a => (a -> Maybe b) -> a -> [b] Source #

Combined with another decoder function f, try to decode a list of a values.

array' int' :: Json -> [Int]

integral' :: (Bounded i, Integral i, AsJType a ws a) => a -> Maybe i Source #

Try to decode a bounded 'Integral n => n' value from some Json value.

scientific' :: AsJType a ws a => a -> Maybe Scientific Source #

Try to decode a Scientific value from some Json or value.

objTuples' :: (Applicative f, AsJType a ws a) => (JString -> f k) -> (a -> f b) -> a -> f [(k, b)] Source #

Try to decode a JSON Object into it's representative list of tuples '(key, value)'. The JSON RFC does not specify that an object must contain unique keys. We do not enforce unique keys during the decoding process and leave it to the user to decide if, and how, they would like to handle this situation.

foldCursor' :: Monad f => b -> (b -> a -> b) -> (c -> DecodeResultT i e f c) -> Decoder' c i e f a -> c -> DecodeResultT i e f b Source #

Generalised moving decoder function.

Starting from the given cursor position, try to move in the direction specified by the given cursor function. Attempting to decode each item at each position using the given Decoder, until the movement is unsuccessful.

The following could be used to leverage the Snoc instance of '[]' to build '[Int]'.

intList :: Monad f => JCurs -> DecodeResult f [Int]
intList = directedConsumption' snoc moveRight1 int

prismDOrFail' :: (AsDecodeError e, MonadError e f) => e -> Prism' a b -> Decoder' c i e f a -> c -> DecodeResultT i e f b Source #

Build the basis for a Decoder based on a Prism'.

JSON Object to Map Functions

mapKeepingF :: (Ord k, Applicative f, AsJType a ws a) => (t -> Maybe v -> Maybe v) -> (JString -> f k) -> (a -> f t) -> a -> f (Map k v) Source #

Provide a generalised and low level way of turning a JSON object into a Map, without enforcing a choice of how we select keys.

mapKeepingFirst :: (Ord k, Applicative f, AsJType a ws a) => (JString -> f k) -> (a -> f b) -> a -> f (Map k b) Source #

Turn a JSON object into a Map by keeping the *first* occurence of any duplicate keys that are encountered.

mapKeepingLast :: (Ord k, Applicative f, AsJType a ws a) => (JString -> f k) -> (a -> f b) -> a -> f (Map k b) Source #

Turn a JSON object into a Map by keeping the *last* occurence of any duplicate keys that are encountered.

Re-exports

data DecodeError Source #

Set of errors that may occur during the decode phase.

Instances
Eq DecodeError Source # 
Instance details

Defined in Waargonaut.Decode.Error

Show DecodeError Source # 
Instance details

Defined in Waargonaut.Decode.Error

AsDecodeError DecodeError Source # 
Instance details

Defined in Waargonaut.Decode.Error

Monad f => MonadReader ParseFn (DecodeResult f) # 
Instance details

Defined in Waargonaut.Decode.Types

Methods

ask :: DecodeResult f ParseFn #

local :: (ParseFn -> ParseFn) -> DecodeResult f a -> DecodeResult f a #

reader :: (ParseFn -> a) -> DecodeResult f a #

Monad f => MonadError DecodeError (DecodeResult f) # 
Instance details

Defined in Waargonaut.Decode.Types

Monad f => MonadError DecodeError (Decoder f) # 
Instance details

Defined in Waargonaut.Decode.Types

Methods

throwError :: DecodeError -> Decoder f a #

catchError :: Decoder f a -> (DecodeError -> Decoder f a) -> Decoder f a #

Monad f => MonadError DecodeError (DecodeResult f) # 
Instance details

Defined in Waargonaut.Decode.Traversal

ppZipperMove :: ZipperMove -> Doc a Source #

Pretty print a given zipper movement, used when printing CursorHistory' to improve the readability of the errors.