waargonaut-0.5.1.0: JSON wrangling

Safe HaskellNone
LanguageHaskell2010

Waargonaut.Decode.Types

Description

Types for the succinct data structure decoder

Synopsis

Documentation

type ParseFn = ByteString -> Either DecodeError Json Source #

Another convenience alias for the type of the function we will use to parse the input string into the Json structure.

type SuccinctCursor = JsonCursor ByteString Poppy512 (SimpleBalancedParens (Vector Word64)) Source #

Convenience alias defined for the concrete JsonCursor type.

type CursorHistory = CursorHistory' Count Source #

We define the index of our CursorHistory' to be the Count.

newtype Decoder f a Source #

Decoder type that is used directly to convert Json structures to other data types.

Constructors

Decoder 
Instances
Monad f => MonadError DecodeError (Decoder f) Source # 
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 => Monad (Decoder f) Source # 
Instance details

Defined in Waargonaut.Decode.Types

Methods

(>>=) :: Decoder f a -> (a -> Decoder f b) -> Decoder f b #

(>>) :: Decoder f a -> Decoder f b -> Decoder f b #

return :: a -> Decoder f a #

fail :: String -> Decoder f a #

Functor f => Functor (Decoder f) Source # 
Instance details

Defined in Waargonaut.Decode.Types

Methods

fmap :: (a -> b) -> Decoder f a -> Decoder f b #

(<$) :: a -> Decoder f b -> Decoder f a #

Monad f => Applicative (Decoder f) Source # 
Instance details

Defined in Waargonaut.Decode.Types

Methods

pure :: a -> Decoder f a #

(<*>) :: Decoder f (a -> b) -> Decoder f a -> Decoder f b #

liftA2 :: (a -> b -> c) -> Decoder f a -> Decoder f b -> Decoder f c #

(*>) :: Decoder f a -> Decoder f b -> Decoder f b #

(<*) :: Decoder f a -> Decoder f b -> Decoder f a #

Monad f => Alt (Decoder f) Source # 
Instance details

Defined in Waargonaut.Decode.Types

Methods

(<!>) :: Decoder f a -> Decoder f a -> Decoder f a #

some :: Applicative (Decoder f) => Decoder f a -> Decoder f [a] #

many :: Applicative (Decoder f) => Decoder f a -> Decoder f [a] #

MFunctor Decoder Source # 
Instance details

Defined in Waargonaut.Decode.Types

Methods

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

newtype DecodeResult f a Source #

Provide some of the type parameters that the underlying DecodeResultT requires. This contains the state and error management as we walk around our zipper and decode our JSON input.

Addtionally we keep our parsing function in a ReaderT such that it's accessible for all of the decoding steps.

Instances
MMonad DecodeResult Source # 
Instance details

Defined in Waargonaut.Decode.Types

Methods

embed :: Monad n => (forall a. m a -> DecodeResult n a) -> DecodeResult m b -> DecodeResult n b #

MonadTrans DecodeResult Source # 
Instance details

Defined in Waargonaut.Decode.Types

Methods

lift :: Monad m => m a -> DecodeResult m a #

Monad f => MonadReader ParseFn (DecodeResult f) Source # 
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 => MonadState CursorHistory (DecodeResult f) Source # 
Instance details

Defined in Waargonaut.Decode.Types

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

Defined in Waargonaut.Decode.Types

Monad f => Monad (DecodeResult f) Source # 
Instance details

Defined in Waargonaut.Decode.Types

Methods

(>>=) :: DecodeResult f a -> (a -> DecodeResult f b) -> DecodeResult f b #

(>>) :: DecodeResult f a -> DecodeResult f b -> DecodeResult f b #

return :: a -> DecodeResult f a #

fail :: String -> DecodeResult f a #

Functor f => Functor (DecodeResult f) Source # 
Instance details

Defined in Waargonaut.Decode.Types

Methods

fmap :: (a -> b) -> DecodeResult f a -> DecodeResult f b #

(<$) :: a -> DecodeResult f b -> DecodeResult f a #

Monad f => Applicative (DecodeResult f) Source # 
Instance details

Defined in Waargonaut.Decode.Types

Methods

pure :: a -> DecodeResult f a #

(<*>) :: DecodeResult f (a -> b) -> DecodeResult f a -> DecodeResult f b #

liftA2 :: (a -> b -> c) -> DecodeResult f a -> DecodeResult f b -> DecodeResult f c #

(*>) :: DecodeResult f a -> DecodeResult f b -> DecodeResult f b #

(<*) :: DecodeResult f a -> DecodeResult f b -> DecodeResult f a #

MFunctor DecodeResult Source # 
Instance details

Defined in Waargonaut.Decode.Types

Methods

hoist :: Monad m => (forall a. m a -> n a) -> DecodeResult m b -> DecodeResult n b #

newtype JCurs Source #

Wrapper type for the SuccinctCursor

Constructors

JCurs 
Instances
JsonTypeAt JCurs Source # 
Instance details

Defined in Waargonaut.Decode.Types

Wrapped JCurs Source # 
Instance details

Defined in Waargonaut.Decode.Types

Associated Types

type Unwrapped JCurs :: * #

JCurs ~ t => Rewrapped JCurs t Source # 
Instance details

Defined in Waargonaut.Decode.Types

type Unwrapped JCurs Source # 
Instance details

Defined in Waargonaut.Decode.Types