aeson-combinators-0.1.0.1: Aeson combinators for dead simple JSON decoding
Copyright(c) Marek Fajkus
LicenseBSD3
Maintainermarek.faj@gmail.com
Safe HaskellNone
LanguageHaskell2010

Data.Aeson.Combinators.Encode

Description

Functions in this module serve as an alternative ToJSON type class. This allows to define for mapping from data type into multiple JSON representations. type level wrapping.

There are two way of defining such encoder:

  • Using simple function a -> Value which doesn't require this library
  • Using this library as DSL together with Contravariant
Synopsis

Importing

This module as meant to be import as qualified

import Data.Aeson.Combinators.Encode as Encode

Alternative to using Encode Combinators

Be aware than in most cause you won't need to use this module. you can utilize Aeson's Value type and it's instance of ToJSON directly.

>>> import qualified Data.Aeson as Aeson
>>> import Data.Aeson ((.=))
>>> data Object = Object { tag :: String, id :: Int }

Define custom encoding function:

>>> :{
encodeObject :: Object -> Value
encodeObject (Object tag id) =
        Aeson.object ["tag" .= tag, "id" .= id]
:}
>>> Aeson.encode (encodeObject (Object "foo" 42))
"{\"tag\":\"foo\",\"id\":42}"

Example Usage

>>> :set -XOverloadedStrings
>>> :set -XDeriveGeneric

First lets define some type

>>> :{
data Person = Person
  { name :: String
  , age  :: Int
  } deriving (Show, Eq)
:}

And first encoder for this type:

>>> :{
personEncoder :: Encoder Person
personEncoder = object
  [ field "name" string name
  , field "age" int age
  ]
:}

We can use this Encoder to encode value into JSON:

>>> encode personEncoder (Person "Jane" 42)
"{\"age\":42,\"name\":\"Jane\"}"

Now we can use Contravariant to manipulate our encoder.

Our type might be wrap in some rither type like this one:

>>> import Data.Functor.Contravariant
>>> data Surrounding = S Person Bool

But we still want to be able to encode it:

>>> :{
surroundingEncoder :: Encoder Surrounding
surroundingEncoder = contramap (\(S person _) -> person) personEncoder
:}

Encoder

newtype Encoder a Source #

Value describing encoding of a into a JSON Value. This is essentially just a wrapper around function that should be applied later.

Covariant to map function over input

Given:

>>> :{
data Person = Person
  { name :: String
  , age  :: Int
  } deriving (Show, Eq)
:}
>>> :{
personEncoder :: Encoder Person
personEncoder = object
  [ field "name" string name
  , field "age" int age
  ]
:}

We can extract person from any pair:

>>> :{
-- Using personEncoder definition from example above
pairEncoder2 :: Encoder (Person, a)
pairEncoder2 = contramap fst personEncoder
:}
>>> encode pairEncoder2 (Person "Jane" 42, Nothing)
"{\"age\":42,\"name\":\"Jane\"}"

Divisible and Decidable

Some of you might know library covariant and ask what is a support for other covariant typeclasses. It's not possible to define lawful Divisble instance for JSON Value and by extension it's not possible to define Decidable either. While it is posible to provide somewhat useful unlawful instances for these this library opts to not to do that.

Constructors

Encoder (a -> Value) 

Instances

Instances details
Contravariant Encoder Source # 
Instance details

Defined in Data.Aeson.Combinators.Encode

Methods

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

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

auto :: ToJSON a => Encoder a Source #

Grab Encoder from ToJSON definition.

run :: Encoder a -> a -> Value Source #

Run Encoder given a value. this is essentially just a function application.

Object Encoding

There are two alternative ways of defining Object encodings. Both provide "eqvivalent" types and functions with consistent naming. Variants without and with ' suffix are meant to be used together.

type KeyValueEncoder a = a -> Pair Source #

Object Encoder

>>> :{
  data Object = Object
    { name :: Text
    , age  :: Int
    } deriving (Show, Eq)
:}
>>> :{
  objectEncoder :: Encoder Object
  objectEncoder = object
    [ field "name" text name
    , field "age" int age
    ]
:}
>>> encode objectEncoder $ Object "Joe" 30
"{\"age\":30,\"name\":\"Joe\"}"

object :: [KeyValueEncoder a] -> Encoder a Source #

Object combinators

field :: Key -> Encoder b -> (a -> b) -> KeyValueEncoder a Source #

Define object field

Alternative Object Encoding

type KeyValueEncoder' a = a -> [Pair] Source #

Object Encoder (alternative)

>>> :set -XRecordWildCards
>>> :{
  data Object = Object
    { name :: Text
    , age  :: Int
    } deriving (Show, Eq)
:}
>>> :{
  objectEncoder' :: Encoder Object
  objectEncoder' = object' $ \Object{..} ->
    [ field' "name" text name
    , field' "age" int age
    ]
:}
>>> encode objectEncoder' $ Object "Joe" 30
"{\"age\":30,\"name\":\"Joe\"}"

object' :: KeyValueEncoder' a -> Encoder a Source #

Object combinators (alternative)

field' :: Key -> Encoder a -> a -> (Key, Value) Source #

Define object field (alternative)

Collections

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

Encode List

jsonArray :: [Encoder a] -> Encoder a Source #

Encode multiple values as array

Encoding Primitive Values

Void, Unit, Bool

void :: Encoder Void Source #

Encode any JSON value to Void value which is impossible to construct.

This Encoder is guarenteed to fail.

unit :: Encoder () Source #

Encode JSON null into ()

bool :: Encoder Bool Source #

Encode JSON booleans to Haskell Bool

Integers (and Natural)

int :: Encoder Int Source #

Encode JSON number to Int

integer :: Encoder Integer Source #

Encode JSON number to unbounded Integer

int8 :: Encoder Int8 Source #

Encode JSON number to Int8

int16 :: Encoder Int16 Source #

Encode JSON number to Int16

int32 :: Encoder Int32 Source #

Encode JSON number to Int32

int64 :: Encoder Int64 Source #

Encode JSON number to Int64

word :: Encoder Word Source #

Encode JSON number to bounded Word

word8 :: Encoder Word8 Source #

Encode JSON number to bounded Word8

word16 :: Encoder Word16 Source #

Encode JSON number to bounded Word16

word32 :: Encoder Word32 Source #

Encode JSON number to bounded Word32

word64 :: Encoder Word64 Source #

Encode JSON number to bounded Word64

natural :: Encoder Natural Source #

Encode JSON number to GHC's Natural (non negative)

This function requires base >= 4.8.0

Floating Points

float :: Encoder Float Source #

Encode JSON number to Float

double :: Encoder Double Source #

Encode JSON number to Double

scientific :: Encoder Scientific Source #

Encode JSON number to arbitrary precision Scientific

Strings

char :: Encoder Char Source #

Encode single character JSON string to Char

text :: Encoder Text Source #

Encode JSON string to Text

string :: Encoder String Source #

Encode JSON string to String

uuid :: Encoder UUID Source #

Encode JSON string to UUID

version :: Encoder Version Source #

Encode JSON string to Version

Encoding Time

zonedTime :: Encoder ZonedTime Source #

Encode JSON string to ZonedTime using Aeson's instance implementation.

Supported string 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.

localTime :: Encoder LocalTime Source #

Encode JSON string to LocalTime using Aeson's instance implementation.

timeOfDay :: Encoder TimeOfDay Source #

Encode JSON string to TimeOfDay using Aeson's instance implementation.

utcTime :: Encoder UTCTime Source #

Encode JSON string to UTCTime using Aesons's instance implementation

day :: Encoder Day Source #

Encode JSON string to Day using Aesons's instance implementation

dayOfWeek :: Encoder DayOfWeek Source #

Encode JSON string to DayOfWeek using Aesons's instance implementation

This function requires 'time-compat' >= 1.9.2

Evaluating Encoders

encode :: Encoder a -> a -> ByteString Source #

Encode value into (Lazy) ByteString

toEncoding :: Encoder a -> a -> Encoding Source #

Convert value to encoding

Aeson compatibility helpers

Aeson compatibility layer to support Aeson 2.0 and older versions. Re-exposes Key and KeyMap, together with suitable conversion functions. For older aeson versions, we provide type definitions for Key and KeyMap.

Users may use fromText and toText to write decoders/encoders for forwards and backwards compatibility.

See Key and KeyMap in aeson >= 2.0 for more details.

data KeyMap v #

A map from JSON key type Key to v.

Instances

Instances details
Functor KeyMap 
Instance details

Defined in Data.Aeson.KeyMap

Methods

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

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

Foldable KeyMap 
Instance details

Defined in Data.Aeson.KeyMap

Methods

fold :: Monoid m => KeyMap m -> m #

foldMap :: Monoid m => (a -> m) -> KeyMap a -> m #

foldMap' :: Monoid m => (a -> m) -> KeyMap a -> m #

foldr :: (a -> b -> b) -> b -> KeyMap a -> b #

foldr' :: (a -> b -> b) -> b -> KeyMap a -> b #

foldl :: (b -> a -> b) -> b -> KeyMap a -> b #

foldl' :: (b -> a -> b) -> b -> KeyMap a -> b #

foldr1 :: (a -> a -> a) -> KeyMap a -> a #

foldl1 :: (a -> a -> a) -> KeyMap a -> a #

toList :: KeyMap a -> [a] #

null :: KeyMap a -> Bool #

length :: KeyMap a -> Int #

elem :: Eq a => a -> KeyMap a -> Bool #

maximum :: Ord a => KeyMap a -> a #

minimum :: Ord a => KeyMap a -> a #

sum :: Num a => KeyMap a -> a #

product :: Num a => KeyMap a -> a #

Traversable KeyMap 
Instance details

Defined in Data.Aeson.KeyMap

Methods

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

sequenceA :: Applicative f => KeyMap (f a) -> f (KeyMap a) #

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

sequence :: Monad m => KeyMap (m a) -> m (KeyMap a) #

Arbitrary1 KeyMap

Since: aeson-2.0.3.0

Instance details

Defined in Data.Aeson.KeyMap

Methods

liftArbitrary :: Gen a -> Gen (KeyMap a) #

liftShrink :: (a -> [a]) -> KeyMap a -> [KeyMap a] #

KeyValue Object

Constructs a singleton KeyMap. For calling functions that demand an Object for constructing objects. To be used in conjunction with mconcat. Prefer to use object where possible.

Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

(.=) :: ToJSON v => Key -> v -> Object #

ToJSON1 KeyMap 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

liftToJSON :: (a -> Value) -> ([a] -> Value) -> KeyMap a -> Value #

liftToJSONList :: (a -> Value) -> ([a] -> Value) -> [KeyMap a] -> Value #

liftToEncoding :: (a -> Encoding) -> ([a] -> Encoding) -> KeyMap a -> Encoding #

liftToEncodingList :: (a -> Encoding) -> ([a] -> Encoding) -> [KeyMap a] -> Encoding #

FromJSON1 KeyMap

Since: aeson-2.0.1.0

Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

liftParseJSON :: (Value -> Parser a) -> (Value -> Parser [a]) -> Value -> Parser (KeyMap a) #

liftParseJSONList :: (Value -> Parser a) -> (Value -> Parser [a]) -> Value -> Parser [KeyMap a] #

Semialign KeyMap 
Instance details

Defined in Data.Aeson.KeyMap

Methods

align :: KeyMap a -> KeyMap b -> KeyMap (These a b) #

alignWith :: (These a b -> c) -> KeyMap a -> KeyMap b -> KeyMap c #

Align KeyMap 
Instance details

Defined in Data.Aeson.KeyMap

Methods

nil :: KeyMap a #

Zip KeyMap 
Instance details

Defined in Data.Aeson.KeyMap

Methods

zip :: KeyMap a -> KeyMap b -> KeyMap (a, b) #

zipWith :: (a -> b -> c) -> KeyMap a -> KeyMap b -> KeyMap c #

Filterable KeyMap 
Instance details

Defined in Data.Aeson.KeyMap

Methods

mapMaybe :: (a -> Maybe b) -> KeyMap a -> KeyMap b #

catMaybes :: KeyMap (Maybe a) -> KeyMap a #

filter :: (a -> Bool) -> KeyMap a -> KeyMap a #

Witherable KeyMap 
Instance details

Defined in Data.Aeson.KeyMap

Methods

wither :: Applicative f => (a -> f (Maybe b)) -> KeyMap a -> f (KeyMap b) #

witherM :: Monad m => (a -> m (Maybe b)) -> KeyMap a -> m (KeyMap b) #

filterA :: Applicative f => (a -> f Bool) -> KeyMap a -> f (KeyMap a) #

witherMap :: Applicative m => (KeyMap b -> r) -> (a -> m (Maybe b)) -> KeyMap a -> m r #

FunctorWithIndex Key KeyMap 
Instance details

Defined in Data.Aeson.KeyMap

Methods

imap :: (Key -> a -> b) -> KeyMap a -> KeyMap b #

FoldableWithIndex Key KeyMap 
Instance details

Defined in Data.Aeson.KeyMap

Methods

ifoldMap :: Monoid m => (Key -> a -> m) -> KeyMap a -> m #

ifoldMap' :: Monoid m => (Key -> a -> m) -> KeyMap a -> m #

ifoldr :: (Key -> a -> b -> b) -> b -> KeyMap a -> b #

ifoldl :: (Key -> b -> a -> b) -> b -> KeyMap a -> b #

ifoldr' :: (Key -> a -> b -> b) -> b -> KeyMap a -> b #

ifoldl' :: (Key -> b -> a -> b) -> b -> KeyMap a -> b #

TraversableWithIndex Key KeyMap 
Instance details

Defined in Data.Aeson.KeyMap

Methods

itraverse :: Applicative f => (Key -> a -> f b) -> KeyMap a -> f (KeyMap b) #

SemialignWithIndex Key KeyMap 
Instance details

Defined in Data.Aeson.KeyMap

Methods

ialignWith :: (Key -> These a b -> c) -> KeyMap a -> KeyMap b -> KeyMap c #

ZipWithIndex Key KeyMap 
Instance details

Defined in Data.Aeson.KeyMap

Methods

izipWith :: (Key -> a -> b -> c) -> KeyMap a -> KeyMap b -> KeyMap c #

FilterableWithIndex Key KeyMap 
Instance details

Defined in Data.Aeson.KeyMap

Methods

imapMaybe :: (Key -> a -> Maybe b) -> KeyMap a -> KeyMap b #

ifilter :: (Key -> a -> Bool) -> KeyMap a -> KeyMap a #

WitherableWithIndex Key KeyMap 
Instance details

Defined in Data.Aeson.KeyMap

Methods

iwither :: Applicative f => (Key -> a -> f (Maybe b)) -> KeyMap a -> f (KeyMap b) #

iwitherM :: Monad m => (Key -> a -> m (Maybe b)) -> KeyMap a -> m (KeyMap b) #

ifilterA :: Applicative f => (Key -> a -> f Bool) -> KeyMap a -> f (KeyMap a) #

Lift v => Lift (KeyMap v :: Type) 
Instance details

Defined in Data.Aeson.KeyMap

Methods

lift :: KeyMap v -> Q Exp #

liftTyped :: KeyMap v -> Q (TExp (KeyMap v)) #

IsList (KeyMap v)

Since: aeson-2.0.2.0

Instance details

Defined in Data.Aeson.KeyMap

Associated Types

type Item (KeyMap v) #

Methods

fromList :: [Item (KeyMap v)] -> KeyMap v #

fromListN :: Int -> [Item (KeyMap v)] -> KeyMap v #

toList :: KeyMap v -> [Item (KeyMap v)] #

Eq v => Eq (KeyMap v) 
Instance details

Defined in Data.Aeson.KeyMap

Methods

(==) :: KeyMap v -> KeyMap v -> Bool #

(/=) :: KeyMap v -> KeyMap v -> Bool #

Data v => Data (KeyMap v) 
Instance details

Defined in Data.Aeson.KeyMap

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> KeyMap v -> c (KeyMap v) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (KeyMap v) #

toConstr :: KeyMap v -> Constr #

dataTypeOf :: KeyMap v -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (KeyMap v)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (KeyMap v)) #

gmapT :: (forall b. Data b => b -> b) -> KeyMap v -> KeyMap v #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> KeyMap v -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> KeyMap v -> r #

gmapQ :: (forall d. Data d => d -> u) -> KeyMap v -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> KeyMap v -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> KeyMap v -> m (KeyMap v) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> KeyMap v -> m (KeyMap v) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> KeyMap v -> m (KeyMap v) #

Ord v => Ord (KeyMap v) 
Instance details

Defined in Data.Aeson.KeyMap

Methods

compare :: KeyMap v -> KeyMap v -> Ordering #

(<) :: KeyMap v -> KeyMap v -> Bool #

(<=) :: KeyMap v -> KeyMap v -> Bool #

(>) :: KeyMap v -> KeyMap v -> Bool #

(>=) :: KeyMap v -> KeyMap v -> Bool #

max :: KeyMap v -> KeyMap v -> KeyMap v #

min :: KeyMap v -> KeyMap v -> KeyMap v #

Read v => Read (KeyMap v) 
Instance details

Defined in Data.Aeson.KeyMap

Show v => Show (KeyMap v) 
Instance details

Defined in Data.Aeson.KeyMap

Methods

showsPrec :: Int -> KeyMap v -> ShowS #

show :: KeyMap v -> String #

showList :: [KeyMap v] -> ShowS #

Semigroup (KeyMap v) 
Instance details

Defined in Data.Aeson.KeyMap

Methods

(<>) :: KeyMap v -> KeyMap v -> KeyMap v #

sconcat :: NonEmpty (KeyMap v) -> KeyMap v #

stimes :: Integral b => b -> KeyMap v -> KeyMap v #

Monoid (KeyMap v) 
Instance details

Defined in Data.Aeson.KeyMap

Methods

mempty :: KeyMap v #

mappend :: KeyMap v -> KeyMap v -> KeyMap v #

mconcat :: [KeyMap v] -> KeyMap v #

Function v => Function (KeyMap v)

Since: aeson-2.0.3.0

Instance details

Defined in Data.Aeson.KeyMap

Methods

function :: (KeyMap v -> b) -> KeyMap v :-> b #

Arbitrary v => Arbitrary (KeyMap v)

Since: aeson-2.0.3.0

Instance details

Defined in Data.Aeson.KeyMap

Methods

arbitrary :: Gen (KeyMap v) #

shrink :: KeyMap v -> [KeyMap v] #

CoArbitrary v => CoArbitrary (KeyMap v)

Since: aeson-2.0.3.0

Instance details

Defined in Data.Aeson.KeyMap

Methods

coarbitrary :: KeyMap v -> Gen b -> Gen b #

Hashable v => Hashable (KeyMap v) 
Instance details

Defined in Data.Aeson.KeyMap

Methods

hashWithSalt :: Int -> KeyMap v -> Int #

hash :: KeyMap v -> Int #

ToJSON v => ToJSON (KeyMap v) 
Instance details

Defined in Data.Aeson.Types.ToJSON

FromJSON v => FromJSON (KeyMap v)

Since: aeson-2.0.1.0

Instance details

Defined in Data.Aeson.Types.FromJSON

NFData v => NFData (KeyMap v) 
Instance details

Defined in Data.Aeson.KeyMap

Methods

rnf :: KeyMap v -> () #

type Item (KeyMap v) 
Instance details

Defined in Data.Aeson.KeyMap

type Item (KeyMap v) = (Key, v)

toHashMapText :: KeyMap v -> HashMap Text v #

Convert a KeyMap to a HashMap Text.

Key

data Key #

Instances

Instances details
Eq Key 
Instance details

Defined in Data.Aeson.Key

Methods

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

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

Data Key 
Instance details

Defined in Data.Aeson.Key

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Key -> c Key #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Key #

toConstr :: Key -> Constr #

dataTypeOf :: Key -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Key) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Key) #

gmapT :: (forall b. Data b => b -> b) -> Key -> Key #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Key -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Key -> r #

gmapQ :: (forall d. Data d => d -> u) -> Key -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Key -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Key -> m Key #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Key -> m Key #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Key -> m Key #

Ord Key 
Instance details

Defined in Data.Aeson.Key

Methods

compare :: Key -> Key -> Ordering #

(<) :: Key -> Key -> Bool #

(<=) :: Key -> Key -> Bool #

(>) :: Key -> Key -> Bool #

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

max :: Key -> Key -> Key #

min :: Key -> Key -> Key #

Read Key 
Instance details

Defined in Data.Aeson.Key

Show Key 
Instance details

Defined in Data.Aeson.Key

Methods

showsPrec :: Int -> Key -> ShowS #

show :: Key -> String #

showList :: [Key] -> ShowS #

IsString Key 
Instance details

Defined in Data.Aeson.Key

Methods

fromString :: String -> Key #

Semigroup Key 
Instance details

Defined in Data.Aeson.Key

Methods

(<>) :: Key -> Key -> Key #

sconcat :: NonEmpty Key -> Key #

stimes :: Integral b => b -> Key -> Key #

Monoid Key 
Instance details

Defined in Data.Aeson.Key

Methods

mempty :: Key #

mappend :: Key -> Key -> Key #

mconcat :: [Key] -> Key #

Function Key

Since: aeson-2.0.3.0

Instance details

Defined in Data.Aeson.Key

Methods

function :: (Key -> b) -> Key :-> b #

Arbitrary Key

Since: aeson-2.0.3.0

Instance details

Defined in Data.Aeson.Key

Methods

arbitrary :: Gen Key #

shrink :: Key -> [Key] #

CoArbitrary Key

Since: aeson-2.0.3.0

Instance details

Defined in Data.Aeson.Key

Methods

coarbitrary :: Key -> Gen b -> Gen b #

Hashable Key 
Instance details

Defined in Data.Aeson.Key

Methods

hashWithSalt :: Int -> Key -> Int #

hash :: Key -> Int #

ToJSON Key 
Instance details

Defined in Data.Aeson.Types.ToJSON

KeyValue Pair 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

(.=) :: ToJSON v => Key -> v -> Pair #

ToJSONKey Key 
Instance details

Defined in Data.Aeson.Types.ToJSON

FromJSON Key 
Instance details

Defined in Data.Aeson.Types.FromJSON

FromJSONKey Key 
Instance details

Defined in Data.Aeson.Types.FromJSON

NFData Key 
Instance details

Defined in Data.Aeson.Key

Methods

rnf :: Key -> () #

Lift Key 
Instance details

Defined in Data.Aeson.Key

Methods

lift :: Key -> Q Exp #

liftTyped :: Key -> Q (TExp Key) #

FunctorWithIndex Key KeyMap 
Instance details

Defined in Data.Aeson.KeyMap

Methods

imap :: (Key -> a -> b) -> KeyMap a -> KeyMap b #

FoldableWithIndex Key KeyMap 
Instance details

Defined in Data.Aeson.KeyMap

Methods

ifoldMap :: Monoid m => (Key -> a -> m) -> KeyMap a -> m #

ifoldMap' :: Monoid m => (Key -> a -> m) -> KeyMap a -> m #

ifoldr :: (Key -> a -> b -> b) -> b -> KeyMap a -> b #

ifoldl :: (Key -> b -> a -> b) -> b -> KeyMap a -> b #

ifoldr' :: (Key -> a -> b -> b) -> b -> KeyMap a -> b #

ifoldl' :: (Key -> b -> a -> b) -> b -> KeyMap a -> b #

TraversableWithIndex Key KeyMap 
Instance details

Defined in Data.Aeson.KeyMap

Methods

itraverse :: Applicative f => (Key -> a -> f b) -> KeyMap a -> f (KeyMap b) #

SemialignWithIndex Key KeyMap 
Instance details

Defined in Data.Aeson.KeyMap

Methods

ialignWith :: (Key -> These a b -> c) -> KeyMap a -> KeyMap b -> KeyMap c #

ZipWithIndex Key KeyMap 
Instance details

Defined in Data.Aeson.KeyMap

Methods

izipWith :: (Key -> a -> b -> c) -> KeyMap a -> KeyMap b -> KeyMap c #

FilterableWithIndex Key KeyMap 
Instance details

Defined in Data.Aeson.KeyMap

Methods

imapMaybe :: (Key -> a -> Maybe b) -> KeyMap a -> KeyMap b #

ifilter :: (Key -> a -> Bool) -> KeyMap a -> KeyMap a #

WitherableWithIndex Key KeyMap 
Instance details

Defined in Data.Aeson.KeyMap

Methods

iwither :: Applicative f => (Key -> a -> f (Maybe b)) -> KeyMap a -> f (KeyMap b) #

iwitherM :: Monad m => (Key -> a -> m (Maybe b)) -> KeyMap a -> m (KeyMap b) #

ifilterA :: Applicative f => (Key -> a -> f Bool) -> KeyMap a -> f (KeyMap a) #

FromPairs Value (DList Pair) 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

fromPairs :: DList Pair -> Value

v ~ Value => KeyValuePair v (DList Pair) 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

pair :: Key -> v -> DList Pair