keyed-vals-0.2.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.Codec

Description

Provides a typeclass that converts types to and from keys or vals and combinators that help it to encode data using Handle

This serves to decouple the encoding/decoding, making it straightforward to use the typed interface in Typed with a wide set of encoding/decoding schemes

Synopsis

decode/encode support

class EncodeKV a where Source #

Specifies how type a encodes as a Key or a Val.

Methods

encodeKV :: a -> Val Source #

Instances

Instances details
ToJSON a => EncodeKV (AesonOf a) Source # 
Instance details

Defined in KeyedVals.Handle.Codec.Aeson

Methods

encodeKV :: AesonOf a -> Val Source #

ToHttpApiData a => EncodeKV (HttpApiDataOf a) Source # 
Instance details

Defined in KeyedVals.Handle.Codec.HttpApiData

EncodeKV (TypedKey v) Source # 
Instance details

Defined in KeyedVals.Handle.Typed

Methods

encodeKV :: TypedKey v -> Val Source #

class DecodeKV a where Source #

Specifies how type a can be decoded from a Key or a Val.

Methods

decodeKV :: Val -> Either Text a Source #

Instances

Instances details
FromJSON a => DecodeKV (AesonOf a) Source # 
Instance details

Defined in KeyedVals.Handle.Codec.Aeson

FromHttpApiData a => DecodeKV (HttpApiDataOf a) Source # 
Instance details

Defined in KeyedVals.Handle.Codec.HttpApiData

decodeOr :: (DecodeKV a, FromHandleErr err) => Maybe Val -> Either err (Maybe a) Source #

Decode a value, transforming decode errors to type err.

decodeOr' :: (DecodeKV b, FromHandleErr err) => Either err (Maybe Val) -> Either err (Maybe b) Source #

Decode a value, transformi decode errors to type err.

decodeOrGone :: (DecodeKV b, FromHandleErr err) => Key -> Maybe Val -> Either err b Source #

Like decodeOr, but transforms Nothing to Gone.

decodeOrGone' :: (DecodeKV b, FromHandleErr err) => Key -> Either err (Maybe Val) -> Either err b Source #

Like decodeOr', but transforms Nothing to Gone.

decode encoded ValsByKey

decodeKVs :: (Ord a, DecodeKV a, DecodeKV b, FromHandleErr err) => ValsByKey -> Either err (Map a b) Source #

Decodes a Map from a ValsByKey with encoded Keys and Vals.

save encoded ValsByKey using a Handle

saveEncodedKVs :: (Ord a, EncodeKV a, EncodeKV b, Monad m, FromHandleErr err) => Handle m -> Key -> Map a b -> m (Either err ()) Source #

Encode a Map as a ValsByKey with the Keys and Vals encoded.

  • HandleErr may be transformed to different error type

updateEncodedKVs :: (Ord a, EncodeKV a, EncodeKV b, Monad m, FromHandleErr err) => Handle m -> Key -> Map a b -> m (Either err ()) Source #

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

error conversion

class FromHandleErr err where Source #

Specifies how to turn HandleErr into a custom error type err.

Methods

fromHandleErr :: HandleErr -> err Source #

Instances

Instances details
FromHandleErr HandleErr Source # 
Instance details

Defined in KeyedVals.Handle.Codec