| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
Database.Beam.Postgres
Contents
Description
Postgres is a popular, open-source RDBMS. It is fairly standards compliant and supports many advanced features and data types.
The beam-postgres module is built atop of postgresql-simple, which is
 used for connection management, transaction support, serialization, and
 deserialization.
beam-postgres supports most beam features as well as many postgres-specific
 features. For example, beam-postgres provides support for full-text search,
 DISTINCT ON, JSON handling, postgres ARRAYs, and the MONEY type.
The documentation for beam-postgres functionality below indicates which
 postgres function each function or type wraps. Postgres maintains its own
 in-depth documentation. Please refer to that for more detailed information on
 behavior.
For examples on how to use beam-postgres usage, see
 its manual.
- data PgRowReadError
 - data PgError
 - data Postgres = Postgres
 - data Pg a
 - data PgCommandSyntax
 - data PgSyntax
 - data PgSelectSyntax
 - data PgInsertSyntax
 - data PgUpdateSyntax
 - data PgDeleteSyntax
 - postgresUriSyntax :: c PgCommandSyntax Postgres Connection Pg -> BeamURIOpeners c
 - json :: (ToJSON a, FromJSON a) => DataType PgDataTypeSyntax (PgJSON a)
 - jsonb :: (ToJSON a, FromJSON a) => DataType PgDataTypeSyntax (PgJSONB a)
 - uuid :: DataType PgDataTypeSyntax UUID
 - money :: DataType PgDataTypeSyntax PgMoney
 - tsquery :: DataType PgDataTypeSyntax TsQuery
 - tsvector :: DataType PgDataTypeSyntax TsVector
 - text :: DataType PgDataTypeSyntax Text
 - bytea :: DataType PgDataTypeSyntax ByteString
 - unboundedArray :: forall a. Typeable a => DataType PgDataTypeSyntax a -> DataType PgDataTypeSyntax (Vector a)
 - smallserial :: Integral a => DataType PgDataTypeSyntax (SqlSerial a)
 - serial :: Integral a => DataType PgDataTypeSyntax (SqlSerial a)
 - bigserial :: Integral a => DataType PgDataTypeSyntax (SqlSerial a)
 - data TsVectorConfig
 - newtype TsVector = TsVector ByteString
 - toTsVector :: IsSqlExpressionSyntaxStringType PgExpressionSyntax str => Maybe TsVectorConfig -> QGenExpr context PgExpressionSyntax s str -> QGenExpr context PgExpressionSyntax s TsVector
 - english :: TsVectorConfig
 - newtype TsQuery = TsQuery ByteString
 - (@@) :: QGenExpr context PgExpressionSyntax s TsVector -> QGenExpr context PgExpressionSyntax s TsQuery -> QGenExpr context PgExpressionSyntax s Bool
 - newtype PgJSON a = PgJSON a
 - newtype PgJSONB a = PgJSONB a
 - class IsPgJSON (json :: * -> *) where
 - data PgJSONEach valType f = PgJSONEach {
- pgJsonEachKey :: C f Text
 - pgJsonEachValue :: C f valType
 
 - data PgJSONKey f = PgJSONKey {}
 - data PgJSONElement a f = PgJSONElement {
- pgJsonElement :: C f a
 
 - (@>) :: IsPgJSON json => QGenExpr ctxt PgExpressionSyntax s (json a) -> QGenExpr ctxt PgExpressionSyntax s (json b) -> QGenExpr ctxt PgExpressionSyntax s Bool
 - (<@) :: IsPgJSON json => QGenExpr ctxt PgExpressionSyntax s (json a) -> QGenExpr ctxt PgExpressionSyntax s (json b) -> QGenExpr ctxt PgExpressionSyntax s Bool
 - (->#) :: IsPgJSON json => QGenExpr ctxt PgExpressionSyntax s (json a) -> QGenExpr ctxt PgExpressionSyntax s Int -> QGenExpr ctxt PgExpressionSyntax s (json b)
 - (->$) :: IsPgJSON json => QGenExpr ctxt PgExpressionSyntax s (json a) -> QGenExpr ctxt PgExpressionSyntax s Text -> QGenExpr ctxt PgExpressionSyntax s (json b)
 - (->>#) :: IsPgJSON json => QGenExpr ctxt PgExpressionSyntax s (json a) -> QGenExpr ctxt PgExpressionSyntax s Int -> QGenExpr ctxt PgExpressionSyntax s Text
 - (->>$) :: IsPgJSON json => QGenExpr ctxt PgExpressionSyntax s (json a) -> QGenExpr ctxt PgExpressionSyntax s Text -> QGenExpr ctxt PgExpressionSyntax s Text
 - (#>) :: IsPgJSON json => QGenExpr ctxt PgExpressionSyntax s (json a) -> QGenExpr ctxt PgExpressionSyntax s (Vector Text) -> QGenExpr ctxt PgExpressionSyntax s (json b)
 - (#>>) :: IsPgJSON json => QGenExpr ctxt PgExpressionSyntax s (json a) -> QGenExpr ctxt PgExpressionSyntax s (Vector Text) -> QGenExpr ctxt PgExpressionSyntax s Text
 - (?) :: IsPgJSON json => QGenExpr ctxt PgExpressionSyntax s (json a) -> QGenExpr ctxt PgExpressionSyntax s Text -> QGenExpr ctxt PgExpressionSyntax s Bool
 - (?|) :: IsPgJSON json => QGenExpr ctxt PgExpressionSyntax s (json a) -> QGenExpr ctxt PgExpressionSyntax s (Vector Text) -> QGenExpr ctxt PgExpressionSyntax s Bool
 - (?&) :: IsPgJSON json => QGenExpr ctxt PgExpressionSyntax s (json a) -> QGenExpr ctxt PgExpressionSyntax s (Vector Text) -> QGenExpr ctxt PgExpressionSyntax s Bool
 - withoutKey :: IsPgJSON json => QGenExpr ctxt PgExpressionSyntax s (json a) -> QGenExpr ctxt PgExpressionSyntax s Text -> QGenExpr ctxt PgExpressionSyntax s (json b)
 - withoutIdx :: IsPgJSON json => QGenExpr ctxt PgExpressionSyntax s (json a) -> QGenExpr ctxt PgExpressionSyntax s Int -> QGenExpr ctxt PgExpressionSyntax s (json b)
 - withoutKeys :: IsPgJSON json => QGenExpr ctxt PgExpressionSyntax s (json a) -> QGenExpr ctxt PgExpressionSyntax s (Vector Text) -> QGenExpr ctxt PgExpressionSyntax s (json b)
 - pgJsonArrayLength :: IsPgJSON json => QGenExpr ctxt PgExpressionSyntax s (json a) -> QGenExpr ctxt PgExpressionSyntax s Int
 - pgJsonbUpdate :: QGenExpr ctxt PgExpressionSyntax s (PgJSONB a) -> QGenExpr ctxt PgExpressionSyntax s (Vector Text) -> QGenExpr ctxt PgExpressionSyntax s (PgJSONB b) -> QGenExpr ctxt PgExpressionSyntax s (PgJSONB a)
 - pgJsonbSet :: QGenExpr ctxt PgExpressionSyntax s (PgJSONB a) -> QGenExpr ctxt PgExpressionSyntax s (Vector Text) -> QGenExpr ctxt PgExpressionSyntax s (PgJSONB b) -> QGenExpr ctxt PgExpressionSyntax s (PgJSONB a)
 - pgJsonbPretty :: QGenExpr ctxt PgExpressionSyntax s (PgJSONB a) -> QGenExpr ctxt PgExpressionSyntax s Text
 - newtype PgMoney = PgMoney {}
 - pgMoney :: Real a => a -> PgMoney
 - pgScaleMoney_ :: Num a => QGenExpr context PgExpressionSyntax s a -> QGenExpr context PgExpressionSyntax s PgMoney -> QGenExpr context PgExpressionSyntax s PgMoney
 - pgDivideMoney_ :: Num a => QGenExpr context PgExpressionSyntax s PgMoney -> QGenExpr context PgExpressionSyntax s a -> QGenExpr context PgExpressionSyntax s PgMoney
 - pgDivideMoneys_ :: Num a => QGenExpr context PgExpressionSyntax s PgMoney -> QGenExpr context PgExpressionSyntax s PgMoney -> QGenExpr context PgExpressionSyntax s a
 - pgAddMoney_ :: QGenExpr context PgExpressionSyntax s PgMoney -> QGenExpr context PgExpressionSyntax s PgMoney -> QGenExpr context PgExpressionSyntax s PgMoney
 - pgSubtractMoney_ :: QGenExpr context PgExpressionSyntax s PgMoney -> QGenExpr context PgExpressionSyntax s PgMoney -> QGenExpr context PgExpressionSyntax s PgMoney
 - pgSumMoneyOver_ :: Maybe PgAggregationSetQuantifierSyntax -> QExpr PgExpressionSyntax s PgMoney -> QExpr PgExpressionSyntax s PgMoney
 - pgAvgMoneyOver_ :: Maybe PgAggregationSetQuantifierSyntax -> QExpr PgExpressionSyntax s PgMoney -> QExpr PgExpressionSyntax s PgMoney
 - pgSumMoney_ :: QExpr PgExpressionSyntax s PgMoney -> QExpr PgExpressionSyntax s PgMoney
 - pgAvgMoney_ :: QExpr PgExpressionSyntax s PgMoney -> QExpr PgExpressionSyntax s PgMoney
 - data PgSetOf (tbl :: (* -> *) -> *)
 - pgUnnest :: forall tbl db s. Beamable tbl => QExpr PgExpressionSyntax s (PgSetOf tbl) -> Q PgSelectSyntax db s (QExprTable PgExpressionSyntax s tbl)
 - pgUnnestArray :: QExpr PgExpressionSyntax s (Vector a) -> Q PgSelectSyntax db s (QExpr PgExpressionSyntax s a)
 - pgUnnestArrayWithOrdinality :: QExpr PgExpressionSyntax s (Vector a) -> Q PgSelectSyntax db s (QExpr PgExpressionSyntax s Int, QExpr PgExpressionSyntax s a)
 - data PgArrayValueContext
 - class PgIsArrayContext ctxt
 - array_ :: forall context f s a. (PgIsArrayContext context, Foldable f) => f (QGenExpr PgArrayValueContext PgExpressionSyntax s a) -> QGenExpr context PgExpressionSyntax s (Vector a)
 - arrayOf_ :: Q PgSelectSyntax db s (QExpr PgExpressionSyntax s a) -> QGenExpr context PgExpressionSyntax s (Vector a)
 - (++.) :: QGenExpr ctxt PgExpressionSyntax s (Vector a) -> QGenExpr ctxt PgExpressionSyntax s (Vector a) -> QGenExpr ctxt PgExpressionSyntax s (Vector a)
 - pgArrayAgg :: QExpr PgExpressionSyntax s a -> QAgg PgExpressionSyntax s (Vector a)
 - pgArrayAggOver :: Maybe PgAggregationSetQuantifierSyntax -> QExpr PgExpressionSyntax s a -> QAgg PgExpressionSyntax s (Vector a)
 - (!.) :: Integral ix => QGenExpr context PgExpressionSyntax s (Vector a) -> QGenExpr context PgExpressionSyntax s ix -> QGenExpr context PgExpressionSyntax s a
 - arrayDims_ :: IsSqlExpressionSyntaxStringType PgExpressionSyntax text => QGenExpr context PgExpressionSyntax s (Vector a) -> QGenExpr context PgExpressionSyntax s text
 - arrayUpper_ :: forall (dim :: Nat) context num v s. (KnownNat dim, WithinBounds dim (Vector v), Integral num) => QGenExpr context PgExpressionSyntax s (Vector v) -> QGenExpr context PgExpressionSyntax s num
 - arrayLower_ :: forall (dim :: Nat) context num v s. (KnownNat dim, WithinBounds dim (Vector v), Integral num) => QGenExpr context PgExpressionSyntax s (Vector v) -> QGenExpr context PgExpressionSyntax s num
 - arrayUpperUnsafe_ :: (Integral dim, Integral length) => QGenExpr context PgExpressionSyntax s (Vector v) -> QGenExpr context PgExpressionSyntax s dim -> QGenExpr context PgExpressionSyntax s (Maybe length)
 - arrayLowerUnsafe_ :: (Integral dim, Integral length) => QGenExpr context PgExpressionSyntax s (Vector v) -> QGenExpr context PgExpressionSyntax s dim -> QGenExpr context PgExpressionSyntax s (Maybe length)
 - arrayLength_ :: forall (dim :: Nat) ctxt num v s. (KnownNat dim, WithinBounds dim (Vector v), Integral num) => QGenExpr ctxt PgExpressionSyntax s (Vector v) -> QGenExpr ctxt PgExpressionSyntax s num
 - arrayLengthUnsafe_ :: (Integral dim, Integral num) => QGenExpr ctxt PgExpressionSyntax s (Vector v) -> QGenExpr ctxt PgExpressionSyntax s dim -> QGenExpr ctxt PgExpressionSyntax s (Maybe num)
 - isSupersetOf_ :: QGenExpr ctxt PgExpressionSyntax s (Vector a) -> QGenExpr ctxt PgExpressionSyntax s (Vector a) -> QGenExpr ctxt PgExpressionSyntax s Bool
 - isSubsetOf_ :: QGenExpr ctxt PgExpressionSyntax s (Vector a) -> QGenExpr ctxt PgExpressionSyntax s (Vector a) -> QGenExpr ctxt PgExpressionSyntax s Bool
 - pgBoolOr :: QExpr PgExpressionSyntax s a -> QAgg PgExpressionSyntax s (Maybe Bool)
 - pgBoolAnd :: QExpr PgExpressionSyntax s a -> QAgg PgExpressionSyntax s (Maybe Bool)
 - pgStringAgg :: IsSqlExpressionSyntaxStringType PgExpressionSyntax str => QExpr PgExpressionSyntax s str -> QExpr PgExpressionSyntax s str -> QAgg PgExpressionSyntax s (Maybe str)
 - pgStringAggOver :: IsSqlExpressionSyntaxStringType PgExpressionSyntax str => Maybe PgAggregationSetQuantifierSyntax -> QExpr PgExpressionSyntax s str -> QExpr PgExpressionSyntax s str -> QAgg PgExpressionSyntax s (Maybe str)
 - pgNubBy_ :: (Projectible PgExpressionSyntax key, Projectible PgExpressionSyntax r) => (r -> key) -> Q PgSelectSyntax db s r -> Q PgSelectSyntax db s r
 - now_ :: QExpr PgExpressionSyntax s LocalTime
 - ilike_ :: IsSqlExpressionSyntaxStringType PgExpressionSyntax text => QExpr PgExpressionSyntax s text -> QExpr PgExpressionSyntax s text -> QExpr PgExpressionSyntax s Bool
 - runBeamPostgres :: Connection -> Pg a -> IO a
 - runBeamPostgresDebug :: (String -> IO ()) -> Connection -> Pg a -> IO a
 - data PgExtensionEntity extension
 - class IsPgExtension extension where
 - pgCreateExtension :: forall extension db. IsPgExtension extension => Migration PgCommandSyntax (CheckedDatabaseEntity Postgres db (PgExtensionEntity extension))
 - pgDropExtension :: forall extension. CheckedDatabaseEntityDescriptor Postgres (PgExtensionEntity extension) -> Migration PgCommandSyntax ()
 - getPgExtension :: DatabaseEntity Postgres db (PgExtensionEntity extension) -> extension
 - data ResultError :: *
- = Incompatible { }
 - | UnexpectedNull { }
 - | ConversionFailed { }
 
 - data SqlError :: * = SqlError {}
 - data Connection :: *
 - data ConnectInfo :: * = ConnectInfo {}
 - defaultConnectInfo :: ConnectInfo
 - connectPostgreSQL :: ByteString -> IO Connection
 - connect :: ConnectInfo -> IO Connection
 - close :: Connection -> IO ()
 
beam-postgres errors
data PgRowReadError Source #
An error that may occur while parsing a row
Constructors
| PgRowReadNoMoreColumns !CInt !CInt | We attempted to read more columns than postgres returned. First argument is the zero-based index of the column we attempted to read, and the second is the total number of columns  | 
| PgRowCouldNotParseField !CInt | There was an error while parsing the field. The first argument gives the zero-based index of the column that could not have been parsed. This is usually caused by your Haskell schema type being incompatible with the one in the database.  | 
Instances
Errors that may arise while using the Pg monad.
Constructors
| PgRowParseError PgRowReadError | |
| PgInternalError String | 
Beam Postgres backend
The Postgres backend type, used to parameterize MonadBeam. See the
 definitions there for more information. The corresponding query monad is
 Pg. See documentation for MonadBeam and the
 user guide for more information on using
 this backend.
Constructors
| Postgres | 
Instances
MonadBeam in which we can run Postgres commands. See the documentation
 for MonadBeam on examples of how to use.
beam-postgres also provides functions that let you run queries without
 MonadBeam. These functions may be more efficient and offer a conduit
 API. See Database.Beam.Postgres.Conduit for more information.
Postgres syntax
data PgCommandSyntax Source #
Representation of an arbitrary Postgres command. This is the combination of
 the command syntax (repesented by PgSyntax), as well as the type of command
 (represented by PgCommandType). The command type is necessary for us to
 know how to retrieve results from the database.
Instances
A piece of Postgres SQL syntax, which may contain embedded escaped byte and
 text sequences. PgSyntax composes monoidally, and may be created with
 emit, emitBuilder, escapeString, escapBytea, and escapeIdentifier.
data PgSelectSyntax Source #
IsSql92SelectSyntax for Postgres
data PgUpdateSyntax Source #
IsSql92UpdateSyntax for Postgres
Beam URI support
postgresUriSyntax :: c PgCommandSyntax Postgres Connection Pg -> BeamURIOpeners c Source #
BeamURIOpeners for the standard postgresql: URI scheme. See the
 postgres documentation for more details on the formatting. See documentation
 for BeamURIOpeners for more information on how to use this with beam
Postgres-specific features
Postgres-specific data types
uuid :: DataType PgDataTypeSyntax UUID Source #
DataType for UUID columns. The pgCryptoGenRandomUUID function in
 the PgCrypto extension can be used to generate UUIDs at random.
text :: DataType PgDataTypeSyntax Text Source #
DataType for Postgres TEXT. characterLargeObject is also mapped to
 this data type
bytea :: DataType PgDataTypeSyntax ByteString Source #
DataType for Postgres BYTEA. binaryLargeObject is also mapped to
 this data type
unboundedArray :: forall a. Typeable a => DataType PgDataTypeSyntax a -> DataType PgDataTypeSyntax (Vector a) Source #
DataType for a Postgres array without any bounds.
Note that array support in beam-migrate is still incomplete.
SERIAL support
smallserial :: Integral a => DataType PgDataTypeSyntax (SqlSerial a) Source #
Postgres SERIAL data types. Automatically generates an appropriate
 DEFAULT clause and sequence
serial :: Integral a => DataType PgDataTypeSyntax (SqlSerial a) Source #
Postgres SERIAL data types. Automatically generates an appropriate
 DEFAULT clause and sequence
bigserial :: Integral a => DataType PgDataTypeSyntax (SqlSerial a) Source #
Postgres SERIAL data types. Automatically generates an appropriate
 DEFAULT clause and sequence
Full-text search
Postgres has comprehensive, and thus complicated, support for full text search. The types and functions in this section map closely to the underlying Postgres API, which is described in the documentation.
TSVECTOR data type
data TsVectorConfig Source #
The identifier of a Postgres text search configuration.
Use the IsString instance to construct new values of this type
The type of a document preprocessed for full-text search. The contained
 ByteString is the Postgres representation of the TSVECTOR type. Use
 toTsVector to construct these on-the-fly from strings.
When this field is embedded in a beam table, defaultMigratableDbSettings
 will give the column the postgres TSVECTOR type.
Constructors
| TsVector ByteString | 
Instances
toTsVector :: IsSqlExpressionSyntaxStringType PgExpressionSyntax str => Maybe TsVectorConfig -> QGenExpr context PgExpressionSyntax s str -> QGenExpr context PgExpressionSyntax s TsVector Source #
The Postgres to_tsvector function. Given a configuration and string,
 return the TSVECTOR that represents the contents of the string.
english :: TsVectorConfig Source #
A full-text search configuration with sensible defaults for english
TSQUERY data type
A query that can be run against a document contained in a TsVector.
When this field is embedded in a beam table, defaultMigratableDbSettings
 will give the column the postgres TSVECTOR type
Constructors
| TsQuery ByteString | 
Instances
(@@) :: QGenExpr context PgExpressionSyntax s TsVector -> QGenExpr context PgExpressionSyntax s TsQuery -> QGenExpr context PgExpressionSyntax s Bool Source #
Determine if the given TSQUERY matches the document represented by the
 TSVECTOR. Behaves exactly like the similarly-named operator in postgres.
JSON and JSONB data types
Postgres supports storing JSON in columns, as either a text-based type
 (JSON) or a specialized binary encoding (JSONB). beam-postgres
 accordingly provides the PgJSON and PgJSONB data types. Each of these
 types takes a type parameter indicating the Haskell object represented by the
 JSON object stored in the column. In order for serialization to work, be sure
 to provide FromJSON and ToJSON instances for this type. If you do not
 know the shape of the data stored, substitute Value for this type
 parameter.
For more information on Psotgres json support see the postgres manual.
The Postgres JSON type, which stores textual values that represent JSON
 objects. The type parameter indicates the Haskell type which the JSON
 encodes. This type must be a member of FromJSON and ToJSON in order for
 deserialization and serialization to work as expected.
The defaultMigratableDbSettings function automatically assigns the postgres
 JSON type to fields with this type.
Constructors
| PgJSON a | 
Instances
| IsPgJSON PgJSON Source # | |
| HasSqlEqualityCheck PgExpressionSyntax (PgJSON a) Source # | |
| HasSqlQuantifiedEqualityCheck PgExpressionSyntax (PgJSON a) Source # | |
| ToJSON a => HasSqlValueSyntax PgValueSyntax (PgJSON a) Source # | |
| (Typeable * a, FromJSON a) => FromBackendRow Postgres (PgJSON a) Source # | |
| HasDefaultSqlDataTypeConstraints PgColumnSchemaSyntax (PgJSON a) Source # | |
| HasDefaultSqlDataType PgDataTypeSyntax (PgJSON a) Source # | |
| Eq a => Eq (PgJSON a) Source # | |
| Ord a => Ord (PgJSON a) Source # | |
| Show a => Show (PgJSON a) Source # | |
| Monoid a => Monoid (PgJSON a) Source # | |
| Hashable a => Hashable (PgJSON a) Source # | |
| (Typeable * x, FromJSON x) => FromField (PgJSON x) Source # | |
The Postgres JSONB type, which stores JSON-encoded data in a
 postgres-specific binary format. Like PgJSON, the type parameter indicates
 the Hgaskell type which the JSON encodes.
Fields with this type are automatically given the Postgres JSONB type
Constructors
| PgJSONB a | 
Instances
| IsPgJSON PgJSONB Source # | |
| HasSqlEqualityCheck PgExpressionSyntax (PgJSONB a) Source # | |
| HasSqlQuantifiedEqualityCheck PgExpressionSyntax (PgJSONB a) Source # | |
| ToJSON a => HasSqlValueSyntax PgValueSyntax (PgJSONB a) Source # | |
| (Typeable * a, FromJSON a) => FromBackendRow Postgres (PgJSONB a) Source # | |
| HasDefaultSqlDataTypeConstraints PgColumnSchemaSyntax (PgJSONB a) Source # | |
| HasDefaultSqlDataType PgDataTypeSyntax (PgJSONB a) Source # | |
| Eq a => Eq (PgJSONB a) Source # | |
| Ord a => Ord (PgJSONB a) Source # | |
| Show a => Show (PgJSONB a) Source # | |
| Monoid a => Monoid (PgJSONB a) Source # | |
| Hashable a => Hashable (PgJSONB a) Source # | |
| (Typeable * x, FromJSON x) => FromField (PgJSONB x) Source # | |
class IsPgJSON (json :: * -> *) where Source #
Postgres provides separate json_ and jsonb_ functions. However, we know
 what we're dealing with based on the type of data, so we can be less obtuse.
For more information on how these functions behave, see the Postgres manual section on JSON.
Minimal complete definition
pgJsonEach, pgJsonEachText, pgJsonKeys, pgJsonArrayElements, pgJsonArrayElementsText, pgJsonTypeOf, pgJsonStripNulls, pgJsonAgg, pgJsonObjectAgg
Methods
pgJsonEach :: QGenExpr ctxt PgExpressionSyntax s (json a) -> QGenExpr ctxt PgExpressionSyntax s (PgSetOf (PgJSONEach (json Value))) Source #
The json_each or jsonb_each function. Values returned as json or
 jsonb respectively. Use pgUnnest to join against the result
pgJsonEachText :: QGenExpr ctxt PgExpressionSyntax s (json a) -> QGenExpr ctxt PgExpressionSyntax s (PgSetOf (PgJSONEach Text)) Source #
Like pgJsonEach, but returning text values instead
pgJsonKeys :: QGenExpr ctxt PgExpressionSyntax s (json a) -> QGenExpr ctxt PgExpressionSyntax s (PgSetOf PgJSONKey) Source #
The json_object_keys and jsonb_object_keys function. Use pgUnnest
 to join against the result.
pgJsonArrayElements :: QGenExpr ctxt PgExpressionSyntax s (json a) -> QGenExpr ctxt PgExpressionSyntax s (PgSetOf (PgJSONElement (json Value))) Source #
The json_array_elements and jsonb_array_elements function. Use
 pgUnnest to join against the result
pgJsonArrayElementsText :: QGenExpr ctxt PgExpressionSyntax s (json a) -> QGenExpr ctxt PgExpressionSyntax s (PgSetOf (PgJSONElement Text)) Source #
Like pgJsonArrayElements, but returning the values as Text
pgJsonTypeOf :: QGenExpr ctxt PgExpressionSyntax s (json a) -> QGenExpr ctxt PgExpressionSyntax s Text Source #
The json_typeof or jsonb_typeof function
pgJsonStripNulls :: QGenExpr ctxt PgExpressionSyntax s (json a) -> QGenExpr ctxt PgExpressionSyntax s (json b) Source #
The json_strip_nulls or jsonb_strip_nulls function.
pgJsonAgg :: QExpr PgExpressionSyntax s a -> QAgg PgExpressionSyntax s (json a) Source #
The json_agg or jsonb_agg aggregate.
pgJsonObjectAgg :: QExpr PgExpressionSyntax s key -> QExpr PgExpressionSyntax s value -> QAgg PgExpressionSyntax s (json a) Source #
The json_object_agg or jsonb_object_agg. The first argument gives the
 key source and the second the corresponding values.
data PgJSONEach valType f Source #
Key-value pair, used as output of pgJsonEachText and pgJsonEach
Constructors
| PgJSONEach | |
Fields 
  | |
Instances
| Beamable (PgJSONEach valType) Source # | |
| Generic (PgJSONEach valType f) Source # | |
| type Rep (PgJSONEach valType f) Source # | |
Output row of pgJsonKeys
data PgJSONElement a f Source #
Output row of pgJsonArrayElements and pgJsonArrayElementsText
Constructors
| PgJSONElement | |
Fields 
  | |
Instances
| Beamable (PgJSONElement a) Source # | |
| Generic (PgJSONElement a f) Source # | |
| type Rep (PgJSONElement a f) Source # | |
(@>) :: IsPgJSON json => QGenExpr ctxt PgExpressionSyntax s (json a) -> QGenExpr ctxt PgExpressionSyntax s (json b) -> QGenExpr ctxt PgExpressionSyntax s Bool Source #
Postgres @> and <@ operators for JSON. Return true if the
 json object pointed to by the arrow is completely contained in the other. See
 the Postgres documentation for more in formation on what this means.
(<@) :: IsPgJSON json => QGenExpr ctxt PgExpressionSyntax s (json a) -> QGenExpr ctxt PgExpressionSyntax s (json b) -> QGenExpr ctxt PgExpressionSyntax s Bool Source #
Postgres @> and <@ operators for JSON. Return true if the
 json object pointed to by the arrow is completely contained in the other. See
 the Postgres documentation for more in formation on what this means.
(->#) :: IsPgJSON json => QGenExpr ctxt PgExpressionSyntax s (json a) -> QGenExpr ctxt PgExpressionSyntax s Int -> QGenExpr ctxt PgExpressionSyntax s (json b) Source #
Access a JSON array by index. Corresponds to the Postgres -> operator.
 See '(->$)' for the corresponding operator for object access.
(->$) :: IsPgJSON json => QGenExpr ctxt PgExpressionSyntax s (json a) -> QGenExpr ctxt PgExpressionSyntax s Text -> QGenExpr ctxt PgExpressionSyntax s (json b) Source #
Acces a JSON object by key. Corresponds to the Postgres -> operator. See
 '(->#)' for the corresponding operator for arrays.
(->>#) :: IsPgJSON json => QGenExpr ctxt PgExpressionSyntax s (json a) -> QGenExpr ctxt PgExpressionSyntax s Int -> QGenExpr ctxt PgExpressionSyntax s Text Source #
Access a JSON array by index, returning the embedded object as a string.
 Corresponds to the Postgres ->> operator. See '(->>$)' for the
 corresponding operator on objects.
(->>$) :: IsPgJSON json => QGenExpr ctxt PgExpressionSyntax s (json a) -> QGenExpr ctxt PgExpressionSyntax s Text -> QGenExpr ctxt PgExpressionSyntax s Text Source #
Access a JSON object by key, returning the embedded object as a string.
 Corresponds to the Postgres ->> operator. See '(->>#)' for the
 corresponding operator on arrays.
(#>) :: IsPgJSON json => QGenExpr ctxt PgExpressionSyntax s (json a) -> QGenExpr ctxt PgExpressionSyntax s (Vector Text) -> QGenExpr ctxt PgExpressionSyntax s (json b) Source #
Access a deeply nested JSON object. The first argument is the JSON object to look within, the second is the path of keys from the first argument to the target. Returns the result as a new json value. Note that the postgres function allows etiher string keys or integer indices, but this function only allows string keys. PRs to improve this functionality are welcome.
(#>>) :: IsPgJSON json => QGenExpr ctxt PgExpressionSyntax s (json a) -> QGenExpr ctxt PgExpressionSyntax s (Vector Text) -> QGenExpr ctxt PgExpressionSyntax s Text Source #
Like '(#>)' but returns the result as a string.
(?) :: IsPgJSON json => QGenExpr ctxt PgExpressionSyntax s (json a) -> QGenExpr ctxt PgExpressionSyntax s Text -> QGenExpr ctxt PgExpressionSyntax s Bool Source #
Postgres ? operator. Checks if the given string exists as top-level key
 of the json object.
(?|) :: IsPgJSON json => QGenExpr ctxt PgExpressionSyntax s (json a) -> QGenExpr ctxt PgExpressionSyntax s (Vector Text) -> QGenExpr ctxt PgExpressionSyntax s Bool Source #
Postgres ?| and ?& operators. Check if any or all of the given strings
 exist as top-level keys of the json object respectively.
(?&) :: IsPgJSON json => QGenExpr ctxt PgExpressionSyntax s (json a) -> QGenExpr ctxt PgExpressionSyntax s (Vector Text) -> QGenExpr ctxt PgExpressionSyntax s Bool Source #
Postgres ?| and ?& operators. Check if any or all of the given strings
 exist as top-level keys of the json object respectively.
withoutKey :: IsPgJSON json => QGenExpr ctxt PgExpressionSyntax s (json a) -> QGenExpr ctxt PgExpressionSyntax s Text -> QGenExpr ctxt PgExpressionSyntax s (json b) Source #
Postgres - operator on json objects. Returns the supplied json object
 with the supplied key deleted. See withoutIdx for the corresponding
 operator on arrays.
withoutIdx :: IsPgJSON json => QGenExpr ctxt PgExpressionSyntax s (json a) -> QGenExpr ctxt PgExpressionSyntax s Int -> QGenExpr ctxt PgExpressionSyntax s (json b) Source #
Postgres - operator on json arrays. See withoutKey for the
 corresponding operator on objects.
withoutKeys :: IsPgJSON json => QGenExpr ctxt PgExpressionSyntax s (json a) -> QGenExpr ctxt PgExpressionSyntax s (Vector Text) -> QGenExpr ctxt PgExpressionSyntax s (json b) Source #
Postgres #- operator. Removes all the keys specificied from the JSON
 object and returns the result.
pgJsonArrayLength :: IsPgJSON json => QGenExpr ctxt PgExpressionSyntax s (json a) -> QGenExpr ctxt PgExpressionSyntax s Int Source #
Postgres json_array_length function. The supplied json object should be
 an array, but this isn't checked at compile-time.
pgJsonbUpdate :: QGenExpr ctxt PgExpressionSyntax s (PgJSONB a) -> QGenExpr ctxt PgExpressionSyntax s (Vector Text) -> QGenExpr ctxt PgExpressionSyntax s (PgJSONB b) -> QGenExpr ctxt PgExpressionSyntax s (PgJSONB a) Source #
The postgres jsonb_set function. pgJsonUpdate expects the value
 specified by the path in the second argument to exist. If it does not, the
 first argument is not modified. pgJsonbSet will create any intermediate
 objects necessary. This corresponds to the create_missing argument of
 jsonb_set being set to false or true respectively.
pgJsonbSet :: QGenExpr ctxt PgExpressionSyntax s (PgJSONB a) -> QGenExpr ctxt PgExpressionSyntax s (Vector Text) -> QGenExpr ctxt PgExpressionSyntax s (PgJSONB b) -> QGenExpr ctxt PgExpressionSyntax s (PgJSONB a) Source #
The postgres jsonb_set function. pgJsonUpdate expects the value
 specified by the path in the second argument to exist. If it does not, the
 first argument is not modified. pgJsonbSet will create any intermediate
 objects necessary. This corresponds to the create_missing argument of
 jsonb_set being set to false or true respectively.
pgJsonbPretty :: QGenExpr ctxt PgExpressionSyntax s (PgJSONB a) -> QGenExpr ctxt PgExpressionSyntax s Text Source #
Postgres jsonb_pretty function
MONEY data type
Postgres MONEY data type. A simple wrapper over ByteString, because
   Postgres money format is locale-dependent, and we don't handle currency
   symbol placement, digit grouping, or decimal separation.
The pgMoney function can be used to convert a number to PgMoney.
Constructors
| PgMoney | |
Fields  | |
Instances
pgMoney :: Real a => a -> PgMoney Source #
Attempt to pack a floating point value as a PgMoney value, paying no
 attention to the locale-dependent currency symbol, digit grouping, or decimal
 point. This will use the . symbol as the decimal separator.
pgScaleMoney_ :: Num a => QGenExpr context PgExpressionSyntax s a -> QGenExpr context PgExpressionSyntax s PgMoney -> QGenExpr context PgExpressionSyntax s PgMoney Source #
Multiply a MONEY value by a numeric value. Corresponds to the Postgres
 * operator.
pgDivideMoney_ :: Num a => QGenExpr context PgExpressionSyntax s PgMoney -> QGenExpr context PgExpressionSyntax s a -> QGenExpr context PgExpressionSyntax s PgMoney Source #
Divide a MONEY value by a numeric value. Corresponds to Postgres /
 where the numerator has type MONEY and the denominator is a number. If you
 would like to divide two MONEY values and have their units cancel out, use
 pgDivideMoneys_.
pgDivideMoneys_ :: Num a => QGenExpr context PgExpressionSyntax s PgMoney -> QGenExpr context PgExpressionSyntax s PgMoney -> QGenExpr context PgExpressionSyntax s a Source #
Dividing two MONEY value results in a number. Corresponds to Postgres /
 on two MONEY values. If you would like to divide MONEY by a scalar, use pgDivideMoney_
pgAddMoney_ :: QGenExpr context PgExpressionSyntax s PgMoney -> QGenExpr context PgExpressionSyntax s PgMoney -> QGenExpr context PgExpressionSyntax s PgMoney Source #
Postgres + and - operators on money.
pgSubtractMoney_ :: QGenExpr context PgExpressionSyntax s PgMoney -> QGenExpr context PgExpressionSyntax s PgMoney -> QGenExpr context PgExpressionSyntax s PgMoney Source #
Postgres + and - operators on money.
pgSumMoneyOver_ :: Maybe PgAggregationSetQuantifierSyntax -> QExpr PgExpressionSyntax s PgMoney -> QExpr PgExpressionSyntax s PgMoney Source #
The Postgres MONEY type can be summed or averaged in an aggregation.
 These functions provide the quantified aggregations. See pgSumMoney_ and
 pgAvgMoney_ for the unquantified versions.
pgAvgMoneyOver_ :: Maybe PgAggregationSetQuantifierSyntax -> QExpr PgExpressionSyntax s PgMoney -> QExpr PgExpressionSyntax s PgMoney Source #
The Postgres MONEY type can be summed or averaged in an aggregation.
 These functions provide the quantified aggregations. See pgSumMoney_ and
 pgAvgMoney_ for the unquantified versions.
pgSumMoney_ :: QExpr PgExpressionSyntax s PgMoney -> QExpr PgExpressionSyntax s PgMoney Source #
The Postgres MONEY type can be summed or averaged in an aggregation. To
 provide an explicit quantification, see pgSumMoneyOver_ and
 pgAvgMoneyOver_.
pgAvgMoney_ :: QExpr PgExpressionSyntax s PgMoney -> QExpr PgExpressionSyntax s PgMoney Source #
The Postgres MONEY type can be summed or averaged in an aggregation. To
 provide an explicit quantification, see pgSumMoneyOver_ and
 pgAvgMoneyOver_.
Set-valued functions
Postgres supports functions that returns sets. We can join directly against
 these sets or arrays. beam-postgres supports this feature via the
 pgUnnest and pgUnnestArray functions.
Any function that returns a set can be typed as an expression returning
 PgSetOf. This polymorphic type takes one argument, which is a Beamable
 type that represents the shape of the data in the rows. For example, the
 json_each function returns a key and a value, so the corresponding
 beam-postgres function (pgJsonEach) returns a value of type 'PgSetOf
 (PgJSONEach Value)', which represents a set containing PgJSONEach
 rows. PgJSONEach is a table with a column for keys (pgJsonEachKey) and
 one for values (pgJsonEachValue).
Any PgSetOf value can be introduced into the Q monad using the pgUnnest
 function.
Postgres arrays (represented by the Vector type) can also be joined
 against using the pgUnnestArray function. This directly corresponds to the
 SQL UNNEST keyword. Unlike sets, arrays have a sense of order. The
 pgUnnestArrayWithOrdinality function allows you to join against the
 elements of an array along with its index. This corresponds to the
 UNNEST .. WITH ORDINALITY clause.
pgUnnest :: forall tbl db s. Beamable tbl => QExpr PgExpressionSyntax s (PgSetOf tbl) -> Q PgSelectSyntax db s (QExprTable PgExpressionSyntax s tbl) Source #
pgUnnestArray :: QExpr PgExpressionSyntax s (Vector a) -> Q PgSelectSyntax db s (QExpr PgExpressionSyntax s a) Source #
pgUnnestArrayWithOrdinality :: QExpr PgExpressionSyntax s (Vector a) -> Q PgSelectSyntax db s (QExpr PgExpressionSyntax s Int, QExpr PgExpressionSyntax s a) Source #
ARRAY types
The functions and types in this section map Postgres ARRAY types to
 Haskell. An array is serialized and deserialized to a Vector
 object. This type most closely matches the semantics of Postgres ARRAYs. In
 general, the names of functions in this section closely match names of the
 native Postgres functions they map to. As with most beam expression
 functions, names are suffixed with an underscore and CamelCased.
Note that Postgres supports arbitrary nesting of vectors. For example, two,
 three, or higher dimensional arrays can be expressed, manipulated, and stored
 in tables. Beam fully supports this use case. A two-dimensional postgres
 array is represented as Vector (Vector a). Simply nest another Vector for
 higher dimensions. Some functions that return data on arrays expect a
 dimension number as a parameter. Since beam can check the dimension at
 compile time, these functions expect a type-level Nat in the expression
 DSL. The unsafe versions of these functions are also provided with the
 Unsafe_ suffix. The safe versions are guaranteed not to fail at run-time
 due to dimension mismatches, the unsafe ones may.
For more information on Postgres array support, refer to the postgres manual.
data PgArrayValueContext Source #
An expression context that determines which types of expressions can be put inside an array element. Any scalar, aggregate, or window expression can be placed within an array.
Instances
class PgIsArrayContext ctxt Source #
If you are extending beam-postgres and provide another expression context that can be represented in an array, provide an empty instance of this class.
Building ARRAYs
array_ :: forall context f s a. (PgIsArrayContext context, Foldable f) => f (QGenExpr PgArrayValueContext PgExpressionSyntax s a) -> QGenExpr context PgExpressionSyntax s (Vector a) Source #
Build a 1-dimensional postgres array from an arbitrary Foldable
 containing expressions.
arrayOf_ :: Q PgSelectSyntax db s (QExpr PgExpressionSyntax s a) -> QGenExpr context PgExpressionSyntax s (Vector a) Source #
Build a 1-dimensional postgres array from a subquery
(++.) :: QGenExpr ctxt PgExpressionSyntax s (Vector a) -> QGenExpr ctxt PgExpressionSyntax s (Vector a) -> QGenExpr ctxt PgExpressionSyntax s (Vector a) Source #
Postgres || operator. Concatenates two vectors and returns their result.
pgArrayAgg :: QExpr PgExpressionSyntax s a -> QAgg PgExpressionSyntax s (Vector a) Source #
An aggregate that adds each value to the resulting array. See pgArrayOver
 if you want to specify a quantifier. Corresponds to the Postgres ARRAY_AGG
 function.
pgArrayAggOver :: Maybe PgAggregationSetQuantifierSyntax -> QExpr PgExpressionSyntax s a -> QAgg PgExpressionSyntax s (Vector a) Source #
Postgres ARRAY_AGG with an explicit quantifier. Includes each row that
 meets the quantification criteria in the result.
Array operators and functions
(!.) :: Integral ix => QGenExpr context PgExpressionSyntax s (Vector a) -> QGenExpr context PgExpressionSyntax s ix -> QGenExpr context PgExpressionSyntax s a Source #
arrayDims_ :: IsSqlExpressionSyntaxStringType PgExpressionSyntax text => QGenExpr context PgExpressionSyntax s (Vector a) -> QGenExpr context PgExpressionSyntax s text Source #
Postgres array_dims() function. Returns a textual representation of the
 dimensions of the array.
arrayUpper_ :: forall (dim :: Nat) context num v s. (KnownNat dim, WithinBounds dim (Vector v), Integral num) => QGenExpr context PgExpressionSyntax s (Vector v) -> QGenExpr context PgExpressionSyntax s num Source #
Return the upper or lower bound of the given array at the given dimension
  (statically supplied as a type application on a Nat). Note
  that beam will attempt to statically determine if the dimension is in range.
  GHC errors will be thrown if this cannot be proved.
For example, to get the upper bound of the 2nd-dimension of an array:
arrayUpper_ @2 vectorValuedExpression
arrayLower_ :: forall (dim :: Nat) context num v s. (KnownNat dim, WithinBounds dim (Vector v), Integral num) => QGenExpr context PgExpressionSyntax s (Vector v) -> QGenExpr context PgExpressionSyntax s num Source #
Return the upper or lower bound of the given array at the given dimension
  (statically supplied as a type application on a Nat). Note
  that beam will attempt to statically determine if the dimension is in range.
  GHC errors will be thrown if this cannot be proved.
For example, to get the upper bound of the 2nd-dimension of an array:
arrayUpper_ @2 vectorValuedExpression
arrayUpperUnsafe_ :: (Integral dim, Integral length) => QGenExpr context PgExpressionSyntax s (Vector v) -> QGenExpr context PgExpressionSyntax s dim -> QGenExpr context PgExpressionSyntax s (Maybe length) Source #
These functions can be used to find the lower and upper bounds of an array where the dimension number is not known until run-time. They are marked unsafe because they may cause query processing to fail at runtime, even if they typecheck successfully.
arrayLowerUnsafe_ :: (Integral dim, Integral length) => QGenExpr context PgExpressionSyntax s (Vector v) -> QGenExpr context PgExpressionSyntax s dim -> QGenExpr context PgExpressionSyntax s (Maybe length) Source #
These functions can be used to find the lower and upper bounds of an array where the dimension number is not known until run-time. They are marked unsafe because they may cause query processing to fail at runtime, even if they typecheck successfully.
arrayLength_ :: forall (dim :: Nat) ctxt num v s. (KnownNat dim, WithinBounds dim (Vector v), Integral num) => QGenExpr ctxt PgExpressionSyntax s (Vector v) -> QGenExpr ctxt PgExpressionSyntax s num Source #
Get the size of the array at the given (statically known) dimension,
 provided as a type-level Nat. Like the arrayUpper_ and arrayLower_
 functions,throws a compile-time error if the dimension is out of bounds.
arrayLengthUnsafe_ :: (Integral dim, Integral num) => QGenExpr ctxt PgExpressionSyntax s (Vector v) -> QGenExpr ctxt PgExpressionSyntax s dim -> QGenExpr ctxt PgExpressionSyntax s (Maybe num) Source #
Get the size of an array at a dimension not known until run-time. Marked unsafe as this may cause runtime errors even if it type checks.
isSupersetOf_ :: QGenExpr ctxt PgExpressionSyntax s (Vector a) -> QGenExpr ctxt PgExpressionSyntax s (Vector a) -> QGenExpr ctxt PgExpressionSyntax s Bool Source #
The Postgres @> operator. Returns true if every member of the second
 array is present in the first.
isSubsetOf_ :: QGenExpr ctxt PgExpressionSyntax s (Vector a) -> QGenExpr ctxt PgExpressionSyntax s (Vector a) -> QGenExpr ctxt PgExpressionSyntax s Bool Source #
The Postgres <@ operator. Returns true if every member of the first
 array is present in the second.
Postgres functions and aggregates
pgBoolOr :: QExpr PgExpressionSyntax s a -> QAgg PgExpressionSyntax s (Maybe Bool) Source #
Postgres bool_or aggregate. Returns true if any of the rows are true.
pgBoolAnd :: QExpr PgExpressionSyntax s a -> QAgg PgExpressionSyntax s (Maybe Bool) Source #
Postgres bool_and aggregate. Returns false unless every row is true.
pgStringAgg :: IsSqlExpressionSyntaxStringType PgExpressionSyntax str => QExpr PgExpressionSyntax s str -> QExpr PgExpressionSyntax s str -> QAgg PgExpressionSyntax s (Maybe str) Source #
Joins the string value in each row of the first argument, using the second
 argument as a delimiter. See pgStringAggOver if you want to provide
 explicit quantification.
pgStringAggOver :: IsSqlExpressionSyntaxStringType PgExpressionSyntax str => Maybe PgAggregationSetQuantifierSyntax -> QExpr PgExpressionSyntax s str -> QExpr PgExpressionSyntax s str -> QAgg PgExpressionSyntax s (Maybe str) Source #
The Postgres string_agg function, with an explicit quantifier. Joins the
 values of the second argument using the delimiter given by the third.
pgNubBy_ :: (Projectible PgExpressionSyntax key, Projectible PgExpressionSyntax r) => (r -> key) -> Q PgSelectSyntax db s r -> Q PgSelectSyntax db s r Source #
Modify a query to only return rows where the supplied key function returns
 a unique value. This corresponds to the Postgres DISTINCT ON support.
now_ :: QExpr PgExpressionSyntax s LocalTime Source #
Postgres NOW() function. Returns the server's timestamp
ilike_ :: IsSqlExpressionSyntaxStringType PgExpressionSyntax text => QExpr PgExpressionSyntax s text -> QExpr PgExpressionSyntax s text -> QExpr PgExpressionSyntax s Bool Source #
Postgres ILIKE operator. A case-insensitive version of like_.
runBeamPostgres :: Connection -> Pg a -> IO a Source #
runBeamPostgresDebug :: (String -> IO ()) -> Connection -> Pg a -> IO a Source #
Postgres extension support
data PgExtensionEntity extension Source #
Represents an extension in a database.
For example, to include the Database.Beam.Postgres.PgCrypto extension in a database,
import Database.Beam.Migrate.PgCrypto
data MyDatabase entity
    = MyDatabase
    { _table1 :: entity (TableEntity Table1)
    , _cryptoExtension :: entity (PgExtensionEntity PgCrypto)
    }
migratableDbSettings :: CheckedDatabaseSettings Postgres MyDatabase
migratableDbSettings = defaultMigratableDbSettings
dbSettings :: DatabaseSettings Postgres MyDatabase
dbSettings = unCheckDatabase migratableDbSettings
Note that our database now only works in the Postgres backend.
Extensions are implemented as records of functions and values that expose
 extension functionality. For example, the pgcrypto extension (implemented
 by PgCrypto) provides cryptographic functions. Thus, PgCrypto is a record
 of functions over QGenExpr which wrap the underlying postgres
 functionality.
You get access to these functions by retrieving them from the entity in the database.
For example, to use the pgcrypto extension in the database above:
let PgCrypto { pgCryptoDigestText = digestText
             , pgCryptoCrypt = crypt } = getPgExtension (_cryptoExtension dbSettings)
in fmap_ (tbl -> (tbl, crypt (_field1 tbl) (_salt tbl))) (all_ (table1 dbSettings))
To implement your own extension, create a record type, and implement the
 IsPgExtension type class.
Instances
| IsDatabaseEntity Postgres (PgExtensionEntity extension) Source # | |
| IsCheckedDatabaseEntity Postgres (PgExtensionEntity extension) Source # | |
| RenamableWithRule (FieldRenamer (DatabaseEntityDescriptor Postgres (PgExtensionEntity e))) Source # | There are no fields to rename when defining entities  | 
| type DatabaseEntityRegularRequirements Postgres (PgExtensionEntity extension) Source # | |
| type DatabaseEntityDefaultRequirements Postgres (PgExtensionEntity extension) Source # | |
| data DatabaseEntityDescriptor Postgres (PgExtensionEntity extension) Source # | |
| data CheckedDatabaseEntityDescriptor Postgres (PgExtensionEntity extension) Source # | |
| type CheckedDatabaseEntityDefaultRequirements Postgres (PgExtensionEntity extension) syntax Source # | |
class IsPgExtension extension where Source #
Type class implemented by any Postgresql extension
Minimal complete definition
Methods
pgExtensionName :: Proxy extension -> Text Source #
Return the name of this extension. This should be the string that is
 passed to CREATE EXTENSION. For example, PgCrypto returns "pgcrypto".
pgExtensionBuild :: extension Source #
Return a value of this extension type. This should fill in all fields in
 the record. For example, PgCrypto builds a record where each function
 wraps the underlying Postgres one.
Instances
pgCreateExtension :: forall extension db. IsPgExtension extension => Migration PgCommandSyntax (CheckedDatabaseEntity Postgres db (PgExtensionEntity extension)) Source #
Migration representing the Postgres CREATE EXTENSION command. Because
 the extension name is statically known by the extension type and
 IsPgExtension type class, this simply produces the checked extension
 entity.
If you need to use the extension in subsequent migration steps, use
 getPgExtension and unCheck to get access to the underlying
 DatabaseEntity.
pgDropExtension :: forall extension. CheckedDatabaseEntityDescriptor Postgres (PgExtensionEntity extension) -> Migration PgCommandSyntax () Source #
Migration representing the Postgres DROP EXTENSION. After this
 executes, you should expect any further uses of the extension to fail.
 Unfortunately, without linear types, we cannot check this.
getPgExtension :: DatabaseEntity Postgres db (PgExtensionEntity extension) -> extension Source #
Get the extension record from a database entity. See the documentation for
 PgExtensionEntity.
postgresql-simple re-exports
data ResultError :: * #
Exception thrown if conversion from a SQL value to a Haskell value fails.
Constructors
| Incompatible | The SQL and Haskell types are not compatible.  | 
Fields 
  | |
| UnexpectedNull | A SQL   | 
Fields 
  | |
| ConversionFailed | The SQL value could not be parsed, or could not be represented as a valid Haskell value, or an unexpected low-level error occurred (e.g. mismatch between metadata and actual data in a row).  | 
Fields 
  | |
Instances
Constructors
| SqlError | |
Fields  | |
data Connection :: * #
Instances
data ConnectInfo :: * #
Constructors
| ConnectInfo | |
Fields 
  | |
Instances
defaultConnectInfo :: ConnectInfo #
Default information for setting up a connection.
Defaults are as follows:
- Server on 
localhost - Port on 
5432 - User 
postgres - No password
 - Database 
postgres 
Use as in the following example:
connect defaultConnectInfo { connectHost = "db.example.com" }connectPostgreSQL :: ByteString -> IO Connection #
Attempt to make a connection based on a libpq connection string. See https://www.postgresql.org/docs/9.5/static/libpq-connect.html#LIBPQ-CONNSTRING for more information. Also note that environment variables also affect parameters not provided, parameters provided as the empty string, and a few other things; see https://www.postgresql.org/docs/9.5/static/libpq-envars.html for details. Here is an example with some of the most commonly used parameters:
host='db.somedomain.com' port=5432 ...
This attempts to connect to db.somedomain.com:5432.  Omitting the port
   will normally default to 5432.
On systems that provide unix domain sockets,  omitting the host parameter
   will cause libpq to attempt to connect via unix domain sockets.
   The default filesystem path to the socket is constructed from the
   port number and the DEFAULT_PGSOCKET_DIR constant defined in the
   pg_config_manual.h header file.  Connecting via unix sockets tends
   to use the peer authentication method, which is very secure and
   does not require a password.
On Windows and other systems without unix domain sockets, omitting
   the host will default to localhost.
... dbname='postgres' user='postgres' password='secret \' \\ pw'
This attempts to connect to a database named postgres with
   user postgres and password secret ' \ pw.  Backslash
   characters will have to be double-quoted in literal Haskell strings,
   of course.  Omitting dbname and user will both default to the
   system username that the client process is running as.
Omitting password will default to an appropriate password found
   in the pgpass file,  or no password at all if a matching line is
   not found.   See
   https://www.postgresql.org/docs/9.5/static/libpq-pgpass.html for
   more information regarding this file.
As all parameters are optional and the defaults are sensible, the empty connection string can be useful for development and exploratory use, assuming your system is set up appropriately.
On Unix, such a setup would typically consist of a local postgresql server listening on port 5432, as well as a system user, database user, and database sharing a common name, with permissions granted to the user on the database.
On Windows,  in addition you will either need pg_hba.conf
   to specify the use of the trust authentication method for
   the connection,  which may not be appropriate for multiuser
   or production machines, or you will need to use a pgpass file
   with the password or md5 authentication methods.
See https://www.postgresql.org/docs/9.5/static/client-authentication.html for more information regarding the authentication process.
SSL/TLS will typically "just work" if your postgresql server supports or
   requires it.  However,  note that libpq is trivially vulnerable to a MITM
   attack without setting additional SSL connection parameters.  In
   particular,  sslmode needs to be set to require, verify-ca, or
   verify-full in order to perform certificate validation.  When sslmode
   is require,  then you will also need to specify a sslrootcert file,
   otherwise no validation of the server's identity will be performed.
   Client authentication via certificates is also possible via the
   sslcert and sslkey parameters.   See
   https://www.postgresql.org/docs/9.5/static/libpq-ssl.html
   for detailed information regarding libpq and SSL.
connect :: ConnectInfo -> IO Connection #
Connect with the given username to the given database. Will throw an exception if it cannot connect.
close :: Connection -> IO () #