{-# LANGUAGE DeriveGeneric, DeriveAnyClass #-}
module ProjectM36.Error where
import ProjectM36.Base
import ProjectM36.MerkleHash
import ProjectM36.DatabaseContextFunctionError
import ProjectM36.AtomFunctionError
import qualified Data.Set as S
import Control.DeepSeq (NFData, rnf)
import Control.DeepSeq.Generics (genericRnf)
import GHC.Generics (Generic)
import qualified Data.Text as T
import Data.Typeable
import Control.Exception
import ProjectM36.SQL.Select
data RelationalError = NoSuchAttributeNamesError (S.Set AttributeName)
| TupleAttributeCountMismatchError Int
| EmptyAttributesError
| DuplicateAttributeNamesError (S.Set AttributeName)
| TupleAttributeTypeMismatchError Attributes
| AttributeCountMismatchError Int
| AttributeNamesMismatchError (S.Set AttributeName)
| AttributeTypesMismatchError Attributes
| AttributeNameInUseError AttributeName
| AttributeIsNotRelationValuedError AttributeName
| CouldNotInferAttributes
| RelVarNotDefinedError RelVarName
| RelVarAlreadyDefinedError RelVarName
| RelationTypeMismatchError Attributes Attributes
| InclusionDependencyCheckError IncDepName (Maybe RelationalError)
| InclusionDependencyNameInUseError IncDepName
| InclusionDependencyNameNotInUseError IncDepName
| ParseError T.Text
| PredicateExpressionError T.Text
| NoCommonTransactionAncestorError TransactionId TransactionId
| NoSuchTransactionError TransactionId
| RootTransactionTraversalError
| HeadNameSwitchingHeadProhibitedError HeadName
| NoSuchHeadNameError HeadName
|
| NewTransactionMayNotHaveChildrenError TransactionId
| ParentCountTraversalError Int Int
| NewTransactionMissingParentError TransactionId
| TransactionId
| TransactionGraphCycleError TransactionId
| SessionIdInUseError TransactionId
| NoSuchSessionError TransactionId
| FailedToFindTransactionError TransactionId
| TransactionIdInUseError TransactionId
| NoSuchFunctionError FunctionName
| NoSuchTypeConstructorName TypeConstructorName
| TypeConstructorAtomTypeMismatch TypeConstructorName AtomType
| AtomTypeMismatchError AtomType AtomType
| TypeConstructorNameMismatch TypeConstructorName TypeConstructorName
| AtomTypeTypeConstructorReconciliationError AtomType TypeConstructorName
| DataConstructorNameInUseError DataConstructorName
| DataConstructorUsesUndeclaredTypeVariable TypeVarName
| TypeConstructorTypeVarsMismatch (S.Set TypeVarName) (S.Set TypeVarName)
| TypeConstructorTypeVarMissing TypeVarName
| TypeConstructorTypeVarsTypesMismatch TypeConstructorName TypeVarMap TypeVarMap
| DataConstructorTypeVarsMismatch DataConstructorName TypeVarMap TypeVarMap
| AtomFunctionTypeVariableResolutionError FunctionName TypeVarName
| AtomFunctionTypeVariableMismatch TypeVarName AtomType AtomType
| IfThenExprExpectedBooleanError AtomType
| AtomTypeNameInUseError AtomTypeName
| IncompletelyDefinedAtomTypeWithConstructorError
| AtomTypeNameNotInUseError AtomTypeName
| AttributeNotSortableError Attribute
| FunctionNameInUseError FunctionName
| FunctionNameNotInUseError FunctionName
| EmptyCommitError
| FunctionArgumentCountMismatchError Int Int
| ConstructedAtomArgumentCountMismatchError Int Int
| NoSuchDataConstructorError DataConstructorName
| NoSuchTypeConstructorError TypeConstructorName
| InvalidAtomTypeName AtomTypeName
| AtomTypeNotSupported AttributeName
| AtomOperatorNotSupported T.Text
| EmptyTuplesError
| AtomTypeCountError [AtomType] [AtomType]
| AtomFunctionTypeError FunctionName Int AtomType AtomType
| AtomFunctionUserError AtomFunctionError
| PrecompiledFunctionRemoveError FunctionName
| RelationValuedAttributesNotSupportedError [AttributeName]
| NotificationNameInUseError NotificationName
| NotificationNameNotInUseError NotificationName
| NotificationValidationError NotificationName NotificationExpression RelationalError
| ImportError ImportError'
| ExportError T.Text
| UnhandledExceptionError String
| MergeTransactionError MergeError
| ScriptError ScriptCompilationError
| LoadFunctionError
| SecurityLoadFunctionError
| DatabaseContextFunctionUserError DatabaseContextFunctionError
| DatabaseLoadError PersistenceError
| SubschemaNameInUseError SchemaName
| SubschemaNameNotInUseError SchemaName
| SchemaCreationError SchemaError
| ImproperDatabaseStateError
| NonConcreteSchemaPlanError
| NoUncommittedContextInEvalError
| TupleExprsReferenceMultipleMarkersError
| MerkleHashValidationError TransactionId MerkleHash MerkleHash
| RegisteredQueryValidationError RegisteredQueryName RelationalError
| RegisteredQueryNameInUseError RegisteredQueryName
| RegisteredQueryNameNotInUseError RegisteredQueryName
| SQLConversionError SQLError
| MultipleErrors [RelationalError]
deriving (Int -> RelationalError -> ShowS
[RelationalError] -> ShowS
RelationalError -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [RelationalError] -> ShowS
$cshowList :: [RelationalError] -> ShowS
show :: RelationalError -> String
$cshow :: RelationalError -> String
showsPrec :: Int -> RelationalError -> ShowS
$cshowsPrec :: Int -> RelationalError -> ShowS
Show,RelationalError -> RelationalError -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: RelationalError -> RelationalError -> Bool
$c/= :: RelationalError -> RelationalError -> Bool
== :: RelationalError -> RelationalError -> Bool
$c== :: RelationalError -> RelationalError -> Bool
Eq,forall x. Rep RelationalError x -> RelationalError
forall x. RelationalError -> Rep RelationalError x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep RelationalError x -> RelationalError
$cfrom :: forall x. RelationalError -> Rep RelationalError x
Generic,Typeable, RelationalError -> ()
forall a. (a -> ()) -> NFData a
rnf :: RelationalError -> ()
$crnf :: RelationalError -> ()
NFData)
data PersistenceError = InvalidDirectoryError FilePath |
MissingTransactionError TransactionId |
WrongDatabaseFormatVersionError String String
deriving (Int -> PersistenceError -> ShowS
[PersistenceError] -> ShowS
PersistenceError -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PersistenceError] -> ShowS
$cshowList :: [PersistenceError] -> ShowS
show :: PersistenceError -> String
$cshow :: PersistenceError -> String
showsPrec :: Int -> PersistenceError -> ShowS
$cshowsPrec :: Int -> PersistenceError -> ShowS
Show, PersistenceError -> PersistenceError -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PersistenceError -> PersistenceError -> Bool
$c/= :: PersistenceError -> PersistenceError -> Bool
== :: PersistenceError -> PersistenceError -> Bool
$c== :: PersistenceError -> PersistenceError -> Bool
Eq, forall x. Rep PersistenceError x -> PersistenceError
forall x. PersistenceError -> Rep PersistenceError x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep PersistenceError x -> PersistenceError
$cfrom :: forall x. PersistenceError -> Rep PersistenceError x
Generic, PersistenceError -> ()
forall a. (a -> ()) -> NFData a
rnf :: PersistenceError -> ()
$crnf :: PersistenceError -> ()
NFData)
someErrors :: [RelationalError] -> RelationalError
someErrors :: [RelationalError] -> RelationalError
someErrors [] = forall a. HasCallStack => String -> a
error String
"no errors in error list: function misuse"
someErrors [RelationalError
err] = RelationalError
err
someErrors [RelationalError]
errList = [RelationalError] -> RelationalError
MultipleErrors [RelationalError]
errList
data MergeError = SelectedHeadMismatchMergeError |
PreferredHeadMissingMergeError HeadName |
StrategyViolatesConstraintMergeError |
InvalidMergeStrategyError MergeStrategy |
TransactionId |
StrategyViolatesComponentMergeError |
StrategyViolatesRelationVariableMergeError RelationalError |
StrategyWithoutPreferredBranchResolutionMergeError |
StrategyViolatesTypeConstructorMergeError |
StrategyViolatesRegisteredQueryMergeError [RegisteredQueryName]
deriving (Int -> MergeError -> ShowS
[MergeError] -> ShowS
MergeError -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [MergeError] -> ShowS
$cshowList :: [MergeError] -> ShowS
show :: MergeError -> String
$cshow :: MergeError -> String
showsPrec :: Int -> MergeError -> ShowS
$cshowsPrec :: Int -> MergeError -> ShowS
Show, MergeError -> MergeError -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: MergeError -> MergeError -> Bool
$c/= :: MergeError -> MergeError -> Bool
== :: MergeError -> MergeError -> Bool
$c== :: MergeError -> MergeError -> Bool
Eq, forall x. Rep MergeError x -> MergeError
forall x. MergeError -> Rep MergeError x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep MergeError x -> MergeError
$cfrom :: forall x. MergeError -> Rep MergeError x
Generic, Typeable)
instance NFData MergeError where rnf :: MergeError -> ()
rnf = forall a. (Generic a, GNFData (Rep a)) => a -> ()
genericRnf
data ScriptCompilationError = TypeCheckCompilationError String String |
SyntaxErrorCompilationError String |
ScriptCompilationDisabledError |
OtherScriptCompilationError String
deriving (Int -> ScriptCompilationError -> ShowS
[ScriptCompilationError] -> ShowS
ScriptCompilationError -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ScriptCompilationError] -> ShowS
$cshowList :: [ScriptCompilationError] -> ShowS
show :: ScriptCompilationError -> String
$cshow :: ScriptCompilationError -> String
showsPrec :: Int -> ScriptCompilationError -> ShowS
$cshowsPrec :: Int -> ScriptCompilationError -> ShowS
Show, ScriptCompilationError -> ScriptCompilationError -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ScriptCompilationError -> ScriptCompilationError -> Bool
$c/= :: ScriptCompilationError -> ScriptCompilationError -> Bool
== :: ScriptCompilationError -> ScriptCompilationError -> Bool
$c== :: ScriptCompilationError -> ScriptCompilationError -> Bool
Eq, forall x. Rep ScriptCompilationError x -> ScriptCompilationError
forall x. ScriptCompilationError -> Rep ScriptCompilationError x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ScriptCompilationError x -> ScriptCompilationError
$cfrom :: forall x. ScriptCompilationError -> Rep ScriptCompilationError x
Generic, Typeable, ScriptCompilationError -> ()
forall a. (a -> ()) -> NFData a
rnf :: ScriptCompilationError -> ()
$crnf :: ScriptCompilationError -> ()
NFData)
instance Exception ScriptCompilationError
data SchemaError = RelVarReferencesMissing (S.Set RelVarName) |
RelVarInReferencedMoreThanOnce RelVarName |
RelVarOutReferencedMoreThanOnce RelVarName
deriving (Int -> SchemaError -> ShowS
[SchemaError] -> ShowS
SchemaError -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SchemaError] -> ShowS
$cshowList :: [SchemaError] -> ShowS
show :: SchemaError -> String
$cshow :: SchemaError -> String
showsPrec :: Int -> SchemaError -> ShowS
$cshowsPrec :: Int -> SchemaError -> ShowS
Show, SchemaError -> SchemaError -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SchemaError -> SchemaError -> Bool
$c/= :: SchemaError -> SchemaError -> Bool
== :: SchemaError -> SchemaError -> Bool
$c== :: SchemaError -> SchemaError -> Bool
Eq, forall x. Rep SchemaError x -> SchemaError
forall x. SchemaError -> Rep SchemaError x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep SchemaError x -> SchemaError
$cfrom :: forall x. SchemaError -> Rep SchemaError x
Generic, Typeable, SchemaError -> ()
forall a. (a -> ()) -> NFData a
rnf :: SchemaError -> ()
$crnf :: SchemaError -> ()
NFData)
data ImportError' = InvalidSHA256Error T.Text
| SHA256MismatchError T.Text T.Text
| InvalidFileURIError T.Text
| ImportFileDecodeError T.Text
| ImportFileError T.Text
| ImportDownloadError T.Text
deriving (Int -> ImportError' -> ShowS
[ImportError'] -> ShowS
ImportError' -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ImportError'] -> ShowS
$cshowList :: [ImportError'] -> ShowS
show :: ImportError' -> String
$cshow :: ImportError' -> String
showsPrec :: Int -> ImportError' -> ShowS
$cshowsPrec :: Int -> ImportError' -> ShowS
Show, ImportError' -> ImportError' -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ImportError' -> ImportError' -> Bool
$c/= :: ImportError' -> ImportError' -> Bool
== :: ImportError' -> ImportError' -> Bool
$c== :: ImportError' -> ImportError' -> Bool
Eq, forall x. Rep ImportError' x -> ImportError'
forall x. ImportError' -> Rep ImportError' x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ImportError' x -> ImportError'
$cfrom :: forall x. ImportError' -> Rep ImportError' x
Generic, Typeable, ImportError' -> ()
forall a. (a -> ()) -> NFData a
rnf :: ImportError' -> ()
$crnf :: ImportError' -> ()
NFData)
data SQLError = NotSupportedError T.Text |
TypeMismatchError AtomType AtomType |
NoSuchSQLFunctionError FuncName |
NoSuchSQLOperatorError OperatorName |
DuplicateTableReferenceError TableAlias |
MissingTableReferenceError TableAlias |
TableAliasMismatchError TableAlias |
UnexpectedTableNameError TableName |
UnexpectedColumnNameError ColumnName |
ColumnNamesMismatch (S.Set UnqualifiedColumnName) (S.Set UnqualifiedColumnName) |
ColumnResolutionError ColumnName |
ColumnAliasResolutionError ColumnAlias |
UnexpectedRelationalExprError RelationalExpr |
UnexpectedAsteriskError ColumnProjectionName |
UnexpectedColumnProjectionName ColumnProjectionName |
AmbiguousColumnResolutionError ColumnName |
DuplicateColumnAliasError ColumnAlias |
AggregateGroupByMismatchError ProjectionScalarExpr |
GroupByColumnNotReferencedInGroupByError [ProjectionScalarExpr] |
UnsupportedGroupByProjectionError ProjectionScalarExpr |
QueryOperatorTypeMismatchError QueryOperator Attributes Attributes |
SQLRelationalError RelationalError
deriving (Int -> SQLError -> ShowS
[SQLError] -> ShowS
SQLError -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SQLError] -> ShowS
$cshowList :: [SQLError] -> ShowS
show :: SQLError -> String
$cshow :: SQLError -> String
showsPrec :: Int -> SQLError -> ShowS
$cshowsPrec :: Int -> SQLError -> ShowS
Show, SQLError -> SQLError -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SQLError -> SQLError -> Bool
$c/= :: SQLError -> SQLError -> Bool
== :: SQLError -> SQLError -> Bool
$c== :: SQLError -> SQLError -> Bool
Eq, forall x. Rep SQLError x -> SQLError
forall x. SQLError -> Rep SQLError x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep SQLError x -> SQLError
$cfrom :: forall x. SQLError -> Rep SQLError x
Generic, Typeable, SQLError -> ()
forall a. (a -> ()) -> NFData a
rnf :: SQLError -> ()
$crnf :: SQLError -> ()
NFData)