highjson-0.2.0.1: Very fast JSON serialisation and parsing library

Safe HaskellNone
LanguageHaskell2010

Data.Json.Parser

Contents

Synopsis

Parsing from different types

parseJsonBs :: JsonReadable t => ByteString -> Either String t Source

Parse json from a strict ByteString

parseJsonT :: JsonReadable t => Text -> Either String t Source

Parse json from a strict Text

Description how to parse JSON to a Haskell type

class JsonReadable t where Source

Typeclass defining an attoparsec Parser how Haskell types should be parsed from JSON. Use predifined instances (with readJson) and runSpec (on ObjSpec) to define instances for custom types

Methods

readJson :: Parser t Source

DSL to easily create parser for custom Haskell types

data ObjSpec ts where Source

List of TypedKeys, should be in the same order as your constructor in runSpec will expect them

Constructors

ObjSpecNil :: ObjSpec [] 
(:&&:) :: (JsonReadable t, Typeable t) => !(TypedKey t) -> !(ObjSpec ts) -> ObjSpec (t : ts) infixr 5 

data ParseSpec k where Source

Parser specification. Use :$: for normal types and FirstConstr / :|: for sum types

Constructors

(:$:) :: HVectElim ts k -> ObjSpec ts -> ParseSpec k infixr 4 
FirstConstr :: KeyedConstr k -> ParseSpec k 
(:|:) :: KeyedConstr k -> ParseSpec k -> ParseSpec k 

Instances

data KeyedConstr k Source

Associates a json key with a parser

Instances

(<||>) :: KeyedConstr k -> ParseSpec k -> ParseSpec k infixr 3 Source

Choice between multiple constructors

class ConstrTagger r where Source

Associated Types

type ResultType r :: * Source

Methods

(.->) :: Text -> Parser (ResultType r) -> r Source

Associate a json key with a parser

data TypedKey t Source

Json object key to a value t

Instances

reqKey :: Typeable t => Text -> TypedKey t Source

Required json object key. Use IsString instance for automatic choice

optKey :: Typeable t => Text -> TypedKey (Maybe t) Source

Optional json object key. Use IsString instance for automatic choice

typedKeyKey :: TypedKey t -> Text Source

Get the textual key of a TypedKey

Low level JSON parsing helpers

readObject :: (Text -> Maybe (Parser a)) -> Parser (HashMap Text a) Source

Parse a json object given a value parser for each key

data WrappedValue Source

A value that is Typeable and JsonReadable

Constructors

forall t . (Typeable t, JsonReadable t) => WrappedValue !t 

getValueByKey :: (Monad m, Typeable t) => Text -> HashMap Text WrappedValue -> m t Source

Get a value out of the map returned by readObject

getOptValueByKey :: (Monad m, Typeable t) => Text -> HashMap Text WrappedValue -> m (Maybe t) Source

Optionally get a value out of the map returned by readObject