Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
ProjectM36.Client
Description
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
.
Synopsis
- data ConnectionInfo
- data Connection
- = InProcessConnection InProcessConnectionConf
- | RemoteConnection RemoteConnectionConf
- type Port = Word16
- type Hostname = String
- type ServiceName = 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 ())
- executeDataFrameExpr :: SessionId -> Connection -> DataFrameExpr -> IO (Either RelationalError DataFrame)
- 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)
- databaseContextFunctionsAsRelation :: SessionId -> Connection -> IO (Either RelationalError Relation)
- planForDatabaseContextExpr :: SessionId -> Connection -> DatabaseContextExpr -> IO (Either RelationalError GraphRefDatabaseContextExpr)
- 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)
- registeredQueriesAsRelation :: SessionId -> Connection -> IO (Either RelationalError Relation)
- notificationsAsRelation :: SessionId -> Connection -> IO (Either RelationalError Relation)
- ddlAsRelation :: SessionId -> Connection -> IO (Either RelationalError Relation)
- atomFunctionsAsRelation :: 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
- addClientNode :: Connection -> Locking Socket -> IO ()
- getDDLHash :: SessionId -> Connection -> IO (Either RelationalError SecureHash)
- convertSQLQuery :: SessionId -> Connection -> Query -> IO (Either RelationalError DataFrameExpr)
- convertSQLDBUpdates :: SessionId -> Connection -> [DBUpdate] -> IO (Either RelationalError DatabaseContextExpr)
- data PersistenceStrategy
- type RelationalExpr = RelationalExprBase ()
- data RelationalExprBase a
- = MakeRelationFromExprs (Maybe [AttributeExprBase a]) (TupleExprsBase a)
- | MakeStaticRelation Attributes RelationTupleSet
- | ExistingRelation Relation
- | RelationVariable RelVarName a
- | RelationValuedAttribute AttributeName
- | Project (AttributeNamesBase a) (RelationalExprBase a)
- | Union (RelationalExprBase a) (RelationalExprBase a)
- | Join (RelationalExprBase a) (RelationalExprBase a)
- | Rename (Set (AttributeName, AttributeName)) (RelationalExprBase a)
- | Difference (RelationalExprBase a) (RelationalExprBase a)
- | Group (AttributeNamesBase a) 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)
- | With (WithNamesAssocsBase a) (RelationalExprBase a)
- data DatabaseContextExprBase a
- = NoOperation
- | Define RelVarName [AttributeExprBase a]
- | Undefine RelVarName
- | Assign RelVarName (RelationalExprBase a)
- | Insert RelVarName (RelationalExprBase a)
- | Delete RelVarName (RestrictionPredicateExprBase a)
- | Update RelVarName AttributeNameAtomExprMap (RestrictionPredicateExprBase a)
- | AddInclusionDependency IncDepName InclusionDependency
- | RemoveInclusionDependency IncDepName
- | AddNotification NotificationName RelationalExpr RelationalExpr RelationalExpr
- | RemoveNotification NotificationName
- | AddTypeConstructor TypeConstructorDef [DataConstructorDef]
- | RemoveTypeConstructor TypeConstructorName
- | RemoveAtomFunction FunctionName
- | RemoveDatabaseContextFunction FunctionName
- | ExecuteDatabaseContextFunction FunctionName [AtomExprBase a]
- | AddRegisteredQuery RegisteredQueryName RelationalExpr
- | RemoveRegisteredQuery RegisteredQueryName
- | MultipleExpr [DatabaseContextExprBase a]
- type DatabaseContextExpr = DatabaseContextExprBase ()
- data DatabaseContextIOExprBase a
- = AddAtomFunction FunctionName [TypeConstructor] FunctionBodyScript
- | LoadAtomFunctions ObjModuleName ObjFunctionName FilePath
- | AddDatabaseContextFunction FunctionName [TypeConstructor] FunctionBodyScript
- | LoadDatabaseContextFunctions ObjModuleName ObjFunctionName FilePath
- | CreateArbitraryRelation RelVarName [AttributeExprBase a] Range
- type DatabaseContextIOExpr = DatabaseContextIOExprBase ()
- data Attribute = Attribute AttributeName AtomType
- data MergeStrategy
- attributesFromList :: [Attribute] -> Attributes
- createSessionAtCommit :: Connection -> TransactionId -> IO (Either RelationalError SessionId)
- createSessionAtHead :: Connection -> HeadName -> IO (Either RelationalError SessionId)
- closeSession :: SessionId -> Connection -> 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
- data Atom
- = IntegerAtom !Integer
- | IntAtom !Int
- | ScientificAtom !Scientific
- | DoubleAtom !Double
- | TextAtom !Text
- | DayAtom !Day
- | DateTimeAtom !UTCTime
- | ByteStringAtom !ByteString
- | BoolAtom !Bool
- | UUIDAtom !UUID
- | RelationAtom !Relation
- | RelationalExprAtom !RelationalExpr
- | SubrelationFoldAtom !Relation !AttributeName
- | ConstructedAtom !DataConstructorName !AtomType [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 :: FunctionName -> [TypeConstructor] -> TypeConstructor -> FunctionBodyScript -> DatabaseContextIOExpr
- validateMerkleHashes :: SessionId -> Connection -> IO (Either RelationalError ())
- data AttributeExprBase a
- data TypeConstructorBase a
- data TypeConstructorDef
- data DataConstructorDef = DataConstructorDef DataConstructorName [DataConstructorDefArg]
- data AttributeNamesBase a
- type RelVarName = StringType
- type IncDepName = StringType
- data InclusionDependency = InclusionDependency RelationalExpr RelationalExpr
- type AttributeName = StringType
- data DataFrame
- data DataFrameExpr
- data AttributeOrderExpr
- data Order
- data RelationalError
- = NoSuchAttributeNamesError (Set AttributeName)
- | TupleAttributeCountMismatchError Int
- | EmptyAttributesError
- | DuplicateAttributeNamesError (Set AttributeName)
- | TupleAttributeTypeMismatchError Attributes
- | AttributeCountMismatchError Int
- | AttributeNamesMismatchError (Set AttributeName)
- | AttributeTypesMismatchError Attributes
- | AttributeNameInUseError AttributeName
- | AttributeIsNotRelationValuedError AttributeName
- | CouldNotInferAttributes
- | RelVarNotDefinedError RelVarName
- | RelVarAlreadyDefinedError RelVarName
- | RelationTypeMismatchError Attributes Attributes
- | InclusionDependencyCheckError IncDepName (Maybe RelationalError)
- | 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 FunctionName
- | 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 FunctionName TypeVarName
- | AtomFunctionTypeVariableMismatch TypeVarName AtomType AtomType
- | IfThenExprExpectedBooleanError AtomType
- | AtomTypeNameInUseError AtomTypeName
- | IncompletelyDefinedAtomTypeWithConstructorError
- | AtomTypeNameNotInUseError AtomTypeName
- | AttributeNotSortableError Attribute
- | FunctionNameInUseError FunctionName
- | FunctionNameNotInUseError FunctionName
- | EmptyCommitError
- | FunctionArgumentCountMismatchError Int Int
- | ConstructedAtomArgumentCountMismatchError Int Int
- | NoSuchDataConstructorError DataConstructorName
- | NoSuchTypeConstructorError TypeConstructorName
- | InvalidAtomTypeName AtomTypeName
- | AtomTypeNotSupported AttributeName
- | AtomOperatorNotSupported Text
- | EmptyTuplesError
- | AtomTypeCountError [AtomType] [AtomType]
- | AtomFunctionTypeError FunctionName Int AtomType AtomType
- | AtomFunctionUserError AtomFunctionError
- | PrecompiledFunctionRemoveError FunctionName
- | RelationValuedAttributesNotSupportedError [AttributeName]
- | NotificationNameInUseError NotificationName
- | NotificationNameNotInUseError NotificationName
- | NotificationValidationError NotificationName NotificationExpression RelationalError
- | ImportError ImportError'
- | ExportError Text
- | UnhandledExceptionError String
- | MergeTransactionError MergeError
- | ScriptError ScriptCompilationError
- | LoadFunctionError
- | SecurityLoadFunctionError
- | DatabaseContextFunctionUserError DatabaseContextFunctionError
- | DatabaseLoadError PersistenceError
- | SubschemaNameInUseError SchemaName
- | SubschemaNameNotInUseError SchemaName
- | SchemaCreationError SchemaError
- | ImproperDatabaseStateError
- | NonConcreteSchemaPlanError
- | NoUncommittedContextInEvalError
- | TupleExprsReferenceMultipleMarkersError
- | MerkleHashValidationError TransactionId MerkleHash MerkleHash
- | RegisteredQueryValidationError RegisteredQueryName RelationalError
- | RegisteredQueryNameInUseError RegisteredQueryName
- | RegisteredQueryNameNotInUseError RegisteredQueryName
- | SQLConversionError SQLError
- | MultipleErrors [RelationalError]
- data RequestTimeoutException = RequestTimeoutException
- data RemoteProcessDiedException = RemoteProcessDiedException
- data AtomType
- = IntAtomType
- | IntegerAtomType
- | ScientificAtomType
- | DoubleAtomType
- | TextAtomType
- | DayAtomType
- | DateTimeAtomType
- | ByteStringAtomType
- | BoolAtomType
- | UUIDAtomType
- | RelationAtomType Attributes
- | SubrelationFoldAtomType AtomType
- | ConstructedAtomType TypeConstructorName TypeVarMap
- | RelationalExprAtomType
- | TypeVariableType TypeVarName
- class (Eq a, NFData a, Serialise a, Show a) => Atomable a where
- toAtom :: a -> Atom
- fromAtom :: Atom -> a
- toAtomType :: proxy a -> AtomType
- toAddTypeExpr :: proxy a -> DatabaseContextExpr
- newtype TupleExprBase a = TupleExpr (Map AttributeName (AtomExprBase a))
- data TupleExprsBase a = TupleExprs a [TupleExprBase a]
- data AtomExprBase a
- = AttributeAtomExpr AttributeName
- | SubrelationAttributeAtomExpr AttributeName AttributeName
- | NakedAtomExpr !Atom
- | FunctionAtomExpr !FunctionName [AtomExprBase a] a
- | RelationAtomExpr (RelationalExprBase a)
- | IfThenAtomExpr (AtomExprBase a) (AtomExprBase a) (AtomExprBase a)
- | ConstructedAtomExpr DataConstructorName [AtomExprBase a] 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)
- basicDatabaseContext :: DatabaseContext
- data RemoteServerAddress
- resolveRemoteServerAddress :: RemoteServerAddress -> IO (SockSpec, SockAddr)
- defaultRemoteServerAddress :: RemoteServerAddress
- defaultServerHostname :: Hostname
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 RPC.
data Connection Source #
Constructors
InProcessConnection InProcessConnectionConf | |
RemoteConnection RemoteConnectionConf |
type ServiceName = String Source #
Either a service name e.g., "http"
or a numeric port number.
type DatabaseName = String Source #
data ConnectionError Source #
There are several reasons why a connection can fail.
Constructors
SetupDatabaseDirectoryError PersistenceError | |
IOExceptionError IOException | |
NoSuchDatabaseByNameError DatabaseName | |
DatabaseValidationError [MerkleValidationError] | |
LoginError |
Instances
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
executeDataFrameExpr :: SessionId -> Connection -> DataFrameExpr -> IO (Either RelationalError DataFrame) Source #
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 #
databaseContextFunctionsAsRelation :: SessionId -> Connection -> IO (Either RelationalError Relation) Source #
planForDatabaseContextExpr :: SessionId -> Connection -> DatabaseContextExpr -> IO (Either RelationalError GraphRefDatabaseContextExpr) 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
.
registeredQueriesAsRelation :: SessionId -> Connection -> IO (Either RelationalError Relation) Source #
ddlAsRelation :: SessionId -> Connection -> IO (Either RelationalError Relation) Source #
Returns a relation representing the complete DDL of the current DatabaseContext
.
atomFunctionsAsRelation :: SessionId -> Connection -> IO (Either RelationalError Relation) Source #
Returns the names and types of the atom functions 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.
addClientNode :: Connection -> Locking Socket -> IO () Source #
getDDLHash :: SessionId -> Connection -> IO (Either RelationalError SecureHash) Source #
Calculate a hash on the DDL of the current database context (not the graph). This is useful for validating on the client that the database schema meets the client's expectation. Any DDL change will change this hash. This hash does not change based on the current isomorphic schema being examined. This function is not affected by the current schema (since they are all isomorphic anyway, they should return the same hash).
convertSQLQuery :: SessionId -> Connection -> Query -> IO (Either RelationalError DataFrameExpr) Source #
Convert a SQL Query expression into a DataFrameExpr. Because the conversion process requires substantial database metadata access (such as retrieving types for various subexpressions), we cannot process SQL client-side. However, the underlying DBMS is completely unaware that the resultant DataFrameExpr has come from SQL.
convertSQLDBUpdates :: SessionId -> Connection -> [DBUpdate] -> IO (Either RelationalError DatabaseContextExpr) Source #
data PersistenceStrategy Source #
The persistence strategy is a global database option which represents how to persist the database in the filesystem, if at all.
Constructors
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) |
Instances
Read PersistenceStrategy Source # | |
Defined in ProjectM36.Base | |
Show PersistenceStrategy Source # | |
Defined in ProjectM36.Base |
type RelationalExpr = RelationalExprBase () Source #
data RelationalExprBase a Source #
A relational expression represents query (read) operations on a database.
Constructors
MakeRelationFromExprs (Maybe [AttributeExprBase a]) (TupleExprsBase a) | |
MakeStaticRelation Attributes RelationTupleSet | |
ExistingRelation Relation | |
RelationVariable RelVarName a | |
RelationValuedAttribute AttributeName | Extract a relation from an |
Project (AttributeNamesBase a) (RelationalExprBase a) | |
Union (RelationalExprBase a) (RelationalExprBase a) | |
Join (RelationalExprBase a) (RelationalExprBase a) | |
Rename (Set (AttributeName, AttributeName)) (RelationalExprBase a) | |
Difference (RelationalExprBase a) (RelationalExprBase a) | |
Group (AttributeNamesBase a) 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) | |
With (WithNamesAssocsBase a) (RelationalExprBase a) |
Instances
data DatabaseContextExprBase a Source #
Database context expressions modify the database context.
Constructors
Instances
type DatabaseContextExpr = DatabaseContextExprBase () Source #
data DatabaseContextIOExprBase a 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.
Constructors
Instances
A relation's type is composed of attribute names and types.
Constructors
Attribute AttributeName AtomType |
Instances
Generic Attribute Source # | |
Read Attribute Source # | |
Show Attribute Source # | |
NFData Attribute Source # | |
Defined in ProjectM36.Base | |
Eq Attribute Source # | |
Hashable Attribute Source # | |
HashBytes Attribute Source # | |
Serialise Attribute Source # | |
type Rep Attribute Source # | |
Defined in ProjectM36.Base type Rep Attribute = D1 ('MetaData "Attribute" "ProjectM36.Base" "project-m36-1.1.1-inplace" 'False) (C1 ('MetaCons "Attribute" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 AttributeName) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 AtomType))) |
data MergeStrategy Source #
Constructors
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. |
Instances
attributesFromList :: [Attribute] -> Attributes Source #
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.
callTestTimeout_ :: SessionId -> Connection -> IO Bool Source #
data RelationCardinality Source #
Used to represent the number of tuples in a relation.
Instances
data TransactionGraphOperator Source #
Operators which manipulate a transaction graph and which transaction the current Session
is based upon.
Constructors
JumpToHead HeadName | |
JumpToTransaction TransactionId | |
WalkBackToTime UTCTime | |
Branch HeadName | |
DeleteBranch HeadName | |
MergeTransactions MergeStrategy HeadName HeadName | |
Commit | |
Rollback |
Instances
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). Alternatively, as an optimization, if a simple commit is possible (meaning that the head has not changed), then a fast-forward commit takes place instead.
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.
Constructors
TransactionIdLookup TransactionId | |
TransactionIdHeadNameLookup HeadName [TransactionIdHeadBacktrack] |
Instances
data TransactionIdHeadBacktrack Source #
Used for git-style head backtracking such as topic~3^2.
Constructors
TransactionIdHeadParentBacktrack Int | git equivalent of ~v: 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 |
Instances
Database atoms are the smallest, undecomposable units of a tuple. Common examples are integers, text, or unique identity keys.
Constructors
Instances
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.
Constructors
EvaluatedNotification | |
Instances
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 :: FunctionName -> [TypeConstructor] -> TypeConstructor -> FunctionBodyScript -> DatabaseContextIOExpr Source #
Create a DatabaseContextIOExpr
which can be used to load a new atom function written in Haskell and loaded at runtime.
validateMerkleHashes :: SessionId -> Connection -> IO (Either RelationalError ()) Source #
data AttributeExprBase a Source #
Create attributes dynamically.
Instances
data TypeConstructorBase a Source #
Constructors
ADTypeConstructor TypeConstructorName [TypeConstructor] | |
PrimitiveTypeConstructor TypeConstructorName AtomType | |
RelationAtomTypeConstructor [AttributeExprBase a] | |
TypeVariable TypeVarName |
Instances
data TypeConstructorDef Source #
Metadata definition for type constructors such as data Either a b
.
Constructors
ADTypeConstructorDef TypeConstructorName [TypeVarName] | |
PrimitiveTypeConstructorDef TypeConstructorName AtomType |
Instances
data DataConstructorDef Source #
Used to define a data constructor in a type constructor context such as Left a | Right b
Constructors
DataConstructorDef DataConstructorName [DataConstructorDefArg] |
Instances
data AttributeNamesBase a Source #
An AtomFunction has a name, a type, and a function body to execute when called.
The AttributeNamesBase
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").
Constructors
Instances
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.
Constructors
InclusionDependency RelationalExpr RelationalExpr |
Instances
type AttributeName = StringType Source #
The AttributeName is the name of an attribute in a relation.
Instances
Generic DataFrame Source # | |
Show DataFrame Source # | |
Eq DataFrame Source # | |
Serialise DataFrame Source # | |
type Rep DataFrame Source # | |
Defined in ProjectM36.DataFrame type Rep DataFrame = D1 ('MetaData "DataFrame" "ProjectM36.DataFrame" "project-m36-1.1.1-inplace" 'False) (C1 ('MetaCons "DataFrame" 'PrefixI 'True) (S1 ('MetaSel ('Just "orders") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [AttributeOrder]) :*: (S1 ('MetaSel ('Just "attributes") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Attributes) :*: S1 ('MetaSel ('Just "tuples") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [DataFrameTuple])))) |
data DataFrameExpr Source #
A Relation can be converted to a DataFrame for sorting, limits, and offsets.
Instances
data AttributeOrderExpr Source #
Instances
Constructors
AscendingOrder | |
DescendingOrder |
data RelationalError Source #
Constructors
Instances
data RequestTimeoutException Source #
Constructors
RequestTimeoutException |
Instances
Exception RequestTimeoutException Source # | |
Defined in ProjectM36.Client | |
Show RequestTimeoutException Source # | |
Defined in ProjectM36.Client | |
Eq RequestTimeoutException Source # | |
Defined in ProjectM36.Client Methods (==) :: RequestTimeoutException -> RequestTimeoutException -> Bool Source # (/=) :: RequestTimeoutException -> RequestTimeoutException -> Bool Source # |
data RemoteProcessDiedException Source #
Constructors
RemoteProcessDiedException |
Instances
Exception RemoteProcessDiedException Source # | |
Defined in ProjectM36.Client | |
Show RemoteProcessDiedException Source # | |
Defined in ProjectM36.Client | |
Eq RemoteProcessDiedException Source # | |
Defined in ProjectM36.Client Methods (==) :: RemoteProcessDiedException -> RemoteProcessDiedException -> Bool Source # (/=) :: RemoteProcessDiedException -> RemoteProcessDiedException -> Bool Source # |
The AtomType uniquely identifies the type of a atom.
Constructors
Instances
class (Eq a, NFData a, Serialise 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.
Minimal complete definition
Nothing
Methods
fromAtom :: Atom -> a Source #
toAtomType :: proxy a -> AtomType Source #
toAddTypeExpr :: proxy a -> DatabaseContextExpr Source #
Creates DatabaseContextExpr necessary to load the type constructor and data constructor into the database.
default toAddTypeExpr :: (Generic a, AtomableG (Rep a)) => proxy a -> DatabaseContextExpr Source #
Instances
Atomable ByteString Source # | |
Defined in ProjectM36.Atomable Methods toAtom :: ByteString -> Atom Source # fromAtom :: Atom -> ByteString Source # toAtomType :: proxy ByteString -> AtomType Source # toAddTypeExpr :: proxy ByteString -> DatabaseContextExpr Source # | |
Atomable Text Source # | |
Atomable Day Source # | |
Atomable UTCTime Source # | |
Atomable UUID Source # | |
Atomable Integer Source # | |
Atomable Bool Source # | |
Atomable Double Source # | |
Atomable Int Source # | |
Atomable a => Atomable (NonEmpty a) Source # | |
Atomable a => Atomable (Maybe a) Source # | |
Atomable a => Atomable [a] Source # | |
Defined in ProjectM36.Atomable | |
(Atomable a, Atomable b) => Atomable (Either a b) Source # | |
newtype TupleExprBase a Source #
Dynamically create a tuple from attribute names and AtomExpr
s.
Constructors
TupleExpr (Map AttributeName (AtomExprBase a)) |
Instances
data TupleExprsBase a Source #
Constructors
TupleExprs a [TupleExprBase a] |
Instances
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.
Constructors
Instances
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.
Constructors
Instances
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.
data RemoteServerAddress Source #
Instances
Show RemoteServerAddress Source # | |
Defined in ProjectM36.Client |
resolveRemoteServerAddress :: RemoteServerAddress -> IO (SockSpec, SockAddr) Source #
Resolve a server address using DNS, if necessary. The caller is expected to set any necessary socket options afterwards.
defaultRemoteServerAddress :: RemoteServerAddress Source #
Use this for connecting to the default remote server.