avers-0.0.17.1: empty

Safe HaskellNone
LanguageHaskell2010

Avers

Contents

Synopsis

The Avers Monad

data Avers a Source #

Instances

Monad Avers Source # 

Methods

(>>=) :: Avers a -> (a -> Avers b) -> Avers b #

(>>) :: Avers a -> Avers b -> Avers b #

return :: a -> Avers a #

fail :: String -> Avers a #

Functor Avers Source # 

Methods

fmap :: (a -> b) -> Avers a -> Avers b #

(<$) :: a -> Avers b -> Avers a #

Applicative Avers Source # 

Methods

pure :: a -> Avers a #

(<*>) :: Avers (a -> b) -> Avers a -> Avers b #

(*>) :: Avers a -> Avers b -> Avers b #

(<*) :: Avers a -> Avers b -> Avers a #

MonadIO Avers Source # 

Methods

liftIO :: IO a -> Avers a #

MonadAvers Avers Source # 

Methods

liftAvers :: Avers a -> Avers a Source #

MonadError AversError Avers Source # 

Methods

throwError :: AversError -> Avers a #

catchError :: Avers a -> (AversError -> Avers a) -> Avers a #

MonadState Handle Avers Source # 

Methods

get :: Avers Handle #

put :: Handle -> Avers () #

state :: (Handle -> (a, Handle)) -> Avers a #

Types

newtype Path Source #

Path

Constructors

Path 

Fields

Instances

Eq Path Source # 

Methods

(==) :: Path -> Path -> Bool #

(/=) :: Path -> Path -> Bool #

Ord Path Source # 

Methods

compare :: Path -> Path -> Ordering #

(<) :: Path -> Path -> Bool #

(<=) :: Path -> Path -> Bool #

(>) :: Path -> Path -> Bool #

(>=) :: Path -> Path -> Bool #

max :: Path -> Path -> Path #

min :: Path -> Path -> Path #

Show Path Source # 

Methods

showsPrec :: Int -> Path -> ShowS #

show :: Path -> String #

showList :: [Path] -> ShowS #

IsString Path Source # 

Methods

fromString :: String -> Path #

Generic Path Source # 

Associated Types

type Rep Path :: * -> * #

Methods

from :: Path -> Rep Path x #

to :: Rep Path x -> Path #

ToJSON Path Source # 
FromJSON Path Source # 
ToDatum Path Source # 

Methods

toDatum :: Path -> Datum #

FromDatum Path Source # 
type Rep Path Source # 
type Rep Path = D1 (MetaData "Path" "Avers.Types" "avers-0.0.17.1-5bAZHu7ABPDLnacsfr9X8" True) (C1 (MetaCons "Path" PrefixI True) (S1 (MetaSel (Just Symbol "unPath") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text)))

class Pk a where Source #

Pk - Types which can be converted to a database primary key.

Minimal complete definition

toPk

Methods

toPk :: a -> Text Source #

newtype ObjId Source #

ObjId

Constructors

ObjId 

Fields

Instances

Eq ObjId Source # 

Methods

(==) :: ObjId -> ObjId -> Bool #

(/=) :: ObjId -> ObjId -> Bool #

Ord ObjId Source # 

Methods

compare :: ObjId -> ObjId -> Ordering #

(<) :: ObjId -> ObjId -> Bool #

(<=) :: ObjId -> ObjId -> Bool #

(>) :: ObjId -> ObjId -> Bool #

(>=) :: ObjId -> ObjId -> Bool #

max :: ObjId -> ObjId -> ObjId #

min :: ObjId -> ObjId -> ObjId #

Show ObjId Source # 

Methods

showsPrec :: Int -> ObjId -> ShowS #

show :: ObjId -> String #

showList :: [ObjId] -> ShowS #

Generic ObjId Source # 

Associated Types

type Rep ObjId :: * -> * #

Methods

from :: ObjId -> Rep ObjId x #

to :: Rep ObjId x -> ObjId #

ToJSON ObjId Source # 
FromJSON ObjId Source # 
ToDatum ObjId Source # 

Methods

toDatum :: ObjId -> Datum #

FromDatum ObjId Source # 
Pk ObjId Source # 

Methods

toPk :: ObjId -> Text Source #

type Rep ObjId Source # 
type Rep ObjId = D1 (MetaData "ObjId" "Avers.Types" "avers-0.0.17.1-5bAZHu7ABPDLnacsfr9X8" True) (C1 (MetaCons "ObjId" PrefixI True) (S1 (MetaSel (Just Symbol "unObjId") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text)))

rootObjId :: ObjId Source #

The root object id is used for object created internally or when there is no applicable creator.

newtype RevId Source #

RevId

Constructors

RevId 

Fields

Instances

Enum RevId Source # 
Eq RevId Source # 

Methods

(==) :: RevId -> RevId -> Bool #

(/=) :: RevId -> RevId -> Bool #

Ord RevId Source # 

Methods

compare :: RevId -> RevId -> Ordering #

(<) :: RevId -> RevId -> Bool #

(<=) :: RevId -> RevId -> Bool #

(>) :: RevId -> RevId -> Bool #

(>=) :: RevId -> RevId -> Bool #

max :: RevId -> RevId -> RevId #

min :: RevId -> RevId -> RevId #

Show RevId Source # 

Methods

showsPrec :: Int -> RevId -> ShowS #

show :: RevId -> String #

showList :: [RevId] -> ShowS #

Generic RevId Source # 

Associated Types

type Rep RevId :: * -> * #

Methods

from :: RevId -> Rep RevId x #

to :: Rep RevId x -> RevId #

ToJSON RevId Source # 
FromJSON RevId Source # 
ToDatum RevId Source # 

Methods

toDatum :: RevId -> Datum #

FromDatum RevId Source # 
Pk RevId Source # 

Methods

toPk :: RevId -> Text Source #

type Rep RevId Source # 
type Rep RevId = D1 (MetaData "RevId" "Avers.Types" "avers-0.0.17.1-5bAZHu7ABPDLnacsfr9X8" True) (C1 (MetaCons "RevId" PrefixI True) (S1 (MetaSel (Just Symbol "unRevId") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int)))

zeroRevId :: RevId Source #

The RevId which is used for the initial snapshot.

data ObjectId Source #

ObjectId

Constructors

BaseObjectId !ObjId

The base object whose snapshots contain the actual content.

ReleaseObjectId !ObjId !RevId

An object describing a particualar release of the base object.

AuthorizationObjectId !ObjId

Object which contains authorization rules.

Instances

Eq ObjectId Source # 
Ord ObjectId Source # 
Show ObjectId Source # 
Generic ObjectId Source # 

Associated Types

type Rep ObjectId :: * -> * #

Methods

from :: ObjectId -> Rep ObjectId x #

to :: Rep ObjectId x -> ObjectId #

ToJSON ObjectId Source # 
FromJSON ObjectId Source # 
ToDatum ObjectId Source # 

Methods

toDatum :: ObjectId -> Datum #

FromDatum ObjectId Source # 
Pk ObjectId Source # 

Methods

toPk :: ObjectId -> Text Source #

type Rep ObjectId Source # 

data Operation Source #

The operations that can be applied to JSON values.

Constructors

Set

Set is applied to Objects. It is used for adding, updating and deleting properties from the object.

Fields

Splice

Splice is used to manipulate Arrays. It can remove and insert multiple elements in a single operation.

Fields

Instances

Eq Operation Source # 
Show Operation Source # 
Generic Operation Source # 

Associated Types

type Rep Operation :: * -> * #

ToJSON Operation Source # 
FromJSON Operation Source # 
ToDatum Operation Source # 

Methods

toDatum :: Operation -> Datum #

FromDatum Operation Source # 
type Rep Operation Source # 

Object

data Object Source #

exists :: ObjId -> Avers Bool Source #

True if the object exists.

createObject :: ToJSON a => ObjectType a -> ObjId -> a -> Avers ObjId Source #

Create a new object of the given type. An initial snapshot (RevId 0) is created from the supplied content.

createObject' :: ToJSON a => ObjId -> UTCTime -> ObjectType a -> ObjId -> a -> Avers () Source #

A more low-level version of createObject, for use when you want to generate your own ObjId or create objects at a specific time.

lookupObject :: ObjId -> Avers Object Source #

Lookup an Object by its ObjId. Throws ObjectNotFound if the object doesn't exist.

deleteObject :: ObjId -> Avers () Source #

Mark the object as deleted.

pruneObject :: ObjId -> Avers () Source #

Prune the object from the database. This is only allowed if the object is marked as deleted. Note that this is a very dangerous operation, it can not be undone.

TODO: Prune related Release and Authoriation objects.

createCheckpoint :: ObjectId -> ObjId -> Avers RevId Source #

Create a checkpoint for for the given object. All patches (and of course snapshots) before the checkpoint can be dropped. Use vacuumObject to do that.

vacuumObject :: ObjectId -> Avers () Source #

Drop all patches and snapshots before the most recent checkpoint. This effectively drops the object's history, and frees space in the database.

Patch

data Patch Source #

Patch

data PatchError Source #

Constructors

UnknownPatchError !Text 

Instances

Show PatchError Source # 
Generic PatchError Source # 

Associated Types

type Rep PatchError :: * -> * #

type Rep PatchError Source # 
type Rep PatchError = D1 (MetaData "PatchError" "Avers.Types" "avers-0.0.17.1-5bAZHu7ABPDLnacsfr9X8" False) (C1 (MetaCons "UnknownPatchError" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text)))

Snapshot

lookupLatestSnapshot :: ObjectId -> Avers Snapshot Source #

Get the snapshot of the newest revision of the given object.

objectContent :: FromJSON a => ObjectId -> Avers a Source #

Fetch the content of the object and try to parse it.

This function will fail with a ParseError if the content can not be decoded into the desired type.

Release

createRelease :: ObjId -> RevId -> Avers () Source #

Create a new release of the given revision. If the object doesn't exist, it will fail with ObjectNotFound.

Patching

resolvePathIn :: Path -> Value -> Maybe Value Source #

Resolve the path in the object.

Session

data Session Source #

The session record that is stored in the database.

A session is a unique identifier attached to a particular object. It contains the creation date and when it was last accessed. If you need to store additional data for a session, we recommend to use cookies.

data ObjectType a Source #

An ObjectType describes a particular type of object that is managed by Avers.

Constructors

ObjectType 

Fields

lookupObjectType :: Text -> Avers SomeObjectType Source #

Lookup an object type which is registered in the Avers monad.

data AversError Source #

Instances

Show AversError Source # 
Generic AversError Source # 

Associated Types

type Rep AversError :: * -> * #

MonadError AversError Avers Source # 

Methods

throwError :: AversError -> Avers a #

catchError :: Avers a -> (AversError -> Avers a) -> Avers a #

type Rep AversError Source # 

data Config Source #

Configuration of the Avers monad.

Constructors

Config 

Fields

data Handle Source #

Instances

MonadState Handle Avers Source # 

Methods

get :: Avers Handle #

put :: Handle -> Avers () #

state :: (Handle -> (a, Handle)) -> Avers a #

newState :: Config -> IO (Either AversError Handle) Source #

Deprecated: Use newHandle instead

Blob

newtype BlobId Source #

BlobId

Constructors

BlobId 

Fields

Instances

Show BlobId Source # 
Generic BlobId Source # 

Associated Types

type Rep BlobId :: * -> * #

Methods

from :: BlobId -> Rep BlobId x #

to :: Rep BlobId x -> BlobId #

ToJSON BlobId Source # 
FromJSON BlobId Source # 
ToDatum BlobId Source # 

Methods

toDatum :: BlobId -> Datum #

FromDatum BlobId Source # 
Pk BlobId Source # 

Methods

toPk :: BlobId -> Text Source #

type Rep BlobId Source # 
type Rep BlobId = D1 (MetaData "BlobId" "Avers.Types" "avers-0.0.17.1-5bAZHu7ABPDLnacsfr9X8" True) (C1 (MetaCons "BlobId" PrefixI True) (S1 (MetaSel (Just Symbol "unBlobId") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text)))

data Blob Source #

Blob

Constructors

Blob 

Instances

Secret

newtype SecretId Source #

SecretId

Constructors

SecretId 

Fields

data Secret Source #

Secret

A Secret is a password (encrypted with scrypt) that is attached to a SecretId (for example the ObjId of an account).

It is up to you to ensure that SecretIds are unique. If you use ObjIds then they by definition are.

Constructors

Secret 

verifySecret :: SecretId -> Text -> Avers () Source #

Verify the value against the secret. If that fails, then this function throws an error.

This function automatically updates the secret in the database if the scrypt params have changed.

applyObjectUpdates Source #

Arguments

:: ObjectId

The object which you want to update

-> RevId

The RevId against which the operations were created

-> ObjId

Committer

-> [Operation]

The operations to apply

-> Bool

True if validation should be skipped

-> Avers ([Patch], Int, [Patch]) 

Views

data View obj a Source #

Constructors

View 

Fields

data SomeView obj where Source #

Constructors

SomeView :: (ToDatum a, FromDatum a, FromJSON obj, ToJSON a) => View obj a -> SomeView obj 

viewTable :: View obj a -> Exp Table Source #

Construct the table name for the given view. The table names look something like this: "view_openGames"

updateView :: ToDatum a => View obj a -> ObjId -> Maybe obj -> Avers () Source #

Index

data Index a Source #

Constructors

Index 

data SomeIndex where Source #

Constructors

SomeIndex :: IsDatum a => Index a -> SomeIndex 

Metrics

Change

data Change Source #

A change in the system, for example a new object, patch, release, blob etc.

Constructors

CPatch !Patch

A new patch was created.

Instances

Show Change Source # 
Generic Change Source # 

Associated Types

type Rep Change :: * -> * #

Methods

from :: Change -> Rep Change x #

to :: Rep Change x -> Change #

ToJSON Change Source # 
type Rep Change Source # 
type Rep Change = D1 (MetaData "Change" "Avers.Types" "avers-0.0.17.1-5bAZHu7ABPDLnacsfr9X8" False) (C1 (MetaCons "CPatch" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Patch)))

changeChannel :: Handle -> IO (TChan Change) Source #

Return a TChan to which all changes in the system are streamed. Make sure to continuously drain items from the TChan, otherwise they will accumulate in memory and you will run OOM eventually.

Do not write into the channel!