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

KeyedVals.Handle.Typed

Description

Provides typeclasses, data types and combinators that constrain the types of keys and values accessed in the key-value store, whilst also linking them to specific storage paths.

Synopsis

How use this module

This section contains information on how to store data using this library. It starts with a preamble that shows the directives and imports used in the examples below

{\-# LANGUAGE DeriveGeneric #-\}
{\-# LANGUAGE DerivingVia #-\}
{\-# LANGUAGE OverloadedStrings #-\}
{\-# LANGUAGE StandaloneDeriving #-\}

import Data.Aeson (FromJSON, ToJSON)
import Data.Text (Text)
import GHC.Generics (Generic)
import KeyedVals.Handle.Codec.Aeson (AesonOf(..))
import KeyedVals.Handle.Codec.HttpApiData (HttpApiDataOf(..))
import qualified KeyedVals.Handle.Mem as Mem
import KeyedVals.Handle.Typed
import Web.HttpApiData (FromHttpApiData, ToHttpApiData)

Usage is fairly simple: PathOf and possibly a VaryingPathOf instance for storable data types are declared. They describe how the data type is encoded and decoded and where in the key-value store the data should be saved.

For example, given this data type:

data Person = Person
  { name :: Text
  , age  :: Int
  } deriving (Eq, Show, Generic)

Suppose each Person is to be stored as JSON, via the Generic implementation, e.g,

instance FromJSON Person
instance ToJSON Person

Also suppose each Person is stored with an Int key. To enable that, define a newtype of Int, e.g,

newtype PersonID = PersonID Int
  deriving stock (Eq, Show)
  deriving (ToHttpApiData, FromHttpApiData, Num, Ord) via Int

Also, suppose the collection of Persons keyed by PersonID is stored at a specific fixed path in the key-value store. E.g, it is to be used as a runtime cache to speed up access to person data, so the path runtimecache/persons is used.

To specify all this, first define DecodeKV and EncodeKV instances for Person:

deriving via (AesonOf Person) instance DecodeKV Person
deriving via (AesonOf Person) instance EncodeKV Person

.. and do the same for PersonID:

deriving via (HttpApiDataOf Int) instance DecodeKV PersonID
deriving via (HttpApiDataOf Int) instance EncodeKV PersonID

Then declare a PathOf instance that binds the types together with the path:

instance PathOf Person where
  type KVPath Person = "/runtime/cache/persons"
  type KeyType Person = PersonID

Note: the DecodeKV and EncodeKV deriving statements above were standalone for illustrative purposes. In most cases, they ought to be part of the deriving clause of the data type. E.g,

newtype AnotherID = AnotherID Int
  deriving stock (Eq, Show)
  deriving (ToHttpApiData, FromHttpApiData, Num, Ord) via Int
  deriving (DecodeKV, EncodeKV) via (HttpApiDataOf Int)

Now one can load and fetch Persons from a storage backend using the functions in this module, e.g:

>>> handle <- Mem.new
>>> tim = Person { name = "Tim", age = 48 }
>>> saveTo handle (key 1) tim
Right ()
>>> loadFrom handle (key 1)
Right (Person { name = "Tim", age = 48 })

Suppose that in addition to the main collection of Persons, it's necessary to store a distinct list of the friends of each Person. I.e, store a small keyed collection of Persons per person.

One way to achieve is to store each such collection at a similar path, e.g suppose the friends for the person with anID are stored at apppersonanIdfriends.

This can be implemented using the existing types along with another newtype that has PathOf and VaryingPathOf instances as follows

newtype Friend = Friend Person
  deriving stock (Eq, Show)
  deriving (FromJSON, ToJSON, EncodeKV, DecodeKV) via Person

instance PathOf Friend where
  type KVPath Friend = "/app/person/{}/friends"
  type KeyType Friend = FriendID -- as defined earlier

instance VaryingPathOf Friend where
  type PathVar Friend = PersonID
  modifyPath _ = expand -- implements modifyPath by expanding the braces to PathVar

This allows Friends to be saved or fetched as follows:

>>> dave = Person { name = "Dave", age = 61 }
>>> saveTo handle (key 2) dave -- save in main person list
Right ()
>>> saveTo handle ( 1 // 2) (Friend dave) -- save as friend of tim (person 1)
Right ()

type-and-path-constrained Handle combinators

type TypedKVs value = Map (KeyType value) value Source #

Represents a related group of values each stored using a key of type KeyType type

countKVs :: forall a m. (Monad m, Ord (KeyType a)) => Handle m -> TypedPath a -> m (Either HandleErr Natural) Source #

Like countKVs with the path and key-values constrained by TypedPath

loadFrom :: forall a m. (Monad m, DecodeKV a) => Handle m -> TypedKey a -> m (Either HandleErr a) Source #

Like mayLoadFrom, but fails with Gone if the value is missing.

loadKVs :: (Monad m, DecodeKV a, DecodeKV (KeyType a), Ord (KeyType a)) => Handle m -> TypedPath a -> m (Either HandleErr (TypedKVs a)) Source #

Like loadKVs with the path and key values constrained by TypedPath

loadSlice :: forall m a. (Monad m, DecodeKV a, PathOf a, DecodeKV (KeyType a), Ord (KeyType a)) => Handle m -> TypedPath a -> NonEmpty (KeyType a) -> m (Either HandleErr (TypedKVs a)) Source #

Like loadSlice with the path and key-values constrained by TypedPath

mayLoadFrom :: forall a m. (Monad m, DecodeKV a, PathOf a) => Handle m -> TypedKey a -> m (Either HandleErr (Maybe a)) Source #

Like loadVal with the key, path and value constrained by TypedKey

modKVs :: (Monad m, EncodeKV a, EncodeKV (KeyType a), DecodeKV a, DecodeKV (KeyType a), Ord (KeyType a)) => (TypedKVs a -> TypedKVs a) -> Handle m -> TypedPath a -> m (Either HandleErr ()) Source #

Combines saveKVs and loadKVs

saveTo :: (Monad m, EncodeKV a, PathOf a) => Handle m -> TypedKey a -> a -> m (Either HandleErr ()) Source #

Like saveTo with the key, path and value constrained by TypedKey

saveKVs :: (Monad m, EncodeKV a, EncodeKV (KeyType a), Ord (KeyType a)) => Handle m -> TypedPath a -> TypedKVs a -> m (Either HandleErr ()) Source #

Like savedKVs with the path and key-values constrained by TypedPath

updateKVs :: (Monad m, EncodeKV a, EncodeKV (KeyType a), Ord (KeyType a)) => Handle m -> TypedPath a -> TypedKVs a -> m (Either HandleErr ()) Source #

Like updateKVs with the path and key-values constrained by TypedPath

link key-value collections to a path

class (KnownSymbol (KVPath value), EncodeKV (KeyType value), DecodeKV (KeyType value)) => PathOf value Source #

Links the storage path of a group of key-values to the types of the key and value.

Associated Types

type KVPath value :: Symbol Source #

type KeyType value Source #

class PathOf value => VaryingPathOf value where Source #

Allow the storage path specifed by PathOf to vary so that related groups of key-values may be stored in similar, related paths.

Associated Types

type PathVar value Source #

Methods

modifyPath :: Proxy value -> PathVar value -> Key -> Key Source #

rawPath :: forall value. PathOf value => Proxy value -> Key Source #

Obtain the raw path to key-values that implement PathOf.

expand :: EncodeKV a => a -> Key -> Key Source #

Supports implementation of modifyPath via substitution of {} within the KVPath.

prepend :: EncodeKV a => Key -> a -> Key -> Key Source #

Supports implementaton of modifyPath

append :: EncodeKV a => Key -> a -> Key -> Key Source #

Supports implementaton of modifyPath.

unify PathOf/VaryingPathOf

data TypedPath v where Source #

A phantom type indicating either an instance of PathOf or of VaryingPathOf.

Allows combinators with similar behaviour for either to be defined just once, rather than separately for each typeclass.

Constructors

Fixed :: PathOf v => TypedPath v 
Variable :: VaryingPathOf v => PathVar v -> TypedPath v 

data TypedKey v Source #

Similar to TypedPath, but includes an actual key along with the phantom type.

Instances

Instances details
EncodeKV (TypedKey v) Source # 
Instance details

Defined in KeyedVals.Handle.Typed

Methods

encodeKV :: TypedKey v -> Val Source #

pathKey :: forall v. TypedPath v -> Key Source #

Obtains the path indicted by a TypedPath as a Key.

pathOf :: TypedKey v -> TypedPath v Source #

Derives the TypedPath corresponding to a TypedKey.

key :: PathOf v => KeyType v -> TypedKey v Source #

Constructs a simple TypedKey.

(//) :: VaryingPathOf v => PathVar v -> KeyType v -> TypedKey v infixr 5 Source #

Constructs an extended TypedKey.

module re-exports

type Key = ByteString Source #

Represents a key used to store a Val.

data Selection Source #

Represents ways of restricting the keys used in a ValsByKey

Constructors

Match !Glob

any keys that match the glob pattern

AllOf !(NonEmpty Key)

any of the specified keys

Instances

Instances details
Show Selection Source # 
Instance details

Defined in KeyedVals.Handle.Internal

Eq Selection Source # 
Instance details

Defined in KeyedVals.Handle.Internal

data HandleErr Source #

Represents the errors that might arise in Handle functions

data Handle m Source #

A handle for accessing the ValsByKey store.