hermes-json-0.2.0.0: Fast JSON decoding via simdjson C++ bindings
Safe HaskellNone
LanguageHaskell2010
Extensions
  • ScopedTypeVariables
  • OverloadedStrings
  • DeriveGeneric
  • DerivingStrategies
  • TypeSynonymInstances
  • FlexibleInstances
  • GeneralizedNewtypeDeriving
  • ExplicitForAll

Data.Hermes.Decoder.Types

Description

Decoder is the monad used for decoding JSON with simdjson via the FFI. This module contains helpers for working with the Decoder context.

Synopsis

Documentation

data Decoder a Source #

A Decoder is some context around the IO needed by the C FFI to allocate local memory. Users shouldn't need to deal with the underlying IO except in advanced use cases. Using decodeEither discharges the IO and returns us to purity, since we know decoding a document is referentially transparent.

Instances

Instances details
Monad Decoder Source # 
Instance details

Defined in Data.Hermes.Decoder.Types

Methods

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

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

return :: a -> Decoder a #

Functor Decoder Source # 
Instance details

Defined in Data.Hermes.Decoder.Types

Methods

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

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

MonadFail Decoder Source # 
Instance details

Defined in Data.Hermes.Decoder.Types

Methods

fail :: String -> Decoder a #

Applicative Decoder Source # 
Instance details

Defined in Data.Hermes.Decoder.Types

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 #

Alternative Decoder Source # 
Instance details

Defined in Data.Hermes.Decoder.Types

Methods

empty :: Decoder a #

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

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

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

MonadIO Decoder Source # 
Instance details

Defined in Data.Hermes.Decoder.Types

Methods

liftIO :: IO a -> Decoder a #

MonadUnliftIO Decoder Source # 
Instance details

Defined in Data.Hermes.Decoder.Types

Methods

withRunInIO :: ((forall a. Decoder a -> IO a) -> IO b) -> Decoder b #

MonadReader HermesEnv Decoder Source # 
Instance details

Defined in Data.Hermes.Decoder.Types

Methods

ask :: Decoder HermesEnv #

local :: (HermesEnv -> HermesEnv) -> Decoder a -> Decoder a #

reader :: (HermesEnv -> a) -> Decoder a #

data HermesEnv Source #

Contains foreign references to the allocated simdjson::parser and simdjson::document. Also maintains a path string that is updated when an object field or array value is entered and which is displayed in errors.

Instances

Instances details
MonadReader HermesEnv Decoder Source # 
Instance details

Defined in Data.Hermes.Decoder.Types

Methods

ask :: Decoder HermesEnv #

local :: (HermesEnv -> HermesEnv) -> Decoder a -> Decoder a #

reader :: (HermesEnv -> a) -> Decoder a #

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
Eq HermesException Source # 
Instance details

Defined in Data.Hermes.Decoder.Types

Show HermesException Source # 
Instance details

Defined in Data.Hermes.Decoder.Types

Generic HermesException Source # 
Instance details

Defined in Data.Hermes.Decoder.Types

Associated Types

type Rep HermesException :: Type -> Type #

Exception HermesException Source # 
Instance details

Defined in Data.Hermes.Decoder.Types

NFData HermesException Source # 
Instance details

Defined in Data.Hermes.Decoder.Types

Methods

rnf :: HermesException -> () #

type Rep HermesException Source # 
Instance details

Defined in Data.Hermes.Decoder.Types

type Rep HermesException = D1 ('MetaData "HermesException" "Data.Hermes.Decoder.Types" "hermes-json-0.2.0.0-3sjqTfy2Csn4QfDtOSujZM" 'False) (C1 ('MetaCons "SIMDException" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DocumentError)) :+: C1 ('MetaCons "InternalException" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DocumentError)))

data DocumentError Source #

Record containing all pertinent information for troubleshooting an exception.

Instances

Instances details
Eq DocumentError Source # 
Instance details

Defined in Data.Hermes.Decoder.Types

Show DocumentError Source # 
Instance details

Defined in Data.Hermes.Decoder.Types

Generic DocumentError Source # 
Instance details

Defined in Data.Hermes.Decoder.Types

Associated Types

type Rep DocumentError :: Type -> Type #

NFData DocumentError Source # 
Instance details

Defined in Data.Hermes.Decoder.Types

Methods

rnf :: DocumentError -> () #

type Rep DocumentError Source # 
Instance details

Defined in Data.Hermes.Decoder.Types

type Rep DocumentError = D1 ('MetaData "DocumentError" "Data.Hermes.Decoder.Types" "hermes-json-0.2.0.0-3sjqTfy2Csn4QfDtOSujZM" 'False) (C1 ('MetaCons "DocumentError" 'PrefixI 'True) ((S1 ('MetaSel ('Just "path") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text) :*: S1 ('MetaSel ('Just "errorMsg") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text)) :*: (S1 ('MetaSel ('Just "docLocation") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text) :*: S1 ('MetaSel ('Just "docDebug") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text))))

withHermesEnv :: MonadUnliftIO m => (HermesEnv -> m a) -> m a Source #

Run an action that is passed a HermesEnv. The simdjson instances are created and destroyed using the bracket function.