module Database.PostgreSQL.PQTypes.Internal.Error (
DetailedQueryError(..)
, QueryError(..)
, HPQTypesError(..)
, LibPQError(..)
, ConversionError(..)
, ArrayItemError(..)
, InvalidValue(..)
, RangeError(..)
, ArrayDimensionMismatch(..)
, RowLengthMismatch(..)
, AffectedRowsMismatch(..)
) where
import Data.Typeable
import qualified Control.Exception as E
import Database.PostgreSQL.PQTypes.Internal.Error.Code
data DetailedQueryError = DetailedQueryError {
qeSeverity :: !String
, qeErrorCode :: !ErrorCode
, qeMessagePrimary :: !String
, qeMessageDetail :: !(Maybe String)
, qeMessageHint :: !(Maybe String)
, qeStatementPosition :: !(Maybe Int)
, qeInternalPosition :: !(Maybe Int)
, qeInternalQuery :: !(Maybe String)
, qeContext :: !(Maybe String)
, qeSourceFile :: !(Maybe String)
, qeSourceLine :: !(Maybe Int)
, qeSourceFunction :: !(Maybe String)
} deriving (Eq, Ord, Show)
newtype QueryError = QueryError String
deriving (Eq, Ord, Show)
newtype HPQTypesError = HPQTypesError String
deriving (Eq, Ord, Show)
newtype LibPQError = LibPQError String
deriving (Eq, Ord, Show)
data ConversionError = forall e. E.Exception e => ConversionError {
convColumn :: !Int
, convColumnName :: !String
, convRow :: !Int
, convError :: !e
}
deriving instance Show ConversionError
data ArrayItemError = forall e. E.Exception e => ArrayItemError {
arrItemIndex :: !Int
, arrItemError :: !e
}
deriving instance Show ArrayItemError
data InvalidValue t = InvalidValue {
ivValue :: t
, ivValidValues :: Maybe [t]
} deriving (Eq, Ord, Show)
data RangeError t = RangeError {
reRange :: [(t, t)]
, reValue :: t
} deriving (Eq, Ord, Show)
data ArrayDimensionMismatch = ArrayDimensionMismatch {
arrDimExpected :: !Int
, arrDimDelivered :: !Int
} deriving (Eq, Ord, Show)
data RowLengthMismatch = RowLengthMismatch {
lengthExpected :: !Int
, lengthDelivered :: !Int
} deriving (Eq, Ord, Show)
data AffectedRowsMismatch = AffectedRowsMismatch {
rowsExpected :: ![(Int, Int)]
, rowsDelivered :: !Int
} deriving (Eq, Ord, Show)
instance E.Exception DetailedQueryError
instance E.Exception QueryError
instance E.Exception HPQTypesError
instance E.Exception LibPQError
instance E.Exception ConversionError
instance E.Exception ArrayItemError
instance (Show t, Typeable t) => E.Exception (InvalidValue t)
instance (Show t, Typeable t) => E.Exception (RangeError t)
instance E.Exception ArrayDimensionMismatch
instance E.Exception RowLengthMismatch
instance E.Exception AffectedRowsMismatch