Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- type StringType = Text
- data Atom
- data AtomType
- type TypeVarMap = Map TypeVarName AtomType
- isRelationAtomType :: AtomType -> Bool
- type AttributeName = StringType
- data Attribute = Attribute AttributeName AtomType
- type Attributes = Vector Attribute
- attributesEqual :: Attributes -> Attributes -> Bool
- 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]) [TupleExprBase a]
- | MakeStaticRelation Attributes RelationTupleSet
- | ExistingRelation Relation
- | RelationVariable RelVarName a
- | Project (AttributeNamesBase a) (RelationalExprBase a)
- | Union (RelationalExprBase a) (RelationalExprBase a)
- | Join (RelationalExprBase a) (RelationalExprBase a)
- | Rename 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 [(RelVarName, RelationalExprBase a)] (RelationalExprBase a)
- 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 Relation
- type SchemaName = StringType
- type Subschemas = Map SchemaName Schema
- data Schemas = Schemas DatabaseContext Subschemas
- newtype Schema = Schema SchemaIsomorphs
- data SchemaIsomorph
- type SchemaIsomorphs = [SchemaIsomorph]
- data DatabaseContext = DatabaseContext {}
- type IncDepName = StringType
- data InclusionDependency = InclusionDependency RelationalExpr RelationalExpr
- type AttributeNameAtomExprMap = Map AttributeName AtomExpr
- type DatabaseContextExprName = StringType
- 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]
- type ObjModuleName = StringType
- type ObjFunctionName = StringType
- type Range = (Int, Int)
- data DatabaseContextIOExpr
- = AddAtomFunction AtomFunctionName [TypeConstructor] AtomFunctionBodyScript
- | LoadAtomFunctions ObjModuleName ObjFunctionName FilePath
- | AddDatabaseContextFunction DatabaseContextFunctionName [TypeConstructor] DatabaseContextFunctionBodyScript
- | LoadDatabaseContextFunctions ObjModuleName ObjFunctionName FilePath
- | CreateArbitraryRelation RelVarName [AttributeExpr] Range
- type RestrictionPredicateExpr = RestrictionPredicateExprBase ()
- 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)
- transactionsForGraph :: TransactionGraph -> Set Transaction
- transactionHeadsForGraph :: TransactionGraph -> TransactionHeads
- data TransactionInfo
- type TransactionId = UUID
- data Transaction = Transaction TransactionId TransactionInfo Schemas
- type DirtyFlag = Bool
- data DisconnectedTransaction = DisconnectedTransaction TransactionId Schemas DirtyFlag
- transactionId :: Transaction -> TransactionId
- transactionInfo :: Transaction -> TransactionInfo
- type AtomExpr = AtomExprBase ()
- data AtomExprBase a
- data ExtendTupleExprBase a = AttributeExtendTupleExpr AttributeName (AtomExprBase a)
- type ExtendTupleExpr = ExtendTupleExprBase ()
- type AtomFunctions = HashSet AtomFunction
- type AtomFunctionName = StringType
- type AtomFunctionBodyScript = StringType
- type AtomFunctionBodyType = [Atom] -> Either AtomFunctionError Atom
- data AtomFunctionBody = AtomFunctionBody (Maybe AtomFunctionBodyScript) AtomFunctionBodyType
- data AtomFunction = AtomFunction {}
- data AttributeNamesBase a
- type AttributeNames = AttributeNamesBase ()
- data PersistenceStrategy
- type AttributeExpr = AttributeExprBase ()
- data AttributeExprBase a
- newtype TupleExprBase a = TupleExpr (Map AttributeName (AtomExprBase a))
- type TupleExpr = TupleExprBase ()
- data MergeStrategy
- type DatabaseContextFunctionName = StringType
- type DatabaseContextFunctionBodyScript = StringType
- type DatabaseContextFunctionBodyType = [Atom] -> DatabaseContext -> Either DatabaseContextFunctionError DatabaseContext
- data DatabaseContextFunctionBody = DatabaseContextFunctionBody (Maybe DatabaseContextFunctionBodyScript) DatabaseContextFunctionBodyType
- data DatabaseContextFunction = DatabaseContextFunction {}
- type DatabaseContextFunctions = HashSet DatabaseContextFunction
- attrTypeVars :: Attribute -> Set TypeVarName
- typeVars :: TypeConstructor -> Set TypeVarName
- attrExprTypeVars :: AttributeExprBase a -> Set TypeVarName
- atomTypeVars :: AtomType -> Set TypeVarName
Documentation
type StringType = Text 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
Eq Attribute Source # | |
Show Attribute Source # | |
Generic Attribute Source # | |
Hashable Attribute Source # | |
Defined in ProjectM36.Base | |
Binary Attribute Source # | |
NFData Attribute Source # | |
Defined in ProjectM36.Base | |
type Rep Attribute Source # | |
Defined in ProjectM36.Base type Rep Attribute = D1 (MetaData "Attribute" "ProjectM36.Base" "project-m36-0.5.1-38P1EVgZYrJ9HDkvLyCm0" 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 Attributes = Vector Attribute Source #
Attributes
represent the head of a relation.
attributesEqual :: Attributes -> Attributes -> Bool Source #
Equality function for a set of attributes.
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
Eq Relation Source # | |
Read Relation Source # | |
Show Relation Source # | |
Generic Relation Source # | |
Hashable Relation Source # | |
Defined in ProjectM36.Base | |
Binary Relation Source # | |
NFData Relation Source # | |
Defined in ProjectM36.Base | |
type Rep Relation Source # | |
Defined in ProjectM36.Base type Rep Relation = D1 (MetaData "Relation" "ProjectM36.Base" "project-m36-0.5.1-38P1EVgZYrJ9HDkvLyCm0" 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.
Instances
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
type RelationVariables = Map RelVarName Relation Source #
type SchemaName = StringType Source #
type Subschemas = Map SchemaName Schema Source #
Every transaction has one concrete database context and any number of isomorphic 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 # | |
Binary Schema Source # | |
type Rep Schema Source # | |
Defined in ProjectM36.Base type Rep Schema = D1 (MetaData "Schema" "ProjectM36.Base" "project-m36-0.5.1-38P1EVgZYrJ9HDkvLyCm0" 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 #
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 #
data DatabaseContextExpr Source #
Database context expressions modify the database context.
Instances
type ObjModuleName = StringType Source #
type ObjFunctionName = StringType Source #
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.
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.
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.
data TransactionInfo Source #
Every transaction has context-specific information attached to it.
TransactionInfo TransactionId (Set TransactionId) UTCTime | |
MergeTransactionInfo TransactionId TransactionId (Set TransactionId) UTCTime |
Instances
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
Eq Transaction Source # | |
Defined in ProjectM36.Base (==) :: Transaction -> Transaction -> Bool # (/=) :: Transaction -> Transaction -> Bool # | |
Ord Transaction Source # | |
Defined in ProjectM36.Base compare :: Transaction -> Transaction -> Ordering # (<) :: Transaction -> Transaction -> Bool # (<=) :: Transaction -> Transaction -> Bool # (>) :: Transaction -> Transaction -> Bool # (>=) :: Transaction -> Transaction -> Bool # max :: Transaction -> Transaction -> Transaction # min :: Transaction -> Transaction -> Transaction # |
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 #
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 AtomFunctionName = StringType Source #
type AtomFunctionBodyScript = StringType Source #
type AtomFunctionBodyType = [Atom] -> Either AtomFunctionError Atom Source #
data AtomFunctionBody Source #
Instances
Show AtomFunctionBody Source # | |
Defined in ProjectM36.Base showsPrec :: Int -> AtomFunctionBody -> ShowS # show :: AtomFunctionBody -> String # showList :: [AtomFunctionBody] -> ShowS # | |
NFData AtomFunctionBody Source # | |
Defined in ProjectM36.Base rnf :: AtomFunctionBody -> () # |
data AtomFunction Source #
An AtomFunction has a name, a type, and a function body to execute when called.
Instances
data AttributeNamesBase a 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").
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 showsPrec :: Int -> PersistenceStrategy -> ShowS # show :: PersistenceStrategy -> String # showList :: [PersistenceStrategy] -> ShowS # |
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 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 #
data DatabaseContextFunctionBody Source #
DatabaseContextFunctionBody (Maybe DatabaseContextFunctionBodyScript) DatabaseContextFunctionBodyType |
Instances
NFData DatabaseContextFunctionBody Source # | |
Defined in ProjectM36.Base rnf :: DatabaseContextFunctionBody -> () # |
data DatabaseContextFunction Source #
Instances
attrTypeVars :: Attribute -> Set TypeVarName Source #
typeVars :: TypeConstructor -> Set TypeVarName Source #
atomTypeVars :: AtomType -> Set TypeVarName Source #