project-m36-0.5.1: Relational Algebra Engine

Safe HaskellNone
LanguageHaskell2010

ProjectM36.Client.Simple

Description

A simplified client interface for Project:M36 database access.

Synopsis

Documentation

simpleConnectProjectM36 :: ConnectionInfo -> IO (Either DbError DbConn) Source #

Same as simpleConnectProjectM36At but always connects to the master branch.

simpleConnectProjectM36At :: HeadName -> ConnectionInfo -> IO (Either DbError DbConn) Source #

A simple alternative to connectProjectM36 which includes simple session management.

withTransaction :: DbConn -> Db a -> IO (Either DbError a) Source #

Runs a Db monad which may include some database updates. If an exception or error occurs, the transaction is rolled back. Otherwise, the transaction is committed to the head of the current branch.

withTransactionUsing :: DbConn -> MergeStrategy -> Db a -> IO (Either DbError a) Source #

Same as withTransaction except that the merge strategy can be specified.

execute :: DatabaseContextExpr -> Db () Source #

Execute a DatabaseContextExpr in the DB monad. Database context expressions manipulate the state of the database. In case of an error, the transaction is terminated and the connection's session is rolled back.

executeOrErr :: DatabaseContextExpr -> Db (Either RelationalError ()) Source #

Run a DatabaseContextExpr update expression. If there is an error, just return it without cancelling the current transaction.

query :: RelationalExpr -> Db Relation Source #

Run a RelationalExpr query in the DB monad. Relational expressions perform read-only queries against the current database state.

queryOrErr :: RelationalExpr -> Db (Either RelationalError Relation) Source #

Run a RelationalExpr query expression. If there is an error, just return it without cancelling the transaction.

cancelTransaction :: DbError -> Db a Source #

Cancel a transaction and carry some error information with it.

orCancelTransaction :: Either RelationalError a -> Db a Source #

Converts the Either result from a Db action into an immediate cancel in the case of error.

rollback :: Db () Source #

Unconditionally roll back the current transaction and throw an exception to terminate the execution of the Db monad.

close :: DbConn -> IO () Source #

Closes the database connection.

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

data Db a Source #

Instances
Monad Db Source # 
Instance details

Defined in ProjectM36.Client.Simple

Methods

(>>=) :: Db a -> (a -> Db b) -> Db b #

(>>) :: Db a -> Db b -> Db b #

return :: a -> Db a #

fail :: String -> Db a #

Functor Db Source # 
Instance details

Defined in ProjectM36.Client.Simple

Methods

fmap :: (a -> b) -> Db a -> Db b #

(<$) :: a -> Db b -> Db a #

Applicative Db Source # 
Instance details

Defined in ProjectM36.Client.Simple

Methods

pure :: a -> Db a #

(<*>) :: Db (a -> b) -> Db a -> Db b #

liftA2 :: (a -> b -> c) -> Db a -> Db b -> Db c #

(*>) :: Db a -> Db b -> Db b #

(<*) :: Db a -> Db b -> Db a #

MonadIO Db Source # 
Instance details

Defined in ProjectM36.Client.Simple

Methods

liftIO :: IO a -> Db a #

data DbError Source #

A union of connection and other errors that can be returned from withTransaction.

Instances
Eq DbError Source # 
Instance details

Defined in ProjectM36.Client.Simple

Methods

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

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

Show DbError Source # 
Instance details

Defined in ProjectM36.Client.Simple

data RelationalError Source #

Constructors

NoSuchAttributeNamesError (Set AttributeName) 
TupleAttributeCountMismatchError Int 
EmptyAttributesError 
DuplicateAttributeNamesError (Set AttributeName) 
TupleAttributeTypeMismatchError Attributes 
AttributeCountMismatchError Int 
AttributeNamesMismatchError (Set AttributeName) 
AttributeNameInUseError AttributeName 
AttributeIsNotRelationValuedError AttributeName 
CouldNotInferAttributes 
RelVarNotDefinedError RelVarName 
RelVarAlreadyDefinedError RelVarName 
RelationTypeMismatchError Attributes Attributes 
InclusionDependencyCheckError IncDepName 
InclusionDependencyNameInUseError IncDepName 
InclusionDependencyNameNotInUseError IncDepName 
ParseError Text 
PredicateExpressionError Text 
NoCommonTransactionAncestorError TransactionId TransactionId 
NoSuchTransactionError TransactionId 
RootTransactionTraversalError 
HeadNameSwitchingHeadProhibitedError HeadName 
NoSuchHeadNameError HeadName 
UnknownHeadError 
NewTransactionMayNotHaveChildrenError TransactionId 
ParentCountTraversalError Int Int 
NewTransactionMissingParentError TransactionId 
TransactionIsNotAHeadError TransactionId 
TransactionGraphCycleError TransactionId 
SessionIdInUseError TransactionId 
NoSuchSessionError TransactionId 
FailedToFindTransactionError TransactionId 
TransactionIdInUseError TransactionId 
NoSuchFunctionError AtomFunctionName 
NoSuchTypeConstructorName TypeConstructorName 
TypeConstructorAtomTypeMismatch TypeConstructorName AtomType 
AtomTypeMismatchError AtomType AtomType 
TypeConstructorNameMismatch TypeConstructorName TypeConstructorName 
AtomTypeTypeConstructorReconciliationError AtomType TypeConstructorName 
DataConstructorNameInUseError DataConstructorName 
DataConstructorUsesUndeclaredTypeVariable TypeVarName 
TypeConstructorTypeVarsMismatch (Set TypeVarName) (Set TypeVarName) 
TypeConstructorTypeVarMissing TypeVarName 
TypeConstructorTypeVarsTypesMismatch TypeConstructorName TypeVarMap TypeVarMap 
DataConstructorTypeVarsMismatch DataConstructorName TypeVarMap TypeVarMap 
AtomFunctionTypeVariableResolutionError AtomFunctionName TypeVarName 
AtomFunctionTypeVariableMismatch TypeVarName AtomType AtomType 
AtomTypeNameInUseError AtomTypeName 
IncompletelyDefinedAtomTypeWithConstructorError 
AtomTypeNameNotInUseError AtomTypeName 
FunctionNameInUseError AtomFunctionName 
FunctionNameNotInUseError AtomFunctionName 
EmptyCommitError 
FunctionArgumentCountMismatchError Int Int 
ConstructedAtomArgumentCountMismatchError Int Int 
NoSuchDataConstructorError DataConstructorName 
NoSuchTypeConstructorError TypeConstructorName 
InvalidAtomTypeName AtomTypeName 
AtomTypeNotSupported AttributeName 
AtomOperatorNotSupported Text 
EmptyTuplesError 
AtomTypeCountError [AtomType] [AtomType] 
AtomFunctionTypeError AtomFunctionName Int AtomType AtomType 
AtomFunctionUserError AtomFunctionError 
PrecompiledFunctionRemoveError AtomFunctionName 
RelationValuedAttributesNotSupportedError [AttributeName] 
NotificationNameInUseError NotificationName 
NotificationNameNotInUseError NotificationName 
ImportError Text 
ExportError Text 
UnhandledExceptionError String 
MergeTransactionError MergeError 
ScriptError ScriptCompilationError 
LoadFunctionError 
DatabaseContextFunctionUserError DatabaseContextFunctionError 
DatabaseLoadError PersistenceError 
SubschemaNameInUseError SchemaName 
SubschemaNameNotInUseError SchemaName 
SchemaCreationError SchemaError 
ImproperDatabaseStateError 
MultipleErrors [RelationalError] 
Instances
Eq RelationalError Source # 
Instance details

Defined in ProjectM36.Error

Show RelationalError Source # 
Instance details

Defined in ProjectM36.Error

Generic RelationalError Source # 
Instance details

Defined in ProjectM36.Error

Associated Types

type Rep RelationalError :: * -> * #

Binary RelationalError Source # 
Instance details

Defined in ProjectM36.Error

NFData RelationalError Source # 
Instance details

Defined in ProjectM36.Error

Methods

rnf :: RelationalError -> () #

type Rep RelationalError Source # 
Instance details

Defined in ProjectM36.Error

type Rep RelationalError = D1 (MetaData "RelationalError" "ProjectM36.Error" "project-m36-0.5.1-38P1EVgZYrJ9HDkvLyCm0" False) ((((((C1 (MetaCons "NoSuchAttributeNamesError" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Set AttributeName))) :+: C1 (MetaCons "TupleAttributeCountMismatchError" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int))) :+: (C1 (MetaCons "EmptyAttributesError" PrefixI False) (U1 :: * -> *) :+: (C1 (MetaCons "DuplicateAttributeNamesError" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Set AttributeName))) :+: C1 (MetaCons "TupleAttributeTypeMismatchError" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Attributes))))) :+: ((C1 (MetaCons "AttributeCountMismatchError" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int)) :+: C1 (MetaCons "AttributeNamesMismatchError" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Set AttributeName)))) :+: (C1 (MetaCons "AttributeNameInUseError" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 AttributeName)) :+: (C1 (MetaCons "AttributeIsNotRelationValuedError" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 AttributeName)) :+: C1 (MetaCons "CouldNotInferAttributes" PrefixI False) (U1 :: * -> *))))) :+: (((C1 (MetaCons "RelVarNotDefinedError" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 RelVarName)) :+: C1 (MetaCons "RelVarAlreadyDefinedError" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 RelVarName))) :+: (C1 (MetaCons "RelationTypeMismatchError" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Attributes) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Attributes)) :+: (C1 (MetaCons "InclusionDependencyCheckError" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 IncDepName)) :+: C1 (MetaCons "InclusionDependencyNameInUseError" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 IncDepName))))) :+: ((C1 (MetaCons "InclusionDependencyNameNotInUseError" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 IncDepName)) :+: C1 (MetaCons "ParseError" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text))) :+: (C1 (MetaCons "PredicateExpressionError" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text)) :+: (C1 (MetaCons "NoCommonTransactionAncestorError" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 TransactionId) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 TransactionId)) :+: C1 (MetaCons "NoSuchTransactionError" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 TransactionId))))))) :+: ((((C1 (MetaCons "RootTransactionTraversalError" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "HeadNameSwitchingHeadProhibitedError" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 HeadName))) :+: (C1 (MetaCons "NoSuchHeadNameError" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 HeadName)) :+: (C1 (MetaCons "UnknownHeadError" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "NewTransactionMayNotHaveChildrenError" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 TransactionId))))) :+: ((C1 (MetaCons "ParentCountTraversalError" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int)) :+: C1 (MetaCons "NewTransactionMissingParentError" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 TransactionId))) :+: (C1 (MetaCons "TransactionIsNotAHeadError" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 TransactionId)) :+: (C1 (MetaCons "TransactionGraphCycleError" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 TransactionId)) :+: C1 (MetaCons "SessionIdInUseError" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 TransactionId)))))) :+: (((C1 (MetaCons "NoSuchSessionError" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 TransactionId)) :+: C1 (MetaCons "FailedToFindTransactionError" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 TransactionId))) :+: (C1 (MetaCons "TransactionIdInUseError" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 TransactionId)) :+: (C1 (MetaCons "NoSuchFunctionError" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 AtomFunctionName)) :+: C1 (MetaCons "NoSuchTypeConstructorName" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 TypeConstructorName))))) :+: ((C1 (MetaCons "TypeConstructorAtomTypeMismatch" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 TypeConstructorName) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 AtomType)) :+: C1 (MetaCons "AtomTypeMismatchError" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 AtomType) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 AtomType))) :+: (C1 (MetaCons "TypeConstructorNameMismatch" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 TypeConstructorName) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 TypeConstructorName)) :+: (C1 (MetaCons "AtomTypeTypeConstructorReconciliationError" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 AtomType) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 TypeConstructorName)) :+: C1 (MetaCons "DataConstructorNameInUseError" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 DataConstructorName)))))))) :+: (((((C1 (MetaCons "DataConstructorUsesUndeclaredTypeVariable" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 TypeVarName)) :+: C1 (MetaCons "TypeConstructorTypeVarsMismatch" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Set TypeVarName)) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Set TypeVarName)))) :+: (C1 (MetaCons "TypeConstructorTypeVarMissing" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 TypeVarName)) :+: (C1 (MetaCons "TypeConstructorTypeVarsTypesMismatch" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 TypeConstructorName) :*: (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 TypeVarMap) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 TypeVarMap))) :+: C1 (MetaCons "DataConstructorTypeVarsMismatch" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 DataConstructorName) :*: (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 TypeVarMap) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 TypeVarMap)))))) :+: ((C1 (MetaCons "AtomFunctionTypeVariableResolutionError" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 AtomFunctionName) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 TypeVarName)) :+: C1 (MetaCons "AtomFunctionTypeVariableMismatch" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 TypeVarName) :*: (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 AtomType) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 AtomType)))) :+: (C1 (MetaCons "AtomTypeNameInUseError" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 AtomTypeName)) :+: (C1 (MetaCons "IncompletelyDefinedAtomTypeWithConstructorError" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "AtomTypeNameNotInUseError" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 AtomTypeName)))))) :+: (((C1 (MetaCons "FunctionNameInUseError" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 AtomFunctionName)) :+: C1 (MetaCons "FunctionNameNotInUseError" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 AtomFunctionName))) :+: (C1 (MetaCons "EmptyCommitError" PrefixI False) (U1 :: * -> *) :+: (C1 (MetaCons "FunctionArgumentCountMismatchError" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int)) :+: C1 (MetaCons "ConstructedAtomArgumentCountMismatchError" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int))))) :+: ((C1 (MetaCons "NoSuchDataConstructorError" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 DataConstructorName)) :+: C1 (MetaCons "NoSuchTypeConstructorError" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 TypeConstructorName))) :+: (C1 (MetaCons "InvalidAtomTypeName" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 AtomTypeName)) :+: (C1 (MetaCons "AtomTypeNotSupported" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 AttributeName)) :+: C1 (MetaCons "AtomOperatorNotSupported" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text))))))) :+: ((((C1 (MetaCons "EmptyTuplesError" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "AtomTypeCountError" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [AtomType]) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [AtomType]))) :+: (C1 (MetaCons "AtomFunctionTypeError" PrefixI False) ((S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 AtomFunctionName) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int)) :*: (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 AtomType) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 AtomType))) :+: (C1 (MetaCons "AtomFunctionUserError" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 AtomFunctionError)) :+: C1 (MetaCons "PrecompiledFunctionRemoveError" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 AtomFunctionName))))) :+: ((C1 (MetaCons "RelationValuedAttributesNotSupportedError" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [AttributeName])) :+: C1 (MetaCons "NotificationNameInUseError" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 NotificationName))) :+: (C1 (MetaCons "NotificationNameNotInUseError" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 NotificationName)) :+: (C1 (MetaCons "ImportError" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text)) :+: C1 (MetaCons "ExportError" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text)))))) :+: (((C1 (MetaCons "UnhandledExceptionError" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String)) :+: C1 (MetaCons "MergeTransactionError" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 MergeError))) :+: (C1 (MetaCons "ScriptError" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 ScriptCompilationError)) :+: (C1 (MetaCons "LoadFunctionError" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "DatabaseContextFunctionUserError" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 DatabaseContextFunctionError))))) :+: ((C1 (MetaCons "DatabaseLoadError" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 PersistenceError)) :+: (C1 (MetaCons "SubschemaNameInUseError" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 SchemaName)) :+: C1 (MetaCons "SubschemaNameNotInUseError" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 SchemaName)))) :+: (C1 (MetaCons "SchemaCreationError" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 SchemaError)) :+: (C1 (MetaCons "ImproperDatabaseStateError" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "MultipleErrors" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [RelationalError])))))))))

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

class (Eq a, NFData a, Binary a, Show a) => Atomable a where Source #

All database values ("atoms") adhere to the Atomable typeclass. This class is derivable allowing new datatypes to be easily marshaling between Haskell values and database values.

Methods

toAtom :: a -> Atom Source #

toAtom :: (Generic a, AtomableG (Rep a)) => a -> Atom Source #

fromAtom :: Atom -> a Source #

fromAtom :: (Generic a, AtomableG (Rep a)) => Atom -> a Source #

Instances
Atomable Bool Source # 
Instance details

Defined in ProjectM36.Atomable

Atomable Double Source # 
Instance details

Defined in ProjectM36.Atomable

Atomable Int Source # 
Instance details

Defined in ProjectM36.Atomable

Atomable Integer Source # 
Instance details

Defined in ProjectM36.Atomable

Atomable ByteString Source # 
Instance details

Defined in ProjectM36.Atomable

Atomable Text Source # 
Instance details

Defined in ProjectM36.Atomable

Atomable UTCTime Source # 
Instance details

Defined in ProjectM36.Atomable

Atomable Day Source # 
Instance details

Defined in ProjectM36.Atomable

Atomable a => Atomable [a] Source # 
Instance details

Defined in ProjectM36.Atomable

Methods

toAtom :: [a] -> Atom Source #

fromAtom :: Atom -> [a] Source #

toAtomType :: proxy [a] -> AtomType Source #

toAddTypeExpr :: proxy [a] -> DatabaseContextExpr Source #

Atomable a => Atomable (Maybe a) Source # 
Instance details

Defined in ProjectM36.Atomable

Atomable a => Atomable (NonEmpty a) Source # 
Instance details

Defined in ProjectM36.Atomable

(Atomable a, Atomable b) => Atomable (Either a b) Source # 
Instance details

Defined in ProjectM36.Atomable

data ConnectionInfo Source #

Construct a ConnectionInfo to describe how to make the Connection. The database can be run within the current process or running remotely via distributed-process.

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)

type NotificationCallback = NotificationName -> EvaluatedNotification -> IO () Source #

The type for notifications callbacks in the client. When a registered notification fires due to a changed relational expression evaluation, the server propagates the notifications to the clients in the form of the callback.

emptyNotificationCallback :: NotificationCallback Source #

The empty notification callback ignores all callbacks.

data 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])))))))

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