waargonaut-0.2.0.1: JSON wrangling

Safe HaskellNone
LanguageHaskell2010

Waargonaut.Types.Json

Contents

Description

Top level types and functions for Waargonaut Json types.

Synopsis

Inner JSON types

data JType ws a Source #

Individual JSON Types and their trailing whitespace.

Constructors

JNull ws 
JBool Bool ws 
JNum JNumber ws 
JStr JString ws 
JArr (JArray ws a) ws 
JObj (JObject ws a) ws 
Instances
Bitraversable JType Source # 
Instance details

Defined in Waargonaut.Types.Json

Methods

bitraverse :: Applicative f => (a -> f c) -> (b -> f d) -> JType a b -> f (JType c d) #

Bifoldable JType Source # 
Instance details

Defined in Waargonaut.Types.Json

Methods

bifold :: Monoid m => JType m m -> m #

bifoldMap :: Monoid m => (a -> m) -> (b -> m) -> JType a b -> m #

bifoldr :: (a -> c -> c) -> (b -> c -> c) -> c -> JType a b -> c #

bifoldl :: (c -> a -> c) -> (c -> b -> c) -> c -> JType a b -> c #

Bifunctor JType Source # 
Instance details

Defined in Waargonaut.Types.Json

Methods

bimap :: (a -> b) -> (c -> d) -> JType a c -> JType b d #

first :: (a -> b) -> JType a c -> JType b c #

second :: (b -> c) -> JType a b -> JType a c #

Functor (JType ws) Source # 
Instance details

Defined in Waargonaut.Types.Json

Methods

fmap :: (a -> b) -> JType ws a -> JType ws b #

(<$) :: a -> JType ws b -> JType ws a #

Foldable (JType ws) Source # 
Instance details

Defined in Waargonaut.Types.Json

Methods

fold :: Monoid m => JType ws m -> m #

foldMap :: Monoid m => (a -> m) -> JType ws a -> m #

foldr :: (a -> b -> b) -> b -> JType ws a -> b #

foldr' :: (a -> b -> b) -> b -> JType ws a -> b #

foldl :: (b -> a -> b) -> b -> JType ws a -> b #

foldl' :: (b -> a -> b) -> b -> JType ws a -> b #

foldr1 :: (a -> a -> a) -> JType ws a -> a #

foldl1 :: (a -> a -> a) -> JType ws a -> a #

toList :: JType ws a -> [a] #

null :: JType ws a -> Bool #

length :: JType ws a -> Int #

elem :: Eq a => a -> JType ws a -> Bool #

maximum :: Ord a => JType ws a -> a #

minimum :: Ord a => JType ws a -> a #

sum :: Num a => JType ws a -> a #

product :: Num a => JType ws a -> a #

Traversable (JType ws) Source # 
Instance details

Defined in Waargonaut.Types.Json

Methods

traverse :: Applicative f => (a -> f b) -> JType ws a -> f (JType ws b) #

sequenceA :: Applicative f => JType ws (f a) -> f (JType ws a) #

mapM :: Monad m => (a -> m b) -> JType ws a -> m (JType ws b) #

sequence :: Monad m => JType ws (m a) -> m (JType ws a) #

(Eq ws, Eq a) => Eq (JType ws a) Source # 
Instance details

Defined in Waargonaut.Types.Json

Methods

(==) :: JType ws a -> JType ws a -> Bool #

(/=) :: JType ws a -> JType ws a -> Bool #

(Show ws, Show a) => Show (JType ws a) Source # 
Instance details

Defined in Waargonaut.Types.Json

Methods

showsPrec :: Int -> JType ws a -> ShowS #

show :: JType ws a -> String #

showList :: [JType ws a] -> ShowS #

AsJType (JType ws a) ws a Source # 
Instance details

Defined in Waargonaut.Types.Json

Methods

_JType :: Prism' (JType ws a) (JType ws a) Source #

_JNull :: Prism' (JType ws a) ws Source #

_JBool :: Prism' (JType ws a) (Bool, ws) Source #

_JNum :: Prism' (JType ws a) (JNumber, ws) Source #

_JStr :: Prism' (JType ws a) (JString, ws) Source #

_JArr :: Prism' (JType ws a) (JArray ws a, ws) Source #

_JObj :: Prism' (JType ws a) (JObject ws a, ws) Source #

class AsJType r ws a | r -> ws a where Source #

Typeclass for things that can represent a JType

Minimal complete definition

_JType

Methods

_JType :: Prism' r (JType ws a) Source #

_JNull :: Prism' r ws Source #

_JBool :: Prism' r (Bool, ws) Source #

_JNum :: Prism' r (JNumber, ws) Source #

_JStr :: Prism' r (JString, ws) Source #

_JArr :: Prism' r (JArray ws a, ws) Source #

_JObj :: Prism' r (JObject ws a, ws) Source #

Instances
AsJType Json WS Json Source #

Json is comprised of the different JType types.

Instance details

Defined in Waargonaut.Types.Json

AsJType (JType ws a) ws a Source # 
Instance details

Defined in Waargonaut.Types.Json

Methods

_JType :: Prism' (JType ws a) (JType ws a) Source #

_JNull :: Prism' (JType ws a) ws Source #

_JBool :: Prism' (JType ws a) (Bool, ws) Source #

_JNum :: Prism' (JType ws a) (JNumber, ws) Source #

_JStr :: Prism' (JType ws a) (JString, ws) Source #

_JArr :: Prism' (JType ws a) (JArray ws a, ws) Source #

_JObj :: Prism' (JType ws a) (JObject ws a, ws) Source #

Top level JSON type

newtype Json Source #

Top level Json type, we specialise the whitespace to WS and the digit type to Digit. Also defining that our structures can recursively only contain Json types.

Constructors

Json (JType WS Json) 
Instances
Eq Json Source # 
Instance details

Defined in Waargonaut.Types.Json

Methods

(==) :: Json -> Json -> Bool #

(/=) :: Json -> Json -> Bool #

Show Json Source # 
Instance details

Defined in Waargonaut.Types.Json

Methods

showsPrec :: Int -> Json -> ShowS #

show :: Json -> String #

showList :: [Json] -> ShowS #

Wrapped Json Source # 
Instance details

Defined in Waargonaut.Types.Json

Associated Types

type Unwrapped Json :: * #

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

Defined in Waargonaut.Types.Json

AsJType Json WS Json Source #

Json is comprised of the different JType types.

Instance details

Defined in Waargonaut.Types.Json

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 #

type Unwrapped Json Source # 
Instance details

Defined in Waargonaut.Types.Json

Parser / Builder

waargonautBuilder :: (WS -> Builder) -> Json -> Builder Source #

Using the given whitespace builder, create a builder for a given Json value.

parseWaargonaut :: (Monad f, CharParsing f) => f Json Source #

Parse to a Json value, keeping all of the information about the leading and trailing whitespace.

Traversals

jsonTraversal :: Traversal' Json Json Source #

Ignoring whitespace, traverse a Json structure.

jsonWSTraversal :: Traversal Json Json WS WS Source #

Traverse the trailing whitespace of this Json structure.

jtypeTraversal :: Traversal (JType ws a) (JType ws a') a a' Source #

Traverse the possible values of a JType, skipping whitespace.

jtypeWSTraversal :: Traversal (JType ws a) (JType ws' a) ws ws' Source #

Traverse all of the whitespace of this Json structure and every element in the tree.