| Copyright | (c) 2022 Tim Emiola |
|---|---|
| License | BSD3 |
| Maintainer | Tim Emiola <adetokunbo@emio.la> |
| Safe Haskell | Safe-Inferred |
| Language | Haskell2010 |
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
- type TypedKVs value = Map (KeyType value) value
- countKVs :: forall a m. (Monad m, Ord (KeyType a)) => Handle m -> TypedPath a -> m (Either HandleErr Natural)
- loadFrom :: forall a m. (Monad m, DecodeKV a) => Handle m -> TypedKey a -> m (Either HandleErr a)
- loadKVs :: (Monad m, DecodeKV a, DecodeKV (KeyType a), Ord (KeyType a)) => Handle m -> TypedPath a -> m (Either HandleErr (TypedKVs a))
- 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))
- mayLoadFrom :: forall a m. (Monad m, DecodeKV a, PathOf a) => Handle m -> TypedKey a -> m (Either HandleErr (Maybe a))
- 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 ())
- saveTo :: (Monad m, EncodeKV a, PathOf a) => Handle m -> TypedKey a -> a -> m (Either HandleErr ())
- saveKVs :: (Monad m, EncodeKV a, EncodeKV (KeyType a), Ord (KeyType a)) => Handle m -> TypedPath a -> TypedKVs a -> m (Either HandleErr ())
- updateKVs :: (Monad m, EncodeKV a, EncodeKV (KeyType a), Ord (KeyType a)) => Handle m -> TypedPath a -> TypedKVs a -> m (Either HandleErr ())
- class (KnownSymbol (KVPath value), EncodeKV (KeyType value), DecodeKV (KeyType value)) => PathOf value where
- class PathOf value => VaryingPathOf value where
- rawPath :: forall value. PathOf value => Proxy value -> Key
- expand :: EncodeKV a => a -> Key -> Key
- prepend :: EncodeKV a => Key -> a -> Key -> Key
- append :: EncodeKV a => Key -> a -> Key -> Key
- data TypedPath v where
- data TypedKey v
- pathKey :: forall v. TypedPath v -> Key
- pathOf :: TypedKey v -> TypedPath v
- key :: PathOf v => KeyType v -> TypedKey v
- (//) :: VaryingPathOf v => PathVar v -> KeyType v -> TypedKey v
- type Key = ByteString
- data Selection
- data HandleErr
- = ConnectionClosed
- | Unanticipated !Text
- | NotDecoded !Text
- | BadKey
- | Gone !Key
- data Handle m
- module KeyedVals.Handle.Codec
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 PathVarThis 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
countKVs :: forall a m. (Monad m, Ord (KeyType a)) => Handle m -> TypedPath a -> m (Either HandleErr Natural) Source #
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 #
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 #
mayLoadFrom :: forall a m. (Monad m, DecodeKV a, PathOf a) => Handle m -> TypedKey a -> m (Either HandleErr (Maybe a)) Source #
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 #
saveTo :: (Monad m, EncodeKV a, PathOf a) => Handle m -> TypedKey a -> a -> m (Either HandleErr ()) Source #
saveKVs :: (Monad m, EncodeKV a, EncodeKV (KeyType a), Ord (KeyType a)) => Handle m -> TypedPath a -> TypedKVs a -> m (Either HandleErr ()) Source #
updateKVs :: (Monad m, EncodeKV a, EncodeKV (KeyType a), Ord (KeyType a)) => Handle m -> TypedPath a -> TypedKVs a -> m (Either HandleErr ()) Source #
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.
class PathOf value => VaryingPathOf value where Source #
Allow the storage path specifed by to vary so that related
groups of key-values may be stored in similar, related paths.PathOf
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.
unify PathOf/VaryingPathOf
data TypedPath v where Source #
A phantom type indicating either an instance of or of
PathOf.VaryingPathOf
Allows combinators with similar behaviour for either to be defined just once, rather than separately for each typeclass.
Similar to TypedPath, but includes an actual key along with the phantom type.
(//) :: 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.
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 |
Represents the errors that might arise in Handle functions
Constructors
| ConnectionClosed | |
| Unanticipated !Text | |
| NotDecoded !Text | |
| BadKey | |
| Gone !Key |
Instances
| Exception HandleErr Source # | |
Defined in KeyedVals.Handle.Internal Methods toException :: HandleErr -> SomeException # fromException :: SomeException -> Maybe HandleErr # displayException :: HandleErr -> String # | |
| Show HandleErr Source # | |
| Eq HandleErr Source # | |
| FromHandleErr HandleErr Source # | |
Defined in KeyedVals.Handle.Codec Methods fromHandleErr :: HandleErr -> HandleErr Source # | |
module KeyedVals.Handle.Codec