Safe Haskell | None |
---|---|
Language | Haskell2010 |
- class Pk a where
- newtype Path = Path {}
- rootPath :: Path
- newtype ObjId = ObjId {}
- rootObjId :: ObjId
- newtype RevId = RevId {}
- zeroRevId :: RevId
- data ObjectId
- objectIdParser :: Parser ObjectId
- parseObjectId :: Text -> Maybe ObjectId
- objectIdBase :: ObjectId -> ObjId
- data Operation
- data PatchError = UnknownPatchError !Text
- type PatchM a = Either PatchError a
- data Object = Object {
- objectId :: !ObjId
- objectType :: !Text
- objectCreatedAt :: !UTCTime
- objectCreatedBy :: !ObjId
- objectDeleted :: !(Maybe Bool)
- data Patch = Patch {}
- data Snapshot = Snapshot {}
- initialSnapshot :: ObjectId -> Snapshot
- data Release = Release
- newtype SecretId = SecretId {
- unSecretId :: Text
- data Secret = Secret {
- secretId :: !SecretId
- secretValue :: !Text
- newtype BlobId = BlobId {}
- data Blob = Blob {}
- newtype SessionId = SessionId {
- unSessionId :: Text
- data Session = Session {}
- data AversError
- internalError :: AversError -> Avers a
- internal :: Avers a -> Avers a
- databaseError :: Text -> Avers a
- patchError :: PatchError -> Avers a
- parseError :: MonadError AversError m => Value -> Text -> m a
- documentNotFound :: Text -> Avers a
- strErr :: String -> Avers a
- data ObjectType a = ObjectType {}
- data SomeObjectType where
- SomeObjectType :: (ToDatum a, FromDatum a, FromJSON a, ToJSON a) => ObjectType a -> SomeObjectType
- parseValueAs :: FromJSON a => ObjectType a -> Value -> Either AversError a
- data Config = Config {
- databaseURI :: !URI
- putBlob :: BlobId -> Text -> ByteString -> IO (Either AversError ())
- objectTypes :: ![SomeObjectType]
- emitMeasurement :: Measurement -> Double -> IO ()
- data Change = CPatch !Patch
- data Handle = Handle {}
- newtype Avers a = Avers {}
- class Monad m => MonadAvers m where
- evalAvers :: Handle -> Avers a -> IO (Either AversError a)
- data View obj a = View {
- viewName :: Text
- viewParser :: Datum -> Either AversError a
- viewObjectTransformer :: obj -> Avers (Maybe a)
- viewIndices :: [SomeIndex]
- data SomeView obj where
Documentation
Pk - Types which can be converted to a database primary key.
Path
This path refers to the root of an object. It is only used in Set
operations.
ObjId
The root object id is used for object created internally or when there is no applicable creator.
RevId
ObjectId
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. |
objectIdBase :: ObjectId -> ObjId Source #
The operations that can be applied to JSON values.
data PatchError Source #
type PatchM a = Either PatchError a Source #
Object | |
|
Patch
Patch | |
|
Snapshot
initialSnapshot :: ObjectId -> Snapshot Source #
The initial snapshot on top of which all future patches are applied.
(deriveJSONOptions "release") ''Release)
SecretId
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 SecretId
s are unique. If you use ObjId
s
then they by definition are.
Secret | |
|
BlobId
Blob
SessionId
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.
Session | |
|
data AversError Source #
internalError :: AversError -> Avers a Source #
databaseError :: Text -> Avers a Source #
patchError :: PatchError -> Avers a Source #
parseError :: MonadError AversError m => Value -> Text -> m a Source #
documentNotFound :: Text -> Avers a Source #
data ObjectType a Source #
An ObjectType
describes a particular type of object that is managed by
Avers.
data SomeObjectType where Source #
SomeObjectType :: (ToDatum a, FromDatum a, FromJSON a, ToJSON a) => ObjectType a -> SomeObjectType |
parseValueAs :: FromJSON a => ObjectType a -> Value -> Either AversError a Source #
Configuration of the Avers
monad.
Config | |
|
A change in the system, for example a new object, patch, release, blob etc.
Handle | |
|
class Monad m => MonadAvers m where Source #
MonadAvers Avers Source # | |
MonadAvers m => MonadAvers (StateT s m) Source # | |
View | |
|