| Safe Haskell | None | 
|---|---|
| Language | Haskell98 | 
Database.PostgreSQL.PQTypes
Description
Set of definitions exposed to the end user.
- data Connection
- data ConnectionStats = ConnectionStats {- statsQueries :: !Int
- statsRows :: !Int
- statsValues :: !Int
- statsParams :: !Int
 
- data ConnectionSettings = ConnectionSettings {- csConnInfo :: !ByteString
- csClientEncoding :: !(Maybe ByteString)
- csComposites :: ![ByteString]
 
- data ConnectionSource
- simpleSource :: ConnectionSettings -> ConnectionSource
- poolSource :: ConnectionSettings -> Int -> NominalDiffTime -> Int -> IO ConnectionSource
- data ErrorCode- = SuccessfulCompletion
- | Warning
- | DynamicResultSetsReturned
- | ImplicitZeroBitPadding
- | NullValueEliminatedInSetFunction
- | PrivilegeNotGranted
- | PrivilegeNotRevoked
- | StringDataRightTruncation_01
- | DeprecatedFeature
- | NoData
- | NoAdditionalDynamicResultSetsReturned
- | SqlStatementNotYetComplete
- | ConnectionException
- | ConnectionDoesNotExist
- | ConnectionFailure
- | SqlclientUnableToEstablishSqlconnection
- | SqlserverRejectedEstablishmentOfSqlconnection
- | TransactionResolutionUnknown
- | ProtocolViolation
- | TriggeredActionException
- | FeatureNotSupported
- | InvalidTransactionInitiation
- | LocatorException
- | InvalidLocatorSpecification
- | InvalidGrantor
- | InvalidGrantOperation
- | InvalidRoleSpecification
- | DiagnosticsException
- | StackedDiagnosticsAccessedWithoutActiveHandler
- | CaseNotFound
- | CardinalityViolation
- | DataException
- | ArraySubscriptError
- | CharacterNotInRepertoire
- | DatetimeFieldOverflow
- | DivisionByZero
- | ErrorInAssignment
- | EscapeCharacterConflict
- | IndicatorOverflow
- | IntervalFieldOverflow
- | InvalidArgumentForLogarithm
- | InvalidArgumentForNtileFunction
- | InvalidArgumentForNthValueFunction
- | InvalidArgumentForPowerFunction
- | InvalidArgumentForWidthBucketFunction
- | InvalidCharacterValueForCast
- | InvalidDatetimeFormat
- | InvalidEscapeCharacter
- | InvalidEscapeOctet
- | InvalidEscapeSequence
- | NonstandardUseOfEscapeCharacter
- | InvalidIndicatorParameterValue
- | InvalidParameterValue
- | InvalidRegularExpression
- | InvalidRowCountInLimitClause
- | InvalidRowCountInResultOffsetClause
- | InvalidTimeZoneDisplacementValue
- | InvalidUseOfEscapeCharacter
- | MostSpecificTypeMismatch
- | NullValueNotAllowed_22
- | NullValueNoIndicatorParameter
- | NumericValueOutOfRange
- | StringDataLengthMismatch
- | StringDataRightTruncation_22
- | SubstringError
- | TrimError
- | UnterminatedCString
- | ZeroLengthCharacterString
- | FloatingPointException
- | InvalidTextRepresentation
- | InvalidBinaryRepresentation
- | BadCopyFileFormat
- | UntranslatableCharacter
- | NotAnXmlDocument
- | InvalidXmlDocument
- | InvalidXmlContent
- | InvalidXmlComment
- | InvalidXmlProcessingInstruction
- | IntegrityConstraintViolation
- | RestrictViolation
- | NotNullViolation
- | ForeignKeyViolation
- | UniqueViolation
- | CheckViolation
- | ExclusionViolation
- | InvalidCursorState
- | InvalidTransactionState
- | ActiveSqlTransaction
- | BranchTransactionAlreadyActive
- | HeldCursorRequiresSameIsolationLevel
- | InappropriateAccessModeForBranchTransaction
- | InappropriateIsolationLevelForBranchTransaction
- | NoActiveSqlTransactionForBranchTransaction
- | ReadOnlySqlTransaction
- | SchemaAndDataStatementMixingNotSupported
- | NoActiveSqlTransaction
- | InFailedSqlTransaction
- | InvalidSqlStatementName
- | TriggeredDataChangeViolation
- | InvalidAuthorizationSpecification
- | InvalidPassword
- | DependentPrivilegeDescriptorsStillExist
- | DependentObjectsStillExist
- | InvalidTransactionTermination
- | SqlRoutineException
- | FunctionExecutedNoReturnStatement
- | ModifyingSqlDataNotPermitted_2F
- | ProhibitedSqlStatementAttempted_2F
- | ReadingSqlDataNotPermitted_2F
- | InvalidCursorName
- | ExternalRoutineException
- | ContainingSqlNotPermitted
- | ModifyingSqlDataNotPermitted_38
- | ProhibitedSqlStatementAttempted_38
- | ReadingSqlDataNotPermitted_38
- | ExternalRoutineInvocationException
- | InvalidSqlstateReturned
- | NullValueNotAllowed_39
- | TriggerProtocolViolated
- | SrfProtocolViolated
- | SavepointException
- | InvalidSavepointSpecification
- | InvalidCatalogName
- | InvalidSchemaName
- | TransactionRollback
- | TransactionIntegrityConstraintViolation
- | SerializationFailure
- | StatementCompletionUnknown
- | DeadlockDetected
- | SyntaxErrorOrAccessRuleViolation
- | SyntaxError
- | InsufficientPrivilege
- | CannotCoerce
- | GroupingError
- | WindowingError
- | InvalidRecursion
- | InvalidForeignKey
- | InvalidName
- | NameTooLong
- | ReservedName
- | DatatypeMismatch
- | IndeterminateDatatype
- | CollationMismatch
- | IndeterminateCollation
- | WrongObjectType
- | UndefinedColumn
- | UndefinedFunction
- | UndefinedTable
- | UndefinedParameter
- | UndefinedObject
- | DuplicateColumn
- | DuplicateCursor
- | DuplicateDatabase
- | DuplicateFunction
- | DuplicatePreparedStatement
- | DuplicateSchema
- | DuplicateTable
- | DuplicateAlias
- | DuplicateObject
- | AmbiguousColumn
- | AmbiguousFunction
- | AmbiguousParameter
- | AmbiguousAlias
- | InvalidColumnReference
- | InvalidColumnDefinition
- | InvalidCursorDefinition
- | InvalidDatabaseDefinition
- | InvalidFunctionDefinition
- | InvalidPreparedStatementDefinition
- | InvalidSchemaDefinition
- | InvalidTableDefinition
- | InvalidObjectDefinition
- | WithCheckOptionViolation
- | InsufficientResources
- | DiskFull
- | OutOfMemory
- | TooManyConnections
- | ConfigurationLimitExceeded
- | ProgramLimitExceeded
- | StatementTooComplex
- | TooManyColumns
- | TooManyArguments
- | ObjectNotInPrerequisiteState
- | ObjectInUse
- | CantChangeRuntimeParam
- | LockNotAvailable
- | OperatorIntervention
- | QueryCanceled
- | AdminShutdown
- | CrashShutdown
- | CannotConnectNow
- | DatabaseDropped
- | SystemError
- | IoError
- | UndefinedFile
- | DuplicateFile
- | ConfigFileError
- | LockFileExists
- | FdwError
- | FdwColumnNameNotFound
- | FdwDynamicParameterValueNeeded
- | FdwFunctionSequenceError
- | FdwInconsistentDescriptorInformation
- | FdwInvalidAttributeValue
- | FdwInvalidColumnName
- | FdwInvalidColumnNumber
- | FdwInvalidDataType
- | FdwInvalidDataTypeDescriptors
- | FdwInvalidDescriptorFieldIdentifier
- | FdwInvalidHandle
- | FdwInvalidOptionIndex
- | FdwInvalidOptionName
- | FdwInvalidStringLengthOrBufferLength
- | FdwInvalidStringFormat
- | FdwInvalidUseOfNullPointer
- | FdwTooManyHandles
- | FdwOutOfMemory
- | FdwNoSchemas
- | FdwOptionNameNotFound
- | FdwReplyHandle
- | FdwSchemaNotFound
- | FdwTableNotFound
- | FdwUnableToCreateExecution
- | FdwUnableToCreateReply
- | FdwUnableToEstablishConnection
- | PlpgsqlError
- | RaiseException
- | NoDataFound
- | TooManyRows
- | InternalError
- | DataCorrupted
- | IndexCorrupted
- | UnknownErrorCode String
 
- 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 = forall e . Exception e => ConversionError {- convColumn :: !Int
- convColumnName :: !String
- convRow :: !Int
- convError :: !e
 
- data ArrayItemError = forall e . 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
 
- data DBException = forall e sql . (Exception e, Show sql) => DBException {- dbeQueryContext :: !sql
- dbeError :: !e
 
- data DBT m a
- runDBT :: (MonadBase IO m, MonadMask m) => ConnectionSource -> TransactionSettings -> DBT m a -> m a
- mapDBT :: (m (a, DBState) -> n (b, DBState)) -> DBT m a -> DBT n b
- data QueryResult t
- ntuples :: QueryResult t -> Int
- nfields :: QueryResult t -> Int
- module Data.Functor.Identity
- module Database.PostgreSQL.PQTypes.Array
- module Database.PostgreSQL.PQTypes.Binary
- module Database.PostgreSQL.PQTypes.Class
- module Database.PostgreSQL.PQTypes.Composite
- module Database.PostgreSQL.PQTypes.Fold
- module Database.PostgreSQL.PQTypes.Format
- module Database.PostgreSQL.PQTypes.FromRow
- module Database.PostgreSQL.PQTypes.FromSQL
- module Database.PostgreSQL.PQTypes.Interval
- module Database.PostgreSQL.PQTypes.JSON
- module Database.PostgreSQL.PQTypes.Notification
- module Database.PostgreSQL.PQTypes.SQL
- module Database.PostgreSQL.PQTypes.SQL.Class
- module Database.PostgreSQL.PQTypes.SQL.Raw
- module Database.PostgreSQL.PQTypes.ToRow
- module Database.PostgreSQL.PQTypes.ToSQL
- module Database.PostgreSQL.PQTypes.Transaction
- module Database.PostgreSQL.PQTypes.Transaction.Settings
- module Database.PostgreSQL.PQTypes.Utils
- module Database.PostgreSQL.PQTypes.XML
Connection
data Connection Source
Wrapper for hiding representation of a connection object.
data ConnectionStats Source
Simple connection statistics.
Constructors
| ConnectionStats | |
| Fields 
 | |
data ConnectionSettings Source
Constructors
| ConnectionSettings | |
| Fields 
 | |
Instances
| Eq ConnectionSettings Source | |
| Ord ConnectionSettings Source | |
| Show ConnectionSettings Source | |
| Default ConnectionSettings Source | Default connection settings. | 
data ConnectionSource Source
Database connection supplier.
simpleSource :: ConnectionSettings -> ConnectionSource Source
Default connection supplier. It estabilishes new
 database connection each time withConnection is called.
Arguments
| :: ConnectionSettings | |
| -> Int | Stripe count. The number of distinct sub-pools to maintain. The smallest acceptable value is 1. | 
| -> NominalDiffTime | Amount of time for which an unused database connection is kept open. The smallest acceptable value is 0.5 seconds. The elapsed time before closing database connection may be a little longer than requested, as the reaper thread wakes at 1-second intervals. | 
| -> Int | Maximum number of database connections to keep open per stripe. The smallest acceptable value is 1. Requests for database connections will block if this limit is reached on a single stripe, even if other stripes have idle connections available. | 
| -> IO ConnectionSource | 
Pooled source. It uses striped pool from resource-pool package to cache estabilished connections and reuse them.
Exceptions
SQL error code. Reference: http://www.postgresql.org/docs/devel/static/errcodes-appendix.html.
Constructors
data DetailedQueryError Source
SQL query error. Reference: description of PQresultErrorField at http://www.postgresql.org/docs/devel/static/libpq-exec.html.
Constructors
| DetailedQueryError | |
| Fields 
 | |
newtype QueryError Source
Simple SQL query error. Thrown when there is no PGresult object corresponding to query execution.
Constructors
| QueryError String | 
data ConversionError Source
Data conversion error. Since it's polymorphic in error type, it nicely reports arbitrarily nested conversion errors.
Constructors
| forall e . Exception e => ConversionError | |
| Fields 
 | |
Instances
data ArrayItemError Source
Array item error. Polymorphic in error type
 for the same reason as ConversionError.
Constructors
| forall e . Exception e => ArrayItemError | |
| Fields 
 | |
Instances
data InvalidValue t Source
"Invalid value" error for various data types.
Constructors
| InvalidValue | |
| Fields 
 | |
Instances
| Eq t => Eq (InvalidValue t) Source | |
| Ord t => Ord (InvalidValue t) Source | |
| Show t => Show (InvalidValue t) Source | |
| (Show t, Typeable * t) => Exception (InvalidValue t) Source | 
data RangeError t Source
Range error for various data types.
Constructors
| RangeError | |
Instances
| Eq t => Eq (RangeError t) Source | |
| Ord t => Ord (RangeError t) Source | |
| Show t => Show (RangeError t) Source | |
| (Show t, Typeable * t) => Exception (RangeError t) Source | 
data ArrayDimensionMismatch Source
Array dimenstion mismatch error.
Constructors
| ArrayDimensionMismatch | |
| Fields 
 | |
data RowLengthMismatch Source
Row length mismatch error.
Constructors
| RowLengthMismatch | |
| Fields 
 | |
data AffectedRowsMismatch Source
Affected/returned rows mismatch error.
Constructors
| AffectedRowsMismatch | |
| Fields 
 | |
data DBException Source
Main exception type. All exceptions thrown by the library are additionally wrapped in this type.
Constructors
| forall e sql . (Exception e, Show sql) => DBException | |
| Fields 
 | |
Instances
Monad transformer
Monad transformer for adding database interaction capabilities to the underlying monad.
Instances
| MonadTrans DBT Source | |
| MonadTransControl DBT Source | |
| MonadBase b m => MonadBase b (DBT m) Source | |
| MonadBaseControl b m => MonadBaseControl b (DBT m) Source | |
| MonadError e m => MonadError e (DBT m) Source | |
| MonadReader r m => MonadReader r (DBT m) Source | |
| MonadState s m => MonadState s (DBT m) Source | |
| MonadWriter w m => MonadWriter w (DBT m) Source | |
| Monad m => Monad (DBT m) Source | |
| Functor m => Functor (DBT m) Source | |
| Monad m => Applicative (DBT m) Source | |
| MonadPlus m => Alternative (DBT m) Source | |
| MonadPlus m => MonadPlus (DBT m) Source | |
| MonadThrow m => MonadThrow (DBT m) Source | |
| MonadCatch m => MonadCatch (DBT m) Source | |
| MonadMask m => MonadMask (DBT m) Source | |
| MonadIO m => MonadIO (DBT m) Source | |
| (MonadBase IO m, MonadMask m) => MonadDB (DBT m) Source | |
| type StT DBT a Source | |
| type StM (DBT m) a = ComposeSt DBT m a Source | 
runDBT :: (MonadBase IO m, MonadMask m) => ConnectionSource -> TransactionSettings -> DBT m a -> m a Source
Evaluate monadic action with supplied connection source and transaction settings.
mapDBT :: (m (a, DBState) -> n (b, DBState)) -> DBT m a -> DBT n b Source
Transform the underlying monad.
Query result
data QueryResult t Source
Representation of a query result. Provides Functor
 and Foldable instances for data transformation and
 extraction appropriately.
Instances
ntuples :: QueryResult t -> Int Source
Extract number of returned tuples (rows) from query result.
nfields :: QueryResult t -> Int Source
Extract number of returned fields (columns) from query result.
Other modules
module Data.Functor.Identity