Safe Haskell | None |
---|---|
Language | Haskell2010 |
Client interface to local and remote Project:M36 databases. To get started, connect with connectProjectM36
, then run some database changes with executeDatabaseContextExpr
, and issue queries using executeRelationalExpr
.
- data ConnectionInfo
- data Connection
- = InProcessConnection InProcessConnectionConf
- | RemoteProcessConnection RemoteProcessConnectionConf
- type Port = Word16
- type Hostname = String
- type DatabaseName = String
- data ConnectionError
- connectProjectM36 :: ConnectionInfo -> IO (Either ConnectionError Connection)
- close :: Connection -> IO ()
- closeRemote_ :: Connection -> IO ()
- executeRelationalExpr :: SessionId -> Connection -> RelationalExpr -> IO (Either RelationalError Relation)
- executeDatabaseContextExpr :: SessionId -> Connection -> DatabaseContextExpr -> IO (Either RelationalError ())
- executeDatabaseContextIOExpr :: SessionId -> Connection -> DatabaseContextIOExpr -> IO (Either RelationalError ())
- executeGraphExpr :: SessionId -> Connection -> TransactionGraphOperator -> IO (Either RelationalError ())
- executeSchemaExpr :: SessionId -> Connection -> SchemaExpr -> IO (Either RelationalError ())
- executeTransGraphRelationalExpr :: SessionId -> Connection -> TransGraphRelationalExpr -> IO (Either RelationalError Relation)
- commit :: SessionId -> Connection -> IO (Either RelationalError ())
- rollback :: SessionId -> Connection -> IO (Either RelationalError ())
- typeForRelationalExpr :: SessionId -> Connection -> RelationalExpr -> IO (Either RelationalError Relation)
- inclusionDependencies :: SessionId -> Connection -> IO (Either RelationalError InclusionDependencies)
- typeConstructorMapping :: SessionId -> Connection -> IO (Either RelationalError TypeConstructorMapping)
- planForDatabaseContextExpr :: SessionId -> Connection -> DatabaseContextExpr -> IO (Either RelationalError DatabaseContextExpr)
- currentSchemaName :: SessionId -> Connection -> IO (Either RelationalError SchemaName)
- type SchemaName = StringType
- type HeadName = StringType
- setCurrentSchemaName :: SessionId -> Connection -> SchemaName -> IO (Either RelationalError ())
- transactionGraphAsRelation :: SessionId -> Connection -> IO (Either RelationalError Relation)
- relationVariablesAsRelation :: SessionId -> Connection -> IO (Either RelationalError Relation)
- disconnectedTransactionIsDirty :: SessionId -> Connection -> IO (Either RelationalError Bool)
- headName :: SessionId -> Connection -> IO (Either RelationalError HeadName)
- remoteDBLookupName :: DatabaseName -> String
- defaultServerPort :: Port
- headTransactionId :: SessionId -> Connection -> IO (Either RelationalError TransactionId)
- defaultDatabaseName :: DatabaseName
- defaultRemoteConnectionInfo :: ConnectionInfo
- defaultHeadName :: HeadName
- data PersistenceStrategy
- type RelationalExpr = RelationalExprBase ()
- 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)
- 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 DatabaseContextIOExpr
- data Attribute = Attribute AttributeName AtomType
- data MergeStrategy
- attributesFromList :: [Attribute] -> Attributes
- createNodeId :: Hostname -> Port -> NodeId
- createSessionAtCommit :: Connection -> TransactionId -> IO (Either RelationalError SessionId)
- createSessionAtHead :: Connection -> HeadName -> IO (Either RelationalError SessionId)
- closeSession :: SessionId -> Connection -> IO ()
- addClientNode :: Connection -> ProcessId -> IO ()
- callTestTimeout_ :: SessionId -> Connection -> IO Bool
- data RelationCardinality
- data TransactionGraphOperator
- autoMergeToHead :: SessionId -> Connection -> MergeStrategy -> HeadName -> IO (Either RelationalError ())
- transactionGraph_ :: Connection -> IO TransactionGraph
- disconnectedTransaction_ :: SessionId -> Connection -> IO DisconnectedTransaction
- type TransGraphRelationalExpr = RelationalExprBase TransactionIdLookup
- data TransactionIdLookup
- data TransactionIdHeadBacktrack
- newtype NodeId :: * = NodeId {}
- data Atom
- data Session
- type SessionId = UUID
- type NotificationCallback = NotificationName -> EvaluatedNotification -> IO ()
- emptyNotificationCallback :: NotificationCallback
- data EvaluatedNotification = EvaluatedNotification {}
- atomTypesAsRelation :: SessionId -> Connection -> IO (Either RelationalError Relation)
- type AttributeExpr = AttributeExprBase ()
- inclusionDependencyForKey :: AttributeNames -> RelationalExpr -> InclusionDependency
- databaseContextExprForUniqueKey :: RelVarName -> [AttributeName] -> DatabaseContextExpr
- databaseContextExprForForeignKey :: IncDepName -> (RelVarName, [AttributeName]) -> (RelVarName, [AttributeName]) -> DatabaseContextExpr
- createScriptedAtomFunction :: AtomFunctionName -> [TypeConstructor] -> TypeConstructor -> AtomFunctionBodyScript -> DatabaseContextIOExpr
- data AttributeExprBase a
- data TypeConstructor
- data TypeConstructorDef
- data DataConstructorDef = DataConstructorDef DataConstructorName [DataConstructorDefArg]
- data AttributeNames
- type RelVarName = StringType
- type IncDepName = StringType
- data InclusionDependency = InclusionDependency RelationalExpr RelationalExpr
- type AttributeName = StringType
- 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 RequestTimeoutException = RequestTimeoutException
- data RemoteProcessDiedException = RemoteProcessDiedException
- data AtomType
- class (Eq a, NFData a, Binary a, Show a) => Atomable a where
- newtype TupleExprBase a = TupleExpr (Map AttributeName (AtomExprBase a))
- data AtomExprBase a
- data RestrictionPredicateExprBase a
- = TruePredicate
- | AndPredicate (RestrictionPredicateExprBase a) (RestrictionPredicateExprBase a)
- | OrPredicate (RestrictionPredicateExprBase a) (RestrictionPredicateExprBase a)
- | NotPredicate (RestrictionPredicateExprBase a)
- | RelationalExprPredicate (RelationalExprBase a)
- | AtomExprPredicate (AtomExprBase a)
- | AttributeEqualityPredicate AttributeName (AtomExprBase a)
- withTransaction :: SessionId -> Connection -> IO (Either RelationalError a) -> IO (Either RelationalError ()) -> IO (Either RelationalError a)
Documentation
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 Connection Source #
InProcessConnection InProcessConnectionConf | |
RemoteProcessConnection RemoteProcessConnectionConf |
type DatabaseName = String Source #
data ConnectionError Source #
There are several reasons why a connection can fail.
connectProjectM36 :: ConnectionInfo -> IO (Either ConnectionError Connection) Source #
To create a Connection
to a remote or local database, create a ConnectionInfo
and call connectProjectM36
.
close :: Connection -> IO () Source #
close
cleans up the database access connection and closes any relevant sockets.
closeRemote_ :: Connection -> IO () Source #
executeRelationalExpr :: SessionId -> Connection -> RelationalExpr -> IO (Either RelationalError Relation) Source #
Execute a relational expression in the context of the session and connection. Relational expressions are queries and therefore cannot alter the database.
executeDatabaseContextExpr :: SessionId -> Connection -> DatabaseContextExpr -> IO (Either RelationalError ()) Source #
Execute a database context expression in the context of the session and connection. Database expressions modify the current session's disconnected transaction but cannot modify the transaction graph.
executeDatabaseContextIOExpr :: SessionId -> Connection -> DatabaseContextIOExpr -> IO (Either RelationalError ()) Source #
Execute a database context IO-monad-based expression for the given session and connection. DatabaseContextIOExpr
s modify the DatabaseContext but cannot be purely implemented.
this is almost completely identical to executeDatabaseContextExpr above
executeGraphExpr :: SessionId -> Connection -> TransactionGraphOperator -> IO (Either RelationalError ()) Source #
Execute a transaction graph expression in the context of the session and connection. Transaction graph operators modify the transaction graph state.
executeSchemaExpr :: SessionId -> Connection -> SchemaExpr -> IO (Either RelationalError ()) Source #
Schema expressions manipulate the isomorphic schemas for the current DatabaseContext
.
executeTransGraphRelationalExpr :: SessionId -> Connection -> TransGraphRelationalExpr -> IO (Either RelationalError Relation) Source #
A trans-graph expression is a relational query executed against the entirety of a transaction graph.
commit :: SessionId -> Connection -> IO (Either RelationalError ()) Source #
After modifying a DatabaseContext
, commit
the transaction to the transaction graph at the head which the session is referencing. This will also trigger checks for any notifications which need to be propagated.
rollback :: SessionId -> Connection -> IO (Either RelationalError ()) Source #
Discard any changes made in the current Session
and DatabaseContext
. This resets the disconnected transaction to reference the original database context of the parent transaction and is a very cheap operation.
typeForRelationalExpr :: SessionId -> Connection -> RelationalExpr -> IO (Either RelationalError Relation) Source #
Return a relation whose type would match that of the relational expression if it were executed. This is useful for checking types and validating a relational expression's types.
inclusionDependencies :: SessionId -> Connection -> IO (Either RelationalError InclusionDependencies) Source #
Return a Map
of the database's constraints at the context of the session and connection.
typeConstructorMapping :: SessionId -> Connection -> IO (Either RelationalError TypeConstructorMapping) Source #
planForDatabaseContextExpr :: SessionId -> Connection -> DatabaseContextExpr -> IO (Either RelationalError DatabaseContextExpr) Source #
Return an optimized database expression which is logically equivalent to the input database expression. This function can be used to determine which expression will actually be evaluated.
currentSchemaName :: SessionId -> Connection -> IO (Either RelationalError SchemaName) Source #
Returns the name of the currently selected isomorphic schema.
type SchemaName = StringType Source #
type HeadName = StringType Source #
A transaction graph's head name references the leaves of the transaction graph and can be used during session creation to indicate at which point in the graph commits should persist.
setCurrentSchemaName :: SessionId -> Connection -> SchemaName -> IO (Either RelationalError ()) Source #
Switch to the named isomorphic schema.
transactionGraphAsRelation :: SessionId -> Connection -> IO (Either RelationalError Relation) Source #
Return a relation which represents the current state of the global transaction graph. The attributes are
* current- boolean attribute representing whether or not the current session references this transaction
* head- text attribute which is a non-empty HeadName
iff the transaction references a head.
* id- id attribute of the transaction
* parents- a relation-valued attribute which contains a relation of transaction ids which are parent transaction to the transaction
relationVariablesAsRelation :: SessionId -> Connection -> IO (Either RelationalError Relation) Source #
Returns the names and types of the relation variables in the current Session
.
disconnectedTransactionIsDirty :: SessionId -> Connection -> IO (Either RelationalError Bool) Source #
headName :: SessionId -> Connection -> IO (Either RelationalError HeadName) Source #
Returns Just the name of the head of the current disconnected transaction or Nothing.
defaultServerPort :: Port Source #
Use this for connecting to remote servers on the default port.
headTransactionId :: SessionId -> Connection -> IO (Either RelationalError TransactionId) Source #
Returns the transaction id for the connection's disconnected transaction committed parent transaction.
defaultDatabaseName :: DatabaseName Source #
Use this for connecting to remote servers with the default database name.
defaultRemoteConnectionInfo :: ConnectionInfo Source #
Create a connection configuration which connects to the localhost on the default server port and default server database name. The configured notification callback is set to ignore all events.
defaultHeadName :: HeadName Source #
Use this for connecting to remote servers with the default head name.
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 RelationalExpr = RelationalExprBase () Source #
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 # | |
data DatabaseContextExpr Source #
Database context expressions modify the database context.
data DatabaseContextIOExpr Source #
Adding an atom function should be nominally a DatabaseExpr except for the fact that it cannot be performed purely. Thus, we create the DatabaseContextIOExpr.
A relation's type is composed of attribute names and types.
data MergeStrategy Source #
UnionMergeStrategy | After a union merge, the merge transaction is a result of union'ing relvars of the same name, introducing all uniquely-named relvars, union of constraints, union of atom functions, notifications, and types (unless the names and definitions collide, e.g. two types of the same name with different definitions) |
UnionPreferMergeStrategy HeadName | Similar to a union merge, but, on conflict, prefer the unmerged section (relvar, function, etc.) from the branch named as the argument. |
SelectedBranchMergeStrategy HeadName | Similar to the our/theirs merge strategy in git, the merge transaction's context is identical to that of the last transaction in the selected branch. |
attributesFromList :: [Attribute] -> Attributes Source #
createNodeId :: Hostname -> Port -> NodeId Source #
Create a NodeId
for use in connecting to a remote server using distributed-process.
createSessionAtCommit :: Connection -> TransactionId -> IO (Either RelationalError SessionId) Source #
Create a new session at the transaction id and return the session's Id.
createSessionAtHead :: Connection -> HeadName -> IO (Either RelationalError SessionId) Source #
Call createSessionAtHead
with a transaction graph's head's name to create a new session pinned to that head. This function returns a SessionId
which can be used in other function calls to reference the point in the transaction graph.
closeSession :: SessionId -> Connection -> IO () Source #
Discards a session, eliminating any uncommitted changes present in the session.
addClientNode :: Connection -> ProcessId -> IO () Source #
Used internally for server connections to keep track of remote nodes for the purpose of sending notifications later.
callTestTimeout_ :: SessionId -> Connection -> IO Bool Source #
data RelationCardinality Source #
Used to represent the number of tuples in a relation.
data TransactionGraphOperator Source #
Operators which manipulate a transaction graph and which transaction the current Session
is based upon.
autoMergeToHead :: SessionId -> Connection -> MergeStrategy -> HeadName -> IO (Either RelationalError ()) Source #
Similar to a git rebase, autoMergeToHead
atomically creates a temporary branch and merges it to the latest commit of the branch referred to by the HeadName
and commits the merge. This is useful to reduce incidents of TransactionIsNotAHeadError
s but at the risk of merge errors (thus making it similar to rebasing).
type TransGraphRelationalExpr = RelationalExprBase TransactionIdLookup Source #
The TransGraphRelationalExpression is equivalent to a relational expression except that relation variables can reference points in the transaction graph (at previous points in time).
data TransactionIdLookup Source #
Record a lookup for a specific transaction in the graph.
data TransactionIdHeadBacktrack Source #
Used for git-style head backtracking such as topic~3^2.
TransactionIdHeadParentBacktrack Int | git equivalent of ~: walk back n parents, arbitrarily choosing a parent when a choice must be made |
TransactionIdHeadBranchBacktrack Int | git equivalent of ^: walk back one parent level to the nth arbitrarily-chosen parent |
TransactionStampHeadBacktrack UTCTime | git equivalent of 'git-rev-list -n 1 --before X' find the first transaction which was created before the timestamp |
Node identifier
Database atoms are the smallest, undecomposable units of a tuple. Common examples are integers, text, or unique identity keys.
Represents a pointer into the database's transaction graph which the DatabaseContextExpr
s can then modify subsequently be committed to extend the transaction graph. The session contains staged (uncommitted) database changes as well as the means to switch between isomorphic schemas.
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 EvaluatedNotification Source #
When a notification is fired, the reportOldExpr
is evaluated in the commit's pre-change context while the reportNewExpr
is evaluated in the post-change context and they are returned along with the original notification.
atomTypesAsRelation :: SessionId -> Connection -> IO (Either RelationalError Relation) Source #
Returns a listing of all available atom types.
type AttributeExpr = AttributeExprBase () Source #
inclusionDependencyForKey :: AttributeNames -> RelationalExpr -> InclusionDependency Source #
Create a uniqueness constraint for the attribute names and relational expression. Note that constraint can span multiple relation variables.
databaseContextExprForUniqueKey :: RelVarName -> [AttributeName] -> DatabaseContextExpr Source #
Create a DatabaseContextExpr
which can be used to add a uniqueness constraint to attributes on one relation variable.
databaseContextExprForForeignKey :: IncDepName -> (RelVarName, [AttributeName]) -> (RelVarName, [AttributeName]) -> DatabaseContextExpr Source #
Create a foreign key constraint from the first relation variable and attributes to the second.
createScriptedAtomFunction :: AtomFunctionName -> [TypeConstructor] -> TypeConstructor -> AtomFunctionBodyScript -> DatabaseContextIOExpr Source #
Create a DatabaseContextIOExpr
which can be used to load a new atom function written in Haskell and loaded at runtime.
data AttributeExprBase a Source #
Create attributes dynamically.
Eq a => Eq (AttributeExprBase a) Source # | |
Show a => Show (AttributeExprBase a) Source # | |
Generic (AttributeExprBase a) Source # | |
Binary a => Binary (AttributeExprBase a) Source # | |
NFData a => NFData (AttributeExprBase a) Source # | |
type Rep (AttributeExprBase a) Source # | |
data TypeConstructor Source #
Found in data constructors and type declarations: Left (Either Int Text) | Right Int
data TypeConstructorDef Source #
Metadata definition for type constructors such as data Either a b
.
data DataConstructorDef Source #
Used to define a data constructor in a type constructor context such as Left a | Right b
data AttributeNames Source #
The AttributeNames
structure represents a set of attribute names or the same set of names but inverted in the context of a relational expression. For example, if a relational expression has attributes named "a", "b", and "c", the InvertedAttributeNames
of ("a","c") is ("b").
type RelVarName = StringType Source #
Relation variables are identified by their names.
type IncDepName = StringType Source #
data InclusionDependency Source #
Inclusion dependencies represent every possible database constraint. Constraints enforce specific, arbitrarily-complex rules to which the database context's relation variables must adhere unconditionally.
type AttributeName = StringType Source #
The AttributeName is the name of an attribute in a relation.
data RelationalError Source #
The AtomType uniquely identifies the type of a atom.
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 #
toAtomType :: proxy a -> AtomType Source #
toAtomType :: (Generic a, AtomableG (Rep a)) => proxy a -> AtomType Source #
toAddTypeExpr :: Proxy a -> DatabaseContextExpr Source #
Creates DatabaseContextExpr necessary to load the type constructor and data constructor into the database.
toAddTypeExpr :: (Generic a, AtomableG (Rep a)) => proxy a -> DatabaseContextExpr Source #
Creates DatabaseContextExpr necessary to load the type constructor and data constructor into the database.
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 # | |
newtype TupleExprBase a Source #
Dynamically create a tuple from attribute names and AtomExpr
s.
data AtomExprBase a Source #
An atom expression represents an action to take when extending a relation or when statically defining a relation or a new tuple.
data RestrictionPredicateExprBase a Source #
Restriction predicates are boolean algebra components which, when composed, indicate whether or not a tuple should be retained during a restriction (filtering) operation.
Binary RestrictionPredicateExpr Source # | |
Eq a => Eq (RestrictionPredicateExprBase a) Source # | |
Show a => Show (RestrictionPredicateExprBase a) Source # | |
Generic (RestrictionPredicateExprBase a) Source # | |
NFData a => NFData (RestrictionPredicateExprBase a) Source # | |
type Rep (RestrictionPredicateExprBase a) Source # | |
withTransaction :: SessionId -> Connection -> IO (Either RelationalError a) -> IO (Either RelationalError ()) -> IO (Either RelationalError a) Source #
Runs an IO monad, commits the result when the monad returns no errors, otherwise, rolls back the changes and the error.