keyed-vals-0.1.0.0: An abstract Handle for accessing collections in stores like Redis
Copyright(c) 2018-2022 Tim Emiola
LicenseBSD3
MaintainerTim Emiola <tim@emio.la>
Safe HaskellSafe-Inferred
LanguageHaskell2010

KeyedVals.Handle.Aeson

Description

Functions that help use Aeson to load and save JSON data using the dictionary service

Synopsis

decode/encode support

decodeOr :: FromJSON a => (Text -> err) -> Maybe Val -> Either err (Maybe a) Source #

Decode a JSON value, transforming decode errors to type err if they occur.

jsonVal :: ToJSON a => a -> Val Source #

Encode JSON as a remote value.

decode ValsByKey

decodeJsonKeyKVs :: (Ord a, FromJSON a, FromJSON b) => (Text -> c) -> ValsByKey -> Either c (Map a b) Source #

Decode a ValsByKey serialized as JSON.

Both the key and value types are valid to deserialize as JSON.

decodeWebKeyKVs :: (Ord a, FromHttpApiData a, FromJSON b) => (Text -> c) -> ValsByKey -> Either c (Map a b) Source #

Decode a ValsByKey serialized as JSON.

  • The key type is deserialized as HttpApiData.
  • The value type is valid to deserialize as JSON.

save ValsByKey using a Handle

saveKVs :: (Ord a, ToJSON b, Monad m) => (HandleErr -> err) -> (a -> Val) -> Handle m -> Key -> Map a b -> m (Either err ()) Source #

Encode a Map as a ValsByKey with the Vals encoded as JSON.

  • The Map keys is encoded as Keys using the provided function,
  • The Map values are encoded as Vals by conversion to JSON.
  • HandleErr may be transformed to different error type

saveKVs' :: (Ord a, ToJSON b, Monad m) => (a -> Val) -> Handle m -> Key -> Map a b -> m (Either HandleErr ()) Source #

Like saveKVs, with HandleErr as the error type.

saveJsonKeyKVs :: (Ord a, ToJSON a, ToJSON b, Monad m) => (HandleErr -> err) -> Handle m -> Key -> Map a b -> m (Either err ()) Source #

Encode a ValsByKey serialized as JSON.

saveHttpApiKVs :: (Ord a, ToHttpApiData a, ToJSON b, Monad m) => (HandleErr -> err) -> Handle m -> Key -> Map a b -> m (Either err ()) Source #

Encode a ValsByKey serialized as JSON, completely replacing the current value if present.

updateHttpApiKVs :: (Ord a, ToHttpApiData a, ToJSON b, Monad m) => (HandleErr -> err) -> Handle m -> Key -> Map a b -> m (Either err ()) Source #

Like saveHttpApiKVs, but updates the keys rather than completely replacing it.