Safe Haskell | None |
---|---|
Language | Haskell2010 |
Database.PostgreSQL.PQTypes.Internal.Error
Description
Definitions of exception types.
Synopsis
- 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)
- newtype QueryError = QueryError String
- newtype HPQTypesError = HPQTypesError String
- newtype LibPQError = LibPQError String
- data ConversionError = Exception e => ConversionError {
- convColumn :: !Int
- convColumnName :: !String
- convRow :: !Int
- convError :: !e
- data ArrayItemError = Exception e => ArrayItemError {
- arrItemIndex :: !Int
- arrItemError :: !e
- data InvalidValue t = InvalidValue {
- ivValue :: t
- ivValidValues :: Maybe [t]
- data RangeError t = RangeError {}
- data ArrayDimensionMismatch = ArrayDimensionMismatch {
- arrDimExpected :: !Int
- arrDimDelivered :: !Int
- data RowLengthMismatch = RowLengthMismatch {
- lengthExpected :: !Int
- lengthDelivered :: !Int
- data AffectedRowsMismatch = AffectedRowsMismatch {
- rowsExpected :: ![(Int, Int)]
- rowsDelivered :: !Int
Documentation
data DetailedQueryError Source #
SQL query error. Reference: description of PQresultErrorField at http://www.postgresql.org/docs/devel/static/libpq-exec.html.
Constructors
DetailedQueryError | |
Fields
|
Instances
newtype QueryError Source #
Simple SQL query error. Thrown when there is no PGresult object corresponding to query execution.
Constructors
QueryError String |
Instances
Eq QueryError Source # | |
Defined in Database.PostgreSQL.PQTypes.Internal.Error | |
Ord QueryError Source # | |
Defined in Database.PostgreSQL.PQTypes.Internal.Error Methods compare :: QueryError -> QueryError -> Ordering # (<) :: QueryError -> QueryError -> Bool # (<=) :: QueryError -> QueryError -> Bool # (>) :: QueryError -> QueryError -> Bool # (>=) :: QueryError -> QueryError -> Bool # max :: QueryError -> QueryError -> QueryError # min :: QueryError -> QueryError -> QueryError # | |
Show QueryError Source # | |
Defined in Database.PostgreSQL.PQTypes.Internal.Error Methods showsPrec :: Int -> QueryError -> ShowS # show :: QueryError -> String # showList :: [QueryError] -> ShowS # | |
Exception QueryError Source # | |
Defined in Database.PostgreSQL.PQTypes.Internal.Error Methods toException :: QueryError -> SomeException # fromException :: SomeException -> Maybe QueryError # displayException :: QueryError -> String # |
newtype HPQTypesError Source #
Internal error in this library.
Constructors
HPQTypesError String |
Instances
newtype LibPQError Source #
Internal error in libpq/libpqtypes library.
Constructors
LibPQError String |
Instances
Eq LibPQError Source # | |
Defined in Database.PostgreSQL.PQTypes.Internal.Error | |
Ord LibPQError Source # | |
Defined in Database.PostgreSQL.PQTypes.Internal.Error Methods compare :: LibPQError -> LibPQError -> Ordering # (<) :: LibPQError -> LibPQError -> Bool # (<=) :: LibPQError -> LibPQError -> Bool # (>) :: LibPQError -> LibPQError -> Bool # (>=) :: LibPQError -> LibPQError -> Bool # max :: LibPQError -> LibPQError -> LibPQError # min :: LibPQError -> LibPQError -> LibPQError # | |
Show LibPQError Source # | |
Defined in Database.PostgreSQL.PQTypes.Internal.Error Methods showsPrec :: Int -> LibPQError -> ShowS # show :: LibPQError -> String # showList :: [LibPQError] -> ShowS # | |
Exception LibPQError Source # | |
Defined in Database.PostgreSQL.PQTypes.Internal.Error Methods toException :: LibPQError -> SomeException # fromException :: SomeException -> Maybe LibPQError # displayException :: LibPQError -> String # |
data ConversionError Source #
Data conversion error. Since it's polymorphic in error type, it nicely reports arbitrarily nested conversion errors.
Constructors
Exception e => ConversionError | |
Fields
|
Instances
Show ConversionError Source # | |
Defined in Database.PostgreSQL.PQTypes.Internal.Error Methods showsPrec :: Int -> ConversionError -> ShowS # show :: ConversionError -> String # showList :: [ConversionError] -> ShowS # | |
Exception ConversionError Source # | |
Defined in Database.PostgreSQL.PQTypes.Internal.Error Methods toException :: ConversionError -> SomeException # |
data ArrayItemError Source #
Array item error. Polymorphic in error type
for the same reason as ConversionError
.
Constructors
Exception e => ArrayItemError | |
Fields
|
Instances
Show ArrayItemError Source # | |
Defined in Database.PostgreSQL.PQTypes.Internal.Error Methods showsPrec :: Int -> ArrayItemError -> ShowS # show :: ArrayItemError -> String # showList :: [ArrayItemError] -> ShowS # | |
Exception ArrayItemError Source # | |
Defined in Database.PostgreSQL.PQTypes.Internal.Error Methods toException :: ArrayItemError -> SomeException # |
data InvalidValue t Source #
"Invalid value" error for various data types.
Constructors
InvalidValue | |
Fields
|
Instances
data RangeError t Source #
Range error for various data types.
Constructors
RangeError | |
Instances
data ArrayDimensionMismatch Source #
Array dimenstion mismatch error.
Constructors
ArrayDimensionMismatch | |
Fields
|
Instances
data RowLengthMismatch Source #
Row length mismatch error.
Constructors
RowLengthMismatch | |
Fields
|
Instances
data AffectedRowsMismatch Source #
Affected/returned rows mismatch error.
Constructors
AffectedRowsMismatch | |
Fields
|