composite-aeson-0.5.3.0: JSON for Vinyl/Frames records

Safe HaskellNone
LanguageHaskell2010

Composite.Aeson.Base

Synopsis

Documentation

newtype ToJson a Source #

Type of functions which take a value a and convert it to an Value.

Wrapper around a function of type a -> Aeson.Value.

Doesn't currently include support for the newer Aeson Encoding machinery, but should.

Constructors

ToJson 

Fields

Instances

Contravariant ToJson Source # 

Methods

contramap :: (a -> b) -> ToJson b -> ToJson a #

(>$) :: b -> ToJson b -> ToJson a #

Wrapped (ToJson a0) Source # 

Associated Types

type Unwrapped (ToJson a0) :: * #

Methods

_Wrapped' :: Iso' (ToJson a0) (Unwrapped (ToJson a0)) #

(~) * (ToJson a0) t0 => Rewrapped (ToJson a1) t0 Source # 
type Unwrapped (ToJson a0) Source # 
type Unwrapped (ToJson a0) = a0 -> Value

newtype FromJson e a Source #

Type of parsers which might emit some custom error of type e and produce a value of type a on success.

a is the type of value that can be parsed from JSON using this profunctor, and e is the type of custom error that can be produced when the JSON is unacceptable. If your parser doesn't produce any custom errors, leave this type polymorphic.

Wrapper about an aeson-better-errors Parse e a.

Constructors

FromJson 

Fields

Instances

Functor (FromJson e) Source # 

Methods

fmap :: (a -> b) -> FromJson e a -> FromJson e b #

(<$) :: a -> FromJson e b -> FromJson e a #

Wrapped (FromJson e0 a0) Source # 

Associated Types

type Unwrapped (FromJson e0 a0) :: * #

Methods

_Wrapped' :: Iso' (FromJson e0 a0) (Unwrapped (FromJson e0 a0)) #

(~) * (FromJson e0 a0) t0 => Rewrapped (FromJson e1 a1) t0 Source # 
type Unwrapped (FromJson e0 a0) Source # 
type Unwrapped (FromJson e0 a0) = Parse e0 a0

data JsonProfunctor e a b Source #

Type of profunctors which produce and consume JSON, a composition of ToJson and FromJson.

a is the type of value that can be converted to Value using this profunctor. b is the type of value that can be parsed from JSON using this profunctor, and e is the type of custom error that can be produced when the JSON is unacceptable. If your parser doesn't produce any custom errors, leave this type polymorphic.

Profunctors must have two type parameters a and b so this type has two, but JsonProfunctors with different types aren't useful for JSON processing directly. See JsonFormat for a wrapper which fixes the two types.

Doesn't currently include support for the newer Aeson Encoding machinery, but should.

Constructors

JsonProfunctor (a -> Value) (Parse e b) 

Instances

Profunctor (JsonProfunctor e) Source # 

Methods

dimap :: (a -> b) -> (c -> d) -> JsonProfunctor e b c -> JsonProfunctor e a d #

lmap :: (a -> b) -> JsonProfunctor e b c -> JsonProfunctor e a c #

rmap :: (b -> c) -> JsonProfunctor e a b -> JsonProfunctor e a c #

(#.) :: Coercible * c b => (b -> c) -> JsonProfunctor e a b -> JsonProfunctor e a c #

(.#) :: Coercible * b a => JsonProfunctor e b c -> (a -> b) -> JsonProfunctor e a c #

_JsonProfunctor :: Iso (JsonProfunctor e a b) (JsonProfunctor e' a' b') (ToJson a, FromJson e b) (ToJson a', FromJson e' b') Source #

Observe that a JsonProfunctor is isomorphic to a pair with a ToJson and FromJson.

newtype JsonFormat e a Source #

Wrapper around JsonProfunctor for use in JSON processing when the profunctor represents a bijection between JSON and a single type a, i.e. for JsonProfunctor e a a.

Constructors

JsonFormat 

Fields

Instances

Wrapped (JsonFormat e0 a0) Source # 

Associated Types

type Unwrapped (JsonFormat e0 a0) :: * #

Methods

_Wrapped' :: Iso' (JsonFormat e0 a0) (Unwrapped (JsonFormat e0 a0)) #

(~) * (JsonFormat e0 a0) t0 => Rewrapped (JsonFormat e1 a1) t0 Source # 
type Unwrapped (JsonFormat e0 a0) Source # 
type Unwrapped (JsonFormat e0 a0) = JsonProfunctor e0 a0 a0

toJsonWithFormat :: JsonFormat e a -> a -> Value Source #

Given a JsonFormat for a, convert a value of a into an Value.

fromJsonWithFormat :: JsonFormat e a -> Parse e a Source #

Given a JsonFormat for a which can produce custom errors of type e, yield an aeson-better-errors Parse which can be used to consume JSON.

parseJsonWithFormat :: (e -> Text) -> JsonFormat e a -> Value -> Parser a Source #

Given a JsonFormat for a which produces custom errors of type e and some function to format those errors as messages, produce an Aeson parser function Value -> Parser a.

parseJsonWithFormat' :: JsonFormat Void a -> Value -> Parser a Source #

Given a JsonFormat for a which doesn't produce custom errors, produce an Aeson parser function Value -> Parser a.

dimapJsonFormat :: (b -> a) -> (a -> b) -> JsonFormat e a -> JsonFormat e b Source #

Wrap a JsonFormat for type a in a pair of functions representing an isomorphism between a and b to produce a new JsonFormat for b.

jsonFormatWithIso :: AnIso' b a -> JsonFormat e a -> JsonFormat e b Source #

Wrap a JsonFormat for type a in an isomorphism to produce a new JsonFormat for b.

wrapJsonFormat :: JsonFormat e a -> (a -> Either e b) -> (b -> a) -> JsonFormat e b Source #

Given a JsonFormat e a and a pair of functions b -> a and a -> Either e b, produce a JsonFormat e b.

This is for the common case of a newtype wrapper which asserts some kind of validation has been done, e.g.:

  newtype MyType = MyType { unMyType :: Int }

  mkMyType :: Int -> Either Text MyType
  mkMyType i | i <= 0    = Left "must be positive!"
             | otherwise = Right (MyType i)

  myTypeJsonFormat :: JsonFormat e MyType
  myTypeJsonFormat = wrapJsonFormat intJsonFormat mkMyType unMyType

jsonFormatWithoutCustomError :: Show e => JsonFormat e a -> JsonFormat e' a Source #

Take a JsonFormat which produces some Show-able custom error and convert any custom errors into Aeson fail style errors. Since the custom errors are never generated by the resulting JsonFormat, any custom error type can be assumed.

This is commonly used to take a more specific JsonFormat MyError MyType and make it a more generic JsonFormat e MyType, e.g. to be used as a defaultJsonFormat.

wrappedJsonFormat :: Wrapped a => JsonFormat e (Unwrapped a) -> JsonFormat e a Source #

Given a format for the value type inside some wrapper type a which instances Wrapped, produce a format which works on the wrapper type.