monad-logger-aeson-0.3.1.0: JSON logging using monad-logger interface
Safe HaskellNone
LanguageHaskell2010

Control.Monad.Logger.Aeson.Internal

Synopsis

Disclaimer

In general, changes to this module will not be reflected in the library's version updates. Direct use of this module should be done with care.

Message-related

data Message Source #

A Message captures a textual component and a metadata component. The metadata component is a list of SeriesElem to support tacking on arbitrary structured data to a log message.

With the OverloadedStrings extension enabled, Message values can be constructed without metadata fairly conveniently, just as if we were using Text directly:

logDebug "Some log message without metadata"

Metadata may be included in a Message via the :# constructor:

logDebug $ "Some log message with metadata" :#
  [ "bloorp" .= (42 :: Int)
  , "bonk" .= ("abc" :: Text)
  ]

The mnemonic for the :# constructor is that the # symbol is sometimes referred to as a hash, a JSON object can be thought of as a hash map, and so with :# (and enough squinting), we are cons-ing a textual message onto a JSON object. Yes, this mnemonic isn't well-typed, but hopefully it still helps!

Since: 0.1.0.0

Constructors

Text :# [SeriesElem] infixr 5 

Instances

Instances details
IsString Message Source # 
Instance details

Defined in Control.Monad.Logger.Aeson.Internal

Methods

fromString :: String -> Message #

ToLogStr Message Source # 
Instance details

Defined in Control.Monad.Logger.Aeson.Internal

Methods

toLogStr :: Message -> LogStr #

newtype SeriesElem Source #

A single key-value pair, where the value is encoded JSON. This is a more restricted version of Series: a SeriesElem is intended to encapsulate exactly one key-value pair, whereas a Series encapsulates zero or more key-value pairs. SeriesElem values can be created via (.=) from aeson.

While a SeriesElem most often will map to a single pair, note that a Semigroup instance is available for performance's sake. The Semigroup instance is useful when multiple pairs are grouped together and then shared across multiple logging calls. In that case, the cost of combining the pairs in the group must only be paid once.

Since: 0.3.0.0

Constructors

UnsafeSeriesElem 

Fields

Instances

Instances details
Semigroup SeriesElem Source #

Since: 0.3.1.0

Instance details

Defined in Control.Monad.Logger.Aeson.Internal

KeyValue SeriesElem Source #

Since: 0.3.0.0

Instance details

Defined in Control.Monad.Logger.Aeson.Internal

Methods

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

data LoggedMessage Source #

This type is the Haskell representation of each JSON log message produced by this library.

While we never interact with this type directly when logging messages with monad-logger-aeson, we may wish to use this type if we are parsing/processing log files generated by this library.

Since: 0.1.0.0

Instances

Instances details
Eq LoggedMessage Source # 
Instance details

Defined in Control.Monad.Logger.Aeson.Internal

Ord LoggedMessage Source # 
Instance details

Defined in Control.Monad.Logger.Aeson.Internal

Show LoggedMessage Source # 
Instance details

Defined in Control.Monad.Logger.Aeson.Internal

Generic LoggedMessage Source # 
Instance details

Defined in Control.Monad.Logger.Aeson.Internal

Associated Types

type Rep LoggedMessage :: Type -> Type #

ToJSON LoggedMessage Source # 
Instance details

Defined in Control.Monad.Logger.Aeson.Internal

FromJSON LoggedMessage Source # 
Instance details

Defined in Control.Monad.Logger.Aeson.Internal

type Rep LoggedMessage Source # 
Instance details

Defined in Control.Monad.Logger.Aeson.Internal

type Rep LoggedMessage = D1 ('MetaData "LoggedMessage" "Control.Monad.Logger.Aeson.Internal" "monad-logger-aeson-0.3.1.0-KcBPeeEeFiu41mA0ywoxv0" 'False) (C1 ('MetaCons "LoggedMessage" 'PrefixI 'True) ((S1 ('MetaSel ('Just "loggedMessageTimestamp") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 UTCTime) :*: (S1 ('MetaSel ('Just "loggedMessageLevel") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 LogLevel) :*: S1 ('MetaSel ('Just "loggedMessageLoc") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe Loc)))) :*: ((S1 ('MetaSel ('Just "loggedMessageLogSource") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe LogSource)) :*: S1 ('MetaSel ('Just "loggedMessageThreadContext") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (KeyMap Value))) :*: (S1 ('MetaSel ('Just "loggedMessageText") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Text) :*: S1 ('MetaSel ('Just "loggedMessageMeta") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (KeyMap Value))))))

threadContextStore :: Store (KeyMap Value) Source #

Thread-safe, global Store that captures the thread context of messages.

Note that there is a bit of somewhat unavoidable name-overloading here: this binding is called threadContextStore because it stores the thread context (i.e. ThreadContext/MDC from Java land) for messages. It also just so happens that the Store type comes from the context package, which is a package providing thread-indexed storage of arbitrary context values. Please don't hate the player!

Since: 0.1.0.0

data OutputOptions Source #

OutputOptions is for use with defaultOutputWith and enables us to configure the JSON output produced by this library.

We can get a hold of a value of this type via defaultOutputOptions.

Since: 0.1.0.0

Constructors

OutputOptions 

Fields

LogItem-related

Encoding-related

monad-logger internals

mkLoggerLoc :: SrcLoc -> Loc Source #

Not exported from 'monad-logger', so copied here.

locFromCS :: CallStack -> Loc Source #

Not exported from 'monad-logger', so copied here.

isDefaultLoc :: Loc -> Bool Source #

Not exported from 'monad-logger', so copied here.

Aeson compat

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

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

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] #

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

value ~ Value => KeyValue (KeyMap value)

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 -> KeyMap value #

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)

keyMapToList :: KeyMap v -> [(Key, v)] Source #

keyMapInsert :: Key -> v -> KeyMap v -> KeyMap v Source #