hermes-json-0.5.0.0: Fast JSON decoding via simdjson C++ bindings
Safe HaskellSafe-Inferred
LanguageHaskell2010

Data.Hermes

Description

Exposes functions for building JSON decoders that harness the power of the simdjson::ondemand API.

A decoder is really a function from a simdjson Value to some Haskell type in the DecoderM monad. It looks like Data.Aeson.parseJSON, except the Value is opaque and can only be used when it's passed by reference across the C FFI.

decodeEither provides the quickest way to feed the initial Value to your decoder. It does this by obtaining a top-level Value from the simdjson document instance. Decoding a document into a scalar from a Value is not supported by simdjson. While simdjson can cast a document directly to a scalar, this library currently exposes no interface for this.

Synopsis

Decoding from ByteString input

decodeEither :: Decoder a -> ByteString -> Either HermesException a Source #

Decode a strict ByteString using the simdjson::ondemand bindings. Creates simdjson instances on each decode.

decodeEitherIO :: Decoder a -> ByteString -> IO a Source #

Decode a strict ByteString using the simdjson::ondemand bindings. Creates simdjson instances on each decode. Runs in IO instead of discharging it.

data Decoder a Source #

Instances

Instances details
MonadFail Decoder Source # 
Instance details

Defined in Data.Hermes.Decoder.Internal

Methods

fail :: String -> Decoder a #

Alternative Decoder Source # 
Instance details

Defined in Data.Hermes.Decoder.Internal

Methods

empty :: Decoder a #

(<|>) :: Decoder a -> Decoder a -> Decoder a #

some :: Decoder a -> Decoder [a] #

many :: Decoder a -> Decoder [a] #

Applicative Decoder Source # 
Instance details

Defined in Data.Hermes.Decoder.Internal

Methods

pure :: a -> Decoder a #

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

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

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

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

Functor Decoder Source # 
Instance details

Defined in Data.Hermes.Decoder.Internal

Methods

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

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

Monad Decoder Source # 
Instance details

Defined in Data.Hermes.Decoder.Internal

Methods

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

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

return :: a -> Decoder a #

Decoder monad

data DecoderM a Source #

DecoderM is some context around the IO needed by the C FFI to allocate local memory. Users have no access to the underlying IO, since this could allow decoders to launch nukes. Using decodeEither discharges the IO and returns us to purity, since we know decoding a document is referentially transparent.

Instances

Instances details
MonadFail DecoderM Source # 
Instance details

Defined in Data.Hermes.Decoder.Internal

Methods

fail :: String -> DecoderM a #

Alternative DecoderM Source # 
Instance details

Defined in Data.Hermes.Decoder.Internal

Methods

empty :: DecoderM a #

(<|>) :: DecoderM a -> DecoderM a -> DecoderM a #

some :: DecoderM a -> DecoderM [a] #

many :: DecoderM a -> DecoderM [a] #

Applicative DecoderM Source # 
Instance details

Defined in Data.Hermes.Decoder.Internal

Methods

pure :: a -> DecoderM a #

(<*>) :: DecoderM (a -> b) -> DecoderM a -> DecoderM b #

liftA2 :: (a -> b -> c) -> DecoderM a -> DecoderM b -> DecoderM c #

(*>) :: DecoderM a -> DecoderM b -> DecoderM b #

(<*) :: DecoderM a -> DecoderM b -> DecoderM a #

Functor DecoderM Source # 
Instance details

Defined in Data.Hermes.Decoder.Internal

Methods

fmap :: (a -> b) -> DecoderM a -> DecoderM b #

(<$) :: a -> DecoderM b -> DecoderM a #

Monad DecoderM Source # 
Instance details

Defined in Data.Hermes.Decoder.Internal

Methods

(>>=) :: DecoderM a -> (a -> DecoderM b) -> DecoderM b #

(>>) :: DecoderM a -> DecoderM b -> DecoderM b #

return :: a -> DecoderM a #

data HermesEnv Source #

Contains foreign references to the allocated simdjson::parser and simdjson::document. Also maintains state for error reporting that is updated when an object field or array value is entered.

Instances

Instances details
Generic HermesEnv Source # 
Instance details

Defined in Data.Hermes.Decoder.Internal

Associated Types

type Rep HermesEnv :: Type -> Type #

NFData HermesEnv Source # 
Instance details

Defined in Data.Hermes.Decoder.Internal

Methods

rnf :: HermesEnv -> () #

Eq HermesEnv Source # 
Instance details

Defined in Data.Hermes.Decoder.Internal

type Rep HermesEnv Source # 
Instance details

Defined in Data.Hermes.Decoder.Internal

mkHermesEnv :: Maybe Int -> IO HermesEnv Source #

Allocates foreign references to a simdjson::ondemand::parser and a simdjson::ondemand::document. The optional capacity argument sets the max capacity in bytes for the simdjson::ondemand::parser, which defaults to 4GB. It is preferable to use withHermesEnv to keep foreign references in scope. Be careful using this, the foreign references can be finalized if the HermesEnv goes out of scope.

Do _not_ share a HermesEnv across multiple threads. Each thread should get its own.

Object field accessors

Obtain an object using withObject that can be passed to these field lookup functions.

atKey :: Text -> Decoder a -> Object -> Decoder a Source #

Find an object field by key, where an exception is thrown if the key is missing.

atKeyOptional :: Text -> Decoder a -> Object -> Decoder (Maybe a) Source #

Find an object field by key, where Nothing is returned if the key is missing.

atKeyStrict :: Text -> Decoder a -> Object -> Decoder a Source #

Uses find_field, which means if you access a field out-of-order this will throw an exception. It also cannot support optional fields.

Decoders

JSON pointer

atPointer :: Text -> Decoder a -> Decoder a Source #

Decode a value at the particular JSON pointer following RFC 6901. Be careful where you use this because it rewinds the document on each successive call.

decodeEither (atPointer "/statuses/99" decodeObject) input

Values

bool :: Decoder Bool Source #

Parse a JSON boolean into a Haskell Bool.

char :: Decoder Char Source #

Parse only a single character.

double :: Decoder Double Source #

Parse a JSON number into a Haskell Double.

int :: Decoder Int Source #

Parse a JSON number into a signed Haskell Int.

scientific :: Decoder Scientific Source #

Parse a Scientific from a Value.

string :: Decoder String Source #

Parse a JSON string into a Haskell String. For best performance you should use text instead.

text :: Decoder Text Source #

Parse a JSON string into Haskell Text.

list :: Decoder a -> Decoder [a] Source #

Parse a homogenous JSON array into a Haskell list.

vector :: Vector v a => Decoder a -> Decoder (v a) Source #

Parse a homogenous JSON array into a generic Vector.

nullable :: Decoder a -> Decoder (Maybe a) Source #

Transforms a parser to return Nothing when the value is null.

objectAsKeyValues Source #

Arguments

:: (Text -> Decoder k)

Parses a Text key in the Decoder monad. JSON keys are always text.

-> Decoder v

Decoder for the field value.

-> Decoder [(k, v)] 

Parse an object into a homogenous list of key-value tuples.

objectAsMap Source #

Arguments

:: Ord k 
=> (Text -> Decoder k)

Parses a Text key in the Decoder monad. JSON keys are always text.

-> Decoder v

Decoder for the field value.

-> Decoder (Map k v) 

Parse an object into a strict Map.

Date and time

Parses date and time types from Data.Time using the same attoparsec parsers as Data.Aeson via https://hackage.haskell.org/package/attoparsec-iso8601.

day :: Decoder Day Source #

Parse a date of the form [+,-]YYYY-MM-DD.

month :: Decoder Month Source #

Parse a date of the form [+,-]YYYY-MM.

quarter :: Decoder Quarter Source #

Parse a date of the form [+,-]YYYY-QN.

timeOfDay :: Decoder TimeOfDay Source #

Parse a time of the form HH:MM[:SS[.SSS]].

timeZone :: Decoder (Maybe TimeZone) Source #

Parse a time zone, and return Nothing if the offset from UTC is zero. (This makes some speedups possible.)

localTime :: Decoder LocalTime Source #

Parse a date and time, of the form YYYY-MM-DD HH:MM[:SS[.SSS]]. The space may be replaced with a T. The number of seconds is optional and may be followed by a fractional component.

utcTime :: Decoder UTCTime Source #

Behaves as zonedTime, but converts any time zone offset into a UTC time.

zonedTime :: Decoder ZonedTime Source #

Parse a date with time zone info. Acceptable formats:

YYYY-MM-DD HH:MM Z YYYY-MM-DD HH:MM:SS Z YYYY-MM-DD HH:MM:SS.SSS Z

The first space may instead be a T, and the second space is optional. The Z represents UTC. The Z may be replaced with a time zone offset of the form +0000 or -08:00, where the first two digits are hours, the : is optional and the second two digits (also optional) are minutes.

Error Types

data HermesException Source #

The library can throw exceptions from simdjson in addition to its own exceptions.

Constructors

SIMDException !DocumentError

An exception thrown from the simdjson library.

InternalException !DocumentError

An exception thrown from an internal library function.

Instances

Instances details
Exception HermesException Source # 
Instance details

Defined in Data.Hermes.Decoder.Internal

Generic HermesException Source # 
Instance details

Defined in Data.Hermes.Decoder.Internal

Associated Types

type Rep HermesException :: Type -> Type #

Show HermesException Source # 
Instance details

Defined in Data.Hermes.Decoder.Internal

NFData HermesException Source # 
Instance details

Defined in Data.Hermes.Decoder.Internal

Methods

rnf :: HermesException -> () #

Eq HermesException Source # 
Instance details

Defined in Data.Hermes.Decoder.Internal

type Rep HermesException Source # 
Instance details

Defined in Data.Hermes.Decoder.Internal

type Rep HermesException = D1 ('MetaData "HermesException" "Data.Hermes.Decoder.Internal" "hermes-json-0.5.0.0-G2R34ND1OAODXngJrd2wFS" 'False) (C1 ('MetaCons "SIMDException" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 DocumentError)) :+: C1 ('MetaCons "InternalException" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 DocumentError)))

data DocumentError Source #

Record containing all pertinent information for troubleshooting an exception.

Constructors

DocumentError 

Fields

  • path :: !Text

    The path to the current element determined by the decoder. Formatted in the JSON Pointer standard per RFC 6901.

  • errorMsg :: !Text

    An error message.

Instances

Instances details
Generic DocumentError Source # 
Instance details

Defined in Data.Hermes.Decoder.Internal

Associated Types

type Rep DocumentError :: Type -> Type #

Show DocumentError Source # 
Instance details

Defined in Data.Hermes.Decoder.Internal

NFData DocumentError Source # 
Instance details

Defined in Data.Hermes.Decoder.Internal

Methods

rnf :: DocumentError -> () #

Eq DocumentError Source # 
Instance details

Defined in Data.Hermes.Decoder.Internal

type Rep DocumentError Source # 
Instance details

Defined in Data.Hermes.Decoder.Internal

type Rep DocumentError = D1 ('MetaData "DocumentError" "Data.Hermes.Decoder.Internal" "hermes-json-0.5.0.0-G2R34ND1OAODXngJrd2wFS" 'False) (C1 ('MetaCons "DocumentError" 'PrefixI 'True) (S1 ('MetaSel ('Just "path") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text) :*: S1 ('MetaSel ('Just "errorMsg") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text)))

Value helpers

getType :: Decoder ValueType Source #

Get the simdjson type of the Value.

isNull :: Decoder Bool Source #

Returns True if the Value is null.

withArray :: (Array -> Decoder a) -> Decoder a Source #

Helper to work with an Array parsed from a Value.

withBool :: (Bool -> Decoder a) -> Decoder a Source #

Helper to work with a Bool parsed from a Value.

withDouble :: (Double -> Decoder a) -> Decoder a Source #

Helper to work with a Double parsed from a Value.

withInt :: (Int -> Decoder a) -> Decoder a Source #

Helper to work with an Int parsed from a Value.

withObject :: (Object -> Decoder a) -> Decoder a Source #

Helper to work with an Object parsed from a Value.

withObjectAsMap Source #

Arguments

:: Ord k 
=> (Text -> Decoder k)

Parses a Text key in the Decoder monad. JSON keys are always text.

-> Decoder v

Decoder for the field value.

-> (Map k v -> Decoder a) 
-> Decoder a 

withString :: (String -> Decoder a) -> Decoder a Source #

Helper to work with a String parsed from a Value.

withText :: (Text -> Decoder a) -> Decoder a Source #

Helper to work with a Text parsed from a Value.

withVector :: Vector v a => Decoder a -> (v a -> Decoder a) -> Decoder a Source #

Raw ByteString access

withRawByteString :: (ByteString -> Decoder a) -> Decoder a Source #

Helper to work with the raw ByteString of the JSON token parsed from the given Value.

simdjson Opaque Types

data Array Source #

A reference to an opaque simdjson::ondemand::array.

data ArrayIter Source #

A reference to an opaque simdjson::ondemand::array_iterator.

data Document Source #

A reference to an opaque simdjson::ondemand::document.

data InputBuffer Source #

A reference to an opaque simdjson::padded_string.

data Object Source #

A reference to an opaque simdjson::ondemand::object.

data Parser Source #

A reference to an opaque simdjson::ondemand::parser.

data Value Source #

A reference to an opaque simdjson::ondemand::value.