project-m36-0.3: Relational Algebra Engine

Safe HaskellNone
LanguageHaskell2010

ProjectM36.Base

Contents

Synopsis

Documentation

data Atom Source #

Database atoms are the smallest, undecomposable units of a tuple. Common examples are integers, text, or unique identity keys.

Instances

Eq Atom Source # 

Methods

(==) :: Atom -> Atom -> Bool #

(/=) :: Atom -> Atom -> Bool #

Show Atom Source # 

Methods

showsPrec :: Int -> Atom -> ShowS #

show :: Atom -> String #

showList :: [Atom] -> ShowS #

Generic Atom Source # 

Associated Types

type Rep Atom :: * -> * #

Methods

from :: Atom -> Rep Atom x #

to :: Rep Atom x -> Atom #

Hashable Atom Source # 

Methods

hashWithSalt :: Int -> Atom -> Int #

hash :: Atom -> Int #

Binary Atom Source # 

Methods

put :: Atom -> Put #

get :: Get Atom #

putList :: [Atom] -> Put #

NFData Atom Source # 

Methods

rnf :: Atom -> () #

type Rep Atom Source # 
type Rep Atom = D1 (MetaData "Atom" "ProjectM36.Base" "project-m36-0.3-6ISpcBZwnv1Gd5svoztbSh" False) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "IntegerAtom" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Integer))) (C1 (MetaCons "IntAtom" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int)))) ((:+:) (C1 (MetaCons "DoubleAtom" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Double))) ((:+:) (C1 (MetaCons "TextAtom" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text))) (C1 (MetaCons "DayAtom" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Day)))))) ((:+:) ((:+:) (C1 (MetaCons "DateTimeAtom" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 UTCTime))) ((:+:) (C1 (MetaCons "ByteStringAtom" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 ByteString))) (C1 (MetaCons "BoolAtom" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Bool))))) ((:+:) (C1 (MetaCons "IntervalAtom" PrefixI False) ((:*:) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Atom)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Atom))) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 OpenInterval)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 OpenInterval))))) ((:+:) (C1 (MetaCons "RelationAtom" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Relation))) (C1 (MetaCons "ConstructedAtom" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 DataConstructorName)) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 AtomType)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Atom])))))))))

data AtomType Source #

The AtomType uniquely identifies the type of a atom.

Instances

Eq AtomType Source # 
Show AtomType Source # 
Generic AtomType Source # 

Associated Types

type Rep AtomType :: * -> * #

Methods

from :: AtomType -> Rep AtomType x #

to :: Rep AtomType x -> AtomType #

Hashable TypeVarMap Source # 
Binary AtomType Source # 

Methods

put :: AtomType -> Put #

get :: Get AtomType #

putList :: [AtomType] -> Put #

NFData AtomType Source # 

Methods

rnf :: AtomType -> () #

type Rep 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.

data Attribute Source #

A relation's type is composed of attribute names and types.

type Attributes = Vector Attribute Source #

Attributes represent the head of a relation.

attributesEqual :: Attributes -> Attributes -> Bool Source #

Equality function for a set of attributes.

data RelationCardinality Source #

Used to represent the number of tuples in a relation.

Constructors

Countable 
Finite Int 

type RelVarName = StringType Source #

Relation variables are identified by their names.

data RelationalExprBase a Source #

A relational expression represents query (read) operations on a database.

Instances

Binary RelationalExpr Source # 
Eq a => Eq (RelationalExprBase a) Source # 
Show a => Show (RelationalExprBase a) Source # 
Generic (RelationalExprBase a) Source # 

Associated Types

type Rep (RelationalExprBase a) :: * -> * #

NFData a => NFData (RelationalExprBase a) Source # 

Methods

rnf :: RelationalExprBase a -> () #

type Rep (RelationalExprBase a) Source # 
type Rep (RelationalExprBase a) = D1 (MetaData "RelationalExprBase" "ProjectM36.Base" "project-m36-0.3-6ISpcBZwnv1Gd5svoztbSh" False) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "MakeRelationFromExprs" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe [AttributeExprBase a]))) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [TupleExprBase a])))) ((:+:) (C1 (MetaCons "MakeStaticRelation" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Attributes)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 RelationTupleSet)))) (C1 (MetaCons "ExistingRelation" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Relation))))) ((:+:) ((:+:) (C1 (MetaCons "RelationVariable" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 RelVarName)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)))) (C1 (MetaCons "Project" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 AttributeNames)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (RelationalExprBase a)))))) ((:+:) (C1 (MetaCons "Union" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (RelationalExprBase a))) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (RelationalExprBase a))))) (C1 (MetaCons "Join" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (RelationalExprBase a))) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (RelationalExprBase a)))))))) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "Rename" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 AttributeName)) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 AttributeName)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (RelationalExprBase a)))))) (C1 (MetaCons "Difference" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (RelationalExprBase a))) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (RelationalExprBase a)))))) ((:+:) (C1 (MetaCons "Group" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 AttributeNames)) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 AttributeName)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (RelationalExprBase a)))))) (C1 (MetaCons "Ungroup" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 AttributeName)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (RelationalExprBase a))))))) ((:+:) ((:+:) (C1 (MetaCons "Restrict" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (RestrictionPredicateExprBase a))) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (RelationalExprBase a))))) (C1 (MetaCons "Equals" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (RelationalExprBase a))) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (RelationalExprBase a)))))) ((:+:) (C1 (MetaCons "NotEquals" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (RelationalExprBase a))) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (RelationalExprBase a))))) (C1 (MetaCons "Extend" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (ExtendTupleExprBase a))) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (RelationalExprBase a)))))))))

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.

data TypeConstructorDef Source #

Metadata definition for type constructors such as data Either a b.

Instances

data TypeConstructor Source #

Found in data constructors and type declarations: Left (Either Int Text) | Right Int

Instances

Eq TypeConstructor Source # 
Show TypeConstructor Source # 
Generic TypeConstructor Source # 
Binary TypeConstructor Source # 
NFData TypeConstructor Source # 

Methods

rnf :: TypeConstructor -> () #

type Rep TypeConstructor Source # 

data DataConstructorDefArg Source #

data Schemas Source #

Every transaction has one concrete database context and any number of isomorphic subschemas.

newtype Schema Source #

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.

Constructors

Schema SchemaIsomorphs 

Instances

Generic Schema Source # 

Associated Types

type Rep Schema :: * -> * #

Methods

from :: Schema -> Rep Schema x #

to :: Rep Schema x -> Schema #

Binary Schema Source # 

Methods

put :: Schema -> Put #

get :: Get Schema #

putList :: [Schema] -> Put #

type Rep Schema Source # 
type Rep Schema = D1 (MetaData "Schema" "ProjectM36.Base" "project-m36-0.3-6ISpcBZwnv1Gd5svoztbSh" True) (C1 (MetaCons "Schema" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 SchemaIsomorphs)))

data SchemaIsomorph Source #

Instances

Show SchemaIsomorph Source # 
Generic SchemaIsomorph Source # 

Associated Types

type Rep SchemaIsomorph :: * -> * #

Binary SchemaIsomorph Source # 
type Rep SchemaIsomorph Source # 

data DatabaseContext 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.

data DatabaseContextExpr Source #

Database context expressions modify the database context.

Instances

Eq DatabaseContextExpr Source # 
Show DatabaseContextExpr Source # 
Generic DatabaseContextExpr Source # 
Binary DatabaseContextExpr Source # 
type Rep DatabaseContextExpr Source # 
type Rep DatabaseContextExpr = D1 (MetaData "DatabaseContextExpr" "ProjectM36.Base" "project-m36-0.3-6ISpcBZwnv1Gd5svoztbSh" False) ((:+:) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "NoOperation" PrefixI False) U1) (C1 (MetaCons "Define" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 RelVarName)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [AttributeExpr]))))) ((:+:) (C1 (MetaCons "Undefine" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 RelVarName))) (C1 (MetaCons "Assign" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 RelVarName)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 RelationalExpr)))))) ((:+:) ((:+:) (C1 (MetaCons "Insert" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 RelVarName)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 RelationalExpr)))) (C1 (MetaCons "Delete" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 RelVarName)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 RestrictionPredicateExpr))))) ((:+:) (C1 (MetaCons "Update" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 RelVarName)) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 AttributeNameAtomExprMap)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 RestrictionPredicateExpr))))) (C1 (MetaCons "AddInclusionDependency" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 IncDepName)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 InclusionDependency))))))) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "RemoveInclusionDependency" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 IncDepName))) (C1 (MetaCons "AddNotification" PrefixI False) ((:*:) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 NotificationName)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 RelationalExpr))) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 RelationalExpr)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 RelationalExpr)))))) ((:+:) (C1 (MetaCons "RemoveNotification" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 NotificationName))) (C1 (MetaCons "AddTypeConstructor" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 TypeConstructorDef)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [DataConstructorDef])))))) ((:+:) ((:+:) (C1 (MetaCons "RemoveTypeConstructor" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 TypeConstructorName))) (C1 (MetaCons "RemoveAtomFunction" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 AtomFunctionName)))) ((:+:) (C1 (MetaCons "RemoveDatabaseContextFunction" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 DatabaseContextFunctionName))) ((:+:) (C1 (MetaCons "ExecuteDatabaseContextFunction" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 DatabaseContextFunctionName)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [AtomExpr])))) (C1 (MetaCons "MultipleExpr" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [DatabaseContextExpr]))))))))

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

Eq DatabaseContextIOExpr Source # 
Show DatabaseContextIOExpr Source # 
Generic DatabaseContextIOExpr Source # 
Binary DatabaseContextIOExpr Source # 
type Rep DatabaseContextIOExpr 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

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 # 
type Rep (RestrictionPredicateExprBase a) = D1 (MetaData "RestrictionPredicateExprBase" "ProjectM36.Base" "project-m36-0.3-6ISpcBZwnv1Gd5svoztbSh" False) ((:+:) ((:+:) (C1 (MetaCons "TruePredicate" PrefixI False) U1) ((:+:) (C1 (MetaCons "AndPredicate" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (RestrictionPredicateExprBase a))) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (RestrictionPredicateExprBase a))))) (C1 (MetaCons "OrPredicate" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (RestrictionPredicateExprBase a))) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (RestrictionPredicateExprBase a))))))) ((:+:) ((:+:) (C1 (MetaCons "NotPredicate" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (RestrictionPredicateExprBase a)))) (C1 (MetaCons "RelationalExprPredicate" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (RelationalExprBase a))))) ((:+:) (C1 (MetaCons "AtomExprPredicate" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (AtomExprBase a)))) (C1 (MetaCons "AttributeEqualityPredicate" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 AttributeName)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (AtomExprBase a))))))))

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.

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.

Instances

Show TransactionInfo Source # 
Generic TransactionInfo Source # 
Binary TransactionInfo Source # 
type Rep TransactionInfo Source # 

type TransactionId = UUID Source #

Every set of modifications made to the database are atomically committed to the transaction graph as a 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.

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

Binary AtomExpr Source # 

Methods

put :: AtomExpr -> Put #

get :: Get AtomExpr #

putList :: [AtomExpr] -> Put #

Eq a => Eq (AtomExprBase a) Source # 
Show a => Show (AtomExprBase a) Source # 
Generic (AtomExprBase a) Source # 

Associated Types

type Rep (AtomExprBase a) :: * -> * #

Methods

from :: AtomExprBase a -> Rep (AtomExprBase a) x #

to :: Rep (AtomExprBase a) x -> AtomExprBase a #

NFData a => NFData (AtomExprBase a) Source # 

Methods

rnf :: AtomExprBase a -> () #

type Rep (AtomExprBase a) Source # 

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").

Instances

Eq AttributeNames Source # 
Show AttributeNames Source # 
Generic AttributeNames Source # 

Associated Types

type Rep AttributeNames :: * -> * #

Binary AttributeNames Source # 
NFData AttributeNames Source # 

Methods

rnf :: AttributeNames -> () #

type Rep AttributeNames 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)

data AttributeExprBase a Source #

Create attributes dynamically.

Instances

Eq a => Eq (AttributeExprBase a) Source # 
Show a => Show (AttributeExprBase a) Source # 
Generic (AttributeExprBase a) Source # 

Associated Types

type Rep (AttributeExprBase a) :: * -> * #

Binary a => Binary (AttributeExprBase a) Source # 
NFData a => NFData (AttributeExprBase a) Source # 

Methods

rnf :: AttributeExprBase a -> () #

type Rep (AttributeExprBase a) Source # 

newtype TupleExprBase a Source #

Dynamically create a tuple from attribute names and AtomExprs.

Instances

Binary TupleExpr Source # 
Eq a => Eq (TupleExprBase a) Source # 
Show a => Show (TupleExprBase a) Source # 
Generic (TupleExprBase a) Source # 

Associated Types

type Rep (TupleExprBase a) :: * -> * #

NFData a => NFData (TupleExprBase a) Source # 

Methods

rnf :: TupleExprBase a -> () #

type Rep (TupleExprBase a) Source # 
type Rep (TupleExprBase a) = D1 (MetaData "TupleExprBase" "ProjectM36.Base" "project-m36-0.3-6ISpcBZwnv1Gd5svoztbSh" True) (C1 (MetaCons "TupleExpr" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Map AttributeName (AtomExprBase a)))))

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.

Orphan instances

Binary UTCTime Source # 

Methods

put :: UTCTime -> Put #

get :: Get UTCTime #

putList :: [UTCTime] -> Put #

Binary Day Source # 

Methods

put :: Day -> Put #

get :: Get Day #

putList :: [Day] -> Put #