Safe Haskell | None |
---|---|
Language | Haskell2010 |
A simplified client interface for Project:M36 database access.
- simpleConnectProjectM36 :: ConnectionInfo -> IO (Either DbError DbConn)
- simpleConnectProjectM36At :: HeadName -> ConnectionInfo -> IO (Either DbError DbConn)
- withTransaction :: DbConn -> Db a -> IO (Either DbError a)
- withTransactionUsing :: DbConn -> MergeStrategy -> Db a -> IO (Either DbError a)
- execute :: DatabaseContextExpr -> Db ()
- executeOrErr :: DatabaseContextExpr -> Db (Either RelationalError ())
- query :: RelationalExpr -> Db Relation
- queryOrErr :: RelationalExpr -> Db (Either RelationalError Relation)
- cancelTransaction :: DbError -> Db a
- orCancelTransaction :: Either RelationalError a -> Db a
- rollback :: Db ()
- close :: DbConn -> IO ()
- data Atom
- data AtomType
- data Db a
- type DbConn = (SessionId, Connection)
- data DbError
- data RelationalError
- = NoSuchAttributeNamesError (Set AttributeName)
- | TupleAttributeCountMismatchError Int
- | TupleAttributeTypeMismatchError Attributes
- | AttributeCountMismatchError Int
- | AttributeNamesMismatchError (Set AttributeName)
- | AttributeNameInUseError AttributeName
- | AttributeIsNotRelationValuedError AttributeName
- | CouldNotInferAttributes
- | RelVarNotDefinedError RelVarName
- | RelVarAlreadyDefinedError RelVarName
- | RelVarAssignmentTypeMismatchError Attributes Attributes
- | InclusionDependencyCheckError IncDepName
- | InclusionDependencyNameInUseError IncDepName
- | InclusionDependencyNameNotInUseError IncDepName
- | ParseError Text
- | PredicateExpressionError Text
- | NoCommonTransactionAncestorError TransactionId TransactionId
- | NoSuchTransactionError TransactionId
- | RootTransactionTraversalError
- | HeadNameSwitchingHeadProhibitedError HeadName
- | NoSuchHeadNameError HeadName
- | UnknownHeadError
- | NewTransactionMayNotHaveChildrenError TransactionId
- | ParentCountTraversalError Int Int
- | NewTransactionMissingParentError TransactionId
- | TransactionIsNotAHeadError TransactionId
- | TransactionGraphCycleError TransactionId
- | SessionIdInUseError TransactionId
- | NoSuchSessionError TransactionId
- | FailedToFindTransactionError TransactionId
- | TransactionIdInUseError TransactionId
- | NoSuchFunctionError AtomFunctionName
- | NoSuchTypeConstructorName TypeConstructorName
- | TypeConstructorAtomTypeMismatch TypeConstructorName AtomType
- | AtomTypeMismatchError AtomType AtomType
- | TypeConstructorNameMismatch TypeConstructorName TypeConstructorName
- | AtomTypeTypeConstructorReconciliationError AtomType TypeConstructorName
- | DataConstructorNameInUseError DataConstructorName
- | DataConstructorUsesUndeclaredTypeVariable TypeVarName
- | TypeConstructorTypeVarsMismatch (Set TypeVarName) (Set TypeVarName)
- | TypeConstructorTypeVarMissing TypeVarName
- | TypeConstructorTypeVarsTypesMismatch TypeConstructorName TypeVarMap TypeVarMap
- | DataConstructorTypeVarsMismatch DataConstructorName TypeVarMap TypeVarMap
- | AtomFunctionTypeVariableResolutionError AtomFunctionName TypeVarName
- | AtomFunctionTypeVariableMismatch TypeVarName AtomType AtomType
- | AtomTypeNameInUseError AtomTypeName
- | IncompletelyDefinedAtomTypeWithConstructorError
- | AtomTypeNameNotInUseError AtomTypeName
- | FunctionNameInUseError AtomFunctionName
- | FunctionNameNotInUseError AtomFunctionName
- | EmptyCommitError
- | FunctionArgumentCountMismatchError Int Int
- | ConstructedAtomArgumentCountMismatchError Int Int
- | NoSuchDataConstructorError DataConstructorName
- | NoSuchTypeConstructorError TypeConstructorName
- | InvalidAtomTypeName AtomTypeName
- | AtomTypeNotSupported AttributeName
- | AtomOperatorNotSupported Text
- | EmptyTuplesError
- | AtomTypeCountError [AtomType] [AtomType]
- | AtomFunctionTypeError AtomFunctionName Int AtomType AtomType
- | AtomFunctionUserError AtomFunctionError
- | PrecompiledFunctionRemoveError AtomFunctionName
- | RelationValuedAttributesNotSupportedError [AttributeName]
- | NotificationNameInUseError NotificationName
- | NotificationNameNotInUseError NotificationName
- | ImportError Text
- | ExportError Text
- | UnhandledExceptionError String
- | MergeTransactionError MergeError
- | ScriptError ScriptCompilationError
- | DatabaseContextFunctionUserError DatabaseContextFunctionError
- | DatabaseLoadError PersistenceError
- | SubschemaNameInUseError SchemaName
- | SubschemaNameNotInUseError SchemaName
- | SchemaCreationError SchemaError
- | ImproperDatabaseStateError
- | MultipleErrors [RelationalError]
- data Attribute = Attribute AttributeName AtomType
- class (Eq a, NFData a, Binary a, Show a) => Atomable a where
- data ConnectionInfo
- data PersistenceStrategy
- type NotificationCallback = NotificationName -> EvaluatedNotification -> IO ()
- emptyNotificationCallback :: NotificationCallback
- data DatabaseContextExpr
- = NoOperation
- | Define RelVarName [AttributeExpr]
- | Undefine RelVarName
- | Assign RelVarName RelationalExpr
- | Insert RelVarName RelationalExpr
- | Delete RelVarName RestrictionPredicateExpr
- | Update RelVarName AttributeNameAtomExprMap RestrictionPredicateExpr
- | AddInclusionDependency IncDepName InclusionDependency
- | RemoveInclusionDependency IncDepName
- | AddNotification NotificationName RelationalExpr RelationalExpr RelationalExpr
- | RemoveNotification NotificationName
- | AddTypeConstructor TypeConstructorDef [DataConstructorDef]
- | RemoveTypeConstructor TypeConstructorName
- | RemoveAtomFunction AtomFunctionName
- | RemoveDatabaseContextFunction DatabaseContextFunctionName
- | ExecuteDatabaseContextFunction DatabaseContextFunctionName [AtomExpr]
- | MultipleExpr [DatabaseContextExpr]
- data RelationalExprBase a
- = MakeRelationFromExprs (Maybe [AttributeExprBase a]) [TupleExprBase a]
- | MakeStaticRelation Attributes RelationTupleSet
- | ExistingRelation Relation
- | RelationVariable RelVarName a
- | Project AttributeNames (RelationalExprBase a)
- | Union (RelationalExprBase a) (RelationalExprBase a)
- | Join (RelationalExprBase a) (RelationalExprBase a)
- | Rename AttributeName AttributeName (RelationalExprBase a)
- | Difference (RelationalExprBase a) (RelationalExprBase a)
- | Group AttributeNames AttributeName (RelationalExprBase a)
- | Ungroup AttributeName (RelationalExprBase a)
- | Restrict (RestrictionPredicateExprBase a) (RelationalExprBase a)
- | Equals (RelationalExprBase a) (RelationalExprBase a)
- | NotEquals (RelationalExprBase a) (RelationalExprBase a)
- | Extend (ExtendTupleExprBase a) (RelationalExprBase a)
Documentation
simpleConnectProjectM36 :: ConnectionInfo -> IO (Either DbError DbConn) Source #
Same as simpleConnectProjectM36At
but always connects to the master
branch.
simpleConnectProjectM36At :: HeadName -> ConnectionInfo -> IO (Either DbError DbConn) Source #
A simple alternative to connectProjectM36
which includes simple session management.
withTransaction :: DbConn -> Db a -> IO (Either DbError a) Source #
Runs a Db monad which may include some database updates. If an exception or error occurs, the transaction is rolled back. Otherwise, the transaction is committed to the head of the current branch.
withTransactionUsing :: DbConn -> MergeStrategy -> Db a -> IO (Either DbError a) Source #
Same a withTransaction
except that the merge strategy can be specified.
execute :: DatabaseContextExpr -> Db () Source #
Execute a DatabaseContextExpr
in the DB
monad. Database context expressions manipulate the state of the database. In case of an error, the transaction is terminated and the connection's session is rolled back.
executeOrErr :: DatabaseContextExpr -> Db (Either RelationalError ()) Source #
Run a DatabaseContextExpr
update expression. If there is an error, just return it without cancelling the current transaction.
query :: RelationalExpr -> Db Relation Source #
Run a RelationalExpr
query in the DB
monad. Relational expressions perform read-only queries against the current database state.
queryOrErr :: RelationalExpr -> Db (Either RelationalError Relation) Source #
Run a RelationalExpr
query expression. If there is an error, just return it without cancelling the transaction.
cancelTransaction :: DbError -> Db a Source #
Cancel a transaction and carry some error information with it.
orCancelTransaction :: Either RelationalError a -> Db a Source #
Unconditionally roll back the current transaction and throw an exception to terminate the execution of the Db monad.
Database atoms are the smallest, undecomposable units of a tuple. Common examples are integers, text, or unique identity keys.
The AtomType uniquely identifies the type of a atom.
type DbConn = (SessionId, Connection) Source #
A union of connection and other errors that can be returned from withTransaction
.
data RelationalError Source #
A relation's type is composed of attribute names and types.
class (Eq a, NFData a, Binary a, Show a) => Atomable a where Source #
All database values ("atoms") adhere to the Atomable
typeclass. This class is derivable allowing new datatypes to be easily marshaling between Haskell values and database values.
toAtom :: (Generic a, AtomableG (Rep a)) => a -> Atom Source #
fromAtom :: Atom -> a Source #
fromAtom :: (Generic a, AtomableG (Rep a)) => Atom -> a Source #
Atomable Bool Source # | |
Atomable Double Source # | |
Atomable Int Source # | |
Atomable Integer Source # | |
Atomable ByteString Source # | |
Atomable Text Source # | |
Atomable UTCTime Source # | |
Atomable Day Source # | |
Atomable a => Atomable [a] Source # | |
Atomable a => Atomable (Maybe a) Source # | |
(Atomable a, Atomable b) => Atomable (Either a b) Source # | |
data ConnectionInfo Source #
Construct a ConnectionInfo
to describe how to make the Connection
. The database can be run within the current process or running remotely via distributed-process.
data PersistenceStrategy Source #
The persistence strategy is a global database option which represents how to persist the database in the filesystem, if at all.
NoPersistence | no filesystem persistence/memory-only database |
MinimalPersistence FilePath | fsync off, not crash-safe |
CrashSafePersistence FilePath | full fsync to disk (flushes kernel and physical drive buffers to ensure that the transaction is on non-volatile storage) |
type NotificationCallback = NotificationName -> EvaluatedNotification -> IO () Source #
The type for notifications callbacks in the client. When a registered notification fires due to a changed relational expression evaluation, the server propagates the notifications to the clients in the form of the callback.
emptyNotificationCallback :: NotificationCallback Source #
The empty notification callback ignores all callbacks.
data DatabaseContextExpr Source #
Database context expressions modify the database context.
data RelationalExprBase a Source #
A relational expression represents query (read) operations on a database.
Binary RelationalExpr Source # | |
Eq a => Eq (RelationalExprBase a) Source # | |
Show a => Show (RelationalExprBase a) Source # | |
Generic (RelationalExprBase a) Source # | |
NFData a => NFData (RelationalExprBase a) Source # | |
type Rep (RelationalExprBase a) Source # | |