Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Synopsis
- type StringType = Text
- type DatabaseName = String
- 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 AtomType
- = IntAtomType
- | IntegerAtomType
- | ScientificAtomType
- | DoubleAtomType
- | TextAtomType
- | DayAtomType
- | DateTimeAtomType
- | ByteStringAtomType
- | BoolAtomType
- | UUIDAtomType
- | RelationAtomType Attributes
- | SubrelationFoldAtomType AtomType
- | ConstructedAtomType TypeConstructorName TypeVarMap
- | RelationalExprAtomType
- | TypeVariableType TypeVarName
- type TypeVarMap = Map TypeVarName AtomType
- isRelationAtomType :: AtomType -> Bool
- attributesContainRelationAtomType :: Attributes -> Bool
- type AttributeName = StringType
- data Attribute = Attribute AttributeName AtomType
- type AttributesHash = Int
- newtype Attributes = Attributes {}
- attributesSet :: Attributes -> HashSet Attribute
- sortedAttributesIndices :: Attributes -> [(Int, Attribute)]
- newtype RelationTupleSet = RelationTupleSet {
- asList :: [RelationTuple]
- data RelationTuple = RelationTuple Attributes (Vector Atom)
- data Relation = Relation Attributes RelationTupleSet
- data RelationCardinality
- type RelVarName = StringType
- 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)
- type WithNamesAssocs = WithNamesAssocsBase ()
- type WithNamesAssocsBase a = [(WithNameExprBase a, RelationalExprBase a)]
- type GraphRefWithNameAssocs = [(GraphRefWithNameExpr, GraphRefRelationalExpr)]
- data WithNameExprBase a = WithNameExpr RelVarName a
- type WithNameExpr = WithNameExprBase ()
- type GraphRefWithNameExpr = WithNameExprBase GraphRefTransactionMarker
- type NotificationName = StringType
- type Notifications = Map NotificationName Notification
- data Notification = Notification {}
- type TypeVarName = StringType
- data TypeConstructorDef
- type TypeConstructor = TypeConstructorBase ()
- data TypeConstructorBase a
- type TypeConstructorMapping = [(TypeConstructorDef, DataConstructorDefs)]
- type TypeConstructorName = StringType
- type TypeConstructorArgName = StringType
- type DataConstructorName = StringType
- type AtomTypeName = StringType
- data DataConstructorDef = DataConstructorDef DataConstructorName [DataConstructorDefArg]
- type DataConstructorDefs = [DataConstructorDef]
- data DataConstructorDefArg
- type InclusionDependencies = Map IncDepName InclusionDependency
- type RelationVariables = Map RelVarName GraphRefRelationalExpr
- data GraphRefTransactionMarker
- type GraphRefRelationalExpr = RelationalExprBase GraphRefTransactionMarker
- type SchemaName = StringType
- type Subschemas = Map SchemaName Schema
- data Schemas = Schemas DatabaseContext Subschemas
- newtype Schema = Schema SchemaIsomorphs
- data SchemaIsomorph
- type SchemaIsomorphs = [SchemaIsomorph]
- type RegisteredQueryName = StringType
- type RegisteredQueries = Map RegisteredQueryName RelationalExpr
- data DatabaseContext = DatabaseContext {}
- type IncDepName = StringType
- data InclusionDependency = InclusionDependency RelationalExpr RelationalExpr
- type AttributeNameAtomExprMap = Map AttributeName AtomExpr
- type DatabaseContextExprName = StringType
- type DatabaseContextExpr = DatabaseContextExprBase ()
- type GraphRefDatabaseContextExpr = DatabaseContextExprBase GraphRefTransactionMarker
- 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 ObjModuleName = StringType
- type ObjFunctionName = StringType
- type Range = (Int, Int)
- 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 GraphRefDatabaseContextIOExpr = DatabaseContextIOExprBase GraphRefTransactionMarker
- type DatabaseContextIOExpr = DatabaseContextIOExprBase ()
- type RestrictionPredicateExpr = RestrictionPredicateExprBase ()
- type GraphRefRestrictionPredicateExpr = RestrictionPredicateExprBase GraphRefTransactionMarker
- 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)
- type HeadName = StringType
- type TransactionHeads = Map HeadName Transaction
- data TransactionGraph = TransactionGraph TransactionHeads (Set Transaction)
- transactionHeadsForGraph :: TransactionGraph -> TransactionHeads
- transactionsForGraph :: TransactionGraph -> Set Transaction
- transactionIdsForGraph :: TransactionGraph -> Set TransactionId
- data TransactionInfo = TransactionInfo {}
- type TransactionParents = NonEmpty TransactionId
- type TransactionId = UUID
- data Transaction = Transaction TransactionId TransactionInfo Schemas
- data DisconnectedTransaction = DisconnectedTransaction TransactionId Schemas DirtyFlag
- type DirtyFlag = Bool
- type TransactionDiffExpr = DatabaseContextExpr
- transactionId :: Transaction -> TransactionId
- transactionInfo :: Transaction -> TransactionInfo
- type AtomExpr = AtomExprBase ()
- type GraphRefAtomExpr = AtomExprBase GraphRefTransactionMarker
- type AggAtomFuncExprInfo = (AttributeName, AttributeName)
- 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 ExtendTupleExprBase a = AttributeExtendTupleExpr AttributeName (AtomExprBase a)
- type ExtendTupleExpr = ExtendTupleExprBase ()
- type GraphRefExtendTupleExpr = ExtendTupleExprBase GraphRefTransactionMarker
- type AtomFunctions = HashSet AtomFunction
- type AtomFunctionBodyType = [Atom] -> Either AtomFunctionError Atom
- type ObjectFileEntryFunctionName = String
- type ObjectFilePath = FilePath
- type ObjectModuleName = String
- data AttributeNamesBase a
- type AttributeNames = AttributeNamesBase ()
- type GraphRefAttributeNames = AttributeNamesBase GraphRefTransactionMarker
- data PersistenceStrategy
- persistenceDirectory :: PersistenceStrategy -> Maybe FilePath
- type AttributeExpr = AttributeExprBase ()
- type GraphRefAttributeExpr = AttributeExprBase GraphRefTransactionMarker
- data AttributeExprBase a
- newtype TupleExprBase a = TupleExpr (Map AttributeName (AtomExprBase a))
- type TupleExpr = TupleExprBase ()
- type GraphRefTupleExpr = TupleExprBase GraphRefTransactionMarker
- data TupleExprsBase a = TupleExprs a [TupleExprBase a]
- type GraphRefTupleExprs = TupleExprsBase GraphRefTransactionMarker
- type TupleExprs = TupleExprsBase ()
- data MergeStrategy
- type DatabaseContextFunctionBodyType = [Atom] -> DatabaseContext -> Either DatabaseContextFunctionError DatabaseContext
- type DatabaseContextFunctions = HashSet DatabaseContextFunction
- type FunctionName = StringType
- type FunctionBodyScript = StringType
- data Function a = Function {
- funcName :: FunctionName
- funcType :: [AtomType]
- funcBody :: FunctionBody a
- data FunctionBody a
- type AtomFunction = Function AtomFunctionBodyType
- type AtomFunctionBody = FunctionBody AtomFunctionBodyType
- type DatabaseContextFunction = Function DatabaseContextFunctionBodyType
- type DatabaseContextFunctionBody = FunctionBody DatabaseContextFunctionBodyType
- attrTypeVars :: Attribute -> Set TypeVarName
- typeVars :: TypeConstructor -> Set TypeVarName
- attrExprTypeVars :: AttributeExprBase a -> Set TypeVarName
- atomTypeVars :: AtomType -> Set TypeVarName
- unimplemented :: HasCallStack => a
- data RelationalExprBaseF (a :: Type) r
- = MakeRelationFromExprsF (Maybe [AttributeExprBase a]) (TupleExprsBase a)
- | MakeStaticRelationF Attributes RelationTupleSet
- | ExistingRelationF Relation
- | RelationVariableF Text a
- | RelationValuedAttributeF Text
- | ProjectF (AttributeNamesBase a) r
- | UnionF r r
- | JoinF r r
- | RenameF (Set (Text, Text)) r
- | DifferenceF r r
- | GroupF (AttributeNamesBase a) Text r
- | UngroupF Text r
- | RestrictF (RestrictionPredicateExprBase a) r
- | EqualsF r r
- | NotEqualsF r r
- | ExtendF (ExtendTupleExprBase a) r
- | WithF [(WithNameExprBase a, r)] r
Documentation
type StringType = Text Source #
type DatabaseName = String Source #
Database atoms are the smallest, undecomposable units of a tuple. Common examples are integers, text, or unique identity keys.
Instances
The AtomType uniquely identifies the type of a atom.
Instances
type TypeVarMap = Map TypeVarName AtomType Source #
isRelationAtomType :: AtomType -> Bool Source #
Return True iff the atom type argument is relation-valued. If True, this indicates that the Atom contains a relation.
type AttributeName = StringType Source #
The AttributeName is the name of an attribute in a relation.
A relation's type is composed of attribute names and types.
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.0.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))) |
type AttributesHash = Int Source #
newtype Attributes Source #
Attributes
represent the head of a relation.
Instances
sortedAttributesIndices :: Attributes -> [(Int, Attribute)] Source #
newtype RelationTupleSet Source #
The relation's tuple set is the body of the relation.
Instances
data RelationTuple Source #
A tuple is a set of attributes mapped to their Atom
values.
Instances
Instances
Generic Relation Source # | |
Read Relation Source # | |
Show Relation Source # | |
NFData Relation Source # | |
Defined in ProjectM36.Base | |
Eq Relation Source # | |
Hashable Relation Source # | |
HashBytes Relation Source # | |
Serialise Relation Source # | A special instance of Serialise which cuts down on duplicate attributes- we should only serialise the attributes at the top-level and not duplicate them per tuple. |
HashBytes (Map RelVarName Relation) Source # | |
Defined in ProjectM36.HashSecurely | |
type Rep Relation Source # | |
Defined in ProjectM36.Base type Rep Relation = D1 ('MetaData "Relation" "ProjectM36.Base" "project-m36-1.0.1-inplace" 'False) (C1 ('MetaCons "Relation" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Attributes) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 RelationTupleSet))) |
data RelationCardinality Source #
Used to represent the number of tuples in a relation.
Instances
type RelVarName = StringType Source #
Relation variables are identified by their names.
type RelationalExpr = RelationalExprBase () Source #
data RelationalExprBase a Source #
A relational expression represents query (read) operations on a database.
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
type WithNamesAssocs = WithNamesAssocsBase () Source #
type WithNamesAssocsBase a = [(WithNameExprBase a, RelationalExprBase a)] Source #
data WithNameExprBase a Source #
Instances
type WithNameExpr = WithNameExprBase () Source #
type NotificationName = StringType Source #
data Notification Source #
When the changeExpr returns a different result in the database context, then the reportExpr is triggered and sent asynchronously to all clients.
Instances
type TypeVarName = StringType Source #
data TypeConstructorDef Source #
Metadata definition for type constructors such as data Either a b
.
ADTypeConstructorDef TypeConstructorName [TypeVarName] | |
PrimitiveTypeConstructorDef TypeConstructorName AtomType |
Instances
type TypeConstructor = TypeConstructorBase () Source #
Found in data constructors and type declarations: Left (Either Int Text) | Right Int
data TypeConstructorBase a Source #
ADTypeConstructor TypeConstructorName [TypeConstructor] | |
PrimitiveTypeConstructor TypeConstructorName AtomType | |
RelationAtomTypeConstructor [AttributeExprBase a] | |
TypeVariable TypeVarName |
Instances
type TypeConstructorName = StringType Source #
type TypeConstructorArgName = StringType Source #
type DataConstructorName = StringType Source #
type AtomTypeName = StringType Source #
data DataConstructorDef Source #
Used to define a data constructor in a type constructor context such as Left a | Right b
Instances
type DataConstructorDefs = [DataConstructorDef] Source #
data DataConstructorDefArg Source #
Instances
data GraphRefTransactionMarker Source #
Instances
type SchemaName = StringType Source #
type Subschemas = Map SchemaName Schema Source #
Every transaction has one concrete database context and any number of isomorphic subschemas.
Instances
Generic Schemas Source # | |
type Rep Schemas Source # | |
Defined in ProjectM36.Base type Rep Schemas = D1 ('MetaData "Schemas" "ProjectM36.Base" "project-m36-1.0.1-inplace" 'False) (C1 ('MetaCons "Schemas" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DatabaseContext) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Subschemas))) |
The DatabaseContext is a snapshot of a database's evolving state and contains everything a database client can change over time. I spent some time thinking about whether the VirtualDatabaseContext/Schema and DatabaseContext data constructors should be the same constructor, but that would allow relation variables to be created in a "virtual" context which would appear to defeat the isomorphisms of the contexts. It should be possible to switch to an alternative schema to view the same equivalent information without information loss. However, allowing all contexts to reference another context while maintaining its own relation variables, new types, etc. could be interesting from a security perspective. For example, if a user creates a new relvar in a virtual context, then does it necessarily appear in all linked contexts? After deliberation, I think the relvar should appear in *all* linked contexts to retain the isomorphic properties, even when the isomorphism is for a subset of the context. This hints that the IsoMorphs should allow for "fall-through"; that is, when a relvar is not defined in the virtual context (for morphing), then the lookup should fall through to the underlying context.
Instances
Generic Schema Source # | |
HashBytes Schema Source # | |
Serialise Schema Source # | |
type Rep Schema Source # | |
Defined in ProjectM36.Base type Rep Schema = D1 ('MetaData "Schema" "ProjectM36.Base" "project-m36-1.0.1-inplace" 'True) (C1 ('MetaCons "Schema" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SchemaIsomorphs))) |
data SchemaIsomorph Source #
IsoRestrict RelVarName RestrictionPredicateExpr (RelVarName, RelVarName) | |
IsoRename RelVarName RelVarName | |
IsoUnion (RelVarName, RelVarName) RestrictionPredicateExpr RelVarName |
Instances
type SchemaIsomorphs = [SchemaIsomorph] Source #
type RegisteredQueryName = StringType Source #
data DatabaseContext Source #
Instances
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.
Instances
type DatabaseContextExprName = StringType Source #
type DatabaseContextExpr = DatabaseContextExprBase () Source #
data DatabaseContextExprBase a Source #
Database context expressions modify the database context.
Instances
type ObjModuleName = StringType Source #
type ObjFunctionName = StringType 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.
Instances
type GraphRefRestrictionPredicateExpr = RestrictionPredicateExprBase GraphRefTransactionMarker Source #
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.
Instances
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.
type TransactionHeads = Map HeadName Transaction Source #
data TransactionGraph Source #
The transaction graph is the global database's state which references every committed transaction.
Instances
Generic TransactionGraph Source # | |
Defined in ProjectM36.Base from :: TransactionGraph -> Rep TransactionGraph x Source # to :: Rep TransactionGraph x -> TransactionGraph Source # | |
type Rep TransactionGraph Source # | |
Defined in ProjectM36.Base type Rep TransactionGraph = D1 ('MetaData "TransactionGraph" "ProjectM36.Base" "project-m36-1.0.1-inplace" 'False) (C1 ('MetaCons "TransactionGraph" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 TransactionHeads) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Set Transaction)))) |
data TransactionInfo Source #
Every transaction has context-specific information attached to it.
The TransactionDiff
s represent child/edge relationships to previous transactions (branches or continuations of the same branch).
Instances
Generic TransactionInfo Source # | |
Defined in ProjectM36.Base from :: TransactionInfo -> Rep TransactionInfo x Source # to :: Rep TransactionInfo x -> TransactionInfo Source # | |
Show TransactionInfo Source # | |
Defined in ProjectM36.Base | |
Serialise TransactionInfo Source # | |
Defined in ProjectM36.Serialise.Base | |
type Rep TransactionInfo Source # | |
Defined in ProjectM36.Base type Rep TransactionInfo = D1 ('MetaData "TransactionInfo" "ProjectM36.Base" "project-m36-1.0.1-inplace" 'False) (C1 ('MetaCons "TransactionInfo" 'PrefixI 'True) (S1 ('MetaSel ('Just "parents") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 TransactionParents) :*: (S1 ('MetaSel ('Just "stamp") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 UTCTime) :*: S1 ('MetaSel ('Just "merkleHash") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 MerkleHash)))) |
type TransactionId = UUID Source #
Every set of modifications made to the database are atomically committed to the transaction graph as a transaction.
data Transaction Source #
Instances
data DisconnectedTransaction Source #
The disconnected transaction represents an in-progress workspace used by sessions before changes are committed. This is similar to git's "index". After a transaction is committed, it is "connected" in the transaction graph and can no longer be modified.
type AtomExpr = AtomExprBase () Source #
type AggAtomFuncExprInfo = (AttributeName, AttributeName) Source #
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.
Instances
data ExtendTupleExprBase a Source #
Used in tuple creation when creating a relation.
Instances
type ExtendTupleExpr = ExtendTupleExprBase () Source #
type AtomFunctions = HashSet AtomFunction Source #
type AtomFunctionBodyType = [Atom] -> Either AtomFunctionError Atom Source #
type ObjectFileEntryFunctionName = String Source #
type ObjectFilePath = FilePath Source #
type ObjectModuleName = String Source #
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").
Instances
type AttributeNames = AttributeNamesBase () 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.
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 AttributeExpr = AttributeExprBase () Source #
data AttributeExprBase a Source #
Create attributes dynamically.
Instances
newtype TupleExprBase a Source #
Dynamically create a tuple from attribute names and AtomExpr
s.
Instances
type TupleExpr = TupleExprBase () Source #
data TupleExprsBase a Source #
TupleExprs a [TupleExprBase a] |
Instances
type TupleExprs = TupleExprsBase () Source #
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. |
Instances
type DatabaseContextFunctionBodyType = [Atom] -> DatabaseContext -> Either DatabaseContextFunctionError DatabaseContext Source #
type FunctionName = StringType Source #
type FunctionBodyScript = StringType Source #
Represents stored, user-created or built-in functions which can operates of types such as Atoms or DatabaseContexts.
Function | |
|
Instances
HashBytes AtomFunction Source # | |
Defined in ProjectM36.HashSecurely | |
HashBytes AtomFunctions Source # | |
Defined in ProjectM36.HashSecurely | |
HashBytes DatabaseContextFunction Source # | |
Defined in ProjectM36.HashSecurely | |
HashBytes DatabaseContextFunctions Source # | |
Defined in ProjectM36.HashSecurely | |
Generic (Function a) Source # | |
NFData a => NFData (Function a) Source # | |
Defined in ProjectM36.Base | |
Eq (Function a) Source # | |
Hashable (Function a) Source # | |
type Rep (Function a) Source # | |
Defined in ProjectM36.Base type Rep (Function a) = D1 ('MetaData "Function" "ProjectM36.Base" "project-m36-1.0.1-inplace" 'False) (C1 ('MetaCons "Function" 'PrefixI 'True) (S1 ('MetaSel ('Just "funcName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 FunctionName) :*: (S1 ('MetaSel ('Just "funcType") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [AtomType]) :*: S1 ('MetaSel ('Just "funcBody") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (FunctionBody a))))) |
data FunctionBody a Source #
FunctionScriptBody FunctionBodyScript a | |
FunctionBuiltInBody a | |
FunctionObjectLoadedBody FilePath ObjectModuleName ObjectFileEntryFunctionName a |
Instances
attrTypeVars :: Attribute -> Set TypeVarName Source #
typeVars :: TypeConstructor -> Set TypeVarName Source #
atomTypeVars :: AtomType -> Set TypeVarName Source #
unimplemented :: HasCallStack => a Source #
data RelationalExprBaseF (a :: Type) r Source #
MakeRelationFromExprsF (Maybe [AttributeExprBase a]) (TupleExprsBase a) | |
MakeStaticRelationF Attributes RelationTupleSet | |
ExistingRelationF Relation | |
RelationVariableF Text a | |
RelationValuedAttributeF Text | |
ProjectF (AttributeNamesBase a) r | |
UnionF r r | |
JoinF r r | |
RenameF (Set (Text, Text)) r | |
DifferenceF r r | |
GroupF (AttributeNamesBase a) Text r | |
UngroupF Text r | |
RestrictF (RestrictionPredicateExprBase a) r | |
EqualsF r r | |
NotEqualsF r r | |
ExtendF (ExtendTupleExprBase a) r | |
WithF [(WithNameExprBase a, r)] r |