project-m36-0.5.1: 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 # 
Instance details

Defined in ProjectM36.Base

Methods

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

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

Show Atom Source # 
Instance details

Defined in ProjectM36.Base

Methods

showsPrec :: Int -> Atom -> ShowS #

show :: Atom -> String #

showList :: [Atom] -> ShowS #

Generic Atom Source # 
Instance details

Defined in ProjectM36.Base

Associated Types

type Rep Atom :: * -> * #

Methods

from :: Atom -> Rep Atom x #

to :: Rep Atom x -> Atom #

Hashable Atom Source # 
Instance details

Defined in ProjectM36.Base

Methods

hashWithSalt :: Int -> Atom -> Int #

hash :: Atom -> Int #

Binary Atom Source # 
Instance details

Defined in ProjectM36.Base

Methods

put :: Atom -> Put #

get :: Get Atom #

putList :: [Atom] -> Put #

NFData Atom Source # 
Instance details

Defined in ProjectM36.Base

Methods

rnf :: Atom -> () #

type Rep Atom Source # 
Instance details

Defined in ProjectM36.Base

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

data AtomType Source #

The AtomType uniquely identifies the type of a atom.

Instances
Eq AtomType Source # 
Instance details

Defined in ProjectM36.Base

Show AtomType Source # 
Instance details

Defined in ProjectM36.Base

Generic AtomType Source # 
Instance details

Defined in ProjectM36.Base

Associated Types

type Rep AtomType :: * -> * #

Methods

from :: AtomType -> Rep AtomType x #

to :: Rep AtomType x -> AtomType #

Hashable TypeVarMap Source # 
Instance details

Defined in ProjectM36.Base

Binary AtomType Source # 
Instance details

Defined in ProjectM36.Base

Methods

put :: AtomType -> Put #

get :: Get AtomType #

putList :: [AtomType] -> Put #

NFData AtomType Source # 
Instance details

Defined in ProjectM36.Base

Methods

rnf :: AtomType -> () #

type Rep AtomType Source # 
Instance details

Defined in ProjectM36.Base

type Rep AtomType = D1 (MetaData "AtomType" "ProjectM36.Base" "project-m36-0.5.1-38P1EVgZYrJ9HDkvLyCm0" False) (((C1 (MetaCons "IntAtomType" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "IntegerAtomType" PrefixI False) (U1 :: * -> *)) :+: (C1 (MetaCons "DoubleAtomType" PrefixI False) (U1 :: * -> *) :+: (C1 (MetaCons "TextAtomType" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "DayAtomType" PrefixI False) (U1 :: * -> *)))) :+: ((C1 (MetaCons "DateTimeAtomType" PrefixI False) (U1 :: * -> *) :+: (C1 (MetaCons "ByteStringAtomType" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "BoolAtomType" PrefixI False) (U1 :: * -> *))) :+: (C1 (MetaCons "RelationAtomType" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Attributes)) :+: (C1 (MetaCons "ConstructedAtomType" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 TypeConstructorName) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 TypeVarMap)) :+: C1 (MetaCons "TypeVariableType" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 TypeVarName))))))

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.

Instances
Eq Attribute Source # 
Instance details

Defined in ProjectM36.Base

Show Attribute Source # 
Instance details

Defined in ProjectM36.Base

Generic Attribute Source # 
Instance details

Defined in ProjectM36.Base

Associated Types

type Rep Attribute :: * -> * #

Hashable Attribute Source # 
Instance details

Defined in ProjectM36.Base

Binary Attribute Source # 
Instance details

Defined in ProjectM36.Base

NFData Attribute Source # 
Instance details

Defined in ProjectM36.Base

Methods

rnf :: Attribute -> () #

type Rep Attribute Source # 
Instance details

Defined in ProjectM36.Base

type Attributes = Vector Attribute Source #

Attributes represent the head of a relation.

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

Equality function for a set of attributes.

newtype RelationTupleSet Source #

The relation's tuple set is the body of the relation.

Constructors

RelationTupleSet 

Fields

Instances
Eq RelationTupleSet Source # 
Instance details

Defined in ProjectM36.Base

Show RelationTupleSet Source # 
Instance details

Defined in ProjectM36.Base

Generic RelationTupleSet Source # 
Instance details

Defined in ProjectM36.Base

Associated Types

type Rep RelationTupleSet :: * -> * #

Hashable RelationTupleSet Source # 
Instance details

Defined in ProjectM36.Base

Binary RelationTupleSet Source # 
Instance details

Defined in ProjectM36.Base

NFData RelationTupleSet Source # 
Instance details

Defined in ProjectM36.Base

Methods

rnf :: RelationTupleSet -> () #

type Rep RelationTupleSet Source # 
Instance details

Defined in ProjectM36.Base

type Rep RelationTupleSet = D1 (MetaData "RelationTupleSet" "ProjectM36.Base" "project-m36-0.5.1-38P1EVgZYrJ9HDkvLyCm0" True) (C1 (MetaCons "RelationTupleSet" PrefixI True) (S1 (MetaSel (Just "asList") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [RelationTuple])))

data RelationTuple Source #

A tuple is a set of attributes mapped to their Atom values.

Instances
Eq RelationTuple Source # 
Instance details

Defined in ProjectM36.Base

Show RelationTuple Source # 
Instance details

Defined in ProjectM36.Base

Generic RelationTuple Source # 
Instance details

Defined in ProjectM36.Base

Associated Types

type Rep RelationTuple :: * -> * #

Hashable RelationTuple Source # 
Instance details

Defined in ProjectM36.Base

Binary RelationTuple Source # 
Instance details

Defined in ProjectM36.Base

NFData RelationTuple Source # 
Instance details

Defined in ProjectM36.Base

Methods

rnf :: RelationTuple -> () #

type Rep RelationTuple Source # 
Instance details

Defined in ProjectM36.Base

data Relation Source #

Instances
Eq Relation Source # 
Instance details

Defined in ProjectM36.Base

Read Relation Source # 
Instance details

Defined in ProjectM36.Base

Show Relation Source # 
Instance details

Defined in ProjectM36.Base

Generic Relation Source # 
Instance details

Defined in ProjectM36.Base

Associated Types

type Rep Relation :: * -> * #

Methods

from :: Relation -> Rep Relation x #

to :: Rep Relation x -> Relation #

Hashable Relation Source # 
Instance details

Defined in ProjectM36.Base

Methods

hashWithSalt :: Int -> Relation -> Int #

hash :: Relation -> Int #

Binary Relation Source # 
Instance details

Defined in ProjectM36.Base

Methods

put :: Relation -> Put #

get :: Get Relation #

putList :: [Relation] -> Put #

NFData Relation Source # 
Instance details

Defined in ProjectM36.Base

Methods

rnf :: Relation -> () #

type Rep Relation Source # 
Instance details

Defined in ProjectM36.Base

data RelationCardinality Source #

Used to represent the number of tuples in a relation.

Constructors

Countable 
Finite Int 
Instances
Eq RelationCardinality Source # 
Instance details

Defined in ProjectM36.Base

Ord RelationCardinality Source # 
Instance details

Defined in ProjectM36.Base

Show RelationCardinality Source # 
Instance details

Defined in ProjectM36.Base

Generic RelationCardinality Source # 
Instance details

Defined in ProjectM36.Base

Associated Types

type Rep RelationCardinality :: * -> * #

type Rep RelationCardinality Source # 
Instance details

Defined in ProjectM36.Base

type Rep RelationCardinality = D1 (MetaData "RelationCardinality" "ProjectM36.Base" "project-m36-0.5.1-38P1EVgZYrJ9HDkvLyCm0" False) (C1 (MetaCons "Countable" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "Finite" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 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 # 
Instance details

Defined in ProjectM36.Base

Binary TransGraphRelationalExpr # 
Instance details

Defined in ProjectM36.TransGraphRelationalExpression

Eq a => Eq (RelationalExprBase a) Source # 
Instance details

Defined in ProjectM36.Base

Show a => Show (RelationalExprBase a) Source # 
Instance details

Defined in ProjectM36.Base

Generic (RelationalExprBase a) Source # 
Instance details

Defined in ProjectM36.Base

Associated Types

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

NFData a => NFData (RelationalExprBase a) Source # 
Instance details

Defined in ProjectM36.Base

Methods

rnf :: RelationalExprBase a -> () #

type Rep (RelationalExprBase a) Source # 
Instance details

Defined in ProjectM36.Base

type Rep (RelationalExprBase a) = D1 (MetaData "RelationalExprBase" "ProjectM36.Base" "project-m36-0.5.1-38P1EVgZYrJ9HDkvLyCm0" False) ((((C1 (MetaCons "MakeRelationFromExprs" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe [AttributeExprBase a])) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [TupleExprBase a])) :+: C1 (MetaCons "MakeStaticRelation" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Attributes) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 RelationTupleSet))) :+: (C1 (MetaCons "ExistingRelation" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Relation)) :+: C1 (MetaCons "RelationVariable" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 RelVarName) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)))) :+: ((C1 (MetaCons "Project" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (AttributeNamesBase a)) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (RelationalExprBase a))) :+: C1 (MetaCons "Union" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (RelationalExprBase a)) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (RelationalExprBase a)))) :+: (C1 (MetaCons "Join" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (RelationalExprBase a)) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (RelationalExprBase a))) :+: C1 (MetaCons "Rename" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 AttributeName) :*: (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 AttributeName) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (RelationalExprBase a))))))) :+: (((C1 (MetaCons "Difference" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (RelationalExprBase a)) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (RelationalExprBase a))) :+: C1 (MetaCons "Group" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (AttributeNamesBase a)) :*: (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 AttributeName) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (RelationalExprBase a))))) :+: (C1 (MetaCons "Ungroup" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 AttributeName) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (RelationalExprBase a))) :+: C1 (MetaCons "Restrict" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (RestrictionPredicateExprBase a)) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (RelationalExprBase a))))) :+: ((C1 (MetaCons "Equals" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (RelationalExprBase a)) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (RelationalExprBase a))) :+: C1 (MetaCons "NotEquals" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (RelationalExprBase a)) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (RelationalExprBase a)))) :+: (C1 (MetaCons "Extend" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (ExtendTupleExprBase a)) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (RelationalExprBase a))) :+: C1 (MetaCons "With" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [(RelVarName, RelationalExprBase a)]) :*: S1 (MetaSel (Nothing :: Maybe 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.

Instances
Eq Notification Source # 
Instance details

Defined in ProjectM36.Base

Show Notification Source # 
Instance details

Defined in ProjectM36.Base

Generic Notification Source # 
Instance details

Defined in ProjectM36.Base

Associated Types

type Rep Notification :: * -> * #

Binary Notification Source # 
Instance details

Defined in ProjectM36.Base

NFData Notification Source # 
Instance details

Defined in ProjectM36.Base

Methods

rnf :: Notification -> () #

type Rep Notification Source # 
Instance details

Defined in ProjectM36.Base

type Rep Notification = D1 (MetaData "Notification" "ProjectM36.Base" "project-m36-0.5.1-38P1EVgZYrJ9HDkvLyCm0" False) (C1 (MetaCons "Notification" PrefixI True) (S1 (MetaSel (Just "changeExpr") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 RelationalExpr) :*: (S1 (MetaSel (Just "reportOldExpr") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 RelationalExpr) :*: S1 (MetaSel (Just "reportNewExpr") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 RelationalExpr))))

data TypeConstructorDef Source #

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

Instances
Eq TypeConstructorDef Source # 
Instance details

Defined in ProjectM36.Base

Show TypeConstructorDef Source # 
Instance details

Defined in ProjectM36.Base

Generic TypeConstructorDef Source # 
Instance details

Defined in ProjectM36.Base

Associated Types

type Rep TypeConstructorDef :: * -> * #

Binary TypeConstructorDef Source # 
Instance details

Defined in ProjectM36.Base

NFData TypeConstructorDef Source # 
Instance details

Defined in ProjectM36.Base

Methods

rnf :: TypeConstructorDef -> () #

type Rep TypeConstructorDef Source # 
Instance details

Defined in ProjectM36.Base

type TypeConstructor = TypeConstructorBase () Source #

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

data TypeConstructorBase a Source #

Instances
Eq a => Eq (TypeConstructorBase a) Source # 
Instance details

Defined in ProjectM36.Base

Show a => Show (TypeConstructorBase a) Source # 
Instance details

Defined in ProjectM36.Base

Generic (TypeConstructorBase a) Source # 
Instance details

Defined in ProjectM36.Base

Associated Types

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

Binary a => Binary (TypeConstructorBase a) Source # 
Instance details

Defined in ProjectM36.Base

NFData a => NFData (TypeConstructorBase a) Source # 
Instance details

Defined in ProjectM36.Base

Methods

rnf :: TypeConstructorBase a -> () #

type Rep (TypeConstructorBase a) Source # 
Instance details

Defined in ProjectM36.Base

data DataConstructorDef Source #

Used to define a data constructor in a type constructor context such as Left a | Right b

data DataConstructorDefArg Source #

Instances
Eq DataConstructorDefArg Source # 
Instance details

Defined in ProjectM36.Base

Show DataConstructorDefArg Source # 
Instance details

Defined in ProjectM36.Base

Generic DataConstructorDefArg Source # 
Instance details

Defined in ProjectM36.Base

Associated Types

type Rep DataConstructorDefArg :: * -> * #

Binary DataConstructorDefArg Source # 
Instance details

Defined in ProjectM36.Base

NFData DataConstructorDefArg Source # 
Instance details

Defined in ProjectM36.Base

Methods

rnf :: DataConstructorDefArg -> () #

type Rep DataConstructorDefArg Source # 
Instance details

Defined in ProjectM36.Base

type Rep DataConstructorDefArg = D1 (MetaData "DataConstructorDefArg" "ProjectM36.Base" "project-m36-0.5.1-38P1EVgZYrJ9HDkvLyCm0" False) (C1 (MetaCons "DataConstructorDefTypeConstructorArg" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 TypeConstructor)) :+: C1 (MetaCons "DataConstructorDefTypeVarNameArg" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 TypeVarName)))

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 # 
Instance details

Defined in ProjectM36.Base

Associated Types

type Rep Schema :: * -> * #

Methods

from :: Schema -> Rep Schema x #

to :: Rep Schema x -> Schema #

Binary Schema Source # 
Instance details

Defined in ProjectM36.Base

Methods

put :: Schema -> Put #

get :: Get Schema #

putList :: [Schema] -> Put #

type Rep Schema Source # 
Instance details

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 #

Instances
Show SchemaIsomorph Source # 
Instance details

Defined in ProjectM36.Base

Generic SchemaIsomorph Source # 
Instance details

Defined in ProjectM36.Base

Associated Types

type Rep SchemaIsomorph :: * -> * #

Binary SchemaIsomorph Source # 
Instance details

Defined in ProjectM36.Base

type Rep SchemaIsomorph Source # 
Instance details

Defined in ProjectM36.Base

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.

Instances
Eq InclusionDependency Source # 
Instance details

Defined in ProjectM36.Base

Show InclusionDependency Source # 
Instance details

Defined in ProjectM36.Base

Generic InclusionDependency Source # 
Instance details

Defined in ProjectM36.Base

Associated Types

type Rep InclusionDependency :: * -> * #

Binary InclusionDependency Source # 
Instance details

Defined in ProjectM36.Base

NFData InclusionDependency Source # 
Instance details

Defined in ProjectM36.Base

Methods

rnf :: InclusionDependency -> () #

type Rep InclusionDependency Source # 
Instance details

Defined in ProjectM36.Base

data DatabaseContextExpr Source #

Database context expressions modify the database context.

Instances
Eq DatabaseContextExpr Source # 
Instance details

Defined in ProjectM36.Base

Show DatabaseContextExpr Source # 
Instance details

Defined in ProjectM36.Base

Generic DatabaseContextExpr Source # 
Instance details

Defined in ProjectM36.Base

Associated Types

type Rep DatabaseContextExpr :: * -> * #

Binary DatabaseContextExpr Source # 
Instance details

Defined in ProjectM36.Base

type Rep DatabaseContextExpr Source # 
Instance details

Defined in ProjectM36.Base

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

type Range = (Int, Int) 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
Eq DatabaseContextIOExpr Source # 
Instance details

Defined in ProjectM36.Base

Show DatabaseContextIOExpr Source # 
Instance details

Defined in ProjectM36.Base

Generic DatabaseContextIOExpr Source # 
Instance details

Defined in ProjectM36.Base

Associated Types

type Rep DatabaseContextIOExpr :: * -> * #

Binary DatabaseContextIOExpr Source # 
Instance details

Defined in ProjectM36.Base

type Rep DatabaseContextIOExpr Source # 
Instance details

Defined in ProjectM36.Base

type Rep DatabaseContextIOExpr = D1 (MetaData "DatabaseContextIOExpr" "ProjectM36.Base" "project-m36-0.5.1-38P1EVgZYrJ9HDkvLyCm0" False) ((C1 (MetaCons "AddAtomFunction" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 AtomFunctionName) :*: (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [TypeConstructor]) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 AtomFunctionBodyScript))) :+: C1 (MetaCons "LoadAtomFunctions" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 ObjModuleName) :*: (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 ObjFunctionName) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 FilePath)))) :+: (C1 (MetaCons "AddDatabaseContextFunction" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 DatabaseContextFunctionName) :*: (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [TypeConstructor]) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 DatabaseContextFunctionBodyScript))) :+: (C1 (MetaCons "LoadDatabaseContextFunctions" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 ObjModuleName) :*: (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 ObjFunctionName) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 FilePath))) :+: C1 (MetaCons "CreateArbitraryRelation" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 RelVarName) :*: (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [AttributeExpr]) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Range))))))

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 # 
Instance details

Defined in ProjectM36.Base

Binary TransGraphRestrictionPredicateExpr # 
Instance details

Defined in ProjectM36.TransGraphRelationalExpression

Eq a => Eq (RestrictionPredicateExprBase a) Source # 
Instance details

Defined in ProjectM36.Base

Show a => Show (RestrictionPredicateExprBase a) Source # 
Instance details

Defined in ProjectM36.Base

Generic (RestrictionPredicateExprBase a) Source # 
Instance details

Defined in ProjectM36.Base

Associated Types

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

NFData a => NFData (RestrictionPredicateExprBase a) Source # 
Instance details

Defined in ProjectM36.Base

type Rep (RestrictionPredicateExprBase a) Source # 
Instance details

Defined in ProjectM36.Base

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

Defined in ProjectM36.Base

Generic TransactionInfo Source # 
Instance details

Defined in ProjectM36.Base

Associated Types

type Rep TransactionInfo :: * -> * #

Binary TransactionInfo Source # 
Instance details

Defined in ProjectM36.Base

type Rep TransactionInfo Source # 
Instance details

Defined in ProjectM36.Base

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 # 
Instance details

Defined in ProjectM36.Base

Methods

put :: AtomExpr -> Put #

get :: Get AtomExpr #

putList :: [AtomExpr] -> Put #

Binary TransGraphAtomExpr # 
Instance details

Defined in ProjectM36.TransGraphRelationalExpression

Eq a => Eq (AtomExprBase a) Source # 
Instance details

Defined in ProjectM36.Base

Show a => Show (AtomExprBase a) Source # 
Instance details

Defined in ProjectM36.Base

Generic (AtomExprBase a) Source # 
Instance details

Defined in ProjectM36.Base

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 # 
Instance details

Defined in ProjectM36.Base

Methods

rnf :: AtomExprBase a -> () #

type Rep (AtomExprBase a) Source # 
Instance details

Defined in ProjectM36.Base

data ExtendTupleExprBase a Source #

Used in tuple creation when creating a relation.

Instances
Binary ExtendTupleExpr Source # 
Instance details

Defined in ProjectM36.Base

Binary TransGraphExtendTupleExpr # 
Instance details

Defined in ProjectM36.TransGraphRelationalExpression

Eq a => Eq (ExtendTupleExprBase a) Source # 
Instance details

Defined in ProjectM36.Base

Show a => Show (ExtendTupleExprBase a) Source # 
Instance details

Defined in ProjectM36.Base

Generic (ExtendTupleExprBase a) Source # 
Instance details

Defined in ProjectM36.Base

Associated Types

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

NFData a => NFData (ExtendTupleExprBase a) Source # 
Instance details

Defined in ProjectM36.Base

Methods

rnf :: ExtendTupleExprBase a -> () #

type Rep (ExtendTupleExprBase a) Source # 
Instance details

Defined in ProjectM36.Base

type Rep (ExtendTupleExprBase a) = D1 (MetaData "ExtendTupleExprBase" "ProjectM36.Base" "project-m36-0.5.1-38P1EVgZYrJ9HDkvLyCm0" False) (C1 (MetaCons "AttributeExtendTupleExpr" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 AttributeName) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (AtomExprBase a))))

data AtomFunction Source #

An AtomFunction has a name, a type, and a function body to execute when called.

Instances
Eq AtomFunction Source # 
Instance details

Defined in ProjectM36.Base

Show AtomFunction Source # 
Instance details

Defined in ProjectM36.Base

Generic AtomFunction Source # 
Instance details

Defined in ProjectM36.Base

Associated Types

type Rep AtomFunction :: * -> * #

Hashable AtomFunction Source # 
Instance details

Defined in ProjectM36.Base

NFData AtomFunction Source # 
Instance details

Defined in ProjectM36.Base

Methods

rnf :: AtomFunction -> () #

type Rep AtomFunction Source # 
Instance details

Defined in ProjectM36.Base

type Rep AtomFunction = D1 (MetaData "AtomFunction" "ProjectM36.Base" "project-m36-0.5.1-38P1EVgZYrJ9HDkvLyCm0" False) (C1 (MetaCons "AtomFunction" PrefixI True) (S1 (MetaSel (Just "atomFuncName") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 AtomFunctionName) :*: (S1 (MetaSel (Just "atomFuncType") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [AtomType]) :*: S1 (MetaSel (Just "atomFuncBody") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 AtomFunctionBody))))

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
Binary AttributeNames Source # 
Instance details

Defined in ProjectM36.Base

Binary TransGraphAttributeNames # 
Instance details

Defined in ProjectM36.TransGraphRelationalExpression

Eq a => Eq (AttributeNamesBase a) Source # 
Instance details

Defined in ProjectM36.Base

Show a => Show (AttributeNamesBase a) Source # 
Instance details

Defined in ProjectM36.Base

Generic (AttributeNamesBase a) Source # 
Instance details

Defined in ProjectM36.Base

Associated Types

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

NFData a => NFData (AttributeNamesBase a) Source # 
Instance details

Defined in ProjectM36.Base

Methods

rnf :: AttributeNamesBase a -> () #

type Rep (AttributeNamesBase a) Source # 
Instance details

Defined in ProjectM36.Base

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 # 
Instance details

Defined in ProjectM36.Base

Show a => Show (AttributeExprBase a) Source # 
Instance details

Defined in ProjectM36.Base

Generic (AttributeExprBase a) Source # 
Instance details

Defined in ProjectM36.Base

Associated Types

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

Binary a => Binary (AttributeExprBase a) Source # 
Instance details

Defined in ProjectM36.Base

NFData a => NFData (AttributeExprBase a) Source # 
Instance details

Defined in ProjectM36.Base

Methods

rnf :: AttributeExprBase a -> () #

type Rep (AttributeExprBase a) Source # 
Instance details

Defined in ProjectM36.Base

newtype TupleExprBase a Source #

Dynamically create a tuple from attribute names and AtomExprs.

Instances
Binary TupleExpr Source # 
Instance details

Defined in ProjectM36.Base

Binary TransGraphTupleExpr # 
Instance details

Defined in ProjectM36.TransGraphRelationalExpression

Eq a => Eq (TupleExprBase a) Source # 
Instance details

Defined in ProjectM36.Base

Show a => Show (TupleExprBase a) Source # 
Instance details

Defined in ProjectM36.Base

Generic (TupleExprBase a) Source # 
Instance details

Defined in ProjectM36.Base

Associated Types

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

NFData a => NFData (TupleExprBase a) Source # 
Instance details

Defined in ProjectM36.Base

Methods

rnf :: TupleExprBase a -> () #

type Rep (TupleExprBase a) Source # 
Instance details

Defined in ProjectM36.Base

type Rep (TupleExprBase a) = D1 (MetaData "TupleExprBase" "ProjectM36.Base" "project-m36-0.5.1-38P1EVgZYrJ9HDkvLyCm0" True) (C1 (MetaCons "TupleExpr" PrefixI False) (S1 (MetaSel (Nothing :: Maybe 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.

Instances
Eq MergeStrategy Source # 
Instance details

Defined in ProjectM36.Base

Show MergeStrategy Source # 
Instance details

Defined in ProjectM36.Base

Generic MergeStrategy Source # 
Instance details

Defined in ProjectM36.Base

Associated Types

type Rep MergeStrategy :: * -> * #

Binary MergeStrategy Source # 
Instance details

Defined in ProjectM36.Base

NFData MergeStrategy Source # 
Instance details

Defined in ProjectM36.Base

Methods

rnf :: MergeStrategy -> () #

type Rep MergeStrategy Source # 
Instance details

Defined in ProjectM36.Base

type Rep MergeStrategy = D1 (MetaData "MergeStrategy" "ProjectM36.Base" "project-m36-0.5.1-38P1EVgZYrJ9HDkvLyCm0" False) (C1 (MetaCons "UnionMergeStrategy" PrefixI False) (U1 :: * -> *) :+: (C1 (MetaCons "UnionPreferMergeStrategy" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 HeadName)) :+: C1 (MetaCons "SelectedBranchMergeStrategy" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 HeadName))))

data DatabaseContextFunction Source #

Orphan instances

Binary UTCTime Source # 
Instance details

Methods

put :: UTCTime -> Put #

get :: Get UTCTime #

putList :: [UTCTime] -> Put #

Binary Day Source # 
Instance details

Methods

put :: Day -> Put #

get :: Get Day #

putList :: [Day] -> Put #