| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Avers
- data Avers a
- evalAvers :: AversState -> Avers a -> IO (Either AversError a)
- newtype Path = Path {}
- class Pk a where
- newtype ObjId = ObjId {}
- rootObjId :: ObjId
- newtype RevId = RevId {}
- zeroRevId :: RevId
- data ObjectId
- data Operation
- data Object = Object {
- objectId :: !ObjId
- objectType :: !Text
- objectCreatedAt :: !UTCTime
- objectCreatedBy :: !ObjId
- objectDeleted :: !(Maybe Bool)
- exists :: ObjId -> Avers Bool
- createObject :: ToJSON a => ObjectType a -> ObjId -> a -> Avers ObjId
- createObject' :: ToJSON a => ObjId -> UTCTime -> ObjectType a -> ObjId -> a -> Avers ()
- lookupObject :: ObjId -> Avers Object
- deleteObject :: ObjId -> Avers ()
- pruneObject :: ObjId -> Avers ()
- objectsOfType :: ObjectType a -> Avers (Vector ObjId)
- allObjectsOfType :: ObjectType a -> Avers (Vector ObjId)
- data Patch = Patch {}
- data PatchError = UnknownPatchError !Text
- lookupPatch :: ObjectId -> RevId -> Avers Patch
- data Snapshot = Snapshot {}
- lookupLatestSnapshot :: ObjectId -> Avers Snapshot
- objectContent :: FromJSON a => ObjectId -> Avers a
- data Release = Release
- lookupRelease :: ObjId -> RevId -> Avers Release
- createRelease :: ObjId -> RevId -> Avers ()
- lookupLatestRelease :: ObjId -> Avers (Maybe RevId)
- resolvePathIn :: Path -> Value -> Maybe Value
- newtype SessionId = SessionId {
- unSessionId :: Text
- data Session = Session {}
- saveSession :: Session -> Avers ()
- lookupSession :: SessionId -> Avers Session
- dropSession :: SessionId -> Avers ()
- data ObjectType a = ObjectType {}
- data SomeObjectType where
- SomeObjectType :: (ToDatum a, FromDatum a, FromJSON a, ToJSON a) => ObjectType a -> SomeObjectType
- lookupObjectType :: Text -> Avers SomeObjectType
- data AversError
- data AversConfig = AversConfig {
- databaseHost :: !Text
- databaseName :: !Text
- putBlob :: BlobId -> Text -> ByteString -> IO ()
- objectTypes :: ![SomeObjectType]
- emitMeasurement :: Measurement -> Double -> IO ()
- data AversState
- newState :: AversConfig -> IO AversState
- strErr :: String -> Avers a
- parseValueAs :: FromJSON a => ObjectType a -> Value -> Either AversError a
- bootstrap :: Avers ()
- newtype BlobId = BlobId {}
- data Blob = Blob {}
- createBlob :: ByteString -> Text -> Avers Blob
- lookupBlob :: BlobId -> Avers Blob
- newtype SecretId = SecretId {
- unSecretId :: Text
- data Secret = Secret {
- secretId :: !SecretId
- secretValue :: !Text
- updateSecret :: SecretId -> Text -> Avers ()
- verifySecret :: SecretId -> Text -> Avers ()
- applyObjectUpdates :: ObjectId -> RevId -> ObjId -> [Operation] -> Bool -> Avers ([Patch], Int, [Patch])
- runQuery :: FromResponse (Result a) => Exp a -> Avers (Result a)
- runQueryCollect :: (FromDatum a, IsSequence e, Result e ~ Sequence a) => Exp e -> Avers (Vector a)
- parseValue :: (FromJSON a, MonadError AversError m) => Value -> m a
- parseDatum :: (FromDatum a, MonadError AversError m) => Datum -> m a
- newId :: Int -> IO Text
- objectsTable :: Exp Table
- blobsTable :: Exp Table
- validateObject :: Text -> Value -> Avers ()
- data View obj a = View {
- viewName :: Text
- viewParser :: Datum -> Either AversError a
- viewObjectTransformer :: obj -> Avers (Maybe a)
- viewIndices :: [SomeIndex]
- data SomeView obj where
- viewTable :: View obj a -> Exp Table
- updateView :: ToDatum a => View obj a -> ObjId -> Maybe obj -> Avers ()
- data Index a = Index {}
- data SomeIndex where
- data Measurement
- = M_avers_storage_lookupObject_duration
- | M_avers_storage_lookupSnapshot_duration
- | M_avers_storage_lookupLatestSnapshot_duration
- | M_avers_storage_newestSnapshot_duration
- | M_avers_storage_patchesAfterRevision_duration
- | M_avers_storage_lookupPatch_duration
- | M_avers_storage_applyObjectUpdates_duration
- | M_avers_storage_applyObjectUpdates_numOperations
- | M_avers_storage_applyObjectUpdates_numPreviousPatches
- | M_avers_storage_exists_duration
- measurementLabels :: Measurement -> [[Char]]
The Avers Monad
evalAvers :: AversState -> Avers a -> IO (Either AversError a) Source
Types
Path
Pk - Types which can be converted to a database primary key.
ObjId
The root object id is used for object created internally or when there is no applicable creator.
RevId
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. |
The operations that can be applied to JSON values.
Object
Constructors
| Object | |
Fields
| |
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.
objectsOfType :: ObjectType a -> Avers (Vector ObjId) Source
allObjectsOfType :: ObjectType a -> Avers (Vector ObjId) Source
Patch
Patch
Constructors
| Patch | |
Fields
| |
Snapshot
Snapshot
Constructors
| Snapshot | |
Fields
| |
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
Session
SessionId
Constructors
| SessionId | |
Fields
| |
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.
Constructors
| Session | |
Fields
| |
saveSession :: Session -> Avers () Source
lookupSession :: SessionId -> Avers Session Source
dropSession :: SessionId -> Avers () Source
data ObjectType a Source
An ObjectType describes a particular type of object that is managed by
Avers.
data SomeObjectType where Source
Constructors
| SomeObjectType :: (ToDatum a, FromDatum a, FromJSON a, ToJSON a) => ObjectType a -> SomeObjectType |
lookupObjectType :: Text -> Avers SomeObjectType Source
Lookup an object type which is registered in the Avers monad.
data AversError Source
Constructors
| InternalError !AversError | |
| DatabaseError !Text | |
| PatchError !PatchError | |
| ParseError !Value !Text | |
| UnknownObjectType !Text | |
| ObjectNotFound !ObjId | |
| DocumentNotFound !Text | |
| AversError !Text | |
| NotAuthorized |
Instances
data AversConfig Source
Configuration of the Avers monad.
Constructors
| AversConfig | |
Fields
| |
data AversState Source
Instances
newState :: AversConfig -> IO AversState Source
parseValueAs :: FromJSON a => ObjectType a -> Value -> Either AversError a Source
Blob
BlobId
Blob
createBlob :: ByteString -> Text -> Avers Blob Source
lookupBlob :: BlobId -> Avers Blob Source
Secret
SecretId
Constructors
| SecretId | |
Fields
| |
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 | |
Fields
| |
updateSecret :: SecretId -> Text -> Avers () Source
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.
runQueryCollect :: (FromDatum a, IsSequence e, Result e ~ Sequence a) => Exp e -> Avers (Vector a) Source
parseValue :: (FromJSON a, MonadError AversError m) => Value -> m a Source
parseDatum :: (FromDatum a, MonadError AversError m) => Datum -> m a Source
blobsTable :: Exp Table Source
validateObject :: Text -> Value -> Avers () Source
Views
Constructors
| View | |
Fields
| |
viewTable :: View obj a -> Exp Table Source
Construct the table name for the given view. The table names look something like this: "view_openGames"
Index
Metrics
data Measurement Source
Constructors
measurementLabels :: Measurement -> [[Char]] Source